mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Merge branch 'derive-ToJSONFields1' into explicit-statements
This commit is contained in:
commit
2d626f9f90
@ -6,11 +6,10 @@ module Data.JSON.Fields
|
||||
, ToJSONFields (..)
|
||||
, ToJSONFields1 (..)
|
||||
, (.=)
|
||||
, noChildren
|
||||
, withChildren
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import qualified Data.Map as Map
|
||||
import Data.Sum (Apply (..), Sum)
|
||||
import qualified Data.Text as Text
|
||||
import qualified Data.Text.Encoding as Text
|
||||
@ -23,13 +22,11 @@ class ToJSONFields1 f where
|
||||
toJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv]
|
||||
default toJSONFields1 :: (KeyValue kv, ToJSON a, GToJSONFields1 (Rep1 f), GConstructorName1 (Rep1 f), Generic1 f) => f a -> [kv]
|
||||
toJSONFields1 s = let r = from1 s in
|
||||
"term" .= gconstructorName1 r : gtoJSONFields1 r
|
||||
|
||||
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
|
||||
"term" .= gconstructorName1 r : Map.foldrWithKey m [] (gtoJSONFields1 r)
|
||||
where
|
||||
m _ [] acc = acc
|
||||
m k [v] acc = (k .= v) : acc
|
||||
m k vs acc = (k .= vs) : acc
|
||||
|
||||
instance ToJSONFields a => ToJSONFields (Join (,) a) where
|
||||
toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ]
|
||||
@ -93,7 +90,7 @@ instance (GConstructorName1 f, GConstructorName1 g) => GConstructorName1 (f :+:
|
||||
|
||||
-- | A typeclass to calculate a list of 'KeyValue's describing the record selector names and associated values on a datatype.
|
||||
class GToJSONFields1 f where
|
||||
gtoJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv]
|
||||
gtoJSONFields1 :: (ToJSON a) => f a -> Map.Map Text [SomeJSON]
|
||||
|
||||
instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where
|
||||
gtoJSONFields1 = gtoJSONFields1 . unM1
|
||||
@ -102,33 +99,33 @@ instance GToJSONFields1 f => GToJSONFields1 (M1 C c f) where
|
||||
gtoJSONFields1 = gtoJSONFields1 . unM1
|
||||
|
||||
instance GToJSONFields1 U1 where
|
||||
gtoJSONFields1 _ = []
|
||||
gtoJSONFields1 _ = mempty
|
||||
|
||||
instance (Selector c, GSelectorJSONValue1 f) => GToJSONFields1 (M1 S c f) where
|
||||
gtoJSONFields1 m1 = case selName m1 of
|
||||
"" -> [ "children" .= json ]
|
||||
n -> [ Text.pack n .= json ]
|
||||
where json = gselectorJSONValue1 (unM1 m1)
|
||||
gtoJSONFields1 m1 = Map.fromList [gselectorJSONValue1 keyName (unM1 m1)]
|
||||
where keyName = case selName m1 of
|
||||
"" -> Nothing
|
||||
n -> Just (Text.pack n)
|
||||
|
||||
instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where
|
||||
gtoJSONFields1 (L1 l) = gtoJSONFields1 l
|
||||
gtoJSONFields1 (R1 r) = gtoJSONFields1 r
|
||||
|
||||
instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :*: g) where
|
||||
gtoJSONFields1 (x :*: y) = gtoJSONFields1 x <> gtoJSONFields1 y
|
||||
gtoJSONFields1 (x :*: y) = Map.unionWith (<>) (gtoJSONFields1 x) (gtoJSONFields1 y)
|
||||
|
||||
-- | A typeclass to retrieve the JSON 'Value' of a record selector.
|
||||
class GSelectorJSONValue1 f where
|
||||
gselectorJSONValue1 :: ToJSON a => f a -> SomeJSON
|
||||
gselectorJSONValue1 :: (ToJSON a) => Maybe Text -> f a -> (Text, [SomeJSON])
|
||||
|
||||
instance GSelectorJSONValue1 Par1 where
|
||||
gselectorJSONValue1 = SomeJSON . unPar1
|
||||
gselectorJSONValue1 k x = (fromMaybe "children" k, [SomeJSON (unPar1 x)])
|
||||
|
||||
instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where
|
||||
gselectorJSONValue1 = SomeJSON . SomeJSON1 . unRec1
|
||||
gselectorJSONValue1 k x = (fromMaybe "children" k, [SomeJSON (SomeJSON1 (unRec1 x))])
|
||||
|
||||
instance ToJSON k => GSelectorJSONValue1 (K1 r k) where
|
||||
gselectorJSONValue1 = SomeJSON . unK1
|
||||
gselectorJSONValue1 k x = (fromMaybe "value" k, [SomeJSON (unK1 x)])
|
||||
|
||||
|
||||
-- TODO: Fix this orphan instance.
|
||||
|
@ -150,7 +150,7 @@ instance Declarations1 Identifier where
|
||||
|
||||
-- | An accessibility modifier, e.g. private, public, protected, etc.
|
||||
newtype AccessibilityModifier a = AccessibilityModifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
|
||||
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
|
||||
@ -163,7 +163,7 @@ instance Evaluatable AccessibilityModifier
|
||||
--
|
||||
-- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'.
|
||||
data Empty a = Empty
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
instance Eq1 Empty where liftEq _ _ _ = True
|
||||
instance Ord1 Empty where liftCompare _ _ _ = EQ
|
||||
@ -174,7 +174,7 @@ instance Evaluatable Empty where
|
||||
|
||||
-- | Syntax representing a parsing or assignment error.
|
||||
data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Error where liftEq = genericLiftEq
|
||||
instance Ord1 Error where liftCompare = genericLiftCompare
|
||||
@ -182,12 +182,6 @@ 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
|
||||
@ -227,7 +221,7 @@ instance Ord ErrorStack where
|
||||
|
||||
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Diffable Context where
|
||||
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s
|
||||
|
@ -3,21 +3,17 @@ 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).
|
||||
newtype Comment a = Comment { commentContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 _ = pure (Rval unit)
|
||||
|
||||
|
@ -9,7 +9,7 @@ import Diffing.Algorithm
|
||||
import Prologue
|
||||
|
||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Diffable Function where
|
||||
equivalentBySubterm = Just . functionName
|
||||
@ -18,8 +18,6 @@ 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,7 +33,7 @@ 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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Ord1 Method where liftCompare = genericLiftCompare
|
||||
@ -44,8 +42,6 @@ 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
|
||||
@ -58,40 +54,34 @@ instance Evaluatable Method where
|
||||
|
||||
-- | A method signature in TypeScript or a method spec in Go.
|
||||
data MethodSignature a = MethodSignature { _methodSignatureContext :: ![a], _methodSignatureName :: !a, _methodSignatureParameters :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -101,14 +91,12 @@ instance Evaluatable OptionalParameter
|
||||
-- TODO: It would be really nice to have a more meaningful type contained in here than [a]
|
||||
-- | A declaration of possibly many variables such as var foo = 5, bar = 6 in JavaScript.
|
||||
newtype VariableDeclaration a = VariableDeclaration { variableDeclarations :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 []) = pure (Rval unit)
|
||||
eval (VariableDeclaration decs) = Rval . multiple <$> traverse subtermValue decs
|
||||
@ -121,14 +109,12 @@ instance Declarations a => Declarations (VariableDeclaration a) where
|
||||
|
||||
-- | A TypeScript/Java style interface declaration to implement.
|
||||
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -138,38 +124,32 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where
|
||||
|
||||
-- | A public field definition such as a field definition in a JavaScript class.
|
||||
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Declarations a => Declarations (Class a) where
|
||||
declaredName (Class _ name _ _) = declaredName name
|
||||
|
||||
instance ToJSONFields1 Class
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
|
||||
@ -189,14 +169,12 @@ instance Evaluatable Class where
|
||||
|
||||
-- | A decorator in Python
|
||||
data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -205,70 +183,60 @@ instance Evaluatable Decorator
|
||||
|
||||
-- | An ADT, i.e. a disjoint sum of products, like 'data' in Haskell, or 'enum' in Rust or Swift.
|
||||
data Datatype a = Datatype { datatypeName :: !a, datatypeConstructors :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
|
||||
data Constructor a = Constructor { constructorName :: !a, constructorFields :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | Comprehension (e.g. ((a for b in c if a()) in Python)
|
||||
data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A declared type (e.g. `a []int` in Go).
|
||||
data Type a = Type { typeName :: !a, typeKind :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | Type alias declarations in Javascript/Haskell, etc.
|
||||
data TypeAlias a = TypeAlias { typeAliasContext :: ![a], typeAliasIdentifier :: !a, typeAliasKind :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -11,27 +11,23 @@ import Prologue
|
||||
|
||||
-- A file directive like the Ruby constant `__FILE__`.
|
||||
data File a = File
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 = Rval . string . BC.pack . modulePath <$> currentModule
|
||||
|
||||
|
||||
-- A line directive like the Ruby constant `__LINE__`.
|
||||
data Line a = Line
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 = Rval . integer . fromIntegral . posLine . spanStart <$> currentSpan
|
||||
|
@ -10,14 +10,12 @@ import Prologue hiding (index)
|
||||
|
||||
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
|
||||
data Call a = Call { callContext :: ![a], callFunction :: !a, callParams :: ![a], callBlock :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -31,14 +29,12 @@ data Comparison a
|
||||
| Equal !a !a
|
||||
| StrictEqual !a !a
|
||||
| Comparison !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 t = Rval <$> (traverse subtermValue t >>= go) where
|
||||
go x = case x of
|
||||
@ -62,14 +58,12 @@ data Arithmetic a
|
||||
| Modulo !a !a
|
||||
| Power !a !a
|
||||
| Negate !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 t = Rval <$> (traverse subtermValue t >>= go) where
|
||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||
@ -85,14 +79,12 @@ instance Evaluatable Arithmetic where
|
||||
data Match a
|
||||
= Matches !a !a
|
||||
| NotMatches !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -102,14 +94,12 @@ data Boolean a
|
||||
| And !a !a
|
||||
| Not !a
|
||||
| XOr !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 t = Rval <$> go (fmap subtermValue t) where
|
||||
@ -124,56 +114,48 @@ instance Evaluatable Boolean where
|
||||
|
||||
-- | Javascript delete operator
|
||||
newtype Delete a = Delete a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A sequence expression such as Javascript or C's comma operator.
|
||||
data SequenceExpression a = SequenceExpression { _firstExpression :: !a, _secondExpression :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | Javascript void operator
|
||||
newtype Void a = Void a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | Javascript typeof operator
|
||||
newtype Typeof a = Typeof a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -187,14 +169,12 @@ data Bitwise a
|
||||
| RShift !a !a
|
||||
| UnsignedRShift !a !a
|
||||
| Complement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 t = Rval <$> (traverse subtermValue t >>= go) where
|
||||
genLShift x y = shiftL x (fromIntegral y)
|
||||
@ -211,14 +191,12 @@ instance Evaluatable Bitwise where
|
||||
-- | Member Access (e.g. a.b)
|
||||
data MemberAccess a
|
||||
= MemberAccess !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 (MemberAccess obj prop) = do
|
||||
obj <- subtermValue obj
|
||||
@ -231,14 +209,12 @@ instance Evaluatable MemberAccess where
|
||||
data Subscript a
|
||||
= Subscript !a ![a]
|
||||
| Member !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Ord1 Subscript where liftCompare = genericLiftCompare
|
||||
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Subscript
|
||||
|
||||
-- TODO: Finish Eval instance for Subscript
|
||||
-- TODO return a special LvalSubscript instance here
|
||||
instance Evaluatable Subscript where
|
||||
@ -249,97 +225,83 @@ instance Evaluatable Subscript where
|
||||
|
||||
-- | Enumeration (e.g. a[1:10:1] in Python (start at index 1, stop at index 10, step 1 element from start to stop))
|
||||
data Enumeration a = Enumeration { enumerationStart :: !a, enumerationEnd :: !a, enumerationStep :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | InstanceOf (e.g. a instanceof b in JavaScript
|
||||
data InstanceOf a = InstanceOf { instanceOfSubject :: !a, instanceOfObject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
|
||||
newtype ScopeResolution a = ScopeResolution [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A non-null expression such as Typescript or Swift's ! expression.
|
||||
newtype NonNullExpression a = NonNullExpression { nonNullExpression :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | An await expression in Javascript or C#.
|
||||
newtype Await a = Await { awaitSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | An object constructor call in Javascript, Java, etc.
|
||||
newtype New a = New { newSubject :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A cast expression to a specified type.
|
||||
data Cast a = Cast { castSubject :: !a, castType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -15,7 +15,7 @@ import Text.Read (readMaybe)
|
||||
-- Boolean
|
||||
|
||||
newtype Boolean a = Boolean { booleanContent :: Bool }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
true :: Boolean a
|
||||
true = Boolean True
|
||||
@ -30,14 +30,11 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Boolean where
|
||||
eval (Boolean x) = pure (Rval (boolean x))
|
||||
|
||||
instance ToJSONFields1 Boolean where
|
||||
toJSONFields1 (Boolean b) = noChildren [ "value" .= b ]
|
||||
|
||||
-- Numeric
|
||||
|
||||
-- | A literal integer of unspecified width. No particular base is implied.
|
||||
newtype Integer a = Integer { integerContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
|
||||
@ -48,17 +45,13 @@ instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
eval (Data.Syntax.Literal.Integer x) =
|
||||
Rval . 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?
|
||||
-- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors.
|
||||
|
||||
-- | A literal float of unspecified width.
|
||||
newtype Float a = Float { floatContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
|
||||
@ -68,12 +61,9 @@ instance Evaluatable Data.Syntax.Literal.Float where
|
||||
eval (Float s) =
|
||||
Rval . 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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare
|
||||
@ -86,12 +76,9 @@ instance Evaluatable Data.Syntax.Literal.Rational where
|
||||
parsed = readMaybe @Prelude.Integer (unpack trimmed)
|
||||
in Rval . 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
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare
|
||||
@ -100,13 +87,10 @@ 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] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
|
||||
@ -117,10 +101,8 @@ 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
|
||||
|
||||
newtype Character a = Character { characterContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
|
||||
@ -128,11 +110,9 @@ instance Show1 Data.Syntax.Literal.Character where liftShowsPrec = genericLiftSh
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Character
|
||||
|
||||
instance ToJSONFields1 Data.Syntax.Literal.Character
|
||||
|
||||
-- | An interpolation element within a string literal.
|
||||
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 InterpolationElement where liftEq = genericLiftEq
|
||||
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
|
||||
@ -141,24 +121,19 @@ 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 }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
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) = pure (Rval (string x))
|
||||
|
||||
data Null a = Null
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
instance Eq1 Null where liftEq = genericLiftEq
|
||||
instance Ord1 Null where liftCompare = genericLiftCompare
|
||||
@ -166,22 +141,18 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Null where eval _ = pure (Rval null)
|
||||
|
||||
instance ToJSONFields1 Null
|
||||
|
||||
newtype Symbol a = Symbol { symbolContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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) = pure (Rval (symbol s))
|
||||
|
||||
newtype Regex a = Regex { regexContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Regex where liftEq = genericLiftEq
|
||||
instance Ord1 Regex where liftCompare = genericLiftCompare
|
||||
@ -189,10 +160,6 @@ instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Heredoc-style string literals?
|
||||
|
||||
instance ToJSONFields1 Regex where
|
||||
toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r]
|
||||
|
||||
|
||||
-- TODO: Implement Eval instance for Regex
|
||||
instance Evaluatable Regex
|
||||
|
||||
@ -200,46 +167,38 @@ instance Evaluatable Regex
|
||||
-- Collections
|
||||
|
||||
newtype Array a = Array { arrayElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
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) = Rval <$> (array =<< traverse subtermValue a)
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
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 t = Rval . hash <$> traverse (subtermValue >=> asPair) (hashElements t)
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
|
||||
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{..}) =
|
||||
Rval <$> (kvPair <$> key <*> value)
|
||||
|
||||
instance ToJSONFields1 Tuple
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
@ -249,14 +208,12 @@ instance Evaluatable Tuple where
|
||||
eval (Tuple cs) = Rval . multiple <$> traverse subtermValue cs
|
||||
|
||||
newtype Set a = Set { setElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -265,28 +222,24 @@ instance Evaluatable Set
|
||||
|
||||
-- | A declared pointer (e.g. var pointer *int in Go)
|
||||
newtype Pointer a = Pointer a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A reference to a pointer's address (e.g. &pointer in Go)
|
||||
newtype Reference a = Reference a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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,7 +3,6 @@ module Data.Syntax.Statement where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Aeson (ToJSON1 (..))
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
import Data.JSON.Fields
|
||||
import Data.Semigroup.App
|
||||
import Data.Semigroup.Foldable
|
||||
@ -29,14 +28,12 @@ instance Evaluatable Statements where
|
||||
|
||||
-- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted.
|
||||
data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -44,14 +41,12 @@ instance Evaluatable If where
|
||||
|
||||
-- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python.
|
||||
data Else a = Else { elseCondition :: !a, elseBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -59,56 +54,48 @@ instance Evaluatable Else
|
||||
|
||||
-- | Goto statement (e.g. `goto a` in Go).
|
||||
newtype Goto a = Goto { gotoLocation :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A pattern-matching or computed jump control-flow statement, like 'switch' in C or JavaScript, or 'case' in Ruby or Haskell.
|
||||
data Match a = Match { matchSubject :: !a, matchPatterns :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A pattern in a pattern-matching or computed jump control-flow statement, like 'case' in C or JavaScript, 'when' in Ruby, or the left-hand side of '->' in the body of Haskell 'case' expressions.
|
||||
data Pattern a = Pattern { _pattern :: !a, patternBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A let statement or local binding, like 'a as b' or 'let a = b'.
|
||||
data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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)
|
||||
@ -120,14 +107,12 @@ instance Evaluatable Let where
|
||||
|
||||
-- | Assignment to a variable or other lvalue.
|
||||
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
lhs <- subtermRef assignmentTarget
|
||||
@ -149,28 +134,24 @@ instance Evaluatable Assignment where
|
||||
|
||||
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
||||
newtype PostIncrement a = PostIncrement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
|
||||
newtype PostDecrement a = PostDecrement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -178,181 +159,153 @@ instance Evaluatable PostDecrement
|
||||
-- Returns
|
||||
|
||||
newtype Return a = Return a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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) = Rval <$> (subtermValue x >>= earlyReturn)
|
||||
|
||||
newtype Yield a = Yield a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Break a = Break a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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) = Rval <$> (subtermValue x >>= throwBreak)
|
||||
|
||||
newtype Continue a = Continue a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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) = Rval <$> (subtermValue a >>= throwContinue)
|
||||
|
||||
newtype Retry a = Retry a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype NoOp a = NoOp a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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 _ = pure (Rval unit)
|
||||
|
||||
-- Loops
|
||||
|
||||
data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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) = Rval <$> forLoop before cond step body
|
||||
|
||||
|
||||
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data While a = While { whileCondition :: !a, whileBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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{..} = Rval <$> while (subtermValue whileCondition) (subtermValue whileBody)
|
||||
|
||||
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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{..} = Rval <$> doWhile (subtermValue doWhileBody) (subtermValue doWhileCondition)
|
||||
|
||||
-- Exception handling
|
||||
|
||||
newtype Throw a = Throw a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Catch a = Catch { catchException :: !a, catchBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Finally a = Finally a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
@ -361,41 +314,34 @@ instance Evaluatable Finally
|
||||
|
||||
-- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl).
|
||||
newtype ScopeEntry a = ScopeEntry [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | ScopeExit (e.g. `END {}` block in Ruby or Perl).
|
||||
newtype ScopeExit a = ScopeExit [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | HashBang line (e.g. `#!/usr/bin/env node`)
|
||||
newtype HashBang a = HashBang ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -7,145 +7,123 @@ import Diffing.Algorithm
|
||||
import Prologue hiding (Map)
|
||||
|
||||
data Array a = Array { arraySize :: Maybe a, arrayElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- TODO: What about type variables? re: FreeVariables1
|
||||
data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Function a = Function { functionParameters :: [a], functionReturn :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Interface a = Interface [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Map a = Map { mapKeyType :: a, mapElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Parenthesized a = Parenthesized a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Pointer a = Pointer a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Product a = Product [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Readonly a = Readonly
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Slice a = Slice a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype TypeParameters a = TypeParameters [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -57,14 +57,12 @@ resolveGoImport (ImportPath path NonRelative) = do
|
||||
--
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -79,14 +77,12 @@ instance Evaluatable Import where
|
||||
--
|
||||
-- If the list of symbols is empty copy and qualify everything to the calling environment.
|
||||
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a}
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -101,14 +97,12 @@ instance Evaluatable QualifiedImport where
|
||||
|
||||
-- | Side effect only imports (no symbols made available to the calling environment).
|
||||
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -118,74 +112,62 @@ instance Evaluatable SideEffectImport where
|
||||
|
||||
-- A composite literal in Go
|
||||
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`).
|
||||
newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A defer statement in Go (e.g. `defer x()`).
|
||||
newtype Defer a = Defer { deferBody :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A go statement (i.e. go routine) in Go (e.g. `go x()`).
|
||||
newtype Go a = Go { goBody :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A label statement in Go (e.g. `label:continue`).
|
||||
data Label a = Label { _labelName :: !a, labelStatement :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A rune literal in Go (e.g. `'⌘'`).
|
||||
newtype Rune a = Rune { _runeLiteral :: ByteString }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Rune
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
-- TODO: Implement Eval instance for Rune
|
||||
instance Evaluatable Rune
|
||||
@ -196,9 +178,7 @@ instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels).
|
||||
newtype Select a = Select { selectCases :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Select
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
-- TODO: Implement Eval instance for Select
|
||||
instance Evaluatable Select
|
||||
@ -209,144 +189,122 @@ instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A send statement in Go (e.g. `channel <- value`).
|
||||
data Send a = Send { sendReceiver :: !a, sendValue :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity).
|
||||
data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`).
|
||||
data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`).
|
||||
newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A receive statement in a Go select statement (e.g. `case value := <-channel` )
|
||||
data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A receive operator unary expression in Go (e.g. `<-channel` )
|
||||
newtype ReceiveOperator a = ReceiveOperator a
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A field declaration in a Go struct type declaration.
|
||||
data Field a = Field { fieldContext :: ![a], fieldName :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Package a = Package { packageName :: !a, packageContents :: ![a] }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`).
|
||||
data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A type conversion expression in Go (e.g. `T(x)` where `T` is a type and `x` is an expression that can be converted to type `T`).
|
||||
data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`).
|
||||
data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -8,39 +8,33 @@ import Diffing.Algorithm
|
||||
|
||||
-- | A Bidirectional channel in Go (e.g. `chan`).
|
||||
newtype BidirectionalChannel a = BidirectionalChannel a
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A Receive channel in Go (e.g. `<-chan`).
|
||||
newtype ReceiveChannel a = ReceiveChannel a
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
-- | A Send channel in Go (e.g. `chan<-`).
|
||||
newtype SendChannel a = SendChannel a
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -11,74 +11,60 @@ data Module a = Module { moduleIdentifier :: !a
|
||||
, moduleExports :: ![a]
|
||||
, moduleStatements :: !a
|
||||
}
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Module
|
||||
|
||||
instance Evaluatable Module
|
||||
|
||||
data Type a = Type { typeIdentifier :: !a, typeParameters :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 Type
|
||||
|
||||
instance Evaluatable Type
|
||||
|
||||
data TypeSynonym a = TypeSynonym { typeSynonymLeft :: !a, typeSynonymRight :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeSynonym where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TypeSynonym
|
||||
|
||||
instance Evaluatable TypeSynonym
|
||||
|
||||
data UnitConstructor a = UnitConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
data UnitConstructor a = UnitConstructor deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 UnitConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 UnitConstructor
|
||||
|
||||
instance Evaluatable UnitConstructor
|
||||
|
||||
newtype TupleConstructor a = TupleConstructor { tupleConstructorArity :: Int } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
newtype TupleConstructor a = TupleConstructor { tupleConstructorArity :: Int } deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TupleConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 TupleConstructor
|
||||
|
||||
instance Evaluatable TupleConstructor
|
||||
|
||||
data ListConstructor a = ListConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
data ListConstructor a = ListConstructor deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ListConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 ListConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 ListConstructor
|
||||
|
||||
instance Evaluatable ListConstructor
|
||||
|
||||
data FunctionConstructor a = FunctionConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
data FunctionConstructor a = FunctionConstructor deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 FunctionConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSONFields1 FunctionConstructor
|
||||
|
||||
instance Evaluatable FunctionConstructor
|
||||
|
@ -2,14 +2,11 @@
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Document
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Ord1 Document where liftCompare = genericLiftCompare
|
||||
@ -19,91 +16,70 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
-- Block elements
|
||||
|
||||
newtype Paragraph a = Paragraph [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Paragraph
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Paragraph where liftEq = genericLiftEq
|
||||
instance Ord1 Paragraph where liftCompare = genericLiftCompare
|
||||
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Heading
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Ord1 Heading where liftCompare = genericLiftCompare
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype UnorderedList a = UnorderedList [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 UnorderedList
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 HTMLBlock where liftEq = genericLiftEq
|
||||
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Table a = Table [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Table
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Ord1 Table where liftCompare = genericLiftCompare
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableRow a = TableRow [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TableRow
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Ord1 TableRow where liftCompare = genericLiftCompare
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableCell a = TableCell [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TableCell
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Ord1 TableCell where liftCompare = genericLiftCompare
|
||||
@ -113,76 +89,56 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
-- Inline elements
|
||||
|
||||
newtype Strong a = Strong [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Strong
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Ord1 Strong where liftCompare = genericLiftCompare
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Emphasis a = Emphasis [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Emphasis
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Ord1 Emphasis where liftCompare = genericLiftCompare
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Text where
|
||||
toJSONFields1 (Text s) = noChildren ["asString" .= unpack s ]
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Link
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Link where liftEq = genericLiftEq
|
||||
instance Ord1 Link where liftCompare = genericLiftCompare
|
||||
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Image
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Image where liftEq = genericLiftEq
|
||||
instance Ord1 Image where liftCompare = genericLiftCompare
|
||||
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
-- TODO: Better ToJSONFields1 instance
|
||||
instance ToJSONFields1 Code
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Code where liftEq = genericLiftEq
|
||||
instance Ord1 Code where liftCompare = genericLiftCompare
|
||||
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data LineBreak a = LineBreak
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 LineBreak
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
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, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Strikethrough where liftEq = genericLiftEq
|
||||
instance Ord1 Strikethrough where liftCompare = genericLiftCompare
|
||||
|
@ -12,10 +12,7 @@ import Prelude hiding (fail)
|
||||
import Prologue hiding (Text)
|
||||
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Text where
|
||||
toJSONFields1 (Text t) = noChildren ["asString" .= BC.unpack t]
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
@ -24,9 +21,7 @@ instance Evaluatable Text
|
||||
|
||||
|
||||
newtype VariableName a = VariableName a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 VariableName
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 VariableName where liftEq = genericLiftEq
|
||||
instance Ord1 VariableName where liftCompare = genericLiftCompare
|
||||
@ -72,61 +67,51 @@ include pathTerm f = do
|
||||
pure (Rval v)
|
||||
|
||||
newtype Require a = Require a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype RequireOnce a = RequireOnce a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype Include a = Include a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype IncludeOnce a = IncludeOnce a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
newtype ArrayElement a = ArrayElement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ArrayElement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ArrayElement where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayElement where liftCompare = genericLiftCompare
|
||||
@ -134,9 +119,7 @@ instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ArrayElement
|
||||
|
||||
newtype GlobalDeclaration a = GlobalDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 GlobalDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
|
||||
@ -144,9 +127,7 @@ instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable GlobalDeclaration
|
||||
|
||||
newtype SimpleVariable a = SimpleVariable a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 SimpleVariable
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 SimpleVariable where liftEq = genericLiftEq
|
||||
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
|
||||
@ -156,9 +137,7 @@ instance Evaluatable SimpleVariable
|
||||
|
||||
-- | TODO: Unify with TypeScript's PredefinedType
|
||||
newtype CastType a = CastType { _castType :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 CastType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 CastType where liftEq = genericLiftEq
|
||||
instance Ord1 CastType where liftCompare = genericLiftCompare
|
||||
@ -166,9 +145,7 @@ instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable CastType
|
||||
|
||||
newtype ErrorControl a = ErrorControl a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ErrorControl
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ErrorControl where liftEq = genericLiftEq
|
||||
instance Ord1 ErrorControl where liftCompare = genericLiftCompare
|
||||
@ -176,9 +153,7 @@ instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ErrorControl
|
||||
|
||||
newtype Clone a = Clone a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Clone
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Clone where liftEq = genericLiftEq
|
||||
instance Ord1 Clone where liftCompare = genericLiftCompare
|
||||
@ -186,9 +161,7 @@ instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Clone
|
||||
|
||||
newtype ShellCommand a = ShellCommand ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ShellCommand
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ShellCommand where liftEq = genericLiftEq
|
||||
instance Ord1 ShellCommand where liftCompare = genericLiftCompare
|
||||
@ -197,9 +170,7 @@ instance Evaluatable ShellCommand
|
||||
|
||||
-- | TODO: Combine with TypeScript update expression.
|
||||
newtype Update a = Update { _updateSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Update
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
@ -207,9 +178,7 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Update
|
||||
|
||||
newtype NewVariable a = NewVariable [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NewVariable
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NewVariable where liftEq = genericLiftEq
|
||||
instance Ord1 NewVariable where liftCompare = genericLiftCompare
|
||||
@ -217,9 +186,7 @@ instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NewVariable
|
||||
|
||||
newtype RelativeScope a = RelativeScope ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 RelativeScope
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 RelativeScope where liftEq = genericLiftEq
|
||||
instance Ord1 RelativeScope where liftCompare = genericLiftCompare
|
||||
@ -227,9 +194,7 @@ instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RelativeScope
|
||||
|
||||
data QualifiedName a = QualifiedName !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 QualifiedName
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 QualifiedName where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
|
||||
@ -239,9 +204,7 @@ instance Evaluatable QualifiedName where
|
||||
eval (fmap subtermValue -> QualifiedName name iden) = Rval <$> evaluateInScopedEnv name iden
|
||||
|
||||
newtype NamespaceName a = NamespaceName (NonEmpty a)
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceName
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Hashable1 NamespaceName where liftHashWithSalt = foldl
|
||||
instance Eq1 NamespaceName where liftEq = genericLiftEq
|
||||
@ -252,9 +215,7 @@ instance Evaluatable NamespaceName where
|
||||
eval (NamespaceName xs) = Rval <$> foldl1 evaluateInScopedEnv (fmap subtermValue xs)
|
||||
|
||||
newtype ConstDeclaration a = ConstDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ConstDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
|
||||
@ -262,9 +223,7 @@ instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstDeclaration
|
||||
|
||||
data ClassConstDeclaration a = ClassConstDeclaration a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassConstDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
|
||||
@ -272,9 +231,7 @@ instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassConstDeclaration
|
||||
|
||||
newtype ClassInterfaceClause a = ClassInterfaceClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassInterfaceClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
|
||||
@ -282,9 +239,7 @@ instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassInterfaceClause
|
||||
|
||||
newtype ClassBaseClause a = ClassBaseClause a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassBaseClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ClassBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
|
||||
@ -293,9 +248,7 @@ instance Evaluatable ClassBaseClause
|
||||
|
||||
|
||||
newtype UseClause a = UseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 UseClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 UseClause where liftEq = genericLiftEq
|
||||
instance Ord1 UseClause where liftCompare = genericLiftCompare
|
||||
@ -303,9 +256,7 @@ instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable UseClause
|
||||
|
||||
newtype ReturnType a = ReturnType a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ReturnType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ReturnType where liftEq = genericLiftEq
|
||||
instance Ord1 ReturnType where liftCompare = genericLiftCompare
|
||||
@ -313,9 +264,7 @@ instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ReturnType
|
||||
|
||||
newtype TypeDeclaration a = TypeDeclaration a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TypeDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
|
||||
@ -323,9 +272,7 @@ instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeDeclaration
|
||||
|
||||
newtype BaseTypeDeclaration a = BaseTypeDeclaration a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 BaseTypeDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
|
||||
@ -333,9 +280,7 @@ instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable BaseTypeDeclaration
|
||||
|
||||
newtype ScalarType a = ScalarType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ScalarType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ScalarType where liftEq = genericLiftEq
|
||||
instance Ord1 ScalarType where liftCompare = genericLiftCompare
|
||||
@ -343,9 +288,7 @@ instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ScalarType
|
||||
|
||||
newtype EmptyIntrinsic a = EmptyIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 EmptyIntrinsic
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -353,9 +296,7 @@ instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EmptyIntrinsic
|
||||
|
||||
newtype ExitIntrinsic a = ExitIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ExitIntrinsic
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -363,9 +304,7 @@ instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ExitIntrinsic
|
||||
|
||||
newtype IssetIntrinsic a = IssetIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 IssetIntrinsic
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -373,9 +312,7 @@ instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IssetIntrinsic
|
||||
|
||||
newtype EvalIntrinsic a = EvalIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 EvalIntrinsic
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -383,9 +320,7 @@ instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EvalIntrinsic
|
||||
|
||||
newtype PrintIntrinsic a = PrintIntrinsic a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PrintIntrinsic
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -393,9 +328,7 @@ instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PrintIntrinsic
|
||||
|
||||
newtype NamespaceAliasingClause a = NamespaceAliasingClause a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceAliasingClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
|
||||
@ -403,9 +336,7 @@ instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable NamespaceAliasingClause
|
||||
|
||||
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
|
||||
@ -413,9 +344,7 @@ instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable NamespaceUseDeclaration
|
||||
|
||||
newtype NamespaceUseClause a = NamespaceUseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
|
||||
@ -423,9 +352,7 @@ instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NamespaceUseClause
|
||||
|
||||
newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 NamespaceUseGroupClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
|
||||
@ -433,14 +360,12 @@ instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable NamespaceUseGroupClause
|
||||
|
||||
data Namespace a = Namespace { namespaceName :: a, namespaceBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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{..} = Rval <$> go names
|
||||
where
|
||||
@ -454,9 +379,7 @@ instance Evaluatable Namespace where
|
||||
go xs <* makeNamespace name addr Nothing
|
||||
|
||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TraitDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
|
||||
@ -464,9 +387,7 @@ instance Show1 TraitDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TraitDeclaration
|
||||
|
||||
data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 AliasAs
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AliasAs where liftEq = genericLiftEq
|
||||
instance Ord1 AliasAs where liftCompare = genericLiftCompare
|
||||
@ -474,9 +395,7 @@ instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AliasAs
|
||||
|
||||
data InsteadOf a = InsteadOf a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InsteadOf
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 InsteadOf where liftEq = genericLiftEq
|
||||
instance Ord1 InsteadOf where liftCompare = genericLiftCompare
|
||||
@ -484,9 +403,7 @@ instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InsteadOf
|
||||
|
||||
newtype TraitUseSpecification a = TraitUseSpecification [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitUseSpecification
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
|
||||
@ -494,9 +411,7 @@ instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TraitUseSpecification
|
||||
|
||||
data TraitUseClause a = TraitUseClause [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 TraitUseClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TraitUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
|
||||
@ -504,9 +419,7 @@ instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TraitUseClause
|
||||
|
||||
data DestructorDeclaration a = DestructorDeclaration [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 DestructorDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
|
||||
@ -514,9 +427,7 @@ instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable DestructorDeclaration
|
||||
|
||||
newtype Static a = Static ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Static
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Static where liftEq = genericLiftEq
|
||||
instance Ord1 Static where liftCompare = genericLiftCompare
|
||||
@ -524,9 +435,7 @@ instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Static
|
||||
|
||||
newtype ClassModifier a = ClassModifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ClassModifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ClassModifier where liftEq = genericLiftEq
|
||||
instance Ord1 ClassModifier where liftCompare = genericLiftCompare
|
||||
@ -534,9 +443,7 @@ instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassModifier
|
||||
|
||||
data ConstructorDeclaration a = ConstructorDeclaration [a] [a] a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 ConstructorDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
|
||||
@ -544,9 +451,7 @@ instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructorDeclaration
|
||||
|
||||
data PropertyDeclaration a = PropertyDeclaration a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PropertyDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
|
||||
@ -554,9 +459,7 @@ instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertyDeclaration
|
||||
|
||||
data PropertyModifier a = PropertyModifier a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 PropertyModifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 PropertyModifier where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
|
||||
@ -564,9 +467,7 @@ instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertyModifier
|
||||
|
||||
data InterfaceDeclaration a = InterfaceDeclaration a a [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InterfaceDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
@ -574,9 +475,7 @@ instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InterfaceDeclaration
|
||||
|
||||
newtype InterfaceBaseClause a = InterfaceBaseClause [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 InterfaceBaseClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
|
||||
@ -584,9 +483,7 @@ instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InterfaceBaseClause
|
||||
|
||||
newtype Echo a = Echo a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Echo
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Echo where liftEq = genericLiftEq
|
||||
instance Ord1 Echo where liftCompare = genericLiftCompare
|
||||
@ -594,9 +491,7 @@ instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Echo
|
||||
|
||||
newtype Unset a = Unset a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Unset
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Unset where liftEq = genericLiftEq
|
||||
instance Ord1 Unset where liftCompare = genericLiftCompare
|
||||
@ -604,9 +499,7 @@ instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Unset
|
||||
|
||||
data Declare a = Declare a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 Declare
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Declare where liftEq = genericLiftEq
|
||||
instance Ord1 Declare where liftCompare = genericLiftCompare
|
||||
@ -614,9 +507,7 @@ instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Declare
|
||||
|
||||
newtype DeclareDirective a = DeclareDirective a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 DeclareDirective
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 DeclareDirective where liftEq = genericLiftEq
|
||||
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
|
||||
@ -624,9 +515,7 @@ instance Show1 DeclareDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable DeclareDirective
|
||||
|
||||
newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance ToJSONFields1 LabeledStatement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
|
@ -88,9 +88,7 @@ resolvePythonModules q = do
|
||||
--
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![(Name, Name)] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Import
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
@ -138,9 +136,7 @@ evalQualifiedImport name path = letrec' name $ \addr -> do
|
||||
unit <$ makeNamespace name addr Nothing
|
||||
|
||||
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedName }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 QualifiedImport
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
@ -162,9 +158,7 @@ instance Evaluatable QualifiedImport where
|
||||
makeNamespace name addr Nothing
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 QualifiedAliasedImport
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
@ -188,26 +182,22 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
|
||||
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||
data Ellipsis a = Ellipsis
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
||||
|
||||
data Redirect a = Redirect !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -43,14 +43,12 @@ cleanNameOrPath :: ByteString -> String
|
||||
cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes
|
||||
|
||||
data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -60,14 +58,12 @@ instance Evaluatable Send where
|
||||
Rval <$> call func (map subtermValue sendArgs) -- TODO pass through sendBlock
|
||||
|
||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -90,14 +86,12 @@ doRequire path = do
|
||||
|
||||
|
||||
newtype Load a = Load { loadArgs :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -127,9 +121,7 @@ doLoad path shouldWrap = do
|
||||
-- TODO: autoload
|
||||
|
||||
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Class
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
@ -146,14 +138,12 @@ instance Evaluatable Class where
|
||||
subtermValue classBody <* makeNamespace name addr super)
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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)
|
||||
@ -163,9 +153,7 @@ instance Evaluatable Module where
|
||||
data LowPrecedenceBoolean a
|
||||
= LowAnd !a !a
|
||||
| LowOr !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LowPrecedenceBoolean
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
|
@ -146,9 +146,7 @@ evalRequire modulePath alias = letrec' alias $ \addr -> do
|
||||
unit <$ makeNamespace alias addr Nothing
|
||||
|
||||
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Import
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
@ -166,14 +164,12 @@ instance Evaluatable Import where
|
||||
| otherwise = Env.overwrite symbols importedEnv
|
||||
|
||||
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -182,14 +178,12 @@ instance Evaluatable JavaScriptRequire where
|
||||
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -197,14 +191,12 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
Rval <$> evalRequire modulePath alias
|
||||
|
||||
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -214,14 +206,12 @@ instance Evaluatable SideEffectImport where
|
||||
|
||||
-- | Qualified Export declarations
|
||||
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [(Name, Name)] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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.
|
||||
@ -232,14 +222,12 @@ instance Evaluatable QualifiedExport where
|
||||
|
||||
-- | Qualified Export declarations that export from another module.
|
||||
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![(Name, Name)]}
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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
|
||||
@ -251,9 +239,7 @@ instance Evaluatable QualifiedExportFrom where
|
||||
pure (Rval unit)
|
||||
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 DefaultExport
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||
@ -274,9 +260,7 @@ instance Evaluatable DefaultExport where
|
||||
|
||||
-- | Lookup type for a type-level key in a typescript map.
|
||||
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LookupType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 LookupType where liftEq = genericLiftEq
|
||||
instance Ord1 LookupType where liftCompare = genericLiftCompare
|
||||
@ -285,9 +269,7 @@ instance Evaluatable LookupType
|
||||
|
||||
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
|
||||
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ShorthandPropertyIdentifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
|
||||
@ -295,9 +277,7 @@ instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShow
|
||||
instance Evaluatable ShorthandPropertyIdentifier
|
||||
|
||||
data Union a = Union { _unionLeft :: !a, _unionRight :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Language.TypeScript.Syntax.Union
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.Union where liftCompare = genericLiftCompare
|
||||
@ -305,9 +285,7 @@ instance Show1 Language.TypeScript.Syntax.Union where liftShowsPrec = genericLif
|
||||
instance Evaluatable Language.TypeScript.Syntax.Union
|
||||
|
||||
data Intersection a = Intersection { _intersectionLeft :: !a, _intersectionRight :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Intersection
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Intersection where liftEq = genericLiftEq
|
||||
instance Ord1 Intersection where liftCompare = genericLiftCompare
|
||||
@ -315,9 +293,7 @@ instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Intersection
|
||||
|
||||
data FunctionType a = FunctionType { _functionTypeParameters :: !a, _functionFormalParameters :: ![a], _functionType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 FunctionType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
@ -325,9 +301,7 @@ instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable FunctionType
|
||||
|
||||
data AmbientFunction a = AmbientFunction { _ambientFunctionContext :: ![a], _ambientFunctionIdentifier :: !a, _ambientFunctionParameters :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AmbientFunction
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AmbientFunction where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
|
||||
@ -335,9 +309,7 @@ instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AmbientFunction
|
||||
|
||||
data ImportRequireClause a = ImportRequireClause { _importRequireIdentifier :: !a, _importRequireSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportRequireClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
|
||||
@ -345,9 +317,7 @@ instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImportRequireClause
|
||||
|
||||
newtype ImportClause a = ImportClause { _importClauseElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ImportClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportClause where liftCompare = genericLiftCompare
|
||||
@ -355,9 +325,7 @@ instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImportClause
|
||||
|
||||
newtype Tuple a = Tuple { _tupleElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Tuple
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
@ -367,9 +335,7 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Tuple
|
||||
|
||||
data Constructor a = Constructor { _constructorTypeParameters :: !a, _constructorFormalParameters :: ![a], _constructorType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Language.TypeScript.Syntax.Constructor
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.Constructor where liftCompare = genericLiftCompare
|
||||
@ -377,9 +343,7 @@ instance Show1 Language.TypeScript.Syntax.Constructor where liftShowsPrec = gene
|
||||
instance Evaluatable Language.TypeScript.Syntax.Constructor
|
||||
|
||||
data TypeParameter a = TypeParameter { _typeParameter :: !a, _typeParameterConstraint :: !a, _typeParameterDefaultType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeParameter
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
@ -387,9 +351,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeParameter
|
||||
|
||||
data TypeAssertion a = TypeAssertion { _typeAssertionParameters :: !a, _typeAssertionExpression :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeAssertion
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
@ -397,9 +359,7 @@ instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeAssertion
|
||||
|
||||
newtype Annotation a = Annotation { _annotationType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Annotation
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
@ -407,9 +367,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Annotation
|
||||
|
||||
newtype Decorator a = Decorator { _decoratorTerm :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Decorator
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
@ -417,9 +375,7 @@ instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Decorator
|
||||
|
||||
newtype ComputedPropertyName a = ComputedPropertyName a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ComputedPropertyName
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
|
||||
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
|
||||
@ -427,9 +383,7 @@ instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ComputedPropertyName
|
||||
|
||||
newtype Constraint a = Constraint { _constraintType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Constraint
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Constraint where liftEq = genericLiftEq
|
||||
instance Ord1 Constraint where liftCompare = genericLiftCompare
|
||||
@ -437,9 +391,7 @@ instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Constraint
|
||||
|
||||
newtype DefaultType a = DefaultType { _defaultType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 DefaultType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 DefaultType where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultType where liftCompare = genericLiftCompare
|
||||
@ -447,9 +399,7 @@ instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable DefaultType
|
||||
|
||||
newtype ParenthesizedType a = ParenthesizedType { _parenthesizedType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ParenthesizedType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
@ -457,9 +407,7 @@ instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ParenthesizedType
|
||||
|
||||
newtype PredefinedType a = PredefinedType { _predefinedType :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 PredefinedType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 PredefinedType where liftEq = genericLiftEq
|
||||
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
|
||||
@ -467,9 +415,7 @@ instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PredefinedType
|
||||
|
||||
newtype TypeIdentifier a = TypeIdentifier ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeIdentifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
|
||||
@ -477,9 +423,7 @@ instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeIdentifier
|
||||
|
||||
data NestedIdentifier a = NestedIdentifier !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 NestedIdentifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
|
||||
@ -487,9 +431,7 @@ instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NestedIdentifier
|
||||
|
||||
data NestedTypeIdentifier a = NestedTypeIdentifier !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 NestedTypeIdentifier
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
|
||||
@ -497,9 +439,7 @@ instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NestedTypeIdentifier
|
||||
|
||||
data GenericType a = GenericType { _genericTypeIdentifier :: !a, _genericTypeArguments :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 GenericType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
@ -507,9 +447,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data TypePredicate a = TypePredicate { _typePredicateIdentifier :: !a, _typePredicateType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypePredicate
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypePredicate where liftEq = genericLiftEq
|
||||
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
|
||||
@ -517,9 +455,7 @@ instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypePredicate
|
||||
|
||||
newtype ObjectType a = ObjectType { _objectTypeElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ObjectType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ObjectType where liftEq = genericLiftEq
|
||||
instance Ord1 ObjectType where liftCompare = genericLiftCompare
|
||||
@ -527,9 +463,7 @@ instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ObjectType
|
||||
|
||||
data With a = With { _withExpression :: !a, _withBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 With
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 With where liftEq = genericLiftEq
|
||||
instance Ord1 With where liftCompare = genericLiftCompare
|
||||
@ -537,9 +471,7 @@ instance Show1 With where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable With
|
||||
|
||||
newtype AmbientDeclaration a = AmbientDeclaration { _ambientDeclarationBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AmbientDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
|
||||
@ -549,9 +481,7 @@ instance Evaluatable AmbientDeclaration where
|
||||
eval (AmbientDeclaration body) = subtermRef body
|
||||
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 EnumDeclaration
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
@ -562,9 +492,7 @@ instance Declarations a => Declarations (EnumDeclaration a) where
|
||||
declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier
|
||||
|
||||
newtype ExtendsClause a = ExtendsClause { _extendsClauses :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ExtendsClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ExtendsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
|
||||
@ -572,9 +500,7 @@ instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ExtendsClause
|
||||
|
||||
newtype ArrayType a = ArrayType { _arrayType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ArrayType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ArrayType where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayType where liftCompare = genericLiftCompare
|
||||
@ -582,9 +508,7 @@ instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ArrayType
|
||||
|
||||
newtype FlowMaybeType a = FlowMaybeType { _flowMaybeType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 FlowMaybeType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
|
||||
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
|
||||
@ -592,9 +516,7 @@ instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable FlowMaybeType
|
||||
|
||||
newtype TypeQuery a = TypeQuery { _typeQuerySubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeQuery
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
|
||||
@ -602,9 +524,7 @@ instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeQuery
|
||||
|
||||
newtype IndexTypeQuery a = IndexTypeQuery { _indexTypeQuerySubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 IndexTypeQuery
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
|
||||
@ -612,9 +532,7 @@ instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IndexTypeQuery
|
||||
|
||||
newtype TypeArguments a = TypeArguments { _typeArguments :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 TypeArguments
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TypeArguments where liftEq = genericLiftEq
|
||||
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
|
||||
@ -622,9 +540,7 @@ instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeArguments
|
||||
|
||||
newtype ThisType a = ThisType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ThisType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ThisType where liftEq = genericLiftEq
|
||||
instance Ord1 ThisType where liftCompare = genericLiftCompare
|
||||
@ -632,9 +548,7 @@ instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ThisType
|
||||
|
||||
newtype ExistentialType a = ExistentialType ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ExistentialType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ExistentialType where liftEq = genericLiftEq
|
||||
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
|
||||
@ -642,9 +556,7 @@ instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ExistentialType
|
||||
|
||||
newtype LiteralType a = LiteralType { _literalTypeSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LiteralType
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 LiteralType where liftEq = genericLiftEq
|
||||
instance Ord1 LiteralType where liftCompare = genericLiftCompare
|
||||
@ -652,9 +564,7 @@ instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LiteralType
|
||||
|
||||
data PropertySignature a = PropertySignature { _modifiers :: ![a], _propertySignaturePropertyName :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 PropertySignature
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 PropertySignature where liftEq = genericLiftEq
|
||||
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
|
||||
@ -662,9 +572,7 @@ instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertySignature
|
||||
|
||||
data CallSignature a = CallSignature { _callSignatureTypeParameters :: !a, _callSignatureParameters :: ![a], _callSignatureType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 CallSignature
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 CallSignature where liftEq = genericLiftEq
|
||||
instance Ord1 CallSignature where liftCompare = genericLiftCompare
|
||||
@ -673,9 +581,7 @@ instance Evaluatable CallSignature
|
||||
|
||||
-- | Todo: Move type params and type to context
|
||||
data ConstructSignature a = ConstructSignature { _constructSignatureTypeParameters :: !a, _constructSignatureParameters :: ![a], _constructSignatureType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ConstructSignature
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ConstructSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
|
||||
@ -683,9 +589,7 @@ instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructSignature
|
||||
|
||||
data IndexSignature a = IndexSignature { _indexSignatureSubject :: a, _indexSignatureType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 IndexSignature
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 IndexSignature where liftEq = genericLiftEq
|
||||
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
|
||||
@ -693,9 +597,7 @@ instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IndexSignature
|
||||
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { _abstractMethodSignatureContext :: ![a], _abstractMethodSignatureName :: !a, _abstractMethodSignatureParameters :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 AbstractMethodSignature
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
|
||||
@ -703,9 +605,7 @@ instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable AbstractMethodSignature
|
||||
|
||||
data Debugger a = Debugger
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Debugger
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Debugger where liftEq = genericLiftEq
|
||||
instance Ord1 Debugger where liftCompare = genericLiftCompare
|
||||
@ -713,9 +613,7 @@ instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Debugger
|
||||
|
||||
data ForOf a = ForOf { _forOfBinding :: !a, _forOfSubject :: !a, _forOfBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ForOf
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ForOf where liftEq = genericLiftEq
|
||||
instance Ord1 ForOf where liftCompare = genericLiftCompare
|
||||
@ -723,9 +621,7 @@ instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ForOf
|
||||
|
||||
data This a = This
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 This
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 This where liftEq = genericLiftEq
|
||||
instance Ord1 This where liftCompare = genericLiftCompare
|
||||
@ -733,9 +629,7 @@ instance Show1 This where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable This
|
||||
|
||||
data LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: !a, _labeledStatementSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 LabeledStatement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
@ -743,9 +637,7 @@ instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LabeledStatement
|
||||
|
||||
newtype Update a = Update { _updateSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Update
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
@ -753,14 +645,12 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Update
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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)
|
||||
@ -770,14 +660,12 @@ instance Evaluatable Module where
|
||||
|
||||
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
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)
|
||||
@ -789,9 +677,7 @@ instance Declarations a => Declarations (InternalModule a) where
|
||||
|
||||
|
||||
data ImportAlias a = ImportAlias { _importAliasSubject :: !a, _importAlias :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImportAlias
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
@ -799,9 +685,7 @@ instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImportAlias
|
||||
|
||||
data Super a = Super
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Super
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
@ -809,9 +693,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Super
|
||||
|
||||
data Undefined a = Undefined
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 Undefined
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Undefined where liftEq = genericLiftEq
|
||||
instance Ord1 Undefined where liftCompare = genericLiftCompare
|
||||
@ -819,9 +701,7 @@ instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Undefined
|
||||
|
||||
data ClassHeritage a = ClassHeritage { _classHeritageExtendsClause :: !a, _implementsClause :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ClassHeritage
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
@ -829,7 +709,7 @@ instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassHeritage
|
||||
|
||||
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, _abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 AbstractClass where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractClass where liftCompare = genericLiftCompare
|
||||
@ -837,8 +717,6 @@ 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)
|
||||
@ -851,9 +729,7 @@ instance Evaluatable AbstractClass where
|
||||
|
||||
|
||||
data JsxElement a = JsxElement { _jsxOpeningElement :: !a, _jsxElements :: ![a], _jsxClosingElement :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxElement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxElement where liftCompare = genericLiftCompare
|
||||
@ -861,9 +737,7 @@ instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxElement
|
||||
|
||||
newtype JsxText a = JsxText ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxText
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxText where liftEq = genericLiftEq
|
||||
instance Ord1 JsxText where liftCompare = genericLiftCompare
|
||||
@ -871,9 +745,7 @@ instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxText
|
||||
|
||||
newtype JsxExpression a = JsxExpression { _jsxExpression :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxExpression
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxExpression where liftEq = genericLiftEq
|
||||
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
|
||||
@ -881,9 +753,7 @@ instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxExpression
|
||||
|
||||
data JsxOpeningElement a = JsxOpeningElement { _jsxOpeningElementIdentifier :: !a, _jsxAttributes :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxOpeningElement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
|
||||
@ -891,9 +761,7 @@ instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxOpeningElement
|
||||
|
||||
newtype JsxClosingElement a = JsxClosingElement { _jsxClosingElementIdentifier :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxClosingElement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
|
||||
@ -901,9 +769,7 @@ instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxClosingElement
|
||||
|
||||
data JsxSelfClosingElement a = JsxSelfClosingElement { _jsxSelfClosingElementIdentifier :: !a, _jsxSelfClosingElementAttributes :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxSelfClosingElement
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
|
||||
@ -911,9 +777,7 @@ instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxSelfClosingElement
|
||||
|
||||
data JsxAttribute a = JsxAttribute { _jsxAttributeTarget :: !a, _jsxAttributeValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxAttribute
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxAttribute where liftEq = genericLiftEq
|
||||
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
|
||||
@ -921,9 +785,7 @@ instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxAttribute
|
||||
|
||||
newtype ImplementsClause a = ImplementsClause { _implementsClauseTypes :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 ImplementsClause
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 ImplementsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
|
||||
@ -931,9 +793,7 @@ instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImplementsClause
|
||||
|
||||
data OptionalParameter a = OptionalParameter { _optionalParameterContext :: ![a], _optionalParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 OptionalParameter
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
@ -941,9 +801,7 @@ instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable OptionalParameter
|
||||
|
||||
data RequiredParameter a = RequiredParameter { _requiredParameterContext :: ![a], _requiredParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 RequiredParameter
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
@ -951,9 +809,7 @@ instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RequiredParameter
|
||||
|
||||
data RestParameter a = RestParameter { _restParameterContext :: ![a], _restParameterSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 RestParameter
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 RestParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RestParameter where liftCompare = genericLiftCompare
|
||||
@ -961,9 +817,7 @@ instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RestParameter
|
||||
|
||||
newtype JsxFragment a = JsxFragment [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxFragment
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxFragment where liftEq = genericLiftEq
|
||||
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
|
||||
@ -971,9 +825,7 @@ instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxFragment
|
||||
|
||||
data JsxNamespaceName a = JsxNamespaceName a a
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance ToJSONFields1 JsxNamespaceName
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
|
||||
|
@ -1,11 +1,12 @@
|
||||
module Semantic.CLI.Spec (spec) where
|
||||
|
||||
import Control.Monad (when)
|
||||
import Data.ByteString.Builder
|
||||
import Data.Foldable (for_)
|
||||
import Semantic.CLI
|
||||
import Semantic.IO
|
||||
import Semantic.Task
|
||||
import Control.Monad (when)
|
||||
import qualified Data.ByteString as B
|
||||
import Data.ByteString.Builder
|
||||
import Data.Foldable (for_)
|
||||
import Semantic.CLI
|
||||
import Semantic.IO
|
||||
import Semantic.Task
|
||||
|
||||
import SpecHelpers
|
||||
|
||||
@ -24,38 +25,30 @@ spec = parallel $ do
|
||||
output <- runTask $ readBlobs (Right files) >>= runParse
|
||||
runBuilder output `shouldBe'` expected
|
||||
where
|
||||
shouldBe' actual expected = do
|
||||
when (actual /= expected) $ print actual
|
||||
shouldBe' actual' expectedFile = do
|
||||
let actual = verbatim actual'
|
||||
expected <- verbatim <$> B.readFile expectedFile
|
||||
actual `shouldBe` expected
|
||||
|
||||
parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], ByteString)]
|
||||
parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], FilePath)]
|
||||
parseFixtures =
|
||||
[ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, pathMode, sExpressionParseTreeOutput)
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, pathMode, jsonParseTreeOutput)
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, pathMode', jsonParseTreeOutput')
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, [], emptyJsonParseTreeOutput)
|
||||
, (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], symbolsOutput)
|
||||
, (show TagsTermRenderer, runParse TagsTermRenderer, [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], tagsOutput)
|
||||
[ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, path, "test/fixtures/ruby/corpus/and-or.parseA.txt")
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, path, prefix </> "parse-tree.json")
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, path', prefix </> "parse-trees.json")
|
||||
, (show JSONTermRenderer, runParse JSONTermRenderer, [], prefix </> "parse-tree-empty.json")
|
||||
, (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), path'', prefix </> "parse-tree.symbols.json")
|
||||
, (show TagsTermRenderer, runParse TagsTermRenderer, path'', prefix </> "parse-tree.tags.json")
|
||||
]
|
||||
where pathMode = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby)]
|
||||
pathMode' = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby), File "test/fixtures/ruby/corpus/and-or.B.rb" (Just Ruby)]
|
||||
where path = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby)]
|
||||
path' = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby), File "test/fixtures/ruby/corpus/and-or.B.rb" (Just Ruby)]
|
||||
path'' = [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)]
|
||||
prefix = "test/fixtures/cli"
|
||||
|
||||
sExpressionParseTreeOutput = "(Program\n (LowAnd\n (Send\n (Identifier))\n (Send\n (Identifier))))\n"
|
||||
jsonParseTreeOutput = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowAnd\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"}]}\n"
|
||||
jsonParseTreeOutput' = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowAnd\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"},{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowOr\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}},\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"term\":\"LowAnd\",\"children\":{\"term\":\"LowOr\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"b\",\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}},\"sourceRange\":[11,17],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,7]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"c\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}},\"sourceRange\":[11,23],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,13]}}],\"sourceRange\":[0,24],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.B.rb\",\"language\":\"Ruby\"}]}\n"
|
||||
emptyJsonParseTreeOutput = "{\"trees\":[]}\n"
|
||||
symbolsOutput = "{\"files\":[{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"symbols\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"kind\":\"Method\",\"symbol\":\"foo\"}],\"language\":\"Ruby\"}]}\n"
|
||||
tagsOutput = "[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"kind\":\"Method\",\"symbol\":\"foo\",\"line\":\"def foo\",\"language\":\"Ruby\"}]\n"
|
||||
|
||||
|
||||
diffFixtures :: [(String, [BlobPair] -> TaskEff Builder, [Both File], ByteString)]
|
||||
diffFixtures :: [(String, [BlobPair] -> TaskEff Builder, [Both File], FilePath)]
|
||||
diffFixtures =
|
||||
[ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, jsonOutput)
|
||||
, (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, sExpressionOutput)
|
||||
, (show ToCDiffRenderer, runDiff ToCDiffRenderer, pathMode, tocOutput)
|
||||
[ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, prefix </> "diff-tree.json")
|
||||
, (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, "test/fixtures/ruby/corpus/method-declaration.diffA-B.txt")
|
||||
, (show ToCDiffRenderer, runDiff ToCDiffRenderer, pathMode, prefix </> "diff-tree.toc.json")
|
||||
]
|
||||
where pathMode = [both (File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)) (File "test/fixtures/ruby/corpus/method-declaration.B.rb" (Just Ruby))]
|
||||
|
||||
jsonOutput = "{\"diffs\":[{\"diff\":{\"merge\":{\"term\":\"Program\",\"children\":[{\"merge\":{\"term\":\"Method\",\"methodContext\":[],\"methodReceiver\":{\"merge\":{\"term\":\"Empty\",\"before\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"after\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}}}},\"methodName\":{\"patch\":{\"replace\":[{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}]}},\"methodParameters\":[{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}}],\"methodBody\":{\"merge\":{\"children\":[{\"patch\":{\"insert\":{\"term\":\"Send\",\"sourceRange\":[13,16],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]},\"sendSelector\":{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"baz\",\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}}}}}],\"before\":{\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,4]}},\"after\":{\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}},\"before\":{\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}},\"after\":{\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}}}}],\"before\":{\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"after\":{\"sourceRange\":[0,21],\"sourceSpan\":{\"start\":[1,1],\"end\":[4,1]}}}},\"stat\":{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb\",\"replace\":[{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"language\":\"Ruby\"},{\"path\":\"test/fixtures/ruby/corpus/method-declaration.B.rb\",\"language\":\"Ruby\"}]}}]}\n"
|
||||
sExpressionOutput = "(Program\n (Method\n (Empty)\n { (Identifier)\n ->(Identifier) }\n {+(Identifier)+}\n (Statements\n {+(Send\n {+(Identifier)+})+})))\n"
|
||||
tocOutput = "{\"changes\":{\"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"}]},\"errors\":{}}\n"
|
||||
prefix = "test/fixtures/cli"
|
||||
|
198
test/fixtures/cli/diff-tree.json
vendored
Normal file
198
test/fixtures/cli/diff-tree.json
vendored
Normal file
@ -0,0 +1,198 @@
|
||||
{
|
||||
"diffs": [
|
||||
{
|
||||
"diff":
|
||||
{
|
||||
"merge":
|
||||
{
|
||||
"term": "Program",
|
||||
"children": [
|
||||
{
|
||||
"merge":
|
||||
{
|
||||
"term": "Method",
|
||||
"methodBody":
|
||||
{
|
||||
"merge":
|
||||
{
|
||||
"children": [
|
||||
{
|
||||
"patch":
|
||||
{
|
||||
"insert":
|
||||
{
|
||||
"term": "Send",
|
||||
"sourceRange": [13, 16],
|
||||
"sendReceiver": null,
|
||||
"sendBlock": null,
|
||||
"sendArgs": [],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 3],
|
||||
"end": [2, 6]
|
||||
},
|
||||
"sendSelector":
|
||||
{
|
||||
"patch":
|
||||
{
|
||||
"insert":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "baz",
|
||||
"sourceRange": [13, 16],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 3],
|
||||
"end": [2, 6]
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}],
|
||||
"before":
|
||||
{
|
||||
"sourceRange": [8, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 1],
|
||||
"end": [2, 4]
|
||||
}
|
||||
},
|
||||
"after":
|
||||
{
|
||||
"sourceRange": [13, 16],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 3],
|
||||
"end": [2, 6]
|
||||
}
|
||||
}
|
||||
}
|
||||
},
|
||||
"methodContext": [],
|
||||
"methodName":
|
||||
{
|
||||
"patch":
|
||||
{
|
||||
"replace": [
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "foo",
|
||||
"sourceRange": [4, 7],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 5],
|
||||
"end": [1, 8]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "bar",
|
||||
"sourceRange": [4, 7],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 5],
|
||||
"end": [1, 8]
|
||||
}
|
||||
}]
|
||||
}
|
||||
},
|
||||
"methodParameters": [
|
||||
{
|
||||
"patch":
|
||||
{
|
||||
"insert":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "a",
|
||||
"sourceRange": [8, 9],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 9],
|
||||
"end": [1, 10]
|
||||
}
|
||||
}
|
||||
}
|
||||
}],
|
||||
"methodReceiver":
|
||||
{
|
||||
"merge":
|
||||
{
|
||||
"term": "Empty",
|
||||
"before":
|
||||
{
|
||||
"sourceRange": [0, 0],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 1]
|
||||
}
|
||||
},
|
||||
"after":
|
||||
{
|
||||
"sourceRange": [0, 0],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 1]
|
||||
}
|
||||
}
|
||||
}
|
||||
},
|
||||
"before":
|
||||
{
|
||||
"sourceRange": [0, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 4]
|
||||
}
|
||||
},
|
||||
"after":
|
||||
{
|
||||
"sourceRange": [0, 20],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [3, 4]
|
||||
}
|
||||
}
|
||||
}
|
||||
}],
|
||||
"before":
|
||||
{
|
||||
"sourceRange": [0, 12],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [3, 1]
|
||||
}
|
||||
},
|
||||
"after":
|
||||
{
|
||||
"sourceRange": [0, 21],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [4, 1]
|
||||
}
|
||||
}
|
||||
}
|
||||
},
|
||||
"stat":
|
||||
{
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb",
|
||||
"replace": [
|
||||
{
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.A.rb",
|
||||
"language": "Ruby"
|
||||
},
|
||||
{
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.B.rb",
|
||||
"language": "Ruby"
|
||||
}]
|
||||
}
|
||||
}]
|
||||
}
|
18
test/fixtures/cli/diff-tree.toc.json
vendored
Normal file
18
test/fixtures/cli/diff-tree.toc.json
vendored
Normal file
@ -0,0 +1,18 @@
|
||||
{
|
||||
"changes":
|
||||
{
|
||||
"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb": [
|
||||
{
|
||||
"span":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [3, 4]
|
||||
},
|
||||
"category": "Method",
|
||||
"term": "bar",
|
||||
"changeType": "modified"
|
||||
}]
|
||||
},
|
||||
"errors":
|
||||
{}
|
||||
}
|
3
test/fixtures/cli/parse-tree-empty.json
vendored
Normal file
3
test/fixtures/cli/parse-tree-empty.json
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
{
|
||||
"trees": []
|
||||
}
|
74
test/fixtures/cli/parse-tree.json
vendored
Normal file
74
test/fixtures/cli/parse-tree.json
vendored
Normal file
@ -0,0 +1,74 @@
|
||||
{
|
||||
"trees": [
|
||||
{
|
||||
"tree":
|
||||
{
|
||||
"term": "Program",
|
||||
"children": [
|
||||
{
|
||||
"term": "LowAnd",
|
||||
"children": [
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "foo",
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "bar",
|
||||
"sourceRange": [8, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 9],
|
||||
"end": [1, 12]
|
||||
}
|
||||
},
|
||||
"sourceRange": [8, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 9],
|
||||
"end": [1, 12]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 12]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 12],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 1]
|
||||
}
|
||||
},
|
||||
"path": "test/fixtures/ruby/corpus/and-or.A.rb",
|
||||
"language": "Ruby"
|
||||
}]
|
||||
}
|
17
test/fixtures/cli/parse-tree.symbols.json
vendored
Normal file
17
test/fixtures/cli/parse-tree.symbols.json
vendored
Normal file
@ -0,0 +1,17 @@
|
||||
{
|
||||
"files": [
|
||||
{
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.A.rb",
|
||||
"symbols": [
|
||||
{
|
||||
"span":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 4]
|
||||
},
|
||||
"kind": "Method",
|
||||
"symbol": "foo"
|
||||
}],
|
||||
"language": "Ruby"
|
||||
}]
|
||||
}
|
13
test/fixtures/cli/parse-tree.tags.json
vendored
Normal file
13
test/fixtures/cli/parse-tree.tags.json
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
[
|
||||
{
|
||||
"span":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 4]
|
||||
},
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.A.rb",
|
||||
"kind": "Method",
|
||||
"symbol": "foo",
|
||||
"line": "def foo",
|
||||
"language": "Ruby"
|
||||
}]
|
234
test/fixtures/cli/parse-trees.json
vendored
Normal file
234
test/fixtures/cli/parse-trees.json
vendored
Normal file
@ -0,0 +1,234 @@
|
||||
{
|
||||
"trees": [
|
||||
{
|
||||
"tree":
|
||||
{
|
||||
"term": "Program",
|
||||
"children": [
|
||||
{
|
||||
"term": "LowAnd",
|
||||
"children": [
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "foo",
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "bar",
|
||||
"sourceRange": [8, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 9],
|
||||
"end": [1, 12]
|
||||
}
|
||||
},
|
||||
"sourceRange": [8, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 9],
|
||||
"end": [1, 12]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 11],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 12]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 12],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 1]
|
||||
}
|
||||
},
|
||||
"path": "test/fixtures/ruby/corpus/and-or.A.rb",
|
||||
"language": "Ruby"
|
||||
},
|
||||
{
|
||||
"tree":
|
||||
{
|
||||
"term": "Program",
|
||||
"children": [
|
||||
{
|
||||
"term": "LowOr",
|
||||
"children": [
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "foo",
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
"sourceRange": [0, 3],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 4]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "bar",
|
||||
"sourceRange": [7, 10],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 8],
|
||||
"end": [1, 11]
|
||||
}
|
||||
},
|
||||
"sourceRange": [7, 10],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 8],
|
||||
"end": [1, 11]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 10],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [1, 11]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "LowAnd",
|
||||
"children": [
|
||||
{
|
||||
"term": "LowOr",
|
||||
"children": [
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "a",
|
||||
"sourceRange": [11, 12],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 1],
|
||||
"end": [2, 2]
|
||||
}
|
||||
},
|
||||
"sourceRange": [11, 12],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 1],
|
||||
"end": [2, 2]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "b",
|
||||
"sourceRange": [16, 17],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 6],
|
||||
"end": [2, 7]
|
||||
}
|
||||
},
|
||||
"sourceRange": [16, 17],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 6],
|
||||
"end": [2, 7]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [11, 17],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 1],
|
||||
"end": [2, 7]
|
||||
}
|
||||
},
|
||||
{
|
||||
"term": "Send",
|
||||
"sendArgs": [],
|
||||
"sendBlock": null,
|
||||
"sendReceiver": null,
|
||||
"sendSelector":
|
||||
{
|
||||
"term": "Identifier",
|
||||
"name": "c",
|
||||
"sourceRange": [22, 23],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 12],
|
||||
"end": [2, 13]
|
||||
}
|
||||
},
|
||||
"sourceRange": [22, 23],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 12],
|
||||
"end": [2, 13]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [11, 23],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [2, 1],
|
||||
"end": [2, 13]
|
||||
}
|
||||
}],
|
||||
"sourceRange": [0, 24],
|
||||
"sourceSpan":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [3, 1]
|
||||
}
|
||||
},
|
||||
"path": "test/fixtures/ruby/corpus/and-or.B.rb",
|
||||
"language": "Ruby"
|
||||
}]
|
||||
}
|
Loading…
Reference in New Issue
Block a user