mirror of
https://github.com/github/semantic.git
synced 2024-12-21 13:51:44 +03:00
Merge remote-tracking branch 'origin/master' into allocator-effect
This commit is contained in:
commit
22874e7105
@ -1,5 +1,13 @@
|
||||
{-# LANGUAGE MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
|
||||
module Data.JSON.Fields where
|
||||
{-# LANGUAGE DefaultSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
|
||||
module Data.JSON.Fields
|
||||
( JSONFields (..)
|
||||
, JSONFields1 (..)
|
||||
, ToJSONFields (..)
|
||||
, ToJSONFields1 (..)
|
||||
, (.=)
|
||||
, noChildren
|
||||
, withChildren
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Sum (Apply(..), Sum)
|
||||
@ -10,7 +18,14 @@ class ToJSONFields a where
|
||||
|
||||
class ToJSONFields1 f where
|
||||
toJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv]
|
||||
default toJSONFields1 :: (KeyValue kv, ToJSON a, Foldable f) => f a -> [kv]
|
||||
toJSONFields1 f = ["children" .= toList f]
|
||||
|
||||
withChildren :: (KeyValue kv, ToJSON a, Foldable f) => f a -> [kv] -> [kv]
|
||||
withChildren f ks = ("children" .= toList f) : ks
|
||||
|
||||
noChildren :: KeyValue kv => [kv] -> [kv]
|
||||
noChildren ks = ("children" .= ([] :: [Int])) : ks
|
||||
|
||||
instance ToJSONFields a => ToJSONFields (Join (,) a) where
|
||||
toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ]
|
||||
@ -24,8 +39,8 @@ instance ToJSON a => ToJSONFields [a] where
|
||||
instance ToJSONFields1 [] where
|
||||
toJSONFields1 list = [ "children" .= list ]
|
||||
|
||||
instance Apply Foldable fs => ToJSONFields1 (Sum fs) where
|
||||
toJSONFields1 r = [ "children" .= toList r ]
|
||||
instance Apply ToJSONFields1 fs => ToJSONFields1 (Sum fs) where
|
||||
toJSONFields1 = apply @ToJSONFields1 toJSONFields1
|
||||
|
||||
instance (ToJSONFields a, ToJSONFields b) => ToJSONFields (a, b) where
|
||||
toJSONFields (a, b) = [ "before" .= JSONFields a, "after" .= JSONFields b ]
|
||||
|
@ -3,7 +3,9 @@
|
||||
module Data.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Aeson (ToJSON(..), object)
|
||||
import Data.AST
|
||||
import Data.JSON.Fields
|
||||
import Data.Range
|
||||
import Data.Record
|
||||
import Data.Span
|
||||
@ -106,6 +108,9 @@ instance Eq1 Identifier where liftEq = genericLiftEq
|
||||
instance Ord1 Identifier where liftCompare = genericLiftCompare
|
||||
instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- Propagating the identifier name into JSON is handled with the IdentifierName analysis.
|
||||
instance ToJSONFields1 Identifier
|
||||
|
||||
instance Evaluatable Identifier where
|
||||
eval (Identifier name) = variable name
|
||||
|
||||
@ -122,6 +127,8 @@ instance Eq1 Program where liftEq = genericLiftEq
|
||||
instance Ord1 Program where liftCompare = genericLiftCompare
|
||||
instance Show1 Program where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Program
|
||||
|
||||
instance Evaluatable Program where
|
||||
eval (Program xs) = eval xs
|
||||
|
||||
@ -133,6 +140,8 @@ instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
|
||||
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
|
||||
instance Show1 AccessibilityModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 AccessibilityModifier
|
||||
|
||||
-- TODO: Implement Eval instance for AccessibilityModifier
|
||||
instance Evaluatable AccessibilityModifier
|
||||
|
||||
@ -142,6 +151,8 @@ instance Evaluatable AccessibilityModifier
|
||||
data Empty a = Empty
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Empty
|
||||
|
||||
instance Eq1 Empty where liftEq _ _ _ = True
|
||||
instance Ord1 Empty where liftCompare _ _ _ = EQ
|
||||
instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty"
|
||||
@ -160,6 +171,13 @@ instance Show1 Error where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Error
|
||||
|
||||
instance ToJSONFields1 Error where
|
||||
toJSONFields1 f@Error{..} = withChildren f [ "stack" .= errorCallStack
|
||||
, "expected" .= errorExpected
|
||||
, "actual" .= errorActual
|
||||
]
|
||||
|
||||
|
||||
errorSyntax :: Error.Error String -> [a] -> Error a
|
||||
errorSyntax Error.Error{..} = Error (ErrorStack (getCallStack callStack)) errorExpected errorActual
|
||||
|
||||
@ -169,6 +187,18 @@ unError span Error{..} = Error.withCallStack (freezeCallStack (fromCallSiteList
|
||||
newtype ErrorStack = ErrorStack { unErrorStack :: [(String, SrcLoc)] }
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance ToJSON ErrorStack where
|
||||
toJSON (ErrorStack es) = toJSON (jSite <$> es) where
|
||||
jSite (site, SrcLoc{..}) = object
|
||||
[ "site" .= site
|
||||
, "package" .= srcLocPackage
|
||||
, "module" .= srcLocModule
|
||||
, "file" .= srcLocFile
|
||||
, "startLine" .= srcLocStartLine
|
||||
, "startColumn" .= srcLocStartCol
|
||||
, "endColumn" .= srcLocEndCol
|
||||
]
|
||||
|
||||
instance Ord ErrorStack where
|
||||
compare = liftCompare (liftCompare compareSrcLoc) `on` unErrorStack
|
||||
where compareSrcLoc s1 s2 = mconcat
|
||||
@ -185,6 +215,8 @@ instance Ord ErrorStack where
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Context
|
||||
|
||||
instance Diffable Context where
|
||||
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s
|
||||
|
||||
|
@ -3,6 +3,8 @@ module Data.Syntax.Comment where
|
||||
|
||||
import Prologue
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.ByteString (unpack)
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
|
||||
-- | An unnested comment (line or block).
|
||||
@ -13,6 +15,9 @@ instance Eq1 Comment where liftEq = genericLiftEq
|
||||
instance Ord1 Comment where liftCompare = genericLiftCompare
|
||||
instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Comment where
|
||||
toJSONFields1 f@Comment{..} = withChildren f ["contents" .= unpack commentContent ]
|
||||
|
||||
instance Evaluatable Comment where
|
||||
eval _ = unit
|
||||
|
||||
|
@ -3,6 +3,7 @@ module Data.Syntax.Declaration where
|
||||
|
||||
import qualified Data.Abstract.Environment as Env
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Set as Set (fromList)
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
@ -17,6 +18,8 @@ instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Function
|
||||
|
||||
-- TODO: Filter the closed-over environment by the free variables in the term.
|
||||
-- TODO: How should we represent function types, where applicable?
|
||||
|
||||
@ -35,13 +38,15 @@ instance Declarations a => Declarations (Function a) where
|
||||
data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Diffable Method where
|
||||
equivalentBySubterm = Just . methodName
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Ord1 Method where liftCompare = genericLiftCompare
|
||||
instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Diffable Method where
|
||||
equivalentBySubterm = Just . methodName
|
||||
|
||||
instance ToJSONFields1 Method
|
||||
|
||||
-- Evaluating a Method creates a closure and makes that value available in the
|
||||
-- local environment.
|
||||
instance Evaluatable Method where
|
||||
@ -61,6 +66,8 @@ instance Eq1 MethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 MethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 MethodSignature
|
||||
|
||||
-- TODO: Implement Eval instance for MethodSignature
|
||||
instance Evaluatable MethodSignature
|
||||
|
||||
@ -72,6 +79,8 @@ instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 RequiredParameter
|
||||
|
||||
-- TODO: Implement Eval instance for RequiredParameter
|
||||
instance Evaluatable RequiredParameter
|
||||
|
||||
@ -83,6 +92,8 @@ instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 OptionalParameter
|
||||
|
||||
-- TODO: Implement Eval instance for OptionalParameter
|
||||
instance Evaluatable OptionalParameter
|
||||
|
||||
@ -98,6 +109,8 @@ instance Eq1 VariableDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 VariableDeclaration
|
||||
|
||||
instance Evaluatable VariableDeclaration where
|
||||
eval (VariableDeclaration []) = unit
|
||||
eval (VariableDeclaration decs) = multiple =<< traverse subtermValue decs
|
||||
@ -116,6 +129,8 @@ instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 InterfaceDeclaration
|
||||
|
||||
-- TODO: Implement Eval instance for InterfaceDeclaration
|
||||
instance Evaluatable InterfaceDeclaration
|
||||
|
||||
@ -131,6 +146,8 @@ instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq
|
||||
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
|
||||
instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 PublicFieldDefinition
|
||||
|
||||
-- TODO: Implement Eval instance for PublicFieldDefinition
|
||||
instance Evaluatable PublicFieldDefinition
|
||||
|
||||
@ -142,6 +159,8 @@ instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Variable
|
||||
|
||||
-- TODO: Implement Eval instance for Variable
|
||||
instance Evaluatable Variable
|
||||
|
||||
@ -151,6 +170,8 @@ data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSupercl
|
||||
instance Declarations a => Declarations (Class a) where
|
||||
declaredName (Class _ name _ _) = declaredName name
|
||||
|
||||
instance ToJSONFields1 Class
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
|
||||
@ -176,6 +197,8 @@ instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Decorator
|
||||
|
||||
-- TODO: Implement Eval instance for Decorator
|
||||
instance Evaluatable Decorator
|
||||
|
||||
@ -190,6 +213,8 @@ instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Declaration.Datatype
|
||||
|
||||
-- TODO: Implement Eval instance for Datatype
|
||||
instance Evaluatable Data.Syntax.Declaration.Datatype
|
||||
|
||||
@ -202,6 +227,8 @@ instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Declaration.Constructor
|
||||
|
||||
-- TODO: Implement Eval instance for Constructor
|
||||
instance Evaluatable Data.Syntax.Declaration.Constructor
|
||||
|
||||
@ -214,6 +241,8 @@ instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||
instance Ord1 Comprehension where liftCompare = genericLiftCompare
|
||||
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Comprehension
|
||||
|
||||
-- TODO: Implement Eval instance for Comprehension
|
||||
instance Evaluatable Comprehension
|
||||
|
||||
@ -226,6 +255,8 @@ instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Type
|
||||
|
||||
-- TODO: Implement Eval instance for Type
|
||||
instance Evaluatable Type
|
||||
|
||||
@ -238,6 +269,8 @@ instance Eq1 TypeAlias where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeAlias
|
||||
|
||||
-- TODO: Implement Eval instance for TypeAlias
|
||||
instance Evaluatable TypeAlias where
|
||||
eval TypeAlias{..} = do
|
||||
|
@ -4,6 +4,7 @@ module Data.Syntax.Directive where
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module (ModuleInfo(..))
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import Data.Span
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
@ -16,6 +17,8 @@ instance Eq1 File where liftEq = genericLiftEq
|
||||
instance Ord1 File where liftCompare = genericLiftCompare
|
||||
instance Show1 File where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 File
|
||||
|
||||
instance Evaluatable File where
|
||||
eval File = currentModule >>= string . BC.pack . modulePath
|
||||
|
||||
@ -28,5 +31,7 @@ instance Eq1 Line where liftEq = genericLiftEq
|
||||
instance Ord1 Line where liftCompare = genericLiftCompare
|
||||
instance Show1 Line where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Line
|
||||
|
||||
instance Evaluatable Line where
|
||||
eval Line = currentSpan >>= integer . fromIntegral . posLine . spanStart
|
||||
|
@ -4,6 +4,7 @@ module Data.Syntax.Expression where
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Number (liftIntegralFrac, liftReal, liftedExponent, liftedFloorDiv)
|
||||
import Data.Fixed
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import Prologue hiding (index)
|
||||
|
||||
@ -15,6 +16,8 @@ instance Eq1 Call where liftEq = genericLiftEq
|
||||
instance Ord1 Call where liftCompare = genericLiftCompare
|
||||
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Call
|
||||
|
||||
instance Evaluatable Call where
|
||||
eval Call{..} = do
|
||||
op <- subtermValue callFunction
|
||||
@ -33,6 +36,8 @@ instance Eq1 Comparison where liftEq = genericLiftEq
|
||||
instance Ord1 Comparison where liftCompare = genericLiftCompare
|
||||
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Comparison
|
||||
|
||||
instance Evaluatable Comparison where
|
||||
eval = traverse subtermValue >=> go where
|
||||
go x = case x of
|
||||
@ -59,6 +64,8 @@ instance Eq1 Arithmetic where liftEq = genericLiftEq
|
||||
instance Ord1 Arithmetic where liftCompare = genericLiftCompare
|
||||
instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Arithmetic
|
||||
|
||||
instance Evaluatable Arithmetic where
|
||||
eval = traverse subtermValue >=> go where
|
||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||
@ -80,6 +87,8 @@ instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Match
|
||||
|
||||
-- TODO: Implement Eval instance for Match
|
||||
instance Evaluatable Match
|
||||
|
||||
@ -95,6 +104,8 @@ instance Eq1 Boolean where liftEq = genericLiftEq
|
||||
instance Ord1 Boolean where liftCompare = genericLiftCompare
|
||||
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Boolean
|
||||
|
||||
instance Evaluatable Boolean where
|
||||
-- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands
|
||||
eval = go . fmap subtermValue where
|
||||
@ -115,6 +126,8 @@ instance Eq1 Delete where liftEq = genericLiftEq
|
||||
instance Ord1 Delete where liftCompare = genericLiftCompare
|
||||
instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Delete
|
||||
|
||||
-- TODO: Implement Eval instance for Delete
|
||||
instance Evaluatable Delete
|
||||
|
||||
@ -127,6 +140,8 @@ instance Eq1 SequenceExpression where liftEq = genericLiftEq
|
||||
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 SequenceExpression
|
||||
|
||||
-- TODO: Implement Eval instance for SequenceExpression
|
||||
instance Evaluatable SequenceExpression
|
||||
|
||||
@ -139,6 +154,8 @@ instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Void
|
||||
|
||||
-- TODO: Implement Eval instance for Void
|
||||
instance Evaluatable Void
|
||||
|
||||
@ -151,6 +168,8 @@ instance Eq1 Typeof where liftEq = genericLiftEq
|
||||
instance Ord1 Typeof where liftCompare = genericLiftCompare
|
||||
instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Typeof
|
||||
|
||||
-- TODO: Implement Eval instance for Typeof
|
||||
instance Evaluatable Typeof
|
||||
|
||||
@ -170,6 +189,8 @@ instance Eq1 Bitwise where liftEq = genericLiftEq
|
||||
instance Ord1 Bitwise where liftCompare = genericLiftCompare
|
||||
instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Bitwise
|
||||
|
||||
instance Evaluatable Bitwise where
|
||||
eval = traverse subtermValue >=> go where
|
||||
genLShift x y = shiftL x (fromIntegral y)
|
||||
@ -192,6 +213,8 @@ instance Eq1 MemberAccess where liftEq = genericLiftEq
|
||||
instance Ord1 MemberAccess where liftCompare = genericLiftCompare
|
||||
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 MemberAccess
|
||||
|
||||
instance Evaluatable MemberAccess where
|
||||
eval (fmap subtermValue -> MemberAccess mem acc) = evaluateInScopedEnv mem acc
|
||||
|
||||
@ -205,7 +228,9 @@ instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Ord1 Subscript where liftCompare = genericLiftCompare
|
||||
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Subscript
|
||||
instance ToJSONFields1 Subscript
|
||||
|
||||
-- TODO: Finish Eval instance for Subscript
|
||||
instance Evaluatable Subscript where
|
||||
eval (Subscript l [r]) = join (index <$> subtermValue l <*> subtermValue r)
|
||||
eval (Subscript _ _) = throwResumable (Unspecialized "Eval unspecialized for subscript with slices")
|
||||
@ -220,6 +245,8 @@ instance Eq1 Enumeration where liftEq = genericLiftEq
|
||||
instance Ord1 Enumeration where liftCompare = genericLiftCompare
|
||||
instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Enumeration
|
||||
|
||||
-- TODO: Implement Eval instance for Enumeration
|
||||
instance Evaluatable Enumeration
|
||||
|
||||
@ -232,6 +259,8 @@ instance Eq1 InstanceOf where liftEq = genericLiftEq
|
||||
instance Ord1 InstanceOf where liftCompare = genericLiftCompare
|
||||
instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 InstanceOf
|
||||
|
||||
-- TODO: Implement Eval instance for InstanceOf
|
||||
instance Evaluatable InstanceOf
|
||||
|
||||
@ -244,6 +273,8 @@ instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeResolution where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ScopeResolution
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeResolution
|
||||
instance Evaluatable ScopeResolution
|
||||
|
||||
@ -256,6 +287,8 @@ instance Eq1 NonNullExpression where liftEq = genericLiftEq
|
||||
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 NonNullExpression
|
||||
|
||||
-- TODO: Implement Eval instance for NonNullExpression
|
||||
instance Evaluatable NonNullExpression
|
||||
|
||||
@ -268,6 +301,8 @@ instance Eq1 Await where liftEq = genericLiftEq
|
||||
instance Ord1 Await where liftCompare = genericLiftCompare
|
||||
instance Show1 Await where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Await
|
||||
|
||||
-- TODO: Implement Eval instance for Await
|
||||
instance Evaluatable Await
|
||||
|
||||
@ -280,6 +315,8 @@ instance Eq1 New where liftEq = genericLiftEq
|
||||
instance Ord1 New where liftCompare = genericLiftCompare
|
||||
instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 New
|
||||
|
||||
-- TODO: Implement Eval instance for New
|
||||
instance Evaluatable New
|
||||
|
||||
@ -292,5 +329,7 @@ instance Eq1 Cast where liftEq = genericLiftEq
|
||||
instance Ord1 Cast where liftCompare = genericLiftCompare
|
||||
instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Cast
|
||||
|
||||
-- TODO: Implement Eval instance for Cast
|
||||
instance Evaluatable Cast
|
||||
|
@ -2,6 +2,7 @@
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Data.JSON.Fields
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.ByteString.Char8 (readInteger, unpack)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
@ -29,6 +30,8 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Boolean where
|
||||
eval (Boolean x) = boolean x
|
||||
|
||||
instance ToJSONFields1 Boolean where
|
||||
toJSONFields1 (Boolean b) = noChildren [ "value" .= b ]
|
||||
|
||||
-- Numeric
|
||||
|
||||
@ -45,6 +48,9 @@ instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
eval (Data.Syntax.Literal.Integer x) =
|
||||
integer =<< maybeM (throwEvalError (IntegerFormatError x)) (fst <$> readInteger x)
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Literal.Integer where
|
||||
toJSONFields1 (Integer i) = noChildren ["asString" .= unpack i]
|
||||
|
||||
|
||||
-- TODO: Should IntegerLiteral hold an Integer instead of a ByteString?
|
||||
-- TODO: Do we care about differentiating between hex/octal/decimal/binary integer literals?
|
||||
@ -62,6 +68,9 @@ instance Evaluatable Data.Syntax.Literal.Float where
|
||||
eval (Float s) =
|
||||
float =<< either (const (throwEvalError (FloatFormatError s))) pure (parseScientific s)
|
||||
|
||||
instance ToJSONFields1 Float where
|
||||
toJSONFields1 (Float f) = noChildren ["asString" .= unpack f]
|
||||
|
||||
-- Rational literals e.g. `2/3r`
|
||||
newtype Rational a = Rational ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
@ -77,6 +86,8 @@ instance Evaluatable Data.Syntax.Literal.Rational where
|
||||
parsed = readMaybe @Prelude.Integer (unpack trimmed)
|
||||
in rational =<< maybe (throwEvalError (RationalFormatError r)) (pure . toRational) parsed
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Literal.Rational where
|
||||
toJSONFields1 (Rational r) = noChildren ["asString" .= unpack r]
|
||||
|
||||
-- Complex literals e.g. `3 + 2i`
|
||||
newtype Complex a = Complex ByteString
|
||||
@ -89,6 +100,9 @@ instance Show1 Data.Syntax.Literal.Complex where liftShowsPrec = genericLiftShow
|
||||
-- TODO: Implement Eval instance for Complex
|
||||
instance Evaluatable Complex
|
||||
|
||||
instance ToJSONFields1 Complex where
|
||||
toJSONFields1 (Complex c) = noChildren ["asString" .= unpack c]
|
||||
|
||||
-- Strings, symbols
|
||||
|
||||
newtype String a = String { stringElements :: [a] }
|
||||
@ -103,6 +117,7 @@ instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShows
|
||||
-- TODO: Implement Eval instance for String
|
||||
instance Evaluatable Data.Syntax.Literal.String
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Literal.String
|
||||
|
||||
-- | An interpolation element within a string literal.
|
||||
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
||||
@ -115,6 +130,7 @@ instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Implement Eval instance for InterpolationElement
|
||||
instance Evaluatable InterpolationElement
|
||||
|
||||
instance ToJSONFields1 InterpolationElement
|
||||
|
||||
-- | A sequence of textual contents within a string literal.
|
||||
newtype TextElement a = TextElement { textElementContent :: ByteString }
|
||||
@ -124,6 +140,9 @@ instance Eq1 TextElement where liftEq = genericLiftEq
|
||||
instance Ord1 TextElement where liftCompare = genericLiftCompare
|
||||
instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TextElement where
|
||||
toJSONFields1 (TextElement c) = noChildren ["asString" .= unpack c]
|
||||
|
||||
instance Evaluatable TextElement where
|
||||
eval (TextElement x) = string x
|
||||
|
||||
@ -136,6 +155,8 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Null where eval = const null
|
||||
|
||||
instance ToJSONFields1 Null
|
||||
|
||||
newtype Symbol a = Symbol { symbolContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
@ -143,6 +164,8 @@ instance Eq1 Symbol where liftEq = genericLiftEq
|
||||
instance Ord1 Symbol where liftCompare = genericLiftCompare
|
||||
instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Symbol
|
||||
|
||||
instance Evaluatable Symbol where
|
||||
eval (Symbol s) = symbol s
|
||||
|
||||
@ -156,6 +179,10 @@ instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Heredoc-style string literals?
|
||||
-- TODO: Character literals.
|
||||
|
||||
instance ToJSONFields1 Regex where
|
||||
toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r]
|
||||
|
||||
|
||||
-- TODO: Implement Eval instance for Regex
|
||||
instance Evaluatable Regex
|
||||
|
||||
@ -169,6 +196,8 @@ instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Array
|
||||
|
||||
instance Evaluatable Array where
|
||||
eval (Array a) = array =<< traverse subtermValue a
|
||||
|
||||
@ -179,6 +208,8 @@ instance Eq1 Hash where liftEq = genericLiftEq
|
||||
instance Ord1 Hash where liftCompare = genericLiftCompare
|
||||
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Hash
|
||||
|
||||
instance Evaluatable Hash where
|
||||
eval = hashElements >>> traverse (subtermValue >=> asPair) >=> hash
|
||||
|
||||
@ -189,10 +220,14 @@ instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||
instance Ord1 KeyValue where liftCompare = genericLiftCompare
|
||||
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 KeyValue
|
||||
|
||||
instance Evaluatable KeyValue where
|
||||
eval (fmap subtermValue -> KeyValue{..}) =
|
||||
join (kvPair <$> key <*> value)
|
||||
|
||||
instance ToJSONFields1 Tuple
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
@ -210,6 +245,8 @@ instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Ord1 Set where liftCompare = genericLiftCompare
|
||||
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Set
|
||||
|
||||
-- TODO: Implement Eval instance for Set
|
||||
instance Evaluatable Set
|
||||
|
||||
@ -224,6 +261,8 @@ instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Pointer
|
||||
|
||||
-- TODO: Implement Eval instance for Pointer
|
||||
instance Evaluatable Pointer
|
||||
|
||||
@ -236,6 +275,8 @@ instance Eq1 Reference where liftEq = genericLiftEq
|
||||
instance Ord1 Reference where liftCompare = genericLiftCompare
|
||||
instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Reference
|
||||
|
||||
-- TODO: Implement Eval instance for Reference
|
||||
instance Evaluatable Reference
|
||||
|
||||
|
@ -3,6 +3,8 @@ module Data.Syntax.Statement where
|
||||
|
||||
import qualified Data.Abstract.Environment as Env
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import Prelude
|
||||
import Prologue
|
||||
@ -15,6 +17,8 @@ instance Eq1 If where liftEq = genericLiftEq
|
||||
instance Ord1 If where liftCompare = genericLiftCompare
|
||||
instance Show1 If where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 If
|
||||
|
||||
instance Evaluatable If where
|
||||
eval (If cond if' else') = do
|
||||
bool <- subtermValue cond
|
||||
@ -28,6 +32,8 @@ instance Eq1 Else where liftEq = genericLiftEq
|
||||
instance Ord1 Else where liftCompare = genericLiftCompare
|
||||
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Else
|
||||
|
||||
-- TODO: Implement Eval instance for Else
|
||||
instance Evaluatable Else
|
||||
|
||||
@ -41,6 +47,8 @@ instance Eq1 Goto where liftEq = genericLiftEq
|
||||
instance Ord1 Goto where liftCompare = genericLiftCompare
|
||||
instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Goto
|
||||
|
||||
-- TODO: Implement Eval instance for Goto
|
||||
instance Evaluatable Goto
|
||||
|
||||
@ -53,6 +61,8 @@ instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Match
|
||||
|
||||
-- TODO: Implement Eval instance for Match
|
||||
instance Evaluatable Match
|
||||
|
||||
@ -65,6 +75,8 @@ instance Eq1 Pattern where liftEq = genericLiftEq
|
||||
instance Ord1 Pattern where liftCompare = genericLiftCompare
|
||||
instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Pattern
|
||||
|
||||
-- TODO: Implement Eval instance for Pattern
|
||||
instance Evaluatable Pattern
|
||||
|
||||
@ -77,6 +89,8 @@ instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Let
|
||||
|
||||
instance Evaluatable Let where
|
||||
eval Let{..} = do
|
||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm letVariable)
|
||||
@ -94,6 +108,8 @@ instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Ord1 Assignment where liftCompare = genericLiftCompare
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Assignment
|
||||
|
||||
instance Evaluatable Assignment where
|
||||
eval Assignment{..} = do
|
||||
case freeVariables (subterm assignmentTarget) of
|
||||
@ -112,6 +128,8 @@ instance Eq1 PostIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 PostIncrement
|
||||
|
||||
-- TODO: Implement Eval instance for PostIncrement
|
||||
instance Evaluatable PostIncrement
|
||||
|
||||
@ -124,6 +142,8 @@ instance Eq1 PostDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 PostDecrement
|
||||
|
||||
-- TODO: Implement Eval instance for PostDecrement
|
||||
instance Evaluatable PostDecrement
|
||||
|
||||
@ -137,6 +157,8 @@ instance Eq1 Return where liftEq = genericLiftEq
|
||||
instance Ord1 Return where liftCompare = genericLiftCompare
|
||||
instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Return
|
||||
|
||||
instance Evaluatable Return where
|
||||
eval (Return x) = subtermValue x >>= earlyReturn
|
||||
|
||||
@ -147,6 +169,8 @@ instance Eq1 Yield where liftEq = genericLiftEq
|
||||
instance Ord1 Yield where liftCompare = genericLiftCompare
|
||||
instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Yield
|
||||
|
||||
-- TODO: Implement Eval instance for Yield
|
||||
instance Evaluatable Yield
|
||||
|
||||
@ -158,6 +182,8 @@ instance Eq1 Break where liftEq = genericLiftEq
|
||||
instance Ord1 Break where liftCompare = genericLiftCompare
|
||||
instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Break
|
||||
|
||||
instance Evaluatable Break where
|
||||
eval (Break x) = subtermValue x >>= throwBreak
|
||||
|
||||
@ -168,6 +194,8 @@ instance Eq1 Continue where liftEq = genericLiftEq
|
||||
instance Ord1 Continue where liftCompare = genericLiftCompare
|
||||
instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Continue
|
||||
|
||||
instance Evaluatable Continue where
|
||||
eval (Continue a) = subtermValue a >>= throwContinue
|
||||
|
||||
@ -178,6 +206,8 @@ instance Eq1 Retry where liftEq = genericLiftEq
|
||||
instance Ord1 Retry where liftCompare = genericLiftCompare
|
||||
instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Retry
|
||||
|
||||
-- TODO: Implement Eval instance for Retry
|
||||
instance Evaluatable Retry
|
||||
|
||||
@ -189,6 +219,8 @@ instance Eq1 NoOp where liftEq = genericLiftEq
|
||||
instance Ord1 NoOp where liftCompare = genericLiftCompare
|
||||
instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 NoOp
|
||||
|
||||
instance Evaluatable NoOp where
|
||||
eval _ = unit
|
||||
|
||||
@ -201,6 +233,8 @@ instance Eq1 For where liftEq = genericLiftEq
|
||||
instance Ord1 For where liftCompare = genericLiftCompare
|
||||
instance Show1 For where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 For
|
||||
|
||||
instance Evaluatable For where
|
||||
eval (fmap subtermValue -> For before cond step body) = forLoop before cond step body
|
||||
|
||||
@ -212,6 +246,8 @@ instance Eq1 ForEach where liftEq = genericLiftEq
|
||||
instance Ord1 ForEach where liftCompare = genericLiftCompare
|
||||
instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ForEach
|
||||
|
||||
-- TODO: Implement Eval instance for ForEach
|
||||
instance Evaluatable ForEach
|
||||
|
||||
@ -223,6 +259,8 @@ instance Eq1 While where liftEq = genericLiftEq
|
||||
instance Ord1 While where liftCompare = genericLiftCompare
|
||||
instance Show1 While where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 While
|
||||
|
||||
instance Evaluatable While where
|
||||
eval While{..} = while (subtermValue whileCondition) (subtermValue whileBody)
|
||||
|
||||
@ -233,6 +271,8 @@ instance Eq1 DoWhile where liftEq = genericLiftEq
|
||||
instance Ord1 DoWhile where liftCompare = genericLiftCompare
|
||||
instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 DoWhile
|
||||
|
||||
instance Evaluatable DoWhile where
|
||||
eval DoWhile{..} = doWhile (subtermValue doWhileBody) (subtermValue doWhileCondition)
|
||||
|
||||
@ -245,6 +285,8 @@ instance Eq1 Throw where liftEq = genericLiftEq
|
||||
instance Ord1 Throw where liftCompare = genericLiftCompare
|
||||
instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Throw
|
||||
|
||||
-- TODO: Implement Eval instance for Throw
|
||||
instance Evaluatable Throw
|
||||
|
||||
@ -256,6 +298,8 @@ instance Eq1 Try where liftEq = genericLiftEq
|
||||
instance Ord1 Try where liftCompare = genericLiftCompare
|
||||
instance Show1 Try where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Try
|
||||
|
||||
-- TODO: Implement Eval instance for Try
|
||||
instance Evaluatable Try
|
||||
|
||||
@ -267,6 +311,8 @@ instance Eq1 Catch where liftEq = genericLiftEq
|
||||
instance Ord1 Catch where liftCompare = genericLiftCompare
|
||||
instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Catch
|
||||
|
||||
-- TODO: Implement Eval instance for Catch
|
||||
instance Evaluatable Catch
|
||||
|
||||
@ -278,6 +324,8 @@ instance Eq1 Finally where liftEq = genericLiftEq
|
||||
instance Ord1 Finally where liftCompare = genericLiftCompare
|
||||
instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Finally
|
||||
|
||||
-- TODO: Implement Eval instance for Finally
|
||||
instance Evaluatable Finally
|
||||
|
||||
@ -292,6 +340,8 @@ instance Eq1 ScopeEntry where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ScopeEntry
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeEntry
|
||||
instance Evaluatable ScopeEntry
|
||||
|
||||
@ -304,6 +354,8 @@ instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeExit where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ScopeExit
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeExit
|
||||
instance Evaluatable ScopeExit
|
||||
|
||||
@ -315,5 +367,8 @@ instance Eq1 HashBang where liftEq = genericLiftEq
|
||||
instance Ord1 HashBang where liftCompare = genericLiftCompare
|
||||
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 HashBang where
|
||||
toJSONFields1 (HashBang f) = noChildren [ "contents" .= unpack f ]
|
||||
|
||||
-- TODO: Implement Eval instance for HashBang
|
||||
instance Evaluatable HashBang
|
||||
|
@ -2,6 +2,7 @@
|
||||
module Data.Syntax.Type where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import Prologue hiding (Map)
|
||||
|
||||
@ -12,6 +13,8 @@ instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Array
|
||||
|
||||
-- TODO: Implement Eval instance for Array
|
||||
instance Evaluatable Array
|
||||
|
||||
@ -24,6 +27,8 @@ instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Annotation where
|
||||
|
||||
-- TODO: Specialize Evaluatable for Type to unify the inferred type of the subject with the specified type
|
||||
instance Evaluatable Annotation where
|
||||
eval Annotation{annotationSubject = Subterm _ action} = action
|
||||
@ -36,6 +41,8 @@ instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Function
|
||||
|
||||
-- TODO: Implement Eval instance for Function
|
||||
instance Evaluatable Function
|
||||
|
||||
@ -47,6 +54,8 @@ instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Ord1 Interface where liftCompare = genericLiftCompare
|
||||
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Interface
|
||||
|
||||
-- TODO: Implement Eval instance for Interface
|
||||
instance Evaluatable Interface
|
||||
|
||||
@ -58,6 +67,8 @@ instance Eq1 Map where liftEq = genericLiftEq
|
||||
instance Ord1 Map where liftCompare = genericLiftCompare
|
||||
instance Show1 Map where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Map
|
||||
|
||||
-- TODO: Implement Eval instance for Map
|
||||
instance Evaluatable Map
|
||||
|
||||
@ -69,6 +80,8 @@ instance Eq1 Parenthesized where liftEq = genericLiftEq
|
||||
instance Ord1 Parenthesized where liftCompare = genericLiftCompare
|
||||
instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Parenthesized
|
||||
|
||||
-- TODO: Implement Eval instance for Parenthesized
|
||||
instance Evaluatable Parenthesized
|
||||
|
||||
@ -80,6 +93,8 @@ instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Pointer
|
||||
|
||||
-- TODO: Implement Eval instance for Pointer
|
||||
instance Evaluatable Pointer
|
||||
|
||||
@ -91,6 +106,8 @@ instance Eq1 Product where liftEq = genericLiftEq
|
||||
instance Ord1 Product where liftCompare = genericLiftCompare
|
||||
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Product
|
||||
|
||||
-- TODO: Implement Eval instance for Product
|
||||
instance Evaluatable Product
|
||||
|
||||
@ -102,6 +119,8 @@ instance Eq1 Readonly where liftEq = genericLiftEq
|
||||
instance Ord1 Readonly where liftCompare = genericLiftCompare
|
||||
instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Readonly
|
||||
|
||||
-- TODO: Implement Eval instance for Readonly
|
||||
instance Evaluatable Readonly
|
||||
|
||||
@ -113,6 +132,8 @@ instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Slice
|
||||
|
||||
-- TODO: Implement Eval instance for Slice
|
||||
instance Evaluatable Slice
|
||||
|
||||
@ -124,5 +145,7 @@ instance Eq1 TypeParameters where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameters where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeParameters
|
||||
|
||||
-- TODO: Implement Eval instance for TypeParameters
|
||||
instance Evaluatable TypeParameters
|
||||
|
@ -8,6 +8,7 @@ import qualified Data.Abstract.Package as Package
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
@ -62,6 +63,8 @@ instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Import
|
||||
|
||||
instance Evaluatable Import where
|
||||
eval (Import importPath _) = do
|
||||
paths <- resolveGoImport importPath
|
||||
@ -82,6 +85,8 @@ instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 QualifiedImport
|
||||
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval (QualifiedImport importPath aliasTerm) = do
|
||||
paths <- resolveGoImport importPath
|
||||
@ -102,6 +107,8 @@ instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 SideEffectImport
|
||||
|
||||
instance Evaluatable SideEffectImport where
|
||||
eval (SideEffectImport importPath _) = do
|
||||
paths <- resolveGoImport importPath
|
||||
@ -117,6 +124,8 @@ instance Eq1 Composite where liftEq = genericLiftEq
|
||||
instance Ord1 Composite where liftCompare = genericLiftCompare
|
||||
instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Composite
|
||||
|
||||
-- TODO: Implement Eval instance for Composite
|
||||
instance Evaluatable Composite
|
||||
|
||||
@ -128,6 +137,8 @@ instance Eq1 DefaultPattern where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 DefaultPattern
|
||||
|
||||
-- TODO: Implement Eval instance for DefaultPattern
|
||||
instance Evaluatable DefaultPattern
|
||||
|
||||
@ -139,6 +150,8 @@ instance Eq1 Defer where liftEq = genericLiftEq
|
||||
instance Ord1 Defer where liftCompare = genericLiftCompare
|
||||
instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Defer
|
||||
|
||||
-- TODO: Implement Eval instance for Defer
|
||||
instance Evaluatable Defer
|
||||
|
||||
@ -150,6 +163,8 @@ instance Eq1 Go where liftEq = genericLiftEq
|
||||
instance Ord1 Go where liftCompare = genericLiftCompare
|
||||
instance Show1 Go where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Go
|
||||
|
||||
-- TODO: Implement Eval instance for Go
|
||||
instance Evaluatable Go
|
||||
|
||||
@ -161,6 +176,8 @@ instance Eq1 Label where liftEq = genericLiftEq
|
||||
instance Ord1 Label where liftCompare = genericLiftCompare
|
||||
instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Label
|
||||
|
||||
-- TODO: Implement Eval instance for Label
|
||||
instance Evaluatable Label
|
||||
|
||||
@ -168,6 +185,8 @@ instance Evaluatable Label
|
||||
newtype Rune a = Rune { _runeLiteral :: ByteString }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Rune
|
||||
|
||||
-- TODO: Implement Eval instance for Rune
|
||||
instance Evaluatable Rune
|
||||
|
||||
@ -179,6 +198,8 @@ instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Select a = Select { selectCases :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Select
|
||||
|
||||
-- TODO: Implement Eval instance for Select
|
||||
instance Evaluatable Select
|
||||
|
||||
@ -194,6 +215,8 @@ instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Send
|
||||
|
||||
-- TODO: Implement Eval instance for Send
|
||||
instance Evaluatable Send
|
||||
|
||||
@ -205,6 +228,8 @@ instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Slice
|
||||
|
||||
-- TODO: Implement Eval instance for Slice
|
||||
instance Evaluatable Slice
|
||||
|
||||
@ -216,6 +241,8 @@ instance Eq1 TypeSwitch where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeSwitch
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitch
|
||||
instance Evaluatable TypeSwitch
|
||||
|
||||
@ -227,6 +254,8 @@ instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeSwitchGuard
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitchGuard
|
||||
instance Evaluatable TypeSwitchGuard
|
||||
|
||||
@ -238,6 +267,8 @@ instance Eq1 Receive where liftEq = genericLiftEq
|
||||
instance Ord1 Receive where liftCompare = genericLiftCompare
|
||||
instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Receive
|
||||
|
||||
-- TODO: Implement Eval instance for Receive
|
||||
instance Evaluatable Receive
|
||||
|
||||
@ -249,6 +280,8 @@ instance Eq1 ReceiveOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ReceiveOperator
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveOperator
|
||||
instance Evaluatable ReceiveOperator
|
||||
|
||||
@ -260,6 +293,8 @@ instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Field
|
||||
|
||||
-- TODO: Implement Eval instance for Field
|
||||
instance Evaluatable Field
|
||||
|
||||
@ -271,6 +306,8 @@ instance Eq1 Package where liftEq = genericLiftEq
|
||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Package
|
||||
|
||||
instance Evaluatable Package where
|
||||
eval (Package _ xs) = eval xs
|
||||
|
||||
@ -283,6 +320,8 @@ instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeAssertion
|
||||
|
||||
-- TODO: Implement Eval instance for TypeAssertion
|
||||
instance Evaluatable TypeAssertion
|
||||
|
||||
@ -294,6 +333,8 @@ instance Eq1 TypeConversion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeConversion
|
||||
|
||||
-- TODO: Implement Eval instance for TypeConversion
|
||||
instance Evaluatable TypeConversion
|
||||
|
||||
@ -305,5 +346,7 @@ instance Eq1 Variadic where liftEq = genericLiftEq
|
||||
instance Ord1 Variadic where liftCompare = genericLiftCompare
|
||||
instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Variadic
|
||||
|
||||
-- TODO: Implement Eval instance for Variadic
|
||||
instance Evaluatable Variadic
|
||||
|
@ -3,6 +3,7 @@ module Language.Go.Type where
|
||||
|
||||
import Prologue
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
|
||||
-- | A Bidirectional channel in Go (e.g. `chan`).
|
||||
@ -13,6 +14,8 @@ instance Eq1 BidirectionalChannel where liftEq = genericLiftEq
|
||||
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 BidirectionalChannel
|
||||
|
||||
-- TODO: Implement Eval instance for BidirectionalChannel
|
||||
instance Evaluatable BidirectionalChannel
|
||||
|
||||
@ -24,6 +27,8 @@ instance Eq1 ReceiveChannel where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ReceiveChannel
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveChannel
|
||||
instance Evaluatable ReceiveChannel
|
||||
|
||||
@ -35,5 +40,7 @@ instance Eq1 SendChannel where liftEq = genericLiftEq
|
||||
instance Ord1 SendChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 SendChannel
|
||||
|
||||
-- TODO: Implement Eval instance for SendChannel
|
||||
instance Evaluatable SendChannel
|
||||
|
@ -2,11 +2,15 @@
|
||||
module Language.Markdown.Syntax where
|
||||
|
||||
import Prologue hiding (Text)
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
|
||||
newtype Document a = Document [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Document
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Ord1 Document where liftCompare = genericLiftCompare
|
||||
instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -17,6 +21,8 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Paragraph a = Paragraph [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Paragraph
|
||||
|
||||
instance Eq1 Paragraph where liftEq = genericLiftEq
|
||||
instance Ord1 Paragraph where liftCompare = genericLiftCompare
|
||||
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -24,6 +30,8 @@ instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Heading
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Ord1 Heading where liftCompare = genericLiftCompare
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -31,10 +39,14 @@ instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype UnorderedList a = UnorderedList [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 UnorderedList
|
||||
|
||||
instance Eq1 UnorderedList where liftEq = genericLiftEq
|
||||
instance Ord1 UnorderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 OrderedList
|
||||
|
||||
newtype OrderedList a = OrderedList [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
@ -42,6 +54,8 @@ instance Eq1 OrderedList where liftEq = genericLiftEq
|
||||
instance Ord1 OrderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 BlockQuote
|
||||
|
||||
newtype BlockQuote a = BlockQuote [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
@ -49,6 +63,8 @@ instance Eq1 BlockQuote where liftEq = genericLiftEq
|
||||
instance Ord1 BlockQuote where liftCompare = genericLiftCompare
|
||||
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ThematicBreak
|
||||
|
||||
data ThematicBreak a = ThematicBreak
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
@ -56,6 +72,9 @@ instance Eq1 ThematicBreak where liftEq = genericLiftEq
|
||||
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 HTMLBlock where
|
||||
toJSONFields1 (HTMLBlock b) = noChildren [ "asString" .= unpack b ]
|
||||
|
||||
newtype HTMLBlock a = HTMLBlock ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
@ -66,6 +85,8 @@ instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Table a = Table [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Table
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Ord1 Table where liftCompare = genericLiftCompare
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -73,6 +94,8 @@ instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype TableRow a = TableRow [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TableRow
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Ord1 TableRow where liftCompare = genericLiftCompare
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -80,6 +103,8 @@ instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype TableCell a = TableCell [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TableCell
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Ord1 TableCell where liftCompare = genericLiftCompare
|
||||
instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -90,6 +115,8 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Strong a = Strong [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Strong
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Ord1 Strong where liftCompare = genericLiftCompare
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -97,6 +124,8 @@ instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Emphasis a = Emphasis [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Emphasis
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Ord1 Emphasis where liftCompare = genericLiftCompare
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -104,6 +133,9 @@ instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Text where
|
||||
toJSONFields1 (Text s) = noChildren ["asString" .= unpack s ]
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -111,6 +143,9 @@ instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Link
|
||||
|
||||
instance Eq1 Link where liftEq = genericLiftEq
|
||||
instance Ord1 Link where liftCompare = genericLiftCompare
|
||||
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -118,6 +153,9 @@ instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
|
||||
data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Image
|
||||
|
||||
instance Eq1 Image where liftEq = genericLiftEq
|
||||
instance Ord1 Image where liftCompare = genericLiftCompare
|
||||
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -125,6 +163,9 @@ instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
|
||||
data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Code
|
||||
|
||||
instance Eq1 Code where liftEq = genericLiftEq
|
||||
instance Ord1 Code where liftCompare = genericLiftCompare
|
||||
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -132,10 +173,14 @@ instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
|
||||
data LineBreak a = LineBreak
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 LineBreak
|
||||
|
||||
instance Eq1 LineBreak where liftEq = genericLiftEq
|
||||
instance Ord1 LineBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Strikethrough
|
||||
|
||||
newtype Strikethrough a = Strikethrough [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
|
@ -5,6 +5,7 @@ import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import Diffing.Algorithm
|
||||
import Prelude hiding (fail)
|
||||
@ -13,6 +14,9 @@ import Prologue hiding (Text)
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Text where
|
||||
toJSONFields1 (Text t) = noChildren ["asString" .= BC.unpack t]
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -22,6 +26,8 @@ instance Evaluatable Text
|
||||
newtype VariableName a = VariableName a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 VariableName
|
||||
|
||||
instance Eq1 VariableName where liftEq = genericLiftEq
|
||||
instance Ord1 VariableName where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableName where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -72,6 +78,8 @@ instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Require
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval (Require path) = include path load
|
||||
|
||||
@ -83,6 +91,8 @@ instance Eq1 RequireOnce where liftEq = genericLiftEq
|
||||
instance Ord1 RequireOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 RequireOnce
|
||||
|
||||
instance Evaluatable RequireOnce where
|
||||
eval (RequireOnce path) = include path require
|
||||
|
||||
@ -94,6 +104,8 @@ instance Eq1 Include where liftEq = genericLiftEq
|
||||
instance Ord1 Include where liftCompare = genericLiftCompare
|
||||
instance Show1 Include where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Include
|
||||
|
||||
instance Evaluatable Include where
|
||||
eval (Include path) = include path load
|
||||
|
||||
@ -105,6 +117,8 @@ instance Eq1 IncludeOnce where liftEq = genericLiftEq
|
||||
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 IncludeOnce
|
||||
|
||||
instance Evaluatable IncludeOnce where
|
||||
eval (IncludeOnce path) = include path require
|
||||
|
||||
@ -112,6 +126,8 @@ instance Evaluatable IncludeOnce where
|
||||
newtype ArrayElement a = ArrayElement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ArrayElement
|
||||
|
||||
instance Eq1 ArrayElement where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayElement where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -120,6 +136,8 @@ instance Evaluatable ArrayElement
|
||||
newtype GlobalDeclaration a = GlobalDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 GlobalDeclaration
|
||||
|
||||
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -128,6 +146,8 @@ instance Evaluatable GlobalDeclaration
|
||||
newtype SimpleVariable a = SimpleVariable a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 SimpleVariable
|
||||
|
||||
instance Eq1 SimpleVariable where liftEq = genericLiftEq
|
||||
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 SimpleVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -138,6 +158,8 @@ instance Evaluatable SimpleVariable
|
||||
newtype CastType a = CastType { _castType :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 CastType
|
||||
|
||||
instance Eq1 CastType where liftEq = genericLiftEq
|
||||
instance Ord1 CastType where liftCompare = genericLiftCompare
|
||||
instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -146,6 +168,8 @@ instance Evaluatable CastType
|
||||
newtype ErrorControl a = ErrorControl a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ErrorControl
|
||||
|
||||
instance Eq1 ErrorControl where liftEq = genericLiftEq
|
||||
instance Ord1 ErrorControl where liftCompare = genericLiftCompare
|
||||
instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -154,6 +178,8 @@ instance Evaluatable ErrorControl
|
||||
newtype Clone a = Clone a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Clone
|
||||
|
||||
instance Eq1 Clone where liftEq = genericLiftEq
|
||||
instance Ord1 Clone where liftCompare = genericLiftCompare
|
||||
instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -162,6 +188,8 @@ instance Evaluatable Clone
|
||||
newtype ShellCommand a = ShellCommand ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ShellCommand
|
||||
|
||||
instance Eq1 ShellCommand where liftEq = genericLiftEq
|
||||
instance Ord1 ShellCommand where liftCompare = genericLiftCompare
|
||||
instance Show1 ShellCommand where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -171,6 +199,8 @@ instance Evaluatable ShellCommand
|
||||
newtype Update a = Update { _updateSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Update
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -179,6 +209,8 @@ instance Evaluatable Update
|
||||
newtype NewVariable a = NewVariable [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NewVariable
|
||||
|
||||
instance Eq1 NewVariable where liftEq = genericLiftEq
|
||||
instance Ord1 NewVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -187,6 +219,8 @@ instance Evaluatable NewVariable
|
||||
newtype RelativeScope a = RelativeScope ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 RelativeScope
|
||||
|
||||
instance Eq1 RelativeScope where liftEq = genericLiftEq
|
||||
instance Ord1 RelativeScope where liftCompare = genericLiftCompare
|
||||
instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -195,6 +229,8 @@ instance Evaluatable RelativeScope
|
||||
data QualifiedName a = QualifiedName !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 QualifiedName
|
||||
|
||||
instance Eq1 QualifiedName where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedName where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -205,6 +241,8 @@ instance Evaluatable QualifiedName where
|
||||
newtype NamespaceName a = NamespaceName (NonEmpty a)
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceName
|
||||
|
||||
instance Eq1 NamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -215,6 +253,8 @@ instance Evaluatable NamespaceName where
|
||||
newtype ConstDeclaration a = ConstDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ConstDeclaration
|
||||
|
||||
instance Eq1 ConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -223,6 +263,8 @@ instance Evaluatable ConstDeclaration
|
||||
data ClassConstDeclaration a = ClassConstDeclaration a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassConstDeclaration
|
||||
|
||||
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -231,6 +273,8 @@ instance Evaluatable ClassConstDeclaration
|
||||
newtype ClassInterfaceClause a = ClassInterfaceClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassInterfaceClause
|
||||
|
||||
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -239,6 +283,8 @@ instance Evaluatable ClassInterfaceClause
|
||||
newtype ClassBaseClause a = ClassBaseClause a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassBaseClause
|
||||
|
||||
instance Eq1 ClassBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassBaseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -248,6 +294,8 @@ instance Evaluatable ClassBaseClause
|
||||
newtype UseClause a = UseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 UseClause
|
||||
|
||||
instance Eq1 UseClause where liftEq = genericLiftEq
|
||||
instance Ord1 UseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -256,6 +304,8 @@ instance Evaluatable UseClause
|
||||
newtype ReturnType a = ReturnType a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ReturnType
|
||||
|
||||
instance Eq1 ReturnType where liftEq = genericLiftEq
|
||||
instance Ord1 ReturnType where liftCompare = genericLiftCompare
|
||||
instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -264,6 +314,8 @@ instance Evaluatable ReturnType
|
||||
newtype TypeDeclaration a = TypeDeclaration a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TypeDeclaration
|
||||
|
||||
instance Eq1 TypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -272,6 +324,8 @@ instance Evaluatable TypeDeclaration
|
||||
newtype BaseTypeDeclaration a = BaseTypeDeclaration a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 BaseTypeDeclaration
|
||||
|
||||
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -280,6 +334,8 @@ instance Evaluatable BaseTypeDeclaration
|
||||
newtype ScalarType a = ScalarType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ScalarType
|
||||
|
||||
instance Eq1 ScalarType where liftEq = genericLiftEq
|
||||
instance Ord1 ScalarType where liftCompare = genericLiftCompare
|
||||
instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -288,6 +344,8 @@ instance Evaluatable ScalarType
|
||||
newtype EmptyIntrinsic a = EmptyIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 EmptyIntrinsic
|
||||
|
||||
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
|
||||
instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -296,6 +354,8 @@ instance Evaluatable EmptyIntrinsic
|
||||
newtype ExitIntrinsic a = ExitIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ExitIntrinsic
|
||||
|
||||
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
|
||||
instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -304,6 +364,8 @@ instance Evaluatable ExitIntrinsic
|
||||
newtype IssetIntrinsic a = IssetIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 IssetIntrinsic
|
||||
|
||||
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
|
||||
instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -312,6 +374,8 @@ instance Evaluatable IssetIntrinsic
|
||||
newtype EvalIntrinsic a = EvalIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 EvalIntrinsic
|
||||
|
||||
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
|
||||
instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -320,6 +384,8 @@ instance Evaluatable EvalIntrinsic
|
||||
newtype PrintIntrinsic a = PrintIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PrintIntrinsic
|
||||
|
||||
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
|
||||
instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -328,6 +394,8 @@ instance Evaluatable PrintIntrinsic
|
||||
newtype NamespaceAliasingClause a = NamespaceAliasingClause a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceAliasingClause
|
||||
|
||||
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -336,6 +404,8 @@ instance Evaluatable NamespaceAliasingClause
|
||||
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseDeclaration
|
||||
|
||||
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -344,6 +414,8 @@ instance Evaluatable NamespaceUseDeclaration
|
||||
newtype NamespaceUseClause a = NamespaceUseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseClause
|
||||
|
||||
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -352,6 +424,8 @@ instance Evaluatable NamespaceUseClause
|
||||
newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseGroupClause
|
||||
|
||||
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -364,6 +438,8 @@ instance Eq1 Namespace where liftEq = genericLiftEq
|
||||
instance Ord1 Namespace where liftCompare = genericLiftCompare
|
||||
instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Namespace
|
||||
|
||||
instance Evaluatable Namespace where
|
||||
eval Namespace{..} = go names
|
||||
where
|
||||
@ -379,6 +455,8 @@ instance Evaluatable Namespace where
|
||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitDeclaration
|
||||
|
||||
instance Eq1 TraitDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 TraitDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -387,6 +465,8 @@ instance Evaluatable TraitDeclaration
|
||||
data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 AliasAs
|
||||
|
||||
instance Eq1 AliasAs where liftEq = genericLiftEq
|
||||
instance Ord1 AliasAs where liftCompare = genericLiftCompare
|
||||
instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -395,6 +475,8 @@ instance Evaluatable AliasAs
|
||||
data InsteadOf a = InsteadOf a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InsteadOf
|
||||
|
||||
instance Eq1 InsteadOf where liftEq = genericLiftEq
|
||||
instance Ord1 InsteadOf where liftCompare = genericLiftCompare
|
||||
instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -403,6 +485,8 @@ instance Evaluatable InsteadOf
|
||||
newtype TraitUseSpecification a = TraitUseSpecification [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitUseSpecification
|
||||
|
||||
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
|
||||
instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -411,6 +495,8 @@ instance Evaluatable TraitUseSpecification
|
||||
data TraitUseClause a = TraitUseClause [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitUseClause
|
||||
|
||||
instance Eq1 TraitUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -419,6 +505,8 @@ instance Evaluatable TraitUseClause
|
||||
data DestructorDeclaration a = DestructorDeclaration [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 DestructorDeclaration
|
||||
|
||||
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -427,6 +515,8 @@ instance Evaluatable DestructorDeclaration
|
||||
newtype Static a = Static ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Static
|
||||
|
||||
instance Eq1 Static where liftEq = genericLiftEq
|
||||
instance Ord1 Static where liftCompare = genericLiftCompare
|
||||
instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -435,6 +525,8 @@ instance Evaluatable Static
|
||||
newtype ClassModifier a = ClassModifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassModifier
|
||||
|
||||
instance Eq1 ClassModifier where liftEq = genericLiftEq
|
||||
instance Ord1 ClassModifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -443,6 +535,8 @@ instance Evaluatable ClassModifier
|
||||
data ConstructorDeclaration a = ConstructorDeclaration [a] [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ConstructorDeclaration
|
||||
|
||||
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -451,6 +545,8 @@ instance Evaluatable ConstructorDeclaration
|
||||
data PropertyDeclaration a = PropertyDeclaration a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PropertyDeclaration
|
||||
|
||||
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -459,6 +555,8 @@ instance Evaluatable PropertyDeclaration
|
||||
data PropertyModifier a = PropertyModifier a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PropertyModifier
|
||||
|
||||
instance Eq1 PropertyModifier where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
|
||||
instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -467,6 +565,8 @@ instance Evaluatable PropertyModifier
|
||||
data InterfaceDeclaration a = InterfaceDeclaration a a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InterfaceDeclaration
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -475,6 +575,8 @@ instance Evaluatable InterfaceDeclaration
|
||||
newtype InterfaceBaseClause a = InterfaceBaseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InterfaceBaseClause
|
||||
|
||||
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -483,6 +585,8 @@ instance Evaluatable InterfaceBaseClause
|
||||
newtype Echo a = Echo a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Echo
|
||||
|
||||
instance Eq1 Echo where liftEq = genericLiftEq
|
||||
instance Ord1 Echo where liftCompare = genericLiftCompare
|
||||
instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -491,6 +595,8 @@ instance Evaluatable Echo
|
||||
newtype Unset a = Unset a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Unset
|
||||
|
||||
instance Eq1 Unset where liftEq = genericLiftEq
|
||||
instance Ord1 Unset where liftCompare = genericLiftCompare
|
||||
instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -499,6 +605,8 @@ instance Evaluatable Unset
|
||||
data Declare a = Declare a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Declare
|
||||
|
||||
instance Eq1 Declare where liftEq = genericLiftEq
|
||||
instance Ord1 Declare where liftCompare = genericLiftCompare
|
||||
instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -507,6 +615,8 @@ instance Evaluatable Declare
|
||||
newtype DeclareDirective a = DeclareDirective a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 DeclareDirective
|
||||
|
||||
instance Eq1 DeclareDirective where liftEq = genericLiftEq
|
||||
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
|
||||
instance Show1 DeclareDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -515,6 +625,8 @@ instance Evaluatable DeclareDirective
|
||||
newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 LabeledStatement
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
@ -8,6 +8,7 @@ import Data.Abstract.Module
|
||||
import Data.Align.Generic
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Mergeable
|
||||
@ -90,6 +91,8 @@ resolvePythonModules q = do
|
||||
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![(Name, Name)] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Import
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -118,6 +121,8 @@ instance Evaluatable Import where
|
||||
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedName }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 QualifiedImport
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -144,6 +149,8 @@ instance Evaluatable QualifiedImport where
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 QualifiedAliasedImport
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -173,6 +180,8 @@ instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||
instance Ord1 Ellipsis where liftCompare = genericLiftCompare
|
||||
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Ellipsis
|
||||
|
||||
-- TODO: Implement Eval instance for Ellipsis
|
||||
instance Evaluatable Ellipsis
|
||||
|
||||
@ -184,5 +193,7 @@ instance Eq1 Redirect where liftEq = genericLiftEq
|
||||
instance Ord1 Redirect where liftCompare = genericLiftCompare
|
||||
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Redirect
|
||||
|
||||
-- TODO: Implement Eval instance for Redirect
|
||||
instance Evaluatable Redirect
|
||||
|
@ -6,6 +6,7 @@ import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.Module as M
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import Diffing.Algorithm
|
||||
import Prelude hiding (fail)
|
||||
@ -48,11 +49,13 @@ instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Send
|
||||
|
||||
instance Evaluatable Send where
|
||||
eval Send{..} = do
|
||||
let sel = case sendSelector of
|
||||
Just sel -> subtermValue sel
|
||||
Nothing -> variable (name "call")
|
||||
Nothing -> variable (name "call")
|
||||
func <- maybe sel (flip evaluateInScopedEnv sel . subtermValue) sendReceiver
|
||||
call func (map subtermValue sendArgs) -- TODO pass through sendBlock
|
||||
|
||||
@ -63,6 +66,8 @@ instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Require
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval (Require _ x) = do
|
||||
name <- subtermValue x >>= asString
|
||||
@ -91,6 +96,8 @@ instance Eq1 Load where liftEq = genericLiftEq
|
||||
instance Ord1 Load where liftCompare = genericLiftCompare
|
||||
instance Show1 Load where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Load
|
||||
|
||||
instance Evaluatable Load where
|
||||
eval (Load [x]) = do
|
||||
path <- subtermValue x >>= asString
|
||||
@ -124,6 +131,8 @@ doLoad path shouldWrap = do
|
||||
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Class
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
|
||||
@ -145,6 +154,8 @@ instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Module
|
||||
|
||||
instance Evaluatable Module where
|
||||
eval (Module iden xs) = do
|
||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||
@ -156,6 +167,8 @@ data LowPrecedenceBoolean a
|
||||
| LowOr !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LowPrecedenceBoolean
|
||||
|
||||
instance Evaluatable LowPrecedenceBoolean where
|
||||
-- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands
|
||||
eval = go . fmap subtermValue where
|
||||
|
@ -8,6 +8,7 @@ import qualified Data.Abstract.Module as M
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import qualified Data.ByteString as B
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import Data.Semigroup.Reducer (Reducer)
|
||||
import Diffing.Algorithm
|
||||
@ -141,6 +142,8 @@ evalRequire modulePath alias = letrec' alias $ \addr -> do
|
||||
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Import
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -163,6 +166,8 @@ instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
|
||||
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
|
||||
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 JavaScriptRequire
|
||||
|
||||
instance Evaluatable JavaScriptRequire where
|
||||
eval (JavaScriptRequire aliasTerm importPath) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions
|
||||
@ -177,6 +182,8 @@ instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 QualifiedAliasedImport
|
||||
|
||||
instance Evaluatable QualifiedAliasedImport where
|
||||
eval (QualifiedAliasedImport aliasTerm importPath) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||
@ -190,6 +197,8 @@ instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 SideEffectImport
|
||||
|
||||
instance Evaluatable SideEffectImport where
|
||||
eval (SideEffectImport importPath) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||
@ -205,6 +214,8 @@ instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 QualifiedExport
|
||||
|
||||
instance Evaluatable QualifiedExport where
|
||||
eval (QualifiedExport exportSymbols) = do
|
||||
-- Insert the aliases with no addresses.
|
||||
@ -221,6 +232,8 @@ instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 QualifiedExportFrom
|
||||
|
||||
instance Evaluatable QualifiedExportFrom where
|
||||
eval (QualifiedExportFrom importPath exportSymbols) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||
@ -234,6 +247,8 @@ instance Evaluatable QualifiedExportFrom where
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 DefaultExport
|
||||
|
||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -255,6 +270,8 @@ instance Evaluatable DefaultExport where
|
||||
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LookupType
|
||||
|
||||
instance Eq1 LookupType where liftEq = genericLiftEq
|
||||
instance Ord1 LookupType where liftCompare = genericLiftCompare
|
||||
instance Show1 LookupType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -264,6 +281,8 @@ instance Evaluatable LookupType
|
||||
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ShorthandPropertyIdentifier
|
||||
|
||||
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -272,6 +291,8 @@ instance Evaluatable ShorthandPropertyIdentifier
|
||||
data Union a = Union { _unionLeft :: !a, _unionRight :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Language.TypeScript.Syntax.Union
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.Union where liftCompare = genericLiftCompare
|
||||
instance Show1 Language.TypeScript.Syntax.Union where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -280,6 +301,8 @@ instance Evaluatable Language.TypeScript.Syntax.Union
|
||||
data Intersection a = Intersection { _intersectionLeft :: !a, _intersectionRight :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Intersection
|
||||
|
||||
instance Eq1 Intersection where liftEq = genericLiftEq
|
||||
instance Ord1 Intersection where liftCompare = genericLiftCompare
|
||||
instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -288,6 +311,8 @@ instance Evaluatable Intersection
|
||||
data FunctionType a = FunctionType { _functionTypeParameters :: !a, _functionFormalParameters :: ![a], _functionType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 FunctionType
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -296,6 +321,8 @@ instance Evaluatable FunctionType
|
||||
data AmbientFunction a = AmbientFunction { _ambientFunctionContext :: ![a], _ambientFunctionIdentifier :: !a, _ambientFunctionParameters :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AmbientFunction
|
||||
|
||||
instance Eq1 AmbientFunction where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
|
||||
instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -304,6 +331,8 @@ instance Evaluatable AmbientFunction
|
||||
data ImportRequireClause a = ImportRequireClause { _importRequireIdentifier :: !a, _importRequireSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportRequireClause
|
||||
|
||||
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -312,6 +341,8 @@ instance Evaluatable ImportRequireClause
|
||||
newtype ImportClause a = ImportClause { _importClauseElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportClause
|
||||
|
||||
instance Eq1 ImportClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -320,6 +351,8 @@ instance Evaluatable ImportClause
|
||||
newtype Tuple a = Tuple { _tupleElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Tuple
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -330,6 +363,8 @@ instance Evaluatable Tuple
|
||||
data Constructor a = Constructor { _constructorTypeParameters :: !a, _constructorFormalParameters :: ![a], _constructorType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Language.TypeScript.Syntax.Constructor
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Language.TypeScript.Syntax.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -338,6 +373,8 @@ instance Evaluatable Language.TypeScript.Syntax.Constructor
|
||||
data TypeParameter a = TypeParameter { _typeParameter :: !a, _typeParameterConstraint :: !a, _typeParameterDefaultType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeParameter
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -346,6 +383,8 @@ instance Evaluatable TypeParameter
|
||||
data TypeAssertion a = TypeAssertion { _typeAssertionParameters :: !a, _typeAssertionExpression :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeAssertion
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -354,6 +393,8 @@ instance Evaluatable TypeAssertion
|
||||
newtype Annotation a = Annotation { _annotationType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Annotation
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -362,6 +403,8 @@ instance Evaluatable Annotation
|
||||
newtype Decorator a = Decorator { _decoratorTerm :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Decorator
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -370,6 +413,8 @@ instance Evaluatable Decorator
|
||||
newtype ComputedPropertyName a = ComputedPropertyName a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ComputedPropertyName
|
||||
|
||||
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
|
||||
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
|
||||
instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -378,6 +423,8 @@ instance Evaluatable ComputedPropertyName
|
||||
newtype Constraint a = Constraint { _constraintType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Constraint
|
||||
|
||||
instance Eq1 Constraint where liftEq = genericLiftEq
|
||||
instance Ord1 Constraint where liftCompare = genericLiftCompare
|
||||
instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -386,6 +433,8 @@ instance Evaluatable Constraint
|
||||
newtype DefaultType a = DefaultType { _defaultType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 DefaultType
|
||||
|
||||
instance Eq1 DefaultType where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultType where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -394,6 +443,8 @@ instance Evaluatable DefaultType
|
||||
newtype ParenthesizedType a = ParenthesizedType { _parenthesizedType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ParenthesizedType
|
||||
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -402,6 +453,8 @@ instance Evaluatable ParenthesizedType
|
||||
newtype PredefinedType a = PredefinedType { _predefinedType :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 PredefinedType
|
||||
|
||||
instance Eq1 PredefinedType where liftEq = genericLiftEq
|
||||
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
|
||||
instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -410,6 +463,8 @@ instance Evaluatable PredefinedType
|
||||
newtype TypeIdentifier a = TypeIdentifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeIdentifier
|
||||
|
||||
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -418,6 +473,8 @@ instance Evaluatable TypeIdentifier
|
||||
data NestedIdentifier a = NestedIdentifier !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 NestedIdentifier
|
||||
|
||||
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -426,6 +483,8 @@ instance Evaluatable NestedIdentifier
|
||||
data NestedTypeIdentifier a = NestedTypeIdentifier !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 NestedTypeIdentifier
|
||||
|
||||
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -434,6 +493,8 @@ instance Evaluatable NestedTypeIdentifier
|
||||
data GenericType a = GenericType { _genericTypeIdentifier :: !a, _genericTypeArguments :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 GenericType
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -442,6 +503,8 @@ instance Evaluatable GenericType
|
||||
data TypePredicate a = TypePredicate { _typePredicateIdentifier :: !a, _typePredicateType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypePredicate
|
||||
|
||||
instance Eq1 TypePredicate where liftEq = genericLiftEq
|
||||
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
|
||||
instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -450,6 +513,8 @@ instance Evaluatable TypePredicate
|
||||
newtype ObjectType a = ObjectType { _objectTypeElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ObjectType
|
||||
|
||||
instance Eq1 ObjectType where liftEq = genericLiftEq
|
||||
instance Ord1 ObjectType where liftCompare = genericLiftCompare
|
||||
instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -458,6 +523,8 @@ instance Evaluatable ObjectType
|
||||
data With a = With { _withExpression :: !a, _withBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 With
|
||||
|
||||
instance Eq1 With where liftEq = genericLiftEq
|
||||
instance Ord1 With where liftCompare = genericLiftCompare
|
||||
instance Show1 With where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -466,6 +533,8 @@ instance Evaluatable With
|
||||
newtype AmbientDeclaration a = AmbientDeclaration { _ambientDeclarationBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AmbientDeclaration
|
||||
|
||||
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 AmbientDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -476,6 +545,8 @@ instance Evaluatable AmbientDeclaration where
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 EnumDeclaration
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -487,6 +558,8 @@ instance Declarations a => Declarations (EnumDeclaration a) where
|
||||
newtype ExtendsClause a = ExtendsClause { _extendsClauses :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ExtendsClause
|
||||
|
||||
instance Eq1 ExtendsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -495,6 +568,8 @@ instance Evaluatable ExtendsClause
|
||||
newtype ArrayType a = ArrayType { _arrayType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ArrayType
|
||||
|
||||
instance Eq1 ArrayType where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayType where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -503,6 +578,8 @@ instance Evaluatable ArrayType
|
||||
newtype FlowMaybeType a = FlowMaybeType { _flowMaybeType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 FlowMaybeType
|
||||
|
||||
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
|
||||
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
|
||||
instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -511,6 +588,8 @@ instance Evaluatable FlowMaybeType
|
||||
newtype TypeQuery a = TypeQuery { _typeQuerySubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeQuery
|
||||
|
||||
instance Eq1 TypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -519,6 +598,8 @@ instance Evaluatable TypeQuery
|
||||
newtype IndexTypeQuery a = IndexTypeQuery { _indexTypeQuerySubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 IndexTypeQuery
|
||||
|
||||
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -527,6 +608,8 @@ instance Evaluatable IndexTypeQuery
|
||||
newtype TypeArguments a = TypeArguments { _typeArguments :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeArguments
|
||||
|
||||
instance Eq1 TypeArguments where liftEq = genericLiftEq
|
||||
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -535,6 +618,8 @@ instance Evaluatable TypeArguments
|
||||
newtype ThisType a = ThisType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ThisType
|
||||
|
||||
instance Eq1 ThisType where liftEq = genericLiftEq
|
||||
instance Ord1 ThisType where liftCompare = genericLiftCompare
|
||||
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -543,6 +628,8 @@ instance Evaluatable ThisType
|
||||
newtype ExistentialType a = ExistentialType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ExistentialType
|
||||
|
||||
instance Eq1 ExistentialType where liftEq = genericLiftEq
|
||||
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
|
||||
instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -551,6 +638,8 @@ instance Evaluatable ExistentialType
|
||||
newtype LiteralType a = LiteralType { _literalTypeSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LiteralType
|
||||
|
||||
instance Eq1 LiteralType where liftEq = genericLiftEq
|
||||
instance Ord1 LiteralType where liftCompare = genericLiftCompare
|
||||
instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -559,6 +648,8 @@ instance Evaluatable LiteralType
|
||||
data PropertySignature a = PropertySignature { _modifiers :: ![a], _propertySignaturePropertyName :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 PropertySignature
|
||||
|
||||
instance Eq1 PropertySignature where liftEq = genericLiftEq
|
||||
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
|
||||
instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -567,6 +658,8 @@ instance Evaluatable PropertySignature
|
||||
data CallSignature a = CallSignature { _callSignatureTypeParameters :: !a, _callSignatureParameters :: ![a], _callSignatureType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 CallSignature
|
||||
|
||||
instance Eq1 CallSignature where liftEq = genericLiftEq
|
||||
instance Ord1 CallSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 CallSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -576,6 +669,8 @@ instance Evaluatable CallSignature
|
||||
data ConstructSignature a = ConstructSignature { _constructSignatureTypeParameters :: !a, _constructSignatureParameters :: ![a], _constructSignatureType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ConstructSignature
|
||||
|
||||
instance Eq1 ConstructSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -584,6 +679,8 @@ instance Evaluatable ConstructSignature
|
||||
data IndexSignature a = IndexSignature { _indexSignatureSubject :: a, _indexSignatureType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 IndexSignature
|
||||
|
||||
instance Eq1 IndexSignature where liftEq = genericLiftEq
|
||||
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -592,6 +689,8 @@ instance Evaluatable IndexSignature
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { _abstractMethodSignatureContext :: ![a], _abstractMethodSignatureName :: !a, _abstractMethodSignatureParameters :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AbstractMethodSignature
|
||||
|
||||
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -600,6 +699,8 @@ instance Evaluatable AbstractMethodSignature
|
||||
data Debugger a = Debugger
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Debugger
|
||||
|
||||
instance Eq1 Debugger where liftEq = genericLiftEq
|
||||
instance Ord1 Debugger where liftCompare = genericLiftCompare
|
||||
instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -608,6 +709,8 @@ instance Evaluatable Debugger
|
||||
data ForOf a = ForOf { _forOfBinding :: !a, _forOfSubject :: !a, _forOfBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ForOf
|
||||
|
||||
instance Eq1 ForOf where liftEq = genericLiftEq
|
||||
instance Ord1 ForOf where liftCompare = genericLiftCompare
|
||||
instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -616,6 +719,8 @@ instance Evaluatable ForOf
|
||||
data This a = This
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 This
|
||||
|
||||
instance Eq1 This where liftEq = genericLiftEq
|
||||
instance Ord1 This where liftCompare = genericLiftCompare
|
||||
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -624,6 +729,8 @@ instance Evaluatable This
|
||||
data LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: !a, _labeledStatementSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LabeledStatement
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -632,6 +739,8 @@ instance Evaluatable LabeledStatement
|
||||
newtype Update a = Update { _updateSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Update
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -644,6 +753,8 @@ instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Module
|
||||
|
||||
instance Evaluatable Module where
|
||||
eval (Module iden xs) = do
|
||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||
@ -659,6 +770,8 @@ instance Eq1 InternalModule where liftEq = genericLiftEq
|
||||
instance Ord1 InternalModule where liftCompare = genericLiftCompare
|
||||
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 InternalModule
|
||||
|
||||
instance Evaluatable InternalModule where
|
||||
eval (InternalModule iden xs) = do
|
||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||
@ -672,6 +785,8 @@ instance Declarations a => Declarations (InternalModule a) where
|
||||
data ImportAlias a = ImportAlias { _importAliasSubject :: !a, _importAlias :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportAlias
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -680,6 +795,8 @@ instance Evaluatable ImportAlias
|
||||
data Super a = Super
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Super
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -688,6 +805,8 @@ instance Evaluatable Super
|
||||
data Undefined a = Undefined
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Undefined
|
||||
|
||||
instance Eq1 Undefined where liftEq = genericLiftEq
|
||||
instance Ord1 Undefined where liftCompare = genericLiftCompare
|
||||
instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -696,6 +815,8 @@ instance Evaluatable Undefined
|
||||
data ClassHeritage a = ClassHeritage { _classHeritageExtendsClause :: !a, _implementsClause :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ClassHeritage
|
||||
|
||||
instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -710,6 +831,8 @@ instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Declarations a => Declarations (AbstractClass a) where
|
||||
declaredName AbstractClass{..} = declaredName abstractClassIdentifier
|
||||
|
||||
instance ToJSONFields1 AbstractClass
|
||||
|
||||
instance Evaluatable AbstractClass where
|
||||
eval AbstractClass{..} = do
|
||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm abstractClassIdentifier)
|
||||
@ -724,6 +847,8 @@ instance Evaluatable AbstractClass where
|
||||
data JsxElement a = JsxElement { _jsxOpeningElement :: !a, _jsxElements :: ![a], _jsxClosingElement :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxElement
|
||||
|
||||
instance Eq1 JsxElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -732,6 +857,8 @@ instance Evaluatable JsxElement
|
||||
newtype JsxText a = JsxText ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxText
|
||||
|
||||
instance Eq1 JsxText where liftEq = genericLiftEq
|
||||
instance Ord1 JsxText where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -740,6 +867,8 @@ instance Evaluatable JsxText
|
||||
newtype JsxExpression a = JsxExpression { _jsxExpression :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxExpression
|
||||
|
||||
instance Eq1 JsxExpression where liftEq = genericLiftEq
|
||||
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -748,6 +877,8 @@ instance Evaluatable JsxExpression
|
||||
data JsxOpeningElement a = JsxOpeningElement { _jsxOpeningElementIdentifier :: !a, _jsxAttributes :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxOpeningElement
|
||||
|
||||
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -756,6 +887,8 @@ instance Evaluatable JsxOpeningElement
|
||||
newtype JsxClosingElement a = JsxClosingElement { _jsxClosingElementIdentifier :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxClosingElement
|
||||
|
||||
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -764,6 +897,8 @@ instance Evaluatable JsxClosingElement
|
||||
data JsxSelfClosingElement a = JsxSelfClosingElement { _jsxSelfClosingElementIdentifier :: !a, _jsxSelfClosingElementAttributes :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxSelfClosingElement
|
||||
|
||||
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -772,6 +907,8 @@ instance Evaluatable JsxSelfClosingElement
|
||||
data JsxAttribute a = JsxAttribute { _jsxAttributeTarget :: !a, _jsxAttributeValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxAttribute
|
||||
|
||||
instance Eq1 JsxAttribute where liftEq = genericLiftEq
|
||||
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -780,6 +917,8 @@ instance Evaluatable JsxAttribute
|
||||
newtype ImplementsClause a = ImplementsClause { _implementsClauseTypes :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImplementsClause
|
||||
|
||||
instance Eq1 ImplementsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -788,6 +927,8 @@ instance Evaluatable ImplementsClause
|
||||
data OptionalParameter a = OptionalParameter { _optionalParameterContext :: ![a], _optionalParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 OptionalParameter
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -796,6 +937,8 @@ instance Evaluatable OptionalParameter
|
||||
data RequiredParameter a = RequiredParameter { _requiredParameterContext :: ![a], _requiredParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 RequiredParameter
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -804,6 +947,8 @@ instance Evaluatable RequiredParameter
|
||||
data RestParameter a = RestParameter { _restParameterContext :: ![a], _restParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 RestParameter
|
||||
|
||||
instance Eq1 RestParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RestParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -812,6 +957,8 @@ instance Evaluatable RestParameter
|
||||
newtype JsxFragment a = JsxFragment [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxFragment
|
||||
|
||||
instance Eq1 JsxFragment where liftEq = genericLiftEq
|
||||
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
|
||||
@ -820,6 +967,8 @@ instance Evaluatable JsxFragment
|
||||
data JsxNamespaceName a = JsxNamespaceName a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxNamespaceName
|
||||
|
||||
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxNamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
Loading…
Reference in New Issue
Block a user