1
1
mirror of https://github.com/github/semantic.git synced 2024-12-27 00:44:57 +03:00

Merge pull request #1908 from github/explicit-statements

Introduce Statements syntax to represent imperative sequences
This commit is contained in:
Timothy Clem 2018-06-01 15:07:26 -07:00 committed by GitHub
commit bbb63a3296
1342 changed files with 2838 additions and 2764 deletions

View File

@ -202,11 +202,14 @@ instance Apply Evaluatable fs => Evaluatable (Sum fs) where
instance Evaluatable s => Evaluatable (TermF s a) where instance Evaluatable s => Evaluatable (TermF s a) where
eval = eval . termFOut eval = eval . termFOut
--- | '[]' is treated as an imperative sequence of statements/declarations s.t.:
--- -- NOTE: Use 'Data.Syntax.Statements' instead of '[]' if you need imperative eval semantics.
--- 1. Each statements effects on the store are accumulated; --
--- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and -- | '[]' is treated as an imperative sequence of statements/declarations s.t.:
--- 3. Only the last statements return value is returned. --
-- 1. Each statements effects on the store are accumulated;
-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and
-- 3. Only the last statements return value is returned.
instance Evaluatable [] where instance Evaluatable [] where
-- 'nonEmpty' and 'foldMap1' enable us to return the last statements result instead of 'unit' for non-empty lists. -- 'nonEmpty' and 'foldMap1' enable us to return the last statements result instead of 'unit' for non-empty lists.
eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty

View File

@ -6,11 +6,10 @@ module Data.JSON.Fields
, ToJSONFields (..) , ToJSONFields (..)
, ToJSONFields1 (..) , ToJSONFields1 (..)
, (.=) , (.=)
, noChildren
, withChildren
) where ) where
import Data.Aeson import Data.Aeson
import qualified Data.Map as Map
import Data.Sum (Apply (..), Sum) import Data.Sum (Apply (..), Sum)
import qualified Data.Text as Text import qualified Data.Text as Text
import qualified Data.Text.Encoding 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] 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] default toJSONFields1 :: (KeyValue kv, ToJSON a, GToJSONFields1 (Rep1 f), GConstructorName1 (Rep1 f), Generic1 f) => f a -> [kv]
toJSONFields1 s = let r = from1 s in toJSONFields1 s = let r = from1 s in
"term" .= gconstructorName1 r : gtoJSONFields1 r "term" .= gconstructorName1 r : Map.foldrWithKey m [] (gtoJSONFields1 r)
where
withChildren :: (KeyValue kv, ToJSON a, Foldable f) => f a -> [kv] -> [kv] m _ [] acc = acc
withChildren f ks = ("children" .= toList f) : ks m k [v] acc = (k .= v) : acc
m k vs acc = (k .= vs) : acc
noChildren :: KeyValue kv => [kv] -> [kv]
noChildren ks = ("children" .= ([] :: [Int])) : ks
instance ToJSONFields a => ToJSONFields (Join (,) a) where instance ToJSONFields a => ToJSONFields (Join (,) a) where
toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ] toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ]
@ -93,7 +90,10 @@ 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. -- | A typeclass to calculate a list of 'KeyValue's describing the record selector names and associated values on a datatype.
class GToJSONFields1 f where class GToJSONFields1 f where
gtoJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv] -- FIXME: Not ideal to allocate a Map each time here, but not an obvious way
-- to deal with product types without record selectors that all end up as an
-- array under a "children" property.
gtoJSONFields1 :: (ToJSON a) => f a -> Map.Map Text [SomeJSON]
instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where
gtoJSONFields1 = gtoJSONFields1 . unM1 gtoJSONFields1 = gtoJSONFields1 . unM1
@ -102,33 +102,33 @@ instance GToJSONFields1 f => GToJSONFields1 (M1 C c f) where
gtoJSONFields1 = gtoJSONFields1 . unM1 gtoJSONFields1 = gtoJSONFields1 . unM1
instance GToJSONFields1 U1 where instance GToJSONFields1 U1 where
gtoJSONFields1 _ = [] gtoJSONFields1 _ = mempty
instance (Selector c, GSelectorJSONValue1 f) => GToJSONFields1 (M1 S c f) where instance (Selector c, GSelectorJSONValue1 f) => GToJSONFields1 (M1 S c f) where
gtoJSONFields1 m1 = case selName m1 of gtoJSONFields1 m1 = Map.fromList [gselectorJSONValue1 keyName (unM1 m1)]
"" -> [ "children" .= json ] where keyName = case selName m1 of
n -> [ Text.pack n .= json ] "" -> Nothing
where json = gselectorJSONValue1 (unM1 m1) n -> Just (Text.pack n)
instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where
gtoJSONFields1 (L1 l) = gtoJSONFields1 l gtoJSONFields1 (L1 l) = gtoJSONFields1 l
gtoJSONFields1 (R1 r) = gtoJSONFields1 r gtoJSONFields1 (R1 r) = gtoJSONFields1 r
instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :*: g) where 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. -- | A typeclass to retrieve the JSON 'Value' of a record selector.
class GSelectorJSONValue1 f where class GSelectorJSONValue1 f where
gselectorJSONValue1 :: ToJSON a => f a -> SomeJSON gselectorJSONValue1 :: (ToJSON a) => Maybe Text -> f a -> (Text, [SomeJSON])
instance GSelectorJSONValue1 Par1 where instance GSelectorJSONValue1 Par1 where
gselectorJSONValue1 = SomeJSON . unPar1 gselectorJSONValue1 k x = (fromMaybe "children" k, [SomeJSON (unPar1 x)])
instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where 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 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. -- TODO: Fix this orphan instance.

View File

@ -148,21 +148,9 @@ instance FreeVariables1 Identifier where
instance Declarations1 Identifier where instance Declarations1 Identifier where
liftDeclaredName _ (Identifier x) = pure x liftDeclaredName _ (Identifier x) = pure x
newtype Program a = Program [a]
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Program where liftEq = genericLiftEq
instance Ord1 Program where liftCompare = genericLiftCompare
instance Show1 Program where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Program where
eval (Program xs) = eval xs
-- | An accessibility modifier, e.g. private, public, protected, etc. -- | An accessibility modifier, e.g. private, public, protected, etc.
newtype AccessibilityModifier a = AccessibilityModifier ByteString 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 Eq1 AccessibilityModifier where liftEq = genericLiftEq
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
@ -175,9 +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'. -- 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 data Empty a = Empty
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 ToJSONFields1 Empty
instance Eq1 Empty where liftEq _ _ _ = True instance Eq1 Empty where liftEq _ _ _ = True
instance Ord1 Empty where liftCompare _ _ _ = EQ instance Ord1 Empty where liftCompare _ _ _ = EQ
@ -188,7 +174,7 @@ instance Evaluatable Empty where
-- | Syntax representing a parsing or assignment error. -- | Syntax representing a parsing or assignment error.
data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] } 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 Eq1 Error where liftEq = genericLiftEq
instance Ord1 Error where liftCompare = genericLiftCompare instance Ord1 Error where liftCompare = genericLiftCompare
@ -196,12 +182,6 @@ instance Show1 Error where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Error 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 String -> [a] -> Error a
errorSyntax Error.Error{..} = Error (ErrorStack (getCallStack callStack)) errorExpected errorActual errorSyntax Error.Error{..} = Error (ErrorStack (getCallStack callStack)) errorExpected errorActual
@ -241,9 +221,7 @@ instance Ord ErrorStack where
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
deriving (Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance ToJSONFields1 Context
instance Diffable Context where instance Diffable Context where
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s

View File

@ -3,21 +3,17 @@ module Data.Syntax.Comment where
import Prologue import Prologue
import Data.Abstract.Evaluatable import Data.Abstract.Evaluatable
import Data.ByteString (unpack)
import Data.JSON.Fields import Data.JSON.Fields
import Diffing.Algorithm import Diffing.Algorithm
-- | An unnested comment (line or block). -- | An unnested comment (line or block).
newtype Comment a = Comment { commentContent :: ByteString } 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 Eq1 Comment where liftEq = genericLiftEq
instance Ord1 Comment where liftCompare = genericLiftCompare instance Ord1 Comment where liftCompare = genericLiftCompare
instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Comment where
toJSONFields1 f@Comment{..} = withChildren f ["contents" .= unpack commentContent ]
instance Evaluatable Comment where instance Evaluatable Comment where
eval _ = pure (Rval unit) eval _ = pure (Rval unit)

View File

@ -9,7 +9,7 @@ import Diffing.Algorithm
import Prologue import Prologue
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a } 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 instance Diffable Function where
equivalentBySubterm = Just . functionName equivalentBySubterm = Just . functionName
@ -18,8 +18,6 @@ instance Eq1 Function where liftEq = genericLiftEq
instance Ord1 Function where liftCompare = genericLiftCompare instance Ord1 Function where liftCompare = genericLiftCompare
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Function
-- TODO: Filter the closed-over environment by the free variables in the term. -- TODO: Filter the closed-over environment by the free variables in the term.
-- TODO: How should we represent function types, where applicable? -- 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 } 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 Eq1 Method where liftEq = genericLiftEq
instance Ord1 Method where liftCompare = genericLiftCompare instance Ord1 Method where liftCompare = genericLiftCompare
@ -44,8 +42,6 @@ instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
instance Diffable Method where instance Diffable Method where
equivalentBySubterm = Just . methodName equivalentBySubterm = Just . methodName
instance ToJSONFields1 Method
-- Evaluating a Method creates a closure and makes that value available in the -- Evaluating a Method creates a closure and makes that value available in the
-- local environment. -- local environment.
instance Evaluatable Method where instance Evaluatable Method where
@ -58,40 +54,34 @@ instance Evaluatable Method where
-- | A method signature in TypeScript or a method spec in Go. -- | A method signature in TypeScript or a method spec in Go.
data MethodSignature a = MethodSignature { _methodSignatureContext :: ![a], _methodSignatureName :: !a, _methodSignatureParameters :: ![a] } 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 Eq1 MethodSignature where liftEq = genericLiftEq
instance Ord1 MethodSignature where liftCompare = genericLiftCompare instance Ord1 MethodSignature where liftCompare = genericLiftCompare
instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 MethodSignature
-- TODO: Implement Eval instance for MethodSignature -- TODO: Implement Eval instance for MethodSignature
instance Evaluatable MethodSignature instance Evaluatable MethodSignature
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a } 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 Eq1 RequiredParameter where liftEq = genericLiftEq
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 RequiredParameter
-- TODO: Implement Eval instance for RequiredParameter -- TODO: Implement Eval instance for RequiredParameter
instance Evaluatable RequiredParameter instance Evaluatable RequiredParameter
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a } 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 Eq1 OptionalParameter where liftEq = genericLiftEq
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 OptionalParameter
-- TODO: Implement Eval instance for OptionalParameter -- TODO: Implement Eval instance for OptionalParameter
instance Evaluatable 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] -- 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. -- | A declaration of possibly many variables such as var foo = 5, bar = 6 in JavaScript.
newtype VariableDeclaration a = VariableDeclaration { variableDeclarations :: [a] } 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 Eq1 VariableDeclaration where liftEq = genericLiftEq
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 VariableDeclaration
instance Evaluatable VariableDeclaration where instance Evaluatable VariableDeclaration where
eval (VariableDeclaration []) = pure (Rval unit) eval (VariableDeclaration []) = pure (Rval unit)
eval (VariableDeclaration decs) = Rval . multiple <$> traverse subtermValue decs 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. -- | A TypeScript/Java style interface declaration to implement.
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationBody :: !a } 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 Eq1 InterfaceDeclaration where liftEq = genericLiftEq
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 InterfaceDeclaration
-- TODO: Implement Eval instance for InterfaceDeclaration -- TODO: Implement Eval instance for InterfaceDeclaration
instance Evaluatable 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. -- | A public field definition such as a field definition in a JavaScript class.
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a } 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 Eq1 PublicFieldDefinition where liftEq = genericLiftEq
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 PublicFieldDefinition
-- TODO: Implement Eval instance for PublicFieldDefinition -- TODO: Implement Eval instance for PublicFieldDefinition
instance Evaluatable PublicFieldDefinition instance Evaluatable PublicFieldDefinition
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a } 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 Eq1 Variable where liftEq = genericLiftEq
instance Ord1 Variable where liftCompare = genericLiftCompare instance Ord1 Variable where liftCompare = genericLiftCompare
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Variable
-- TODO: Implement Eval instance for Variable -- TODO: Implement Eval instance for Variable
instance Evaluatable Variable instance Evaluatable Variable
data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: !a } 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 instance Declarations a => Declarations (Class a) where
declaredName (Class _ name _ _) = declaredName name declaredName (Class _ name _ _) = declaredName name
instance ToJSONFields1 Class
instance Diffable Class where instance Diffable Class where
equivalentBySubterm = Just . classIdentifier equivalentBySubterm = Just . classIdentifier
@ -189,14 +169,12 @@ instance Evaluatable Class where
-- | A decorator in Python -- | A decorator in Python
data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a } 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 Eq1 Decorator where liftEq = genericLiftEq
instance Ord1 Decorator where liftCompare = genericLiftCompare instance Ord1 Decorator where liftCompare = genericLiftCompare
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Decorator
-- TODO: Implement Eval instance for Decorator -- TODO: Implement Eval instance for Decorator
instance Evaluatable 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. -- | 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] } 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 Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare
instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Data.Syntax.Declaration.Datatype
-- TODO: Implement Eval instance for Datatype -- TODO: Implement Eval instance for Datatype
instance Evaluatable Data.Syntax.Declaration.Datatype instance Evaluatable Data.Syntax.Declaration.Datatype
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift. -- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
data Constructor a = Constructor { constructorName :: !a, constructorFields :: !a } 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 Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Data.Syntax.Declaration.Constructor
-- TODO: Implement Eval instance for Constructor -- TODO: Implement Eval instance for Constructor
instance Evaluatable Data.Syntax.Declaration.Constructor instance Evaluatable Data.Syntax.Declaration.Constructor
-- | Comprehension (e.g. ((a for b in c if a()) in Python) -- | Comprehension (e.g. ((a for b in c if a()) in Python)
data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a } 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 Eq1 Comprehension where liftEq = genericLiftEq
instance Ord1 Comprehension where liftCompare = genericLiftCompare instance Ord1 Comprehension where liftCompare = genericLiftCompare
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Comprehension
-- TODO: Implement Eval instance for Comprehension -- TODO: Implement Eval instance for Comprehension
instance Evaluatable Comprehension instance Evaluatable Comprehension
-- | A declared type (e.g. `a []int` in Go). -- | A declared type (e.g. `a []int` in Go).
data Type a = Type { typeName :: !a, typeKind :: !a } 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 Eq1 Type where liftEq = genericLiftEq
instance Ord1 Type where liftCompare = genericLiftCompare instance Ord1 Type where liftCompare = genericLiftCompare
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Type
-- TODO: Implement Eval instance for Type -- TODO: Implement Eval instance for Type
instance Evaluatable Type instance Evaluatable Type
-- | Type alias declarations in Javascript/Haskell, etc. -- | Type alias declarations in Javascript/Haskell, etc.
data TypeAlias a = TypeAlias { typeAliasContext :: ![a], typeAliasIdentifier :: !a, typeAliasKind :: !a } 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 Eq1 TypeAlias where liftEq = genericLiftEq
instance Ord1 TypeAlias where liftCompare = genericLiftCompare instance Ord1 TypeAlias where liftCompare = genericLiftCompare
instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeAlias
-- TODO: Implement Eval instance for TypeAlias -- TODO: Implement Eval instance for TypeAlias
instance Evaluatable TypeAlias where instance Evaluatable TypeAlias where
eval TypeAlias{..} = do eval TypeAlias{..} = do

View File

@ -11,27 +11,23 @@ import Prologue
-- A file directive like the Ruby constant `__FILE__`. -- A file directive like the Ruby constant `__FILE__`.
data File a = 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 Eq1 File where liftEq = genericLiftEq
instance Ord1 File where liftCompare = genericLiftCompare instance Ord1 File where liftCompare = genericLiftCompare
instance Show1 File where liftShowsPrec = genericLiftShowsPrec instance Show1 File where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 File
instance Evaluatable File where instance Evaluatable File where
eval File = Rval . string . BC.pack . modulePath <$> currentModule eval File = Rval . string . BC.pack . modulePath <$> currentModule
-- A line directive like the Ruby constant `__LINE__`. -- A line directive like the Ruby constant `__LINE__`.
data Line a = 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 Eq1 Line where liftEq = genericLiftEq
instance Ord1 Line where liftCompare = genericLiftCompare instance Ord1 Line where liftCompare = genericLiftCompare
instance Show1 Line where liftShowsPrec = genericLiftShowsPrec instance Show1 Line where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Line
instance Evaluatable Line where instance Evaluatable Line where
eval Line = Rval . integer . fromIntegral . posLine . spanStart <$> currentSpan eval Line = Rval . integer . fromIntegral . posLine . spanStart <$> currentSpan

View File

@ -10,14 +10,12 @@ import Prologue hiding (index)
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell. -- | 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 } 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 Eq1 Call where liftEq = genericLiftEq
instance Ord1 Call where liftCompare = genericLiftCompare instance Ord1 Call where liftCompare = genericLiftCompare
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Call
instance Evaluatable Call where instance Evaluatable Call where
eval Call{..} = do eval Call{..} = do
op <- subtermValue callFunction op <- subtermValue callFunction
@ -31,14 +29,12 @@ data Comparison a
| Equal !a !a | Equal !a !a
| StrictEqual !a !a | StrictEqual !a !a
| Comparison !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 Eq1 Comparison where liftEq = genericLiftEq
instance Ord1 Comparison where liftCompare = genericLiftCompare instance Ord1 Comparison where liftCompare = genericLiftCompare
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Comparison
instance Evaluatable Comparison where instance Evaluatable Comparison where
eval t = Rval <$> (traverse subtermValue t >>= go) where eval t = Rval <$> (traverse subtermValue t >>= go) where
go x = case x of go x = case x of
@ -62,14 +58,12 @@ data Arithmetic a
| Modulo !a !a | Modulo !a !a
| Power !a !a | Power !a !a
| Negate !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 Eq1 Arithmetic where liftEq = genericLiftEq
instance Ord1 Arithmetic where liftCompare = genericLiftCompare instance Ord1 Arithmetic where liftCompare = genericLiftCompare
instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Arithmetic
instance Evaluatable Arithmetic where instance Evaluatable Arithmetic where
eval t = Rval <$> (traverse subtermValue t >>= go) where eval t = Rval <$> (traverse subtermValue t >>= go) where
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+) go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
@ -85,14 +79,12 @@ instance Evaluatable Arithmetic where
data Match a data Match a
= Matches !a !a = Matches !a !a
| NotMatches !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 Eq1 Match where liftEq = genericLiftEq
instance Ord1 Match where liftCompare = genericLiftCompare instance Ord1 Match where liftCompare = genericLiftCompare
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Match
-- TODO: Implement Eval instance for Match -- TODO: Implement Eval instance for Match
instance Evaluatable Match instance Evaluatable Match
@ -102,14 +94,12 @@ data Boolean a
| And !a !a | And !a !a
| Not !a | Not !a
| XOr !a !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 Eq1 Boolean where liftEq = genericLiftEq
instance Ord1 Boolean where liftCompare = genericLiftCompare instance Ord1 Boolean where liftCompare = genericLiftCompare
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Boolean
instance Evaluatable Boolean where 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 -- 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 eval t = Rval <$> go (fmap subtermValue t) where
@ -124,56 +114,48 @@ instance Evaluatable Boolean where
-- | Javascript delete operator -- | Javascript delete operator
newtype Delete a = Delete a 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 Eq1 Delete where liftEq = genericLiftEq
instance Ord1 Delete where liftCompare = genericLiftCompare instance Ord1 Delete where liftCompare = genericLiftCompare
instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Delete
-- TODO: Implement Eval instance for Delete -- TODO: Implement Eval instance for Delete
instance Evaluatable Delete instance Evaluatable Delete
-- | A sequence expression such as Javascript or C's comma operator. -- | A sequence expression such as Javascript or C's comma operator.
data SequenceExpression a = SequenceExpression { _firstExpression :: !a, _secondExpression :: !a } 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 Eq1 SequenceExpression where liftEq = genericLiftEq
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 SequenceExpression
-- TODO: Implement Eval instance for SequenceExpression -- TODO: Implement Eval instance for SequenceExpression
instance Evaluatable SequenceExpression instance Evaluatable SequenceExpression
-- | Javascript void operator -- | Javascript void operator
newtype Void a = Void a 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 Eq1 Void where liftEq = genericLiftEq
instance Ord1 Void where liftCompare = genericLiftCompare instance Ord1 Void where liftCompare = genericLiftCompare
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Void
-- TODO: Implement Eval instance for Void -- TODO: Implement Eval instance for Void
instance Evaluatable Void instance Evaluatable Void
-- | Javascript typeof operator -- | Javascript typeof operator
newtype Typeof a = Typeof a 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 Eq1 Typeof where liftEq = genericLiftEq
instance Ord1 Typeof where liftCompare = genericLiftCompare instance Ord1 Typeof where liftCompare = genericLiftCompare
instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Typeof
-- TODO: Implement Eval instance for Typeof -- TODO: Implement Eval instance for Typeof
instance Evaluatable Typeof instance Evaluatable Typeof
@ -187,14 +169,12 @@ data Bitwise a
| RShift !a !a | RShift !a !a
| UnsignedRShift !a !a | UnsignedRShift !a !a
| Complement 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 Eq1 Bitwise where liftEq = genericLiftEq
instance Ord1 Bitwise where liftCompare = genericLiftCompare instance Ord1 Bitwise where liftCompare = genericLiftCompare
instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Bitwise
instance Evaluatable Bitwise where instance Evaluatable Bitwise where
eval t = Rval <$> (traverse subtermValue t >>= go) where eval t = Rval <$> (traverse subtermValue t >>= go) where
genLShift x y = shiftL x (fromIntegral y) genLShift x y = shiftL x (fromIntegral y)
@ -211,14 +191,12 @@ instance Evaluatable Bitwise where
-- | Member Access (e.g. a.b) -- | Member Access (e.g. a.b)
data MemberAccess a data MemberAccess a
= MemberAccess !a !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 Eq1 MemberAccess where liftEq = genericLiftEq
instance Ord1 MemberAccess where liftCompare = genericLiftCompare instance Ord1 MemberAccess where liftCompare = genericLiftCompare
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 MemberAccess
instance Evaluatable MemberAccess where instance Evaluatable MemberAccess where
eval (MemberAccess obj prop) = do eval (MemberAccess obj prop) = do
obj <- subtermValue obj obj <- subtermValue obj
@ -231,14 +209,12 @@ instance Evaluatable MemberAccess where
data Subscript a data Subscript a
= Subscript !a ![a] = Subscript !a ![a]
| Member !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 Eq1 Subscript where liftEq = genericLiftEq
instance Ord1 Subscript where liftCompare = genericLiftCompare instance Ord1 Subscript where liftCompare = genericLiftCompare
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Subscript
-- TODO: Finish Eval instance for Subscript -- TODO: Finish Eval instance for Subscript
-- TODO return a special LvalSubscript instance here -- TODO return a special LvalSubscript instance here
instance Evaluatable Subscript where 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)) -- | 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 } 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 Eq1 Enumeration where liftEq = genericLiftEq
instance Ord1 Enumeration where liftCompare = genericLiftCompare instance Ord1 Enumeration where liftCompare = genericLiftCompare
instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Enumeration
-- TODO: Implement Eval instance for Enumeration -- TODO: Implement Eval instance for Enumeration
instance Evaluatable Enumeration instance Evaluatable Enumeration
-- | InstanceOf (e.g. a instanceof b in JavaScript -- | InstanceOf (e.g. a instanceof b in JavaScript
data InstanceOf a = InstanceOf { instanceOfSubject :: !a, instanceOfObject :: !a } 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 Eq1 InstanceOf where liftEq = genericLiftEq
instance Ord1 InstanceOf where liftCompare = genericLiftCompare instance Ord1 InstanceOf where liftCompare = genericLiftCompare
instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 InstanceOf
-- TODO: Implement Eval instance for InstanceOf -- TODO: Implement Eval instance for InstanceOf
instance Evaluatable InstanceOf instance Evaluatable InstanceOf
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++) -- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
newtype ScopeResolution a = ScopeResolution [a] 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 Eq1 ScopeResolution where liftEq = genericLiftEq
instance Ord1 ScopeResolution where liftCompare = genericLiftCompare instance Ord1 ScopeResolution where liftCompare = genericLiftCompare
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ScopeResolution
-- TODO: Implement Eval instance for ScopeResolution -- TODO: Implement Eval instance for ScopeResolution
instance Evaluatable ScopeResolution instance Evaluatable ScopeResolution
-- | A non-null expression such as Typescript or Swift's ! expression. -- | A non-null expression such as Typescript or Swift's ! expression.
newtype NonNullExpression a = NonNullExpression { nonNullExpression :: a } 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 Eq1 NonNullExpression where liftEq = genericLiftEq
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 NonNullExpression
-- TODO: Implement Eval instance for NonNullExpression -- TODO: Implement Eval instance for NonNullExpression
instance Evaluatable NonNullExpression instance Evaluatable NonNullExpression
-- | An await expression in Javascript or C#. -- | An await expression in Javascript or C#.
newtype Await a = Await { awaitSubject :: a } 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 Eq1 Await where liftEq = genericLiftEq
instance Ord1 Await where liftCompare = genericLiftCompare instance Ord1 Await where liftCompare = genericLiftCompare
instance Show1 Await where liftShowsPrec = genericLiftShowsPrec instance Show1 Await where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Await
-- TODO: Implement Eval instance for Await -- TODO: Implement Eval instance for Await
instance Evaluatable Await instance Evaluatable Await
-- | An object constructor call in Javascript, Java, etc. -- | An object constructor call in Javascript, Java, etc.
newtype New a = New { newSubject :: [a] } 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 Eq1 New where liftEq = genericLiftEq
instance Ord1 New where liftCompare = genericLiftCompare instance Ord1 New where liftCompare = genericLiftCompare
instance Show1 New where liftShowsPrec = genericLiftShowsPrec instance Show1 New where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 New
-- TODO: Implement Eval instance for New -- TODO: Implement Eval instance for New
instance Evaluatable New instance Evaluatable New
-- | A cast expression to a specified type. -- | A cast expression to a specified type.
data Cast a = Cast { castSubject :: !a, castType :: !a } 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 Eq1 Cast where liftEq = genericLiftEq
instance Ord1 Cast where liftCompare = genericLiftCompare instance Ord1 Cast where liftCompare = genericLiftCompare
instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Cast
-- TODO: Implement Eval instance for Cast -- TODO: Implement Eval instance for Cast
instance Evaluatable Cast instance Evaluatable Cast

View File

@ -15,7 +15,7 @@ import Text.Read (readMaybe)
-- Boolean -- Boolean
newtype Boolean a = Boolean { booleanContent :: Bool } 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 a
true = Boolean True true = Boolean True
@ -30,14 +30,11 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Boolean where instance Evaluatable Boolean where
eval (Boolean x) = pure (Rval (boolean x)) eval (Boolean x) = pure (Rval (boolean x))
instance ToJSONFields1 Boolean where
toJSONFields1 (Boolean b) = noChildren [ "value" .= b ]
-- Numeric -- Numeric
-- | A literal integer of unspecified width. No particular base is implied. -- | A literal integer of unspecified width. No particular base is implied.
newtype Integer a = Integer { integerContent :: ByteString } 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 Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
@ -48,15 +45,12 @@ instance Evaluatable Data.Syntax.Literal.Integer where
eval (Data.Syntax.Literal.Integer x) = eval (Data.Syntax.Literal.Integer x) =
Rval . integer <$> maybeM (throwEvalError (IntegerFormatError x)) (fst <$> readInteger 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: Should IntegerLiteral hold an Integer instead of a ByteString?
-- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors. -- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors.
-- | A literal float of unspecified width. -- | A literal float of unspecified width.
newtype Float a = Float { floatContent :: ByteString } 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 Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
@ -66,12 +60,9 @@ instance Evaluatable Data.Syntax.Literal.Float where
eval (Float s) = eval (Float s) =
Rval . float <$> either (const (throwEvalError (FloatFormatError s))) pure (parseScientific 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` -- Rational literals e.g. `2/3r`
newtype Rational a = Rational ByteString 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 Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare
@ -84,12 +75,9 @@ instance Evaluatable Data.Syntax.Literal.Rational where
parsed = readMaybe @Prelude.Integer (unpack trimmed) parsed = readMaybe @Prelude.Integer (unpack trimmed)
in Rval . rational <$> maybe (throwEvalError (RationalFormatError r)) (pure . toRational) parsed 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` -- Complex literals e.g. `3 + 2i`
newtype Complex a = Complex ByteString 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 Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare
@ -98,13 +86,10 @@ instance Show1 Data.Syntax.Literal.Complex where liftShowsPrec = genericLiftShow
-- TODO: Implement Eval instance for Complex -- TODO: Implement Eval instance for Complex
instance Evaluatable Complex instance Evaluatable Complex
instance ToJSONFields1 Complex where
toJSONFields1 (Complex c) = noChildren ["asString" .= unpack c]
-- Strings, symbols -- Strings, symbols
newtype String a = String { stringElements :: [a] } 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 Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
@ -115,10 +100,8 @@ instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShows
-- TODO: Implement Eval instance for String -- TODO: Implement Eval instance for String
instance Evaluatable Data.Syntax.Literal.String instance Evaluatable Data.Syntax.Literal.String
instance ToJSONFields1 Data.Syntax.Literal.String
newtype Character a = Character { characterContent :: ByteString } 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 Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
@ -126,11 +109,9 @@ instance Show1 Data.Syntax.Literal.Character where liftShowsPrec = genericLiftSh
instance Evaluatable Data.Syntax.Literal.Character instance Evaluatable Data.Syntax.Literal.Character
instance ToJSONFields1 Data.Syntax.Literal.Character
-- | An interpolation element within a string literal. -- | An interpolation element within a string literal.
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a } 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 Eq1 InterpolationElement where liftEq = genericLiftEq
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
@ -139,24 +120,19 @@ instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for InterpolationElement -- TODO: Implement Eval instance for InterpolationElement
instance Evaluatable InterpolationElement instance Evaluatable InterpolationElement
instance ToJSONFields1 InterpolationElement
-- | A sequence of textual contents within a string literal. -- | A sequence of textual contents within a string literal.
newtype TextElement a = TextElement { textElementContent :: ByteString } 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 Eq1 TextElement where liftEq = genericLiftEq
instance Ord1 TextElement where liftCompare = genericLiftCompare instance Ord1 TextElement where liftCompare = genericLiftCompare
instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TextElement where
toJSONFields1 (TextElement c) = noChildren ["asString" .= unpack c]
instance Evaluatable TextElement where instance Evaluatable TextElement where
eval (TextElement x) = pure (Rval (string x)) eval (TextElement x) = pure (Rval (string x))
data Null a = Null 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 Eq1 Null where liftEq = genericLiftEq
instance Ord1 Null where liftCompare = genericLiftCompare instance Ord1 Null where liftCompare = genericLiftCompare
@ -164,22 +140,18 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Null where eval _ = pure (Rval null) instance Evaluatable Null where eval _ = pure (Rval null)
instance ToJSONFields1 Null
newtype Symbol a = Symbol { symbolContent :: ByteString } 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 Eq1 Symbol where liftEq = genericLiftEq
instance Ord1 Symbol where liftCompare = genericLiftCompare instance Ord1 Symbol where liftCompare = genericLiftCompare
instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Symbol
instance Evaluatable Symbol where instance Evaluatable Symbol where
eval (Symbol s) = pure (Rval (symbol s)) eval (Symbol s) = pure (Rval (symbol s))
newtype Regex a = Regex { regexContent :: ByteString } 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 Eq1 Regex where liftEq = genericLiftEq
instance Ord1 Regex where liftCompare = genericLiftCompare instance Ord1 Regex where liftCompare = genericLiftCompare
@ -187,10 +159,6 @@ instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
-- TODO: Heredoc-style string literals? -- TODO: Heredoc-style string literals?
instance ToJSONFields1 Regex where
toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r]
-- TODO: Implement Eval instance for Regex -- TODO: Implement Eval instance for Regex
instance Evaluatable Regex instance Evaluatable Regex
@ -198,46 +166,38 @@ instance Evaluatable Regex
-- Collections -- Collections
newtype Array a = Array { arrayElements :: [a] } 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 Eq1 Array where liftEq = genericLiftEq
instance Ord1 Array where liftCompare = genericLiftCompare instance Ord1 Array where liftCompare = genericLiftCompare
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Array
instance Evaluatable Array where instance Evaluatable Array where
eval (Array a) = Rval <$> (array =<< traverse subtermValue a) eval (Array a) = Rval <$> (array =<< traverse subtermValue a)
newtype Hash a = Hash { hashElements :: [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 Eq1 Hash where liftEq = genericLiftEq
instance Ord1 Hash where liftCompare = genericLiftCompare instance Ord1 Hash where liftCompare = genericLiftCompare
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Hash
instance Evaluatable Hash where instance Evaluatable Hash where
eval t = Rval . hash <$> traverse (subtermValue >=> asPair) (hashElements t) eval t = Rval . hash <$> traverse (subtermValue >=> asPair) (hashElements t)
data KeyValue a = KeyValue { key :: !a, value :: !a } 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 Eq1 KeyValue where liftEq = genericLiftEq
instance Ord1 KeyValue where liftCompare = genericLiftCompare instance Ord1 KeyValue where liftCompare = genericLiftCompare
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 KeyValue
instance Evaluatable KeyValue where instance Evaluatable KeyValue where
eval (fmap subtermValue -> KeyValue{..}) = eval (fmap subtermValue -> KeyValue{..}) =
Rval <$> (kvPair <$> key <*> value) Rval <$> (kvPair <$> key <*> value)
instance ToJSONFields1 Tuple
newtype Tuple a = Tuple { tupleContents :: [a] } 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 Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare instance Ord1 Tuple where liftCompare = genericLiftCompare
@ -247,14 +207,12 @@ instance Evaluatable Tuple where
eval (Tuple cs) = Rval . multiple <$> traverse subtermValue cs eval (Tuple cs) = Rval . multiple <$> traverse subtermValue cs
newtype Set a = Set { setElements :: [a] } 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 Eq1 Set where liftEq = genericLiftEq
instance Ord1 Set where liftCompare = genericLiftCompare instance Ord1 Set where liftCompare = genericLiftCompare
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Set
-- TODO: Implement Eval instance for Set -- TODO: Implement Eval instance for Set
instance Evaluatable Set instance Evaluatable Set
@ -263,28 +221,24 @@ instance Evaluatable Set
-- | A declared pointer (e.g. var pointer *int in Go) -- | A declared pointer (e.g. var pointer *int in Go)
newtype Pointer a = Pointer a 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 Eq1 Pointer where liftEq = genericLiftEq
instance Ord1 Pointer where liftCompare = genericLiftCompare instance Ord1 Pointer where liftCompare = genericLiftCompare
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Pointer
-- TODO: Implement Eval instance for Pointer -- TODO: Implement Eval instance for Pointer
instance Evaluatable Pointer instance Evaluatable Pointer
-- | A reference to a pointer's address (e.g. &pointer in Go) -- | A reference to a pointer's address (e.g. &pointer in Go)
newtype Reference a = Reference a 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 Eq1 Reference where liftEq = genericLiftEq
instance Ord1 Reference where liftCompare = genericLiftCompare instance Ord1 Reference where liftCompare = genericLiftCompare
instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Reference
-- TODO: Implement Eval instance for Reference -- TODO: Implement Eval instance for Reference
instance Evaluatable Reference instance Evaluatable Reference

View File

@ -2,22 +2,38 @@
module Data.Syntax.Statement where module Data.Syntax.Statement where
import Data.Abstract.Evaluatable import Data.Abstract.Evaluatable
import Data.ByteString.Char8 (unpack) import Data.Aeson (ToJSON1 (..))
import Data.JSON.Fields import Data.JSON.Fields
import Data.Semigroup.App
import Data.Semigroup.Foldable
import Diffing.Algorithm import Diffing.Algorithm
import Prelude import Prelude
import Prologue import Prologue
-- | Imperative sequence of statements/declarations s.t.:
--
-- 1. Each statements effects on the store are accumulated;
-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and
-- 3. Only the last statements return value is returned.
newtype Statements a = Statements [a]
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Statements where liftEq = genericLiftEq
instance Ord1 Statements where liftCompare = genericLiftCompare
instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec
instance ToJSON1 Statements
instance Evaluatable Statements where
eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs)
-- | 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. -- | 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 } 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 Eq1 If where liftEq = genericLiftEq
instance Ord1 If where liftCompare = genericLiftCompare instance Ord1 If where liftCompare = genericLiftCompare
instance Show1 If where liftShowsPrec = genericLiftShowsPrec instance Show1 If where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 If
instance Evaluatable If where instance Evaluatable If where
eval (If cond if' else') = do eval (If cond if' else') = do
bool <- subtermValue cond bool <- subtermValue cond
@ -25,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. -- | 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 } 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 Eq1 Else where liftEq = genericLiftEq
instance Ord1 Else where liftCompare = genericLiftCompare instance Ord1 Else where liftCompare = genericLiftCompare
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Else
-- TODO: Implement Eval instance for Else -- TODO: Implement Eval instance for Else
instance Evaluatable Else instance Evaluatable Else
@ -40,56 +54,48 @@ instance Evaluatable Else
-- | Goto statement (e.g. `goto a` in Go). -- | Goto statement (e.g. `goto a` in Go).
newtype Goto a = Goto { gotoLocation :: a } 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 Eq1 Goto where liftEq = genericLiftEq
instance Ord1 Goto where liftCompare = genericLiftCompare instance Ord1 Goto where liftCompare = genericLiftCompare
instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Goto
-- TODO: Implement Eval instance for Goto -- TODO: Implement Eval instance for Goto
instance Evaluatable 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. -- | 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 } 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 Eq1 Match where liftEq = genericLiftEq
instance Ord1 Match where liftCompare = genericLiftCompare instance Ord1 Match where liftCompare = genericLiftCompare
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Match
-- TODO: Implement Eval instance for Match -- TODO: Implement Eval instance for Match
instance Evaluatable 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. -- | 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 } 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 Eq1 Pattern where liftEq = genericLiftEq
instance Ord1 Pattern where liftCompare = genericLiftCompare instance Ord1 Pattern where liftCompare = genericLiftCompare
instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Pattern
-- TODO: Implement Eval instance for Pattern -- TODO: Implement Eval instance for Pattern
instance Evaluatable Pattern instance Evaluatable Pattern
-- | A let statement or local binding, like 'a as b' or 'let a = b'. -- | A let statement or local binding, like 'a as b' or 'let a = b'.
data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a } 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 Eq1 Let where liftEq = genericLiftEq
instance Ord1 Let where liftCompare = genericLiftCompare instance Ord1 Let where liftCompare = genericLiftCompare
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Let
instance Evaluatable Let where instance Evaluatable Let where
eval Let{..} = do eval Let{..} = do
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm letVariable) name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm letVariable)
@ -101,14 +107,12 @@ instance Evaluatable Let where
-- | Assignment to a variable or other lvalue. -- | Assignment to a variable or other lvalue.
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a } 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 Eq1 Assignment where liftEq = genericLiftEq
instance Ord1 Assignment where liftCompare = genericLiftCompare instance Ord1 Assignment where liftCompare = genericLiftCompare
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Assignment
instance Evaluatable Assignment where instance Evaluatable Assignment where
eval Assignment{..} = do eval Assignment{..} = do
lhs <- subtermRef assignmentTarget lhs <- subtermRef assignmentTarget
@ -130,28 +134,24 @@ instance Evaluatable Assignment where
-- | Post increment operator (e.g. 1++ in Go, or i++ in C). -- | Post increment operator (e.g. 1++ in Go, or i++ in C).
newtype PostIncrement a = PostIncrement a 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 Eq1 PostIncrement where liftEq = genericLiftEq
instance Ord1 PostIncrement where liftCompare = genericLiftCompare instance Ord1 PostIncrement where liftCompare = genericLiftCompare
instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 PostIncrement
-- TODO: Implement Eval instance for PostIncrement -- TODO: Implement Eval instance for PostIncrement
instance Evaluatable PostIncrement instance Evaluatable PostIncrement
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C). -- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
newtype PostDecrement a = PostDecrement a 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 Eq1 PostDecrement where liftEq = genericLiftEq
instance Ord1 PostDecrement where liftCompare = genericLiftCompare instance Ord1 PostDecrement where liftCompare = genericLiftCompare
instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 PostDecrement
-- TODO: Implement Eval instance for PostDecrement -- TODO: Implement Eval instance for PostDecrement
instance Evaluatable PostDecrement instance Evaluatable PostDecrement
@ -182,181 +182,153 @@ instance Evaluatable PreDecrement
-- Returns -- Returns
newtype Return a = Return a 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 Eq1 Return where liftEq = genericLiftEq
instance Ord1 Return where liftCompare = genericLiftCompare instance Ord1 Return where liftCompare = genericLiftCompare
instance Show1 Return where liftShowsPrec = genericLiftShowsPrec instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Return
instance Evaluatable Return where instance Evaluatable Return where
eval (Return x) = Rval <$> (subtermValue x >>= earlyReturn) eval (Return x) = Rval <$> (subtermValue x >>= earlyReturn)
newtype Yield a = Yield a 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 Eq1 Yield where liftEq = genericLiftEq
instance Ord1 Yield where liftCompare = genericLiftCompare instance Ord1 Yield where liftCompare = genericLiftCompare
instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Yield
-- TODO: Implement Eval instance for Yield -- TODO: Implement Eval instance for Yield
instance Evaluatable Yield instance Evaluatable Yield
newtype Break a = Break a 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 Eq1 Break where liftEq = genericLiftEq
instance Ord1 Break where liftCompare = genericLiftCompare instance Ord1 Break where liftCompare = genericLiftCompare
instance Show1 Break where liftShowsPrec = genericLiftShowsPrec instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Break
instance Evaluatable Break where instance Evaluatable Break where
eval (Break x) = Rval <$> (subtermValue x >>= throwBreak) eval (Break x) = Rval <$> (subtermValue x >>= throwBreak)
newtype Continue a = Continue a 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 Eq1 Continue where liftEq = genericLiftEq
instance Ord1 Continue where liftCompare = genericLiftCompare instance Ord1 Continue where liftCompare = genericLiftCompare
instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Continue
instance Evaluatable Continue where instance Evaluatable Continue where
eval (Continue a) = Rval <$> (subtermValue a >>= throwContinue) eval (Continue a) = Rval <$> (subtermValue a >>= throwContinue)
newtype Retry a = Retry a 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 Eq1 Retry where liftEq = genericLiftEq
instance Ord1 Retry where liftCompare = genericLiftCompare instance Ord1 Retry where liftCompare = genericLiftCompare
instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Retry
-- TODO: Implement Eval instance for Retry -- TODO: Implement Eval instance for Retry
instance Evaluatable Retry instance Evaluatable Retry
newtype NoOp a = NoOp a 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 Eq1 NoOp where liftEq = genericLiftEq
instance Ord1 NoOp where liftCompare = genericLiftCompare instance Ord1 NoOp where liftCompare = genericLiftCompare
instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 NoOp
instance Evaluatable NoOp where instance Evaluatable NoOp where
eval _ = pure (Rval unit) eval _ = pure (Rval unit)
-- Loops -- Loops
data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a } 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 Eq1 For where liftEq = genericLiftEq
instance Ord1 For where liftCompare = genericLiftCompare instance Ord1 For where liftCompare = genericLiftCompare
instance Show1 For where liftShowsPrec = genericLiftShowsPrec instance Show1 For where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 For
instance Evaluatable For where instance Evaluatable For where
eval (fmap subtermValue -> For before cond step body) = Rval <$> forLoop before cond step body eval (fmap subtermValue -> For before cond step body) = Rval <$> forLoop before cond step body
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a } 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 Eq1 ForEach where liftEq = genericLiftEq
instance Ord1 ForEach where liftCompare = genericLiftCompare instance Ord1 ForEach where liftCompare = genericLiftCompare
instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ForEach
-- TODO: Implement Eval instance for ForEach -- TODO: Implement Eval instance for ForEach
instance Evaluatable ForEach instance Evaluatable ForEach
data While a = While { whileCondition :: !a, whileBody :: !a } 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 Eq1 While where liftEq = genericLiftEq
instance Ord1 While where liftCompare = genericLiftCompare instance Ord1 While where liftCompare = genericLiftCompare
instance Show1 While where liftShowsPrec = genericLiftShowsPrec instance Show1 While where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 While
instance Evaluatable While where instance Evaluatable While where
eval While{..} = Rval <$> while (subtermValue whileCondition) (subtermValue whileBody) eval While{..} = Rval <$> while (subtermValue whileCondition) (subtermValue whileBody)
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a } 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 Eq1 DoWhile where liftEq = genericLiftEq
instance Ord1 DoWhile where liftCompare = genericLiftCompare instance Ord1 DoWhile where liftCompare = genericLiftCompare
instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 DoWhile
instance Evaluatable DoWhile where instance Evaluatable DoWhile where
eval DoWhile{..} = Rval <$> doWhile (subtermValue doWhileBody) (subtermValue doWhileCondition) eval DoWhile{..} = Rval <$> doWhile (subtermValue doWhileBody) (subtermValue doWhileCondition)
-- Exception handling -- Exception handling
newtype Throw a = Throw a 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 Eq1 Throw where liftEq = genericLiftEq
instance Ord1 Throw where liftCompare = genericLiftCompare instance Ord1 Throw where liftCompare = genericLiftCompare
instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Throw
-- TODO: Implement Eval instance for Throw -- TODO: Implement Eval instance for Throw
instance Evaluatable Throw instance Evaluatable Throw
data Try a = Try { tryBody :: !a, tryCatch :: ![a] } 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 Eq1 Try where liftEq = genericLiftEq
instance Ord1 Try where liftCompare = genericLiftCompare instance Ord1 Try where liftCompare = genericLiftCompare
instance Show1 Try where liftShowsPrec = genericLiftShowsPrec instance Show1 Try where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Try
-- TODO: Implement Eval instance for Try -- TODO: Implement Eval instance for Try
instance Evaluatable Try instance Evaluatable Try
data Catch a = Catch { catchException :: !a, catchBody :: !a } 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 Eq1 Catch where liftEq = genericLiftEq
instance Ord1 Catch where liftCompare = genericLiftCompare instance Ord1 Catch where liftCompare = genericLiftCompare
instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Catch
-- TODO: Implement Eval instance for Catch -- TODO: Implement Eval instance for Catch
instance Evaluatable Catch instance Evaluatable Catch
newtype Finally a = Finally a 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 Eq1 Finally where liftEq = genericLiftEq
instance Ord1 Finally where liftCompare = genericLiftCompare instance Ord1 Finally where liftCompare = genericLiftCompare
instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Finally
-- TODO: Implement Eval instance for Finally -- TODO: Implement Eval instance for Finally
instance Evaluatable Finally instance Evaluatable Finally
@ -365,41 +337,34 @@ instance Evaluatable Finally
-- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl). -- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl).
newtype ScopeEntry a = ScopeEntry [a] 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 Eq1 ScopeEntry where liftEq = genericLiftEq
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ScopeEntry
-- TODO: Implement Eval instance for ScopeEntry -- TODO: Implement Eval instance for ScopeEntry
instance Evaluatable ScopeEntry instance Evaluatable ScopeEntry
-- | ScopeExit (e.g. `END {}` block in Ruby or Perl). -- | ScopeExit (e.g. `END {}` block in Ruby or Perl).
newtype ScopeExit a = ScopeExit [a] 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 Eq1 ScopeExit where liftEq = genericLiftEq
instance Ord1 ScopeExit where liftCompare = genericLiftCompare instance Ord1 ScopeExit where liftCompare = genericLiftCompare
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ScopeExit
-- TODO: Implement Eval instance for ScopeExit -- TODO: Implement Eval instance for ScopeExit
instance Evaluatable ScopeExit instance Evaluatable ScopeExit
-- | HashBang line (e.g. `#!/usr/bin/env node`) -- | HashBang line (e.g. `#!/usr/bin/env node`)
newtype HashBang a = HashBang ByteString 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 Eq1 HashBang where liftEq = genericLiftEq
instance Ord1 HashBang where liftCompare = genericLiftCompare instance Ord1 HashBang where liftCompare = genericLiftCompare
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 HashBang where
toJSONFields1 (HashBang f) = noChildren [ "contents" .= unpack f ]
-- TODO: Implement Eval instance for HashBang -- TODO: Implement Eval instance for HashBang
instance Evaluatable HashBang instance Evaluatable HashBang

View File

@ -8,146 +8,124 @@ import Prelude hiding (Int, Float, Bool)
import Prologue hiding (Map) import Prologue hiding (Map)
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a } 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 Eq1 Array where liftEq = genericLiftEq
instance Ord1 Array where liftCompare = genericLiftCompare instance Ord1 Array where liftCompare = genericLiftCompare
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Array
-- TODO: Implement Eval instance for Array -- TODO: Implement Eval instance for Array
instance Evaluatable Array instance Evaluatable Array
-- TODO: What about type variables? re: FreeVariables1 -- TODO: What about type variables? re: FreeVariables1
data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a } 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 Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare instance Ord1 Annotation where liftCompare = genericLiftCompare
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec 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 -- TODO: Specialize Evaluatable for Type to unify the inferred type of the subject with the specified type
instance Evaluatable Annotation where instance Evaluatable Annotation where
eval Annotation{annotationSubject = Subterm _ action} = action eval Annotation{annotationSubject = Subterm _ action} = action
data Function a = Function { functionParameters :: ![a], functionReturn :: !a } 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 Eq1 Function where liftEq = genericLiftEq
instance Ord1 Function where liftCompare = genericLiftCompare instance Ord1 Function where liftCompare = genericLiftCompare
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Function
-- TODO: Implement Eval instance for Function -- TODO: Implement Eval instance for Function
instance Evaluatable Function instance Evaluatable Function
newtype Interface a = Interface [a] 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 Eq1 Interface where liftEq = genericLiftEq
instance Ord1 Interface where liftCompare = genericLiftCompare instance Ord1 Interface where liftCompare = genericLiftCompare
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Interface
-- TODO: Implement Eval instance for Interface -- TODO: Implement Eval instance for Interface
instance Evaluatable Interface instance Evaluatable Interface
data Map a = Map { mapKeyType :: !a, mapElementType :: !a } 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 Eq1 Map where liftEq = genericLiftEq
instance Ord1 Map where liftCompare = genericLiftCompare instance Ord1 Map where liftCompare = genericLiftCompare
instance Show1 Map where liftShowsPrec = genericLiftShowsPrec instance Show1 Map where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Map
-- TODO: Implement Eval instance for Map -- TODO: Implement Eval instance for Map
instance Evaluatable Map instance Evaluatable Map
newtype Parenthesized a = Parenthesized a 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 Eq1 Parenthesized where liftEq = genericLiftEq
instance Ord1 Parenthesized where liftCompare = genericLiftCompare instance Ord1 Parenthesized where liftCompare = genericLiftCompare
instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Parenthesized
-- TODO: Implement Eval instance for Parenthesized -- TODO: Implement Eval instance for Parenthesized
instance Evaluatable Parenthesized instance Evaluatable Parenthesized
newtype Pointer a = Pointer a 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 Eq1 Pointer where liftEq = genericLiftEq
instance Ord1 Pointer where liftCompare = genericLiftCompare instance Ord1 Pointer where liftCompare = genericLiftCompare
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Pointer
-- TODO: Implement Eval instance for Pointer -- TODO: Implement Eval instance for Pointer
instance Evaluatable Pointer instance Evaluatable Pointer
newtype Product a = Product [a] 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 Eq1 Product where liftEq = genericLiftEq
instance Ord1 Product where liftCompare = genericLiftCompare instance Ord1 Product where liftCompare = genericLiftCompare
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Product
-- TODO: Implement Eval instance for Product -- TODO: Implement Eval instance for Product
instance Evaluatable Product instance Evaluatable Product
data Readonly a = Readonly 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 Eq1 Readonly where liftEq = genericLiftEq
instance Ord1 Readonly where liftCompare = genericLiftCompare instance Ord1 Readonly where liftCompare = genericLiftCompare
instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Readonly
-- TODO: Implement Eval instance for Readonly -- TODO: Implement Eval instance for Readonly
instance Evaluatable Readonly instance Evaluatable Readonly
newtype Slice a = Slice a 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 Eq1 Slice where liftEq = genericLiftEq
instance Ord1 Slice where liftCompare = genericLiftCompare instance Ord1 Slice where liftCompare = genericLiftCompare
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Slice
-- TODO: Implement Eval instance for Slice -- TODO: Implement Eval instance for Slice
instance Evaluatable Slice instance Evaluatable Slice
newtype TypeParameters a = TypeParameters [a] 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 Eq1 TypeParameters where liftEq = genericLiftEq
instance Ord1 TypeParameters where liftCompare = genericLiftCompare instance Ord1 TypeParameters where liftCompare = genericLiftCompare
instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeParameters
-- TODO: Implement Eval instance for TypeParameters -- TODO: Implement Eval instance for TypeParameters
instance Evaluatable TypeParameters instance Evaluatable TypeParameters

View File

@ -86,11 +86,11 @@ type Syntax =
, Statement.NoOp , Statement.NoOp
, Statement.Pattern , Statement.Pattern
, Statement.Return , Statement.Return
, Statement.Statements
, Syntax.Context , Syntax.Context
, Syntax.Error , Syntax.Error
, Syntax.Empty , Syntax.Empty
, Syntax.Identifier , Syntax.Identifier
, Syntax.Program
, Type.Annotation , Type.Annotation
, Type.Array , Type.Array
, Type.Function , Type.Function
@ -111,7 +111,7 @@ assignment :: Assignment
assignment = handleError program <|> parseError assignment = handleError program <|> parseError
program :: Assignment program :: Assignment
program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyTerm expression) program = makeTerm <$> symbol SourceFile <*> children (Statement.Statements <$> manyTerm expression)
expression :: Assignment expression :: Assignment
expression = term (handleError (choice expressionChoices)) expression = term (handleError (choice expressionChoices))

View File

@ -57,14 +57,12 @@ resolveGoImport (ImportPath path NonRelative) = do
-- --
-- If the list of symbols is empty copy everything to the calling environment. -- If the list of symbols is empty copy everything to the calling environment.
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a } 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 Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare instance Ord1 Import where liftCompare = genericLiftCompare
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Import
instance Evaluatable Import where instance Evaluatable Import where
eval (Import importPath _) = do eval (Import importPath _) = do
paths <- resolveGoImport importPath 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. -- If the list of symbols is empty copy and qualify everything to the calling environment.
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a} 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 Eq1 QualifiedImport where liftEq = genericLiftEq
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 QualifiedImport
instance Evaluatable QualifiedImport where instance Evaluatable QualifiedImport where
eval (QualifiedImport importPath aliasTerm) = do eval (QualifiedImport importPath aliasTerm) = do
paths <- resolveGoImport importPath paths <- resolveGoImport importPath
@ -101,14 +97,12 @@ instance Evaluatable QualifiedImport where
-- | Side effect only imports (no symbols made available to the calling environment). -- | Side effect only imports (no symbols made available to the calling environment).
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a } 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 Eq1 SideEffectImport where liftEq = genericLiftEq
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 SideEffectImport
instance Evaluatable SideEffectImport where instance Evaluatable SideEffectImport where
eval (SideEffectImport importPath _) = do eval (SideEffectImport importPath _) = do
paths <- resolveGoImport importPath paths <- resolveGoImport importPath
@ -118,74 +112,62 @@ instance Evaluatable SideEffectImport where
-- A composite literal in Go -- A composite literal in Go
data Composite a = Composite { compositeType :: !a, compositeElement :: !a } 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 Eq1 Composite where liftEq = genericLiftEq
instance Ord1 Composite where liftCompare = genericLiftCompare instance Ord1 Composite where liftCompare = genericLiftCompare
instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Composite
-- TODO: Implement Eval instance for Composite -- TODO: Implement Eval instance for Composite
instance Evaluatable Composite instance Evaluatable Composite
-- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`). -- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`).
newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a } 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 Eq1 DefaultPattern where liftEq = genericLiftEq
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 DefaultPattern
-- TODO: Implement Eval instance for DefaultPattern -- TODO: Implement Eval instance for DefaultPattern
instance Evaluatable DefaultPattern instance Evaluatable DefaultPattern
-- | A defer statement in Go (e.g. `defer x()`). -- | A defer statement in Go (e.g. `defer x()`).
newtype Defer a = Defer { deferBody :: a } 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 Eq1 Defer where liftEq = genericLiftEq
instance Ord1 Defer where liftCompare = genericLiftCompare instance Ord1 Defer where liftCompare = genericLiftCompare
instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Defer
-- TODO: Implement Eval instance for Defer -- TODO: Implement Eval instance for Defer
instance Evaluatable Defer instance Evaluatable Defer
-- | A go statement (i.e. go routine) in Go (e.g. `go x()`). -- | A go statement (i.e. go routine) in Go (e.g. `go x()`).
newtype Go a = Go { goBody :: a } 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 Eq1 Go where liftEq = genericLiftEq
instance Ord1 Go where liftCompare = genericLiftCompare instance Ord1 Go where liftCompare = genericLiftCompare
instance Show1 Go where liftShowsPrec = genericLiftShowsPrec instance Show1 Go where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Go
-- TODO: Implement Eval instance for Go -- TODO: Implement Eval instance for Go
instance Evaluatable Go instance Evaluatable Go
-- | A label statement in Go (e.g. `label:continue`). -- | A label statement in Go (e.g. `label:continue`).
data Label a = Label { _labelName :: !a, labelStatement :: !a } 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 Eq1 Label where liftEq = genericLiftEq
instance Ord1 Label where liftCompare = genericLiftCompare instance Ord1 Label where liftCompare = genericLiftCompare
instance Show1 Label where liftShowsPrec = genericLiftShowsPrec instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Label
-- TODO: Implement Eval instance for Label -- TODO: Implement Eval instance for Label
instance Evaluatable Label instance Evaluatable Label
-- | A rune literal in Go (e.g. `'⌘'`). -- | A rune literal in Go (e.g. `'⌘'`).
newtype Rune a = Rune { _runeLiteral :: ByteString } newtype Rune a = Rune { _runeLiteral :: ByteString }
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 ToJSONFields1 Rune
-- TODO: Implement Eval instance for Rune -- TODO: Implement Eval instance for Rune
instance Evaluatable 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). -- | 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 } newtype Select a = Select { selectCases :: 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 ToJSONFields1 Select
-- TODO: Implement Eval instance for Select -- TODO: Implement Eval instance for Select
instance Evaluatable Select instance Evaluatable Select
@ -209,144 +189,122 @@ instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
-- | A send statement in Go (e.g. `channel <- value`). -- | A send statement in Go (e.g. `channel <- value`).
data Send a = Send { sendReceiver :: !a, sendValue :: !a } 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 Eq1 Send where liftEq = genericLiftEq
instance Ord1 Send where liftCompare = genericLiftCompare instance Ord1 Send where liftCompare = genericLiftCompare
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Send
-- TODO: Implement Eval instance for Send -- TODO: Implement Eval instance for Send
instance Evaluatable 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). -- | 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 } 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 Eq1 Slice where liftEq = genericLiftEq
instance Ord1 Slice where liftCompare = genericLiftCompare instance Ord1 Slice where liftCompare = genericLiftCompare
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Slice
-- TODO: Implement Eval instance for Slice -- TODO: Implement Eval instance for Slice
instance Evaluatable Slice instance Evaluatable Slice
-- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`). -- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`).
data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a } 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 Eq1 TypeSwitch where liftEq = genericLiftEq
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeSwitch
-- TODO: Implement Eval instance for TypeSwitch -- TODO: Implement Eval instance for TypeSwitch
instance Evaluatable TypeSwitch instance Evaluatable TypeSwitch
-- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`). -- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`).
newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a } 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 Eq1 TypeSwitchGuard where liftEq = genericLiftEq
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeSwitchGuard
-- TODO: Implement Eval instance for TypeSwitchGuard -- TODO: Implement Eval instance for TypeSwitchGuard
instance Evaluatable TypeSwitchGuard instance Evaluatable TypeSwitchGuard
-- | A receive statement in a Go select statement (e.g. `case value := <-channel` ) -- | A receive statement in a Go select statement (e.g. `case value := <-channel` )
data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a } 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 Eq1 Receive where liftEq = genericLiftEq
instance Ord1 Receive where liftCompare = genericLiftCompare instance Ord1 Receive where liftCompare = genericLiftCompare
instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Receive
-- TODO: Implement Eval instance for Receive -- TODO: Implement Eval instance for Receive
instance Evaluatable Receive instance Evaluatable Receive
-- | A receive operator unary expression in Go (e.g. `<-channel` ) -- | A receive operator unary expression in Go (e.g. `<-channel` )
newtype ReceiveOperator a = ReceiveOperator a 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 Eq1 ReceiveOperator where liftEq = genericLiftEq
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ReceiveOperator
-- TODO: Implement Eval instance for ReceiveOperator -- TODO: Implement Eval instance for ReceiveOperator
instance Evaluatable ReceiveOperator instance Evaluatable ReceiveOperator
-- | A field declaration in a Go struct type declaration. -- | A field declaration in a Go struct type declaration.
data Field a = Field { fieldContext :: ![a], fieldName :: !a } 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 Eq1 Field where liftEq = genericLiftEq
instance Ord1 Field where liftCompare = genericLiftCompare instance Ord1 Field where liftCompare = genericLiftCompare
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Field
-- TODO: Implement Eval instance for Field -- TODO: Implement Eval instance for Field
instance Evaluatable Field instance Evaluatable Field
data Package a = Package { packageName :: !a, packageContents :: ![a] } 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 Eq1 Package where liftEq = genericLiftEq
instance Ord1 Package where liftCompare = genericLiftCompare instance Ord1 Package where liftCompare = genericLiftCompare
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Package
instance Evaluatable Package where instance Evaluatable Package where
eval (Package _ xs) = eval xs 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`). -- | 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 } 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 Eq1 TypeAssertion where liftEq = genericLiftEq
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeAssertion
-- TODO: Implement Eval instance for TypeAssertion -- TODO: Implement Eval instance for TypeAssertion
instance Evaluatable 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`). -- | 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 } 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 Eq1 TypeConversion where liftEq = genericLiftEq
instance Ord1 TypeConversion where liftCompare = genericLiftCompare instance Ord1 TypeConversion where liftCompare = genericLiftCompare
instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeConversion
-- TODO: Implement Eval instance for TypeConversion -- TODO: Implement Eval instance for TypeConversion
instance Evaluatable TypeConversion instance Evaluatable TypeConversion
-- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`). -- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`).
data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a } 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 Eq1 Variadic where liftEq = genericLiftEq
instance Ord1 Variadic where liftCompare = genericLiftCompare instance Ord1 Variadic where liftCompare = genericLiftCompare
instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Variadic
-- TODO: Implement Eval instance for Variadic -- TODO: Implement Eval instance for Variadic
instance Evaluatable Variadic instance Evaluatable Variadic

View File

@ -8,39 +8,33 @@ import Diffing.Algorithm
-- | A Bidirectional channel in Go (e.g. `chan`). -- | A Bidirectional channel in Go (e.g. `chan`).
newtype BidirectionalChannel a = BidirectionalChannel a 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 Eq1 BidirectionalChannel where liftEq = genericLiftEq
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 BidirectionalChannel
-- TODO: Implement Eval instance for BidirectionalChannel -- TODO: Implement Eval instance for BidirectionalChannel
instance Evaluatable BidirectionalChannel instance Evaluatable BidirectionalChannel
-- | A Receive channel in Go (e.g. `<-chan`). -- | A Receive channel in Go (e.g. `<-chan`).
newtype ReceiveChannel a = ReceiveChannel a 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 Eq1 ReceiveChannel where liftEq = genericLiftEq
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ReceiveChannel
-- TODO: Implement Eval instance for ReceiveChannel -- TODO: Implement Eval instance for ReceiveChannel
instance Evaluatable ReceiveChannel instance Evaluatable ReceiveChannel
-- | A Send channel in Go (e.g. `chan<-`). -- | A Send channel in Go (e.g. `chan<-`).
newtype SendChannel a = SendChannel a 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 Eq1 SendChannel where liftEq = genericLiftEq
instance Ord1 SendChannel where liftCompare = genericLiftCompare instance Ord1 SendChannel where liftCompare = genericLiftCompare
instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 SendChannel
-- TODO: Implement Eval instance for SendChannel -- TODO: Implement Eval instance for SendChannel
instance Evaluatable SendChannel instance Evaluatable SendChannel

View File

@ -11,14 +11,12 @@ data Module a = Module { moduleIdentifier :: !a
, moduleExports :: ![a] , moduleExports :: ![a]
, moduleStatements :: !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 Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Module
instance Evaluatable Module instance Evaluatable Module
data StrictType a = StrictType { strictTypeIdentifier :: !a, strictTypeParameters :: !a } data StrictType a = StrictType { strictTypeIdentifier :: !a, strictTypeParameters :: !a }
@ -44,65 +42,53 @@ instance ToJSONFields1 StrictTypeVariable
instance Evaluatable StrictTypeVariable instance Evaluatable StrictTypeVariable
data Type a = Type { typeIdentifier :: !a, typeParameters :: !a } 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 Eq1 Type where liftEq = genericLiftEq
instance Ord1 Type where liftCompare = genericLiftCompare instance Ord1 Type where liftCompare = genericLiftCompare
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Type
instance Evaluatable Type instance Evaluatable Type
data TypeSynonym a = TypeSynonym { typeSynonymLeft :: !a, typeSynonymRight :: !a } 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 Eq1 TypeSynonym where liftEq = genericLiftEq
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TypeSynonym
instance Evaluatable 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 Eq1 UnitConstructor where liftEq = genericLiftEq
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 UnitConstructor
instance Evaluatable 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 Eq1 TupleConstructor where liftEq = genericLiftEq
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 TupleConstructor
instance Evaluatable 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 Eq1 ListConstructor where liftEq = genericLiftEq
instance Ord1 ListConstructor where liftCompare = genericLiftCompare instance Ord1 ListConstructor where liftCompare = genericLiftCompare
instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ListConstructor
instance Evaluatable 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 Eq1 FunctionConstructor where liftEq = genericLiftEq
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 FunctionConstructor
instance Evaluatable FunctionConstructor instance Evaluatable FunctionConstructor
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorName :: !a, recordDataConstructorFields :: !a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorName :: !a, recordDataConstructorFields :: !a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)

View File

@ -80,6 +80,7 @@ type Syntax =
, Statement.PreIncrement , Statement.PreIncrement
, Statement.PreDecrement , Statement.PreDecrement
, Statement.While , Statement.While
, Statement.Statements
, Statement.Throw , Statement.Throw
, Statement.Try , Statement.Try
, Syntax.Context , Syntax.Context
@ -87,7 +88,6 @@ type Syntax =
, Syntax.Error , Syntax.Error
, Syntax.Identifier , Syntax.Identifier
, Syntax.AccessibilityModifier , Syntax.AccessibilityModifier
, Syntax.Program
, Type.Array , Type.Array
, Type.Bool , Type.Bool
, Type.Int , Type.Int
@ -103,7 +103,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
-- | Assignment from AST in Java's grammar onto a program in Java's syntax. -- | Assignment from AST in Java's grammar onto a program in Java's syntax.
assignment :: Assignment assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syntax.Program <$> manyTerm expression) <|> parseError assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Statement.Statements <$> manyTerm expression) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. -- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]

View File

@ -2,14 +2,11 @@
module Language.Markdown.Syntax where module Language.Markdown.Syntax where
import Prologue hiding (Text) import Prologue hiding (Text)
import Data.ByteString.Char8 (unpack)
import Data.JSON.Fields import Data.JSON.Fields
import Diffing.Algorithm import Diffing.Algorithm
newtype Document a = Document [a] newtype Document a = Document [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 ToJSONFields1 Document
instance Eq1 Document where liftEq = genericLiftEq instance Eq1 Document where liftEq = genericLiftEq
instance Ord1 Document where liftCompare = genericLiftCompare instance Ord1 Document where liftCompare = genericLiftCompare
@ -19,91 +16,70 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
-- Block elements -- Block elements
newtype Paragraph a = Paragraph [a] newtype Paragraph a = Paragraph [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 ToJSONFields1 Paragraph
instance Eq1 Paragraph where liftEq = genericLiftEq instance Eq1 Paragraph where liftEq = genericLiftEq
instance Ord1 Paragraph where liftCompare = genericLiftCompare instance Ord1 Paragraph where liftCompare = genericLiftCompare
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] } data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [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 ToJSONFields1 Heading
instance Eq1 Heading where liftEq = genericLiftEq instance Eq1 Heading where liftEq = genericLiftEq
instance Ord1 Heading where liftCompare = genericLiftCompare instance Ord1 Heading where liftCompare = genericLiftCompare
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
newtype UnorderedList a = UnorderedList [a] newtype UnorderedList a = UnorderedList [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 ToJSONFields1 UnorderedList
instance Eq1 UnorderedList where liftEq = genericLiftEq instance Eq1 UnorderedList where liftEq = genericLiftEq
instance Ord1 UnorderedList where liftCompare = genericLiftCompare instance Ord1 UnorderedList where liftCompare = genericLiftCompare
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 OrderedList
newtype OrderedList a = OrderedList [a] 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 Eq1 OrderedList where liftEq = genericLiftEq
instance Ord1 OrderedList where liftCompare = genericLiftCompare instance Ord1 OrderedList where liftCompare = genericLiftCompare
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 BlockQuote
newtype BlockQuote a = BlockQuote [a] 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 Eq1 BlockQuote where liftEq = genericLiftEq
instance Ord1 BlockQuote where liftCompare = genericLiftCompare instance Ord1 BlockQuote where liftCompare = genericLiftCompare
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 ThematicBreak
data ThematicBreak a = 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 Eq1 ThematicBreak where liftEq = genericLiftEq
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 HTMLBlock where
toJSONFields1 (HTMLBlock b) = noChildren [ "asString" .= unpack b ]
newtype HTMLBlock a = HTMLBlock ByteString 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 Eq1 HTMLBlock where liftEq = genericLiftEq
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
newtype Table a = Table [a] newtype Table a = Table [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 ToJSONFields1 Table
instance Eq1 Table where liftEq = genericLiftEq instance Eq1 Table where liftEq = genericLiftEq
instance Ord1 Table where liftCompare = genericLiftCompare instance Ord1 Table where liftCompare = genericLiftCompare
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
newtype TableRow a = TableRow [a] newtype TableRow a = TableRow [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 ToJSONFields1 TableRow
instance Eq1 TableRow where liftEq = genericLiftEq instance Eq1 TableRow where liftEq = genericLiftEq
instance Ord1 TableRow where liftCompare = genericLiftCompare instance Ord1 TableRow where liftCompare = genericLiftCompare
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
newtype TableCell a = TableCell [a] newtype TableCell a = TableCell [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 ToJSONFields1 TableCell
instance Eq1 TableCell where liftEq = genericLiftEq instance Eq1 TableCell where liftEq = genericLiftEq
instance Ord1 TableCell where liftCompare = genericLiftCompare instance Ord1 TableCell where liftCompare = genericLiftCompare
@ -113,76 +89,56 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
-- Inline elements -- Inline elements
newtype Strong a = Strong [a] newtype Strong a = Strong [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 ToJSONFields1 Strong
instance Eq1 Strong where liftEq = genericLiftEq instance Eq1 Strong where liftEq = genericLiftEq
instance Ord1 Strong where liftCompare = genericLiftCompare instance Ord1 Strong where liftCompare = genericLiftCompare
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
newtype Emphasis a = Emphasis [a] newtype Emphasis a = Emphasis [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 ToJSONFields1 Emphasis
instance Eq1 Emphasis where liftEq = genericLiftEq instance Eq1 Emphasis where liftEq = genericLiftEq
instance Ord1 Emphasis where liftCompare = genericLiftCompare instance Ord1 Emphasis where liftCompare = genericLiftCompare
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
newtype Text a = Text ByteString newtype Text a = Text 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 ToJSONFields1 Text where
toJSONFields1 (Text s) = noChildren ["asString" .= unpack s ]
instance Eq1 Text where liftEq = genericLiftEq instance Eq1 Text where liftEq = genericLiftEq
instance Ord1 Text where liftCompare = genericLiftCompare instance Ord1 Text where liftCompare = genericLiftCompare
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString } data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
-- TODO: Better ToJSONFields1 instance
instance ToJSONFields1 Link
instance Eq1 Link where liftEq = genericLiftEq instance Eq1 Link where liftEq = genericLiftEq
instance Ord1 Link where liftCompare = genericLiftCompare instance Ord1 Link where liftCompare = genericLiftCompare
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString } data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
-- TODO: Better ToJSONFields1 instance
instance ToJSONFields1 Image
instance Eq1 Image where liftEq = genericLiftEq instance Eq1 Image where liftEq = genericLiftEq
instance Ord1 Image where liftCompare = genericLiftCompare instance Ord1 Image where liftCompare = genericLiftCompare
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString } data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
-- TODO: Better ToJSONFields1 instance
instance ToJSONFields1 Code
instance Eq1 Code where liftEq = genericLiftEq instance Eq1 Code where liftEq = genericLiftEq
instance Ord1 Code where liftCompare = genericLiftCompare instance Ord1 Code where liftCompare = genericLiftCompare
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
data LineBreak a = LineBreak data LineBreak a = LineBreak
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance ToJSONFields1 LineBreak
instance Eq1 LineBreak where liftEq = genericLiftEq instance Eq1 LineBreak where liftEq = genericLiftEq
instance Ord1 LineBreak where liftCompare = genericLiftCompare instance Ord1 LineBreak where liftCompare = genericLiftCompare
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Strikethrough
newtype Strikethrough a = Strikethrough [a] 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 Eq1 Strikethrough where liftEq = genericLiftEq
instance Ord1 Strikethrough where liftCompare = genericLiftCompare instance Ord1 Strikethrough where liftCompare = genericLiftCompare

View File

@ -9,7 +9,17 @@ module Language.PHP.Assignment
import Assigning.Assignment hiding (Assignment, Error) import Assigning.Assignment hiding (Assignment, Error)
import Data.Record import Data.Record
import Data.Sum import Data.Sum
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm1, contextualize, postContextualize) import Data.Syntax
( contextualize
, emptyTerm
, handleError
, infixContext
, makeTerm
, makeTerm'
, makeTerm1
, parseError
, postContextualize
)
import Language.PHP.Grammar as Grammar import Language.PHP.Grammar as Grammar
import qualified Assigning.Assignment as Assignment import qualified Assigning.Assignment as Assignment
import qualified Data.Abstract.Name as Name import qualified Data.Abstract.Name as Name
@ -62,6 +72,7 @@ type Syntax = '[
, Statement.Match , Statement.Match
, Statement.Pattern , Statement.Pattern
, Statement.Return , Statement.Return
, Statement.Statements
, Statement.Throw , Statement.Throw
, Statement.Try , Statement.Try
, Statement.While , Statement.While
@ -105,7 +116,6 @@ type Syntax = '[
, Syntax.NamespaceUseGroupClause , Syntax.NamespaceUseGroupClause
, Syntax.NewVariable , Syntax.NewVariable
, Syntax.PrintIntrinsic , Syntax.PrintIntrinsic
, Syntax.Program
, Syntax.PropertyDeclaration , Syntax.PropertyDeclaration
, Syntax.PropertyModifier , Syntax.PropertyModifier
, Syntax.QualifiedName , Syntax.QualifiedName
@ -132,31 +142,9 @@ type Syntax = '[
type Term = Term.Term (Sum Syntax) (Record Location) type Term = Term.Term (Sum Syntax) (Record Location)
type Assignment = Assignment.Assignment [] Grammar Term type Assignment = Assignment.Assignment [] Grammar Term
append :: a -> [a] -> [a]
append x xs = xs ++ [x]
bookend :: a -> [a] -> a -> [a]
bookend head list last = head : append last list
-- | Assignment from AST in PHP's grammar onto a program in PHP's syntax. -- | Assignment from AST in PHP's grammar onto a program in PHP's syntax.
assignment :: Assignment assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError
term :: Assignment -> Assignment
term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term)
commentedTerm :: Assignment -> Assignment
commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm)
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm = many . commentedTerm
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm = fmap NonEmpty.toList . someTerm'
someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term)
someTerm' = NonEmpty.some1 . commentedTerm
text :: Assignment text :: Assignment
text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source) text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source)
@ -754,7 +742,7 @@ functionStaticDeclaration :: Assignment
functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration) functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration)
staticVariableDeclaration :: Assignment staticVariableDeclaration :: Assignment
staticVariableDeclaration = makeTerm <$> symbol StaticVariableDeclaration <*> children (Statement.Assignment <$> pure [] <*> term variableName <*> (term expression <|> emptyTerm)) staticVariableDeclaration = makeTerm <$> symbol StaticVariableDeclaration <*> children (Statement.Assignment [] <$> term variableName <*> (term expression <|> emptyTerm))
comment :: Assignment comment :: Assignment
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
@ -762,6 +750,31 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
string :: Assignment string :: Assignment
string = makeTerm <$> (symbol Grammar.String <|> symbol Heredoc) <*> (Literal.TextElement <$> source) string = makeTerm <$> (symbol Grammar.String <|> symbol Heredoc) <*> (Literal.TextElement <$> source)
-- Helpers
append :: a -> [a] -> [a]
append x xs = xs ++ [x]
bookend :: a -> [a] -> a -> [a]
bookend head list last = head : append last list
term :: Assignment -> Assignment
term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term)
commentedTerm :: Assignment -> Assignment
commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm)
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm = many . commentedTerm
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm = fmap NonEmpty.toList . someTerm'
someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term)
someTerm' = NonEmpty.some1 . commentedTerm
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
infixTerm :: Assignment infixTerm :: Assignment
-> Assignment -> Assignment

View File

@ -12,10 +12,7 @@ import Prelude hiding (fail)
import Prologue hiding (Text) import Prologue hiding (Text)
newtype Text a = Text ByteString newtype Text a = Text ByteString
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 ToJSONFields1 Text where
toJSONFields1 (Text t) = noChildren ["asString" .= BC.unpack t]
instance Eq1 Text where liftEq = genericLiftEq instance Eq1 Text where liftEq = genericLiftEq
instance Ord1 Text where liftCompare = genericLiftCompare instance Ord1 Text where liftCompare = genericLiftCompare
@ -24,9 +21,7 @@ instance Evaluatable Text
newtype VariableName a = VariableName a newtype VariableName a = VariableName 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 ToJSONFields1 VariableName
instance Eq1 VariableName where liftEq = genericLiftEq instance Eq1 VariableName where liftEq = genericLiftEq
instance Ord1 VariableName where liftCompare = genericLiftCompare instance Ord1 VariableName where liftCompare = genericLiftCompare
@ -72,61 +67,51 @@ include pathTerm f = do
pure (Rval v) pure (Rval v)
newtype Require a = Require a 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 Eq1 Require where liftEq = genericLiftEq
instance Ord1 Require where liftCompare = genericLiftCompare instance Ord1 Require where liftCompare = genericLiftCompare
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Require
instance Evaluatable Require where instance Evaluatable Require where
eval (Require path) = include path load eval (Require path) = include path load
newtype RequireOnce a = RequireOnce a 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 Eq1 RequireOnce where liftEq = genericLiftEq
instance Ord1 RequireOnce where liftCompare = genericLiftCompare instance Ord1 RequireOnce where liftCompare = genericLiftCompare
instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 RequireOnce
instance Evaluatable RequireOnce where instance Evaluatable RequireOnce where
eval (RequireOnce path) = include path require eval (RequireOnce path) = include path require
newtype Include a = Include a 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 Eq1 Include where liftEq = genericLiftEq
instance Ord1 Include where liftCompare = genericLiftCompare instance Ord1 Include where liftCompare = genericLiftCompare
instance Show1 Include where liftShowsPrec = genericLiftShowsPrec instance Show1 Include where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Include
instance Evaluatable Include where instance Evaluatable Include where
eval (Include path) = include path load eval (Include path) = include path load
newtype IncludeOnce a = IncludeOnce a 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 Eq1 IncludeOnce where liftEq = genericLiftEq
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 IncludeOnce
instance Evaluatable IncludeOnce where instance Evaluatable IncludeOnce where
eval (IncludeOnce path) = include path require eval (IncludeOnce path) = include path require
newtype ArrayElement a = ArrayElement a newtype ArrayElement a = ArrayElement 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 ToJSONFields1 ArrayElement
instance Eq1 ArrayElement where liftEq = genericLiftEq instance Eq1 ArrayElement where liftEq = genericLiftEq
instance Ord1 ArrayElement where liftCompare = genericLiftCompare instance Ord1 ArrayElement where liftCompare = genericLiftCompare
@ -134,9 +119,7 @@ instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayElement instance Evaluatable ArrayElement
newtype GlobalDeclaration a = GlobalDeclaration [a] newtype GlobalDeclaration a = GlobalDeclaration [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 ToJSONFields1 GlobalDeclaration
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
@ -144,9 +127,7 @@ instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GlobalDeclaration instance Evaluatable GlobalDeclaration
newtype SimpleVariable a = SimpleVariable a newtype SimpleVariable a = SimpleVariable 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 ToJSONFields1 SimpleVariable
instance Eq1 SimpleVariable where liftEq = genericLiftEq instance Eq1 SimpleVariable where liftEq = genericLiftEq
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
@ -156,9 +137,7 @@ instance Evaluatable SimpleVariable
-- | TODO: Unify with TypeScript's PredefinedType -- | TODO: Unify with TypeScript's PredefinedType
newtype CastType a = CastType { _castType :: ByteString } newtype CastType a = CastType { _castType :: ByteString }
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 ToJSONFields1 CastType
instance Eq1 CastType where liftEq = genericLiftEq instance Eq1 CastType where liftEq = genericLiftEq
instance Ord1 CastType where liftCompare = genericLiftCompare instance Ord1 CastType where liftCompare = genericLiftCompare
@ -166,9 +145,7 @@ instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CastType instance Evaluatable CastType
newtype ErrorControl a = ErrorControl a newtype ErrorControl a = ErrorControl 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 ToJSONFields1 ErrorControl
instance Eq1 ErrorControl where liftEq = genericLiftEq instance Eq1 ErrorControl where liftEq = genericLiftEq
instance Ord1 ErrorControl where liftCompare = genericLiftCompare instance Ord1 ErrorControl where liftCompare = genericLiftCompare
@ -176,9 +153,7 @@ instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ErrorControl instance Evaluatable ErrorControl
newtype Clone a = Clone a newtype Clone a = Clone 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 ToJSONFields1 Clone
instance Eq1 Clone where liftEq = genericLiftEq instance Eq1 Clone where liftEq = genericLiftEq
instance Ord1 Clone where liftCompare = genericLiftCompare instance Ord1 Clone where liftCompare = genericLiftCompare
@ -186,9 +161,7 @@ instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Clone instance Evaluatable Clone
newtype ShellCommand a = ShellCommand ByteString newtype ShellCommand a = ShellCommand ByteString
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 ToJSONFields1 ShellCommand
instance Eq1 ShellCommand where liftEq = genericLiftEq instance Eq1 ShellCommand where liftEq = genericLiftEq
instance Ord1 ShellCommand where liftCompare = genericLiftCompare instance Ord1 ShellCommand where liftCompare = genericLiftCompare
@ -197,9 +170,7 @@ instance Evaluatable ShellCommand
-- | TODO: Combine with TypeScript update expression. -- | TODO: Combine with TypeScript update expression.
newtype Update a = Update { _updateSubject :: a } newtype Update a = Update { _updateSubject :: 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 ToJSONFields1 Update
instance Eq1 Update where liftEq = genericLiftEq instance Eq1 Update where liftEq = genericLiftEq
instance Ord1 Update where liftCompare = genericLiftCompare instance Ord1 Update where liftCompare = genericLiftCompare
@ -207,9 +178,7 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Update instance Evaluatable Update
newtype NewVariable a = NewVariable [a] newtype NewVariable a = NewVariable [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 ToJSONFields1 NewVariable
instance Eq1 NewVariable where liftEq = genericLiftEq instance Eq1 NewVariable where liftEq = genericLiftEq
instance Ord1 NewVariable where liftCompare = genericLiftCompare instance Ord1 NewVariable where liftCompare = genericLiftCompare
@ -217,9 +186,7 @@ instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NewVariable instance Evaluatable NewVariable
newtype RelativeScope a = RelativeScope ByteString newtype RelativeScope a = RelativeScope ByteString
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 ToJSONFields1 RelativeScope
instance Eq1 RelativeScope where liftEq = genericLiftEq instance Eq1 RelativeScope where liftEq = genericLiftEq
instance Ord1 RelativeScope where liftCompare = genericLiftCompare instance Ord1 RelativeScope where liftCompare = genericLiftCompare
@ -227,9 +194,7 @@ instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RelativeScope instance Evaluatable RelativeScope
data QualifiedName a = QualifiedName !a !a data QualifiedName a = QualifiedName !a !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 ToJSONFields1 QualifiedName
instance Eq1 QualifiedName where liftEq = genericLiftEq instance Eq1 QualifiedName where liftEq = genericLiftEq
instance Ord1 QualifiedName where liftCompare = genericLiftCompare instance Ord1 QualifiedName where liftCompare = genericLiftCompare
@ -239,9 +204,7 @@ instance Evaluatable QualifiedName where
eval (fmap subtermValue -> QualifiedName name iden) = Rval <$> evaluateInScopedEnv name iden eval (fmap subtermValue -> QualifiedName name iden) = Rval <$> evaluateInScopedEnv name iden
newtype NamespaceName a = NamespaceName (NonEmpty a) newtype NamespaceName a = NamespaceName (NonEmpty a)
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Mergeable, Ord, Show, Traversable) deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance ToJSONFields1 NamespaceName
instance Hashable1 NamespaceName where liftHashWithSalt = foldl instance Hashable1 NamespaceName where liftHashWithSalt = foldl
instance Eq1 NamespaceName where liftEq = genericLiftEq instance Eq1 NamespaceName where liftEq = genericLiftEq
@ -252,9 +215,7 @@ instance Evaluatable NamespaceName where
eval (NamespaceName xs) = Rval <$> foldl1 evaluateInScopedEnv (fmap subtermValue xs) eval (NamespaceName xs) = Rval <$> foldl1 evaluateInScopedEnv (fmap subtermValue xs)
newtype ConstDeclaration a = ConstDeclaration [a] newtype ConstDeclaration a = ConstDeclaration [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 ToJSONFields1 ConstDeclaration
instance Eq1 ConstDeclaration where liftEq = genericLiftEq instance Eq1 ConstDeclaration where liftEq = genericLiftEq
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
@ -262,9 +223,7 @@ instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstDeclaration instance Evaluatable ConstDeclaration
data ClassConstDeclaration a = ClassConstDeclaration a [a] data ClassConstDeclaration a = ClassConstDeclaration a [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 ToJSONFields1 ClassConstDeclaration
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
@ -272,9 +231,7 @@ instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassConstDeclaration instance Evaluatable ClassConstDeclaration
newtype ClassInterfaceClause a = ClassInterfaceClause [a] newtype ClassInterfaceClause a = ClassInterfaceClause [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 ToJSONFields1 ClassInterfaceClause
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
@ -282,9 +239,7 @@ instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassInterfaceClause instance Evaluatable ClassInterfaceClause
newtype ClassBaseClause a = ClassBaseClause a newtype ClassBaseClause a = ClassBaseClause 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 ToJSONFields1 ClassBaseClause
instance Eq1 ClassBaseClause where liftEq = genericLiftEq instance Eq1 ClassBaseClause where liftEq = genericLiftEq
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
@ -293,9 +248,7 @@ instance Evaluatable ClassBaseClause
newtype UseClause a = UseClause [a] newtype UseClause a = UseClause [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 ToJSONFields1 UseClause
instance Eq1 UseClause where liftEq = genericLiftEq instance Eq1 UseClause where liftEq = genericLiftEq
instance Ord1 UseClause where liftCompare = genericLiftCompare instance Ord1 UseClause where liftCompare = genericLiftCompare
@ -303,9 +256,7 @@ instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable UseClause instance Evaluatable UseClause
newtype ReturnType a = ReturnType a newtype ReturnType a = ReturnType 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 ToJSONFields1 ReturnType
instance Eq1 ReturnType where liftEq = genericLiftEq instance Eq1 ReturnType where liftEq = genericLiftEq
instance Ord1 ReturnType where liftCompare = genericLiftCompare instance Ord1 ReturnType where liftCompare = genericLiftCompare
@ -313,9 +264,7 @@ instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ReturnType instance Evaluatable ReturnType
newtype TypeDeclaration a = TypeDeclaration a newtype TypeDeclaration a = TypeDeclaration 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 ToJSONFields1 TypeDeclaration
instance Eq1 TypeDeclaration where liftEq = genericLiftEq instance Eq1 TypeDeclaration where liftEq = genericLiftEq
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
@ -323,9 +272,7 @@ instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeDeclaration instance Evaluatable TypeDeclaration
newtype BaseTypeDeclaration a = BaseTypeDeclaration a newtype BaseTypeDeclaration a = BaseTypeDeclaration 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 ToJSONFields1 BaseTypeDeclaration
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
@ -333,9 +280,7 @@ instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BaseTypeDeclaration instance Evaluatable BaseTypeDeclaration
newtype ScalarType a = ScalarType ByteString newtype ScalarType a = ScalarType ByteString
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 ToJSONFields1 ScalarType
instance Eq1 ScalarType where liftEq = genericLiftEq instance Eq1 ScalarType where liftEq = genericLiftEq
instance Ord1 ScalarType where liftCompare = genericLiftCompare instance Ord1 ScalarType where liftCompare = genericLiftCompare
@ -343,9 +288,7 @@ instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ScalarType instance Evaluatable ScalarType
newtype EmptyIntrinsic a = EmptyIntrinsic a newtype EmptyIntrinsic a = EmptyIntrinsic 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 ToJSONFields1 EmptyIntrinsic
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
@ -353,9 +296,7 @@ instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EmptyIntrinsic instance Evaluatable EmptyIntrinsic
newtype ExitIntrinsic a = ExitIntrinsic a newtype ExitIntrinsic a = ExitIntrinsic 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 ToJSONFields1 ExitIntrinsic
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
@ -363,9 +304,7 @@ instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExitIntrinsic instance Evaluatable ExitIntrinsic
newtype IssetIntrinsic a = IssetIntrinsic a newtype IssetIntrinsic a = IssetIntrinsic 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 ToJSONFields1 IssetIntrinsic
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
@ -373,9 +312,7 @@ instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IssetIntrinsic instance Evaluatable IssetIntrinsic
newtype EvalIntrinsic a = EvalIntrinsic a newtype EvalIntrinsic a = EvalIntrinsic 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 ToJSONFields1 EvalIntrinsic
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
@ -383,9 +320,7 @@ instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EvalIntrinsic instance Evaluatable EvalIntrinsic
newtype PrintIntrinsic a = PrintIntrinsic a newtype PrintIntrinsic a = PrintIntrinsic 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 ToJSONFields1 PrintIntrinsic
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
@ -393,9 +328,7 @@ instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PrintIntrinsic instance Evaluatable PrintIntrinsic
newtype NamespaceAliasingClause a = NamespaceAliasingClause a newtype NamespaceAliasingClause a = NamespaceAliasingClause 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 ToJSONFields1 NamespaceAliasingClause
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
@ -403,9 +336,7 @@ instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceAliasingClause instance Evaluatable NamespaceAliasingClause
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [a] newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [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 ToJSONFields1 NamespaceUseDeclaration
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
@ -413,9 +344,7 @@ instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceUseDeclaration instance Evaluatable NamespaceUseDeclaration
newtype NamespaceUseClause a = NamespaceUseClause [a] newtype NamespaceUseClause a = NamespaceUseClause [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 ToJSONFields1 NamespaceUseClause
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
@ -423,9 +352,7 @@ instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NamespaceUseClause instance Evaluatable NamespaceUseClause
newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [a] newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [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 ToJSONFields1 NamespaceUseGroupClause
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
@ -433,14 +360,12 @@ instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceUseGroupClause instance Evaluatable NamespaceUseGroupClause
data Namespace a = Namespace { namespaceName :: a, namespaceBody :: a } 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 Eq1 Namespace where liftEq = genericLiftEq
instance Ord1 Namespace where liftCompare = genericLiftCompare instance Ord1 Namespace where liftCompare = genericLiftCompare
instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Namespace
instance Evaluatable Namespace where instance Evaluatable Namespace where
eval Namespace{..} = Rval <$> go names eval Namespace{..} = Rval <$> go names
where where
@ -454,9 +379,7 @@ instance Evaluatable Namespace where
go xs <* makeNamespace name addr Nothing go xs <* makeNamespace name addr Nothing
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] } data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [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 ToJSONFields1 TraitDeclaration
instance Eq1 TraitDeclaration where liftEq = genericLiftEq instance Eq1 TraitDeclaration where liftEq = genericLiftEq
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
@ -464,9 +387,7 @@ instance Show1 TraitDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitDeclaration instance Evaluatable TraitDeclaration
data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: a } data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: 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 ToJSONFields1 AliasAs
instance Eq1 AliasAs where liftEq = genericLiftEq instance Eq1 AliasAs where liftEq = genericLiftEq
instance Ord1 AliasAs where liftCompare = genericLiftCompare instance Ord1 AliasAs where liftCompare = genericLiftCompare
@ -474,9 +395,7 @@ instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AliasAs instance Evaluatable AliasAs
data InsteadOf a = InsteadOf a a data InsteadOf a = InsteadOf a 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 ToJSONFields1 InsteadOf
instance Eq1 InsteadOf where liftEq = genericLiftEq instance Eq1 InsteadOf where liftEq = genericLiftEq
instance Ord1 InsteadOf where liftCompare = genericLiftCompare instance Ord1 InsteadOf where liftCompare = genericLiftCompare
@ -484,9 +403,7 @@ instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InsteadOf instance Evaluatable InsteadOf
newtype TraitUseSpecification a = TraitUseSpecification [a] newtype TraitUseSpecification a = TraitUseSpecification [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 ToJSONFields1 TraitUseSpecification
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
@ -494,9 +411,7 @@ instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitUseSpecification instance Evaluatable TraitUseSpecification
data TraitUseClause a = TraitUseClause [a] a data TraitUseClause a = TraitUseClause [a] 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 ToJSONFields1 TraitUseClause
instance Eq1 TraitUseClause where liftEq = genericLiftEq instance Eq1 TraitUseClause where liftEq = genericLiftEq
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
@ -504,9 +419,7 @@ instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitUseClause instance Evaluatable TraitUseClause
data DestructorDeclaration a = DestructorDeclaration [a] a data DestructorDeclaration a = DestructorDeclaration [a] 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 ToJSONFields1 DestructorDeclaration
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
@ -514,9 +427,7 @@ instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DestructorDeclaration instance Evaluatable DestructorDeclaration
newtype Static a = Static ByteString newtype Static a = Static ByteString
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 ToJSONFields1 Static
instance Eq1 Static where liftEq = genericLiftEq instance Eq1 Static where liftEq = genericLiftEq
instance Ord1 Static where liftCompare = genericLiftCompare instance Ord1 Static where liftCompare = genericLiftCompare
@ -524,9 +435,7 @@ instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Static instance Evaluatable Static
newtype ClassModifier a = ClassModifier ByteString newtype ClassModifier a = ClassModifier ByteString
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 ToJSONFields1 ClassModifier
instance Eq1 ClassModifier where liftEq = genericLiftEq instance Eq1 ClassModifier where liftEq = genericLiftEq
instance Ord1 ClassModifier where liftCompare = genericLiftCompare instance Ord1 ClassModifier where liftCompare = genericLiftCompare
@ -534,9 +443,7 @@ instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassModifier instance Evaluatable ClassModifier
data ConstructorDeclaration a = ConstructorDeclaration [a] [a] a data ConstructorDeclaration a = ConstructorDeclaration [a] [a] 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 ToJSONFields1 ConstructorDeclaration
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
@ -544,9 +451,7 @@ instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructorDeclaration instance Evaluatable ConstructorDeclaration
data PropertyDeclaration a = PropertyDeclaration a [a] data PropertyDeclaration a = PropertyDeclaration a [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 ToJSONFields1 PropertyDeclaration
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
@ -554,9 +459,7 @@ instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertyDeclaration instance Evaluatable PropertyDeclaration
data PropertyModifier a = PropertyModifier a a data PropertyModifier a = PropertyModifier a 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 ToJSONFields1 PropertyModifier
instance Eq1 PropertyModifier where liftEq = genericLiftEq instance Eq1 PropertyModifier where liftEq = genericLiftEq
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
@ -564,9 +467,7 @@ instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertyModifier instance Evaluatable PropertyModifier
data InterfaceDeclaration a = InterfaceDeclaration a a [a] data InterfaceDeclaration a = InterfaceDeclaration a a [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 ToJSONFields1 InterfaceDeclaration
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
@ -574,9 +475,7 @@ instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InterfaceDeclaration instance Evaluatable InterfaceDeclaration
newtype InterfaceBaseClause a = InterfaceBaseClause [a] newtype InterfaceBaseClause a = InterfaceBaseClause [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 ToJSONFields1 InterfaceBaseClause
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
@ -584,9 +483,7 @@ instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InterfaceBaseClause instance Evaluatable InterfaceBaseClause
newtype Echo a = Echo a newtype Echo a = Echo 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 ToJSONFields1 Echo
instance Eq1 Echo where liftEq = genericLiftEq instance Eq1 Echo where liftEq = genericLiftEq
instance Ord1 Echo where liftCompare = genericLiftCompare instance Ord1 Echo where liftCompare = genericLiftCompare
@ -594,9 +491,7 @@ instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Echo instance Evaluatable Echo
newtype Unset a = Unset a newtype Unset a = Unset 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 ToJSONFields1 Unset
instance Eq1 Unset where liftEq = genericLiftEq instance Eq1 Unset where liftEq = genericLiftEq
instance Ord1 Unset where liftCompare = genericLiftCompare instance Ord1 Unset where liftCompare = genericLiftCompare
@ -604,9 +499,7 @@ instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Unset instance Evaluatable Unset
data Declare a = Declare a a data Declare a = Declare a 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 ToJSONFields1 Declare
instance Eq1 Declare where liftEq = genericLiftEq instance Eq1 Declare where liftEq = genericLiftEq
instance Ord1 Declare where liftCompare = genericLiftCompare instance Ord1 Declare where liftCompare = genericLiftCompare
@ -614,9 +507,7 @@ instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Declare instance Evaluatable Declare
newtype DeclareDirective a = DeclareDirective a newtype DeclareDirective a = DeclareDirective 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 ToJSONFields1 DeclareDirective
instance Eq1 DeclareDirective where liftEq = genericLiftEq instance Eq1 DeclareDirective where liftEq = genericLiftEq
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
@ -624,9 +515,7 @@ instance Show1 DeclareDirective where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DeclareDirective instance Evaluatable DeclareDirective
newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: a } newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: 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 ToJSONFields1 LabeledStatement
instance Eq1 LabeledStatement where liftEq = genericLiftEq instance Eq1 LabeledStatement where liftEq = genericLiftEq
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare instance Ord1 LabeledStatement where liftCompare = genericLiftCompare

View File

@ -10,7 +10,18 @@ module Language.Python.Assignment
import Assigning.Assignment hiding (Assignment, Error) import Assigning.Assignment hiding (Assignment, Error)
import Data.Abstract.Name (name) import Data.Abstract.Name (name)
import Data.Record import Data.Record
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize) import Data.Syntax
( contextualize
, emptyTerm
, handleError
, infixContext
, makeTerm
, makeTerm'
, makeTerm''
, makeTerm1
, parseError
, postContextualize
)
import GHC.Stack import GHC.Stack
import Language.Python.Grammar as Grammar import Language.Python.Grammar as Grammar
import Language.Python.Syntax as Python.Syntax import Language.Python.Syntax as Python.Syntax
@ -68,6 +79,7 @@ type Syntax =
, Statement.Let , Statement.Let
, Statement.NoOp , Statement.NoOp
, Statement.Return , Statement.Return
, Statement.Statements
, Statement.Throw , Statement.Throw
, Statement.Try , Statement.Try
, Statement.While , Statement.While
@ -80,7 +92,6 @@ type Syntax =
, Syntax.Empty , Syntax.Empty
, Syntax.Error , Syntax.Error
, Syntax.Identifier , Syntax.Identifier
, Syntax.Program
, Type.Annotation , Type.Annotation
, [] , []
] ]
@ -90,17 +101,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
-- | Assignment from AST in Python's grammar onto a program in Python's syntax. -- | Assignment from AST in Python's grammar onto a program in Python's syntax.
assignment :: Assignment assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program <$> manyTerm expression) <|> parseError assignment = handleError $ makeTerm <$> symbol Module <*> children (Statement.Statements <$> manyTerm expression) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
expression :: Assignment expression :: Assignment
expression = handleError (choice expressionChoices) expression = handleError (choice expressionChoices)
@ -394,7 +395,7 @@ import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliase
makeNameAliasPair from Nothing = (from, from) makeNameAliasPair from Nothing = (from, from)
assertStatement :: Assignment assertStatement :: Assignment
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call [] <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
printStatement :: Assignment printStatement :: Assignment
printStatement = do printStatement = do
@ -408,19 +409,19 @@ printStatement = do
printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm) printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm)
nonlocalStatement :: Assignment nonlocalStatement :: Assignment
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
globalStatement :: Assignment globalStatement :: Assignment
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
await :: Assignment await :: Assignment
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) await = makeTerm <$> symbol Await <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
returnStatement :: Assignment returnStatement :: Assignment
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm)) returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm))
deleteStatement :: Assignment deleteStatement :: Assignment
deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm) deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call [] <$> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm)
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier . name <$> source) where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier . name <$> source)
raiseStatement :: Assignment raiseStatement :: Assignment
@ -432,7 +433,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> ter
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
execStatement :: Assignment execStatement :: Assignment
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm) execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call [] <$> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm)
passStatement :: Assignment passStatement :: Assignment
passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance) passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance)
@ -456,7 +457,7 @@ slice = makeTerm <$> symbol Slice <*> children
<*> (term expression <|> emptyTerm)) <*> (term expression <|> emptyTerm))
call :: Assignment call :: Assignment
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> pure [] <*> term (identifier <|> expression) <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm) call = makeTerm <$> symbol Call <*> children (Expression.Call [] <$> term (identifier <|> expression) <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm)
boolean :: Assignment boolean :: Assignment
boolean = makeTerm <$> token Grammar.True <*> pure Literal.true boolean = makeTerm <$> token Grammar.True <*> pure Literal.true
@ -483,6 +484,19 @@ ifClause = symbol IfClause *> children expressions
conditionalExpression :: Assignment conditionalExpression :: Assignment
conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (flip Statement.If <$> term expression <*> term expression <*> expressions) conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (flip Statement.If <$> term expression <*> term expression <*> expressions)
-- Helpers
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
-- | Match a left-associated infix chain of terms, optionally followed by comments. Like 'chainl1' but assigning comment nodes automatically. -- | Match a left-associated infix chain of terms, optionally followed by comments. Like 'chainl1' but assigning comment nodes automatically.
chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> Term) -> Assignment chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> Term) -> Assignment
chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op

View File

@ -88,9 +88,7 @@ resolvePythonModules q = do
-- --
-- If the list of symbols is empty copy everything to the calling environment. -- If the list of symbols is empty copy everything to the calling environment.
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![(Name, Name)] } data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![(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 ToJSONFields1 Import
instance Eq1 Import where liftEq = genericLiftEq instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare instance Ord1 Import where liftCompare = genericLiftCompare
@ -138,9 +136,7 @@ evalQualifiedImport name path = letrec' name $ \addr -> do
unit <$ makeNamespace name addr Nothing unit <$ makeNamespace name addr Nothing
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedName } newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedName }
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 ToJSONFields1 QualifiedImport
instance Eq1 QualifiedImport where liftEq = genericLiftEq instance Eq1 QualifiedImport where liftEq = genericLiftEq
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
@ -162,9 +158,7 @@ instance Evaluatable QualifiedImport where
makeNamespace name addr Nothing makeNamespace name addr Nothing
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a } data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !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 ToJSONFields1 QualifiedAliasedImport
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare 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) -- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
data Ellipsis a = Ellipsis 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 Eq1 Ellipsis where liftEq = genericLiftEq
instance Ord1 Ellipsis where liftCompare = genericLiftCompare instance Ord1 Ellipsis where liftCompare = genericLiftCompare
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Ellipsis
-- TODO: Implement Eval instance for Ellipsis -- TODO: Implement Eval instance for Ellipsis
instance Evaluatable Ellipsis instance Evaluatable Ellipsis
data Redirect a = Redirect !a !a 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 Eq1 Redirect where liftEq = genericLiftEq
instance Ord1 Redirect where liftCompare = genericLiftCompare instance Ord1 Redirect where liftCompare = genericLiftCompare
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Redirect
-- TODO: Implement Eval instance for Redirect -- TODO: Implement Eval instance for Redirect
instance Evaluatable Redirect instance Evaluatable Redirect

View File

@ -10,7 +10,18 @@ import Assigning.Assignment hiding (Assignment, Error)
import Data.Abstract.Name (name) import Data.Abstract.Name (name)
import Data.List (elem) import Data.List (elem)
import Data.Record import Data.Record
import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1) import Data.Syntax
( contextualize
, emptyTerm
, handleError
, infixContext
, makeTerm
, makeTerm'
, makeTerm''
, makeTerm1
, parseError
, postContextualize
)
import Language.Ruby.Grammar as Grammar import Language.Ruby.Grammar as Grammar
import qualified Assigning.Assignment as Assignment import qualified Assigning.Assignment as Assignment
import Data.Sum import Data.Sum
@ -69,6 +80,7 @@ type Syntax = '[
, Statement.Return , Statement.Return
, Statement.ScopeEntry , Statement.ScopeEntry
, Statement.ScopeExit , Statement.ScopeExit
, Statement.Statements
, Statement.Try , Statement.Try
, Statement.While , Statement.While
, Statement.Yield , Statement.Yield
@ -76,7 +88,6 @@ type Syntax = '[
, Syntax.Empty , Syntax.Empty
, Syntax.Error , Syntax.Error
, Syntax.Identifier , Syntax.Identifier
, Syntax.Program
, Ruby.Syntax.Class , Ruby.Syntax.Class
, Ruby.Syntax.Load , Ruby.Syntax.Load
, Ruby.Syntax.LowPrecedenceBoolean , Ruby.Syntax.LowPrecedenceBoolean
@ -92,7 +103,7 @@ type Assignment = Assignment' Term
-- | Assignment from AST in Rubys grammar onto a program in Rubys syntax. -- | Assignment from AST in Rubys grammar onto a program in Rubys syntax.
assignment :: Assignment assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> many expression) <|> parseError assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> many expression) <|> parseError
expression :: Assignment expression :: Assignment
expression = term (handleError (choice expressionChoices)) expression = term (handleError (choice expressionChoices))
@ -480,7 +491,7 @@ emptyStatement :: Assignment
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)
-- Helper functions -- Helpers
invert :: Assignment -> Assignment invert :: Assignment -> Assignment
invert term = makeTerm <$> location <*> fmap Expression.Not term invert term = makeTerm <$> location <*> fmap Expression.Not term

View File

@ -43,14 +43,12 @@ cleanNameOrPath :: ByteString -> String
cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes
data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a } 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 Eq1 Send where liftEq = genericLiftEq
instance Ord1 Send where liftCompare = genericLiftCompare instance Ord1 Send where liftCompare = genericLiftCompare
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Send
instance Evaluatable Send where instance Evaluatable Send where
eval Send{..} = do eval Send{..} = do
let sel = case sendSelector of let sel = case sendSelector of
@ -60,14 +58,12 @@ instance Evaluatable Send where
Rval <$> call func (map subtermValue sendArgs) -- TODO pass through sendBlock Rval <$> call func (map subtermValue sendArgs) -- TODO pass through sendBlock
data Require a = Require { requireRelative :: Bool, requirePath :: !a } 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 Eq1 Require where liftEq = genericLiftEq
instance Ord1 Require where liftCompare = genericLiftCompare instance Ord1 Require where liftCompare = genericLiftCompare
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Require
instance Evaluatable Require where instance Evaluatable Require where
eval (Require _ x) = do eval (Require _ x) = do
name <- subtermValue x >>= asString name <- subtermValue x >>= asString
@ -90,14 +86,12 @@ doRequire path = do
newtype Load a = Load { loadArgs :: [a] } 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 Eq1 Load where liftEq = genericLiftEq
instance Ord1 Load where liftCompare = genericLiftCompare instance Ord1 Load where liftCompare = genericLiftCompare
instance Show1 Load where liftShowsPrec = genericLiftShowsPrec instance Show1 Load where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Load
instance Evaluatable Load where instance Evaluatable Load where
eval (Load [x]) = do eval (Load [x]) = do
path <- subtermValue x >>= asString path <- subtermValue x >>= asString
@ -127,9 +121,7 @@ doLoad path shouldWrap = do
-- TODO: autoload -- TODO: autoload
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a } data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe 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 ToJSONFields1 Class
instance Diffable Class where instance Diffable Class where
equivalentBySubterm = Just . classIdentifier equivalentBySubterm = Just . classIdentifier
@ -146,14 +138,12 @@ instance Evaluatable Class where
subtermValue classBody <* makeNamespace name addr super) subtermValue classBody <* makeNamespace name addr super)
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } 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 Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Module
instance Evaluatable Module where instance Evaluatable Module where
eval (Module iden xs) = do eval (Module iden xs) = do
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
@ -163,9 +153,7 @@ instance Evaluatable Module where
data LowPrecedenceBoolean a data LowPrecedenceBoolean a
= LowAnd !a !a = LowAnd !a !a
| LowOr !a !a | LowOr !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 ToJSONFields1 LowPrecedenceBoolean
instance Evaluatable LowPrecedenceBoolean where 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 -- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands

View File

@ -11,7 +11,18 @@ import Data.Abstract.Name (name)
import qualified Assigning.Assignment as Assignment import qualified Assigning.Assignment as Assignment
import Data.Record import Data.Record
import Data.Sum import Data.Sum
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, contextualize, postContextualize) import Data.Syntax
( contextualize
, emptyTerm
, handleError
, infixContext
, makeTerm
, makeTerm'
, makeTerm''
, makeTerm1
, parseError
, postContextualize
)
import qualified Data.Syntax as Syntax import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Comment as Comment import qualified Data.Syntax.Comment as Comment
import qualified Data.Syntax.Declaration as Declaration import qualified Data.Syntax.Declaration as Declaration
@ -80,6 +91,7 @@ type Syntax = '[
, Statement.Return , Statement.Return
, Statement.ScopeEntry , Statement.ScopeEntry
, Statement.ScopeExit , Statement.ScopeExit
, Statement.Statements
, Statement.Throw , Statement.Throw
, Statement.Try , Statement.Try
, Statement.While , Statement.While
@ -88,7 +100,6 @@ type Syntax = '[
, Syntax.Empty , Syntax.Empty
, Syntax.Error , Syntax.Error
, Syntax.Identifier , Syntax.Identifier
, Syntax.Program
, Syntax.Context , Syntax.Context
, Type.Readonly , Type.Readonly
, Type.TypeParameters , Type.TypeParameters
@ -175,14 +186,7 @@ type Assignment = Assignment.Assignment [] Grammar Term
-- | Assignment from AST in TypeScripts grammar onto a program in TypeScripts syntax. -- | Assignment from AST in TypeScripts grammar onto a program in TypeScripts syntax.
assignment :: Assignment assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyTerm statement) <|> parseError assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> manyTerm statement) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
expression :: Assignment expression :: Assignment
expression = handleError everything expression = handleError everything
@ -858,6 +862,16 @@ binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm
]) ])
where invert cons a b = Expression.Not (makeTerm1 (cons a b)) where invert cons a b = Expression.Not (makeTerm1 (cons a b))
-- Helpers
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
emptyStatement :: Assignment emptyStatement :: Assignment
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)

View File

@ -146,9 +146,7 @@ evalRequire modulePath alias = letrec' alias $ \addr -> do
unit <$ makeNamespace alias addr Nothing unit <$ makeNamespace alias addr Nothing
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath } data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: 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 ToJSONFields1 Import
instance Eq1 Import where liftEq = genericLiftEq instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare instance Ord1 Import where liftCompare = genericLiftCompare
@ -166,14 +164,12 @@ instance Evaluatable Import where
| otherwise = Env.overwrite symbols importedEnv | otherwise = Env.overwrite symbols importedEnv
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath } 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 Eq1 JavaScriptRequire where liftEq = genericLiftEq
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 JavaScriptRequire
instance Evaluatable JavaScriptRequire where instance Evaluatable JavaScriptRequire where
eval (JavaScriptRequire aliasTerm importPath) = do eval (JavaScriptRequire aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions
@ -182,14 +178,12 @@ instance Evaluatable JavaScriptRequire where
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath } 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 Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 QualifiedAliasedImport
instance Evaluatable QualifiedAliasedImport where instance Evaluatable QualifiedAliasedImport where
eval (QualifiedAliasedImport aliasTerm importPath) = do eval (QualifiedAliasedImport aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
@ -197,14 +191,12 @@ instance Evaluatable QualifiedAliasedImport where
Rval <$> evalRequire modulePath alias Rval <$> evalRequire modulePath alias
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath } 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 Eq1 SideEffectImport where liftEq = genericLiftEq
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 SideEffectImport
instance Evaluatable SideEffectImport where instance Evaluatable SideEffectImport where
eval (SideEffectImport importPath) = do eval (SideEffectImport importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
@ -214,14 +206,12 @@ instance Evaluatable SideEffectImport where
-- | Qualified Export declarations -- | Qualified Export declarations
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [(Name, Name)] } 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 Eq1 QualifiedExport where liftEq = genericLiftEq
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 QualifiedExport
instance Evaluatable QualifiedExport where instance Evaluatable QualifiedExport where
eval (QualifiedExport exportSymbols) = do eval (QualifiedExport exportSymbols) = do
-- Insert the aliases with no addresses. -- Insert the aliases with no addresses.
@ -232,14 +222,12 @@ instance Evaluatable QualifiedExport where
-- | Qualified Export declarations that export from another module. -- | Qualified Export declarations that export from another module.
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![(Name, Name)]} 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 Eq1 QualifiedExportFrom where liftEq = genericLiftEq
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 QualifiedExportFrom
instance Evaluatable QualifiedExportFrom where instance Evaluatable QualifiedExportFrom where
eval (QualifiedExportFrom importPath exportSymbols) = do eval (QualifiedExportFrom importPath exportSymbols) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
@ -251,9 +239,7 @@ instance Evaluatable QualifiedExportFrom where
pure (Rval unit) pure (Rval unit)
newtype DefaultExport a = DefaultExport { defaultExport :: a } newtype DefaultExport a = DefaultExport { defaultExport :: 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 ToJSONFields1 DefaultExport
instance Eq1 DefaultExport where liftEq = genericLiftEq instance Eq1 DefaultExport where liftEq = genericLiftEq
instance Ord1 DefaultExport where liftCompare = genericLiftCompare 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. -- | Lookup type for a type-level key in a typescript map.
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a } data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: 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 ToJSONFields1 LookupType
instance Eq1 LookupType where liftEq = genericLiftEq instance Eq1 LookupType where liftEq = genericLiftEq
instance Ord1 LookupType where liftCompare = genericLiftCompare 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 } -- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier ByteString newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier 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 ToJSONFields1 ShorthandPropertyIdentifier
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
@ -295,9 +277,7 @@ instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShow
instance Evaluatable ShorthandPropertyIdentifier instance Evaluatable ShorthandPropertyIdentifier
data Union a = Union { _unionLeft :: !a, _unionRight :: !a } data Union a = Union { _unionLeft :: !a, _unionRight :: !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 ToJSONFields1 Language.TypeScript.Syntax.Union
instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.Union where liftCompare = genericLiftCompare 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 instance Evaluatable Language.TypeScript.Syntax.Union
data Intersection a = Intersection { _intersectionLeft :: !a, _intersectionRight :: !a } data Intersection a = Intersection { _intersectionLeft :: !a, _intersectionRight :: !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 ToJSONFields1 Intersection
instance Eq1 Intersection where liftEq = genericLiftEq instance Eq1 Intersection where liftEq = genericLiftEq
instance Ord1 Intersection where liftCompare = genericLiftCompare instance Ord1 Intersection where liftCompare = genericLiftCompare
@ -315,9 +293,7 @@ instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Intersection instance Evaluatable Intersection
data FunctionType a = FunctionType { _functionTypeParameters :: !a, _functionFormalParameters :: ![a], _functionType :: !a } data FunctionType a = FunctionType { _functionTypeParameters :: !a, _functionFormalParameters :: ![a], _functionType :: !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 ToJSONFields1 FunctionType
instance Eq1 FunctionType where liftEq = genericLiftEq instance Eq1 FunctionType where liftEq = genericLiftEq
instance Ord1 FunctionType where liftCompare = genericLiftCompare instance Ord1 FunctionType where liftCompare = genericLiftCompare
@ -325,9 +301,7 @@ instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionType instance Evaluatable FunctionType
data AmbientFunction a = AmbientFunction { _ambientFunctionContext :: ![a], _ambientFunctionIdentifier :: !a, _ambientFunctionParameters :: ![a] } data AmbientFunction a = AmbientFunction { _ambientFunctionContext :: ![a], _ambientFunctionIdentifier :: !a, _ambientFunctionParameters :: ![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 ToJSONFields1 AmbientFunction
instance Eq1 AmbientFunction where liftEq = genericLiftEq instance Eq1 AmbientFunction where liftEq = genericLiftEq
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
@ -335,9 +309,7 @@ instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AmbientFunction instance Evaluatable AmbientFunction
data ImportRequireClause a = ImportRequireClause { _importRequireIdentifier :: !a, _importRequireSubject :: !a } data ImportRequireClause a = ImportRequireClause { _importRequireIdentifier :: !a, _importRequireSubject :: !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 ToJSONFields1 ImportRequireClause
instance Eq1 ImportRequireClause where liftEq = genericLiftEq instance Eq1 ImportRequireClause where liftEq = genericLiftEq
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
@ -345,9 +317,7 @@ instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportRequireClause instance Evaluatable ImportRequireClause
newtype ImportClause a = ImportClause { _importClauseElements :: [a] } newtype ImportClause a = ImportClause { _importClauseElements :: [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 ToJSONFields1 ImportClause
instance Eq1 ImportClause where liftEq = genericLiftEq instance Eq1 ImportClause where liftEq = genericLiftEq
instance Ord1 ImportClause where liftCompare = genericLiftCompare instance Ord1 ImportClause where liftCompare = genericLiftCompare
@ -355,9 +325,7 @@ instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportClause instance Evaluatable ImportClause
newtype Tuple a = Tuple { _tupleElements :: [a] } newtype Tuple a = Tuple { _tupleElements :: [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 ToJSONFields1 Tuple
instance Eq1 Tuple where liftEq = genericLiftEq instance Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare instance Ord1 Tuple where liftCompare = genericLiftCompare
@ -367,9 +335,7 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Tuple instance Evaluatable Tuple
data Constructor a = Constructor { _constructorTypeParameters :: !a, _constructorFormalParameters :: ![a], _constructorType :: !a } data Constructor a = Constructor { _constructorTypeParameters :: !a, _constructorFormalParameters :: ![a], _constructorType :: !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 ToJSONFields1 Language.TypeScript.Syntax.Constructor
instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.Constructor where liftCompare = genericLiftCompare 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 instance Evaluatable Language.TypeScript.Syntax.Constructor
data TypeParameter a = TypeParameter { _typeParameter :: !a, _typeParameterConstraint :: !a, _typeParameterDefaultType :: !a } data TypeParameter a = TypeParameter { _typeParameter :: !a, _typeParameterConstraint :: !a, _typeParameterDefaultType :: !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 ToJSONFields1 TypeParameter
instance Eq1 TypeParameter where liftEq = genericLiftEq instance Eq1 TypeParameter where liftEq = genericLiftEq
instance Ord1 TypeParameter where liftCompare = genericLiftCompare instance Ord1 TypeParameter where liftCompare = genericLiftCompare
@ -387,9 +351,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeParameter instance Evaluatable TypeParameter
data TypeAssertion a = TypeAssertion { _typeAssertionParameters :: !a, _typeAssertionExpression :: !a } data TypeAssertion a = TypeAssertion { _typeAssertionParameters :: !a, _typeAssertionExpression :: !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 ToJSONFields1 TypeAssertion
instance Eq1 TypeAssertion where liftEq = genericLiftEq instance Eq1 TypeAssertion where liftEq = genericLiftEq
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
@ -397,9 +359,7 @@ instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeAssertion instance Evaluatable TypeAssertion
newtype Annotation a = Annotation { _annotationType :: a } newtype Annotation a = Annotation { _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 ToJSONFields1 Annotation
instance Eq1 Annotation where liftEq = genericLiftEq instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare instance Ord1 Annotation where liftCompare = genericLiftCompare
@ -407,9 +367,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Annotation instance Evaluatable Annotation
newtype Decorator a = Decorator { _decoratorTerm :: a } newtype Decorator a = Decorator { _decoratorTerm :: 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 ToJSONFields1 Decorator
instance Eq1 Decorator where liftEq = genericLiftEq instance Eq1 Decorator where liftEq = genericLiftEq
instance Ord1 Decorator where liftCompare = genericLiftCompare instance Ord1 Decorator where liftCompare = genericLiftCompare
@ -417,9 +375,7 @@ instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Decorator instance Evaluatable Decorator
newtype ComputedPropertyName a = ComputedPropertyName a newtype ComputedPropertyName a = ComputedPropertyName 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 ToJSONFields1 ComputedPropertyName
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
@ -427,9 +383,7 @@ instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ComputedPropertyName instance Evaluatable ComputedPropertyName
newtype Constraint a = Constraint { _constraintType :: a } newtype Constraint a = Constraint { _constraintType :: 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 ToJSONFields1 Constraint
instance Eq1 Constraint where liftEq = genericLiftEq instance Eq1 Constraint where liftEq = genericLiftEq
instance Ord1 Constraint where liftCompare = genericLiftCompare instance Ord1 Constraint where liftCompare = genericLiftCompare
@ -437,9 +391,7 @@ instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Constraint instance Evaluatable Constraint
newtype DefaultType a = DefaultType { _defaultType :: a } newtype DefaultType a = DefaultType { _defaultType :: 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 ToJSONFields1 DefaultType
instance Eq1 DefaultType where liftEq = genericLiftEq instance Eq1 DefaultType where liftEq = genericLiftEq
instance Ord1 DefaultType where liftCompare = genericLiftCompare instance Ord1 DefaultType where liftCompare = genericLiftCompare
@ -447,9 +399,7 @@ instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultType instance Evaluatable DefaultType
newtype ParenthesizedType a = ParenthesizedType { _parenthesizedType :: a } newtype ParenthesizedType a = ParenthesizedType { _parenthesizedType :: 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 ToJSONFields1 ParenthesizedType
instance Eq1 ParenthesizedType where liftEq = genericLiftEq instance Eq1 ParenthesizedType where liftEq = genericLiftEq
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
@ -457,9 +407,7 @@ instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ParenthesizedType instance Evaluatable ParenthesizedType
newtype PredefinedType a = PredefinedType { _predefinedType :: ByteString } newtype PredefinedType a = PredefinedType { _predefinedType :: 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 ToJSONFields1 PredefinedType
instance Eq1 PredefinedType where liftEq = genericLiftEq instance Eq1 PredefinedType where liftEq = genericLiftEq
instance Ord1 PredefinedType where liftCompare = genericLiftCompare instance Ord1 PredefinedType where liftCompare = genericLiftCompare
@ -467,9 +415,7 @@ instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PredefinedType instance Evaluatable PredefinedType
newtype TypeIdentifier a = TypeIdentifier ByteString newtype TypeIdentifier a = TypeIdentifier 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 ToJSONFields1 TypeIdentifier
instance Eq1 TypeIdentifier where liftEq = genericLiftEq instance Eq1 TypeIdentifier where liftEq = genericLiftEq
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
@ -477,9 +423,7 @@ instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeIdentifier instance Evaluatable TypeIdentifier
data NestedIdentifier a = NestedIdentifier !a !a data NestedIdentifier a = NestedIdentifier !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 ToJSONFields1 NestedIdentifier
instance Eq1 NestedIdentifier where liftEq = genericLiftEq instance Eq1 NestedIdentifier where liftEq = genericLiftEq
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
@ -487,9 +431,7 @@ instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedIdentifier instance Evaluatable NestedIdentifier
data NestedTypeIdentifier a = NestedTypeIdentifier !a !a data NestedTypeIdentifier a = NestedTypeIdentifier !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 ToJSONFields1 NestedTypeIdentifier
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
@ -497,9 +439,7 @@ instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedTypeIdentifier instance Evaluatable NestedTypeIdentifier
data GenericType a = GenericType { _genericTypeIdentifier :: !a, _genericTypeArguments :: !a } data GenericType a = GenericType { _genericTypeIdentifier :: !a, _genericTypeArguments :: !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 ToJSONFields1 GenericType
instance Eq1 GenericType where liftEq = genericLiftEq instance Eq1 GenericType where liftEq = genericLiftEq
instance Ord1 GenericType where liftCompare = genericLiftCompare instance Ord1 GenericType where liftCompare = genericLiftCompare
@ -507,9 +447,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GenericType instance Evaluatable GenericType
data TypePredicate a = TypePredicate { _typePredicateIdentifier :: !a, _typePredicateType :: !a } data TypePredicate a = TypePredicate { _typePredicateIdentifier :: !a, _typePredicateType :: !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 ToJSONFields1 TypePredicate
instance Eq1 TypePredicate where liftEq = genericLiftEq instance Eq1 TypePredicate where liftEq = genericLiftEq
instance Ord1 TypePredicate where liftCompare = genericLiftCompare instance Ord1 TypePredicate where liftCompare = genericLiftCompare
@ -517,9 +455,7 @@ instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypePredicate instance Evaluatable TypePredicate
newtype ObjectType a = ObjectType { _objectTypeElements :: [a] } newtype ObjectType a = ObjectType { _objectTypeElements :: [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 ToJSONFields1 ObjectType
instance Eq1 ObjectType where liftEq = genericLiftEq instance Eq1 ObjectType where liftEq = genericLiftEq
instance Ord1 ObjectType where liftCompare = genericLiftCompare instance Ord1 ObjectType where liftCompare = genericLiftCompare
@ -527,9 +463,7 @@ instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ObjectType instance Evaluatable ObjectType
data With a = With { _withExpression :: !a, _withBody :: !a } data With a = With { _withExpression :: !a, _withBody :: !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 ToJSONFields1 With
instance Eq1 With where liftEq = genericLiftEq instance Eq1 With where liftEq = genericLiftEq
instance Ord1 With where liftCompare = genericLiftCompare instance Ord1 With where liftCompare = genericLiftCompare
@ -537,9 +471,7 @@ instance Show1 With where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable With instance Evaluatable With
newtype AmbientDeclaration a = AmbientDeclaration { _ambientDeclarationBody :: a } newtype AmbientDeclaration a = AmbientDeclaration { _ambientDeclarationBody :: 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 ToJSONFields1 AmbientDeclaration
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
@ -549,9 +481,7 @@ instance Evaluatable AmbientDeclaration where
eval (AmbientDeclaration body) = subtermRef body eval (AmbientDeclaration body) = subtermRef body
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![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 ToJSONFields1 EnumDeclaration
instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Eq1 EnumDeclaration where liftEq = genericLiftEq
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
@ -562,9 +492,7 @@ instance Declarations a => Declarations (EnumDeclaration a) where
declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier
newtype ExtendsClause a = ExtendsClause { _extendsClauses :: [a] } newtype ExtendsClause a = ExtendsClause { _extendsClauses :: [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 ToJSONFields1 ExtendsClause
instance Eq1 ExtendsClause where liftEq = genericLiftEq instance Eq1 ExtendsClause where liftEq = genericLiftEq
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
@ -572,9 +500,7 @@ instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExtendsClause instance Evaluatable ExtendsClause
newtype ArrayType a = ArrayType { _arrayType :: a } newtype ArrayType a = ArrayType { _arrayType :: 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 ToJSONFields1 ArrayType
instance Eq1 ArrayType where liftEq = genericLiftEq instance Eq1 ArrayType where liftEq = genericLiftEq
instance Ord1 ArrayType where liftCompare = genericLiftCompare instance Ord1 ArrayType where liftCompare = genericLiftCompare
@ -582,9 +508,7 @@ instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayType instance Evaluatable ArrayType
newtype FlowMaybeType a = FlowMaybeType { _flowMaybeType :: a } newtype FlowMaybeType a = FlowMaybeType { _flowMaybeType :: 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 ToJSONFields1 FlowMaybeType
instance Eq1 FlowMaybeType where liftEq = genericLiftEq instance Eq1 FlowMaybeType where liftEq = genericLiftEq
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
@ -592,9 +516,7 @@ instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FlowMaybeType instance Evaluatable FlowMaybeType
newtype TypeQuery a = TypeQuery { _typeQuerySubject :: a } newtype TypeQuery a = TypeQuery { _typeQuerySubject :: 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 ToJSONFields1 TypeQuery
instance Eq1 TypeQuery where liftEq = genericLiftEq instance Eq1 TypeQuery where liftEq = genericLiftEq
instance Ord1 TypeQuery where liftCompare = genericLiftCompare instance Ord1 TypeQuery where liftCompare = genericLiftCompare
@ -602,9 +524,7 @@ instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeQuery instance Evaluatable TypeQuery
newtype IndexTypeQuery a = IndexTypeQuery { _indexTypeQuerySubject :: a } newtype IndexTypeQuery a = IndexTypeQuery { _indexTypeQuerySubject :: 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 ToJSONFields1 IndexTypeQuery
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
@ -612,9 +532,7 @@ instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexTypeQuery instance Evaluatable IndexTypeQuery
newtype TypeArguments a = TypeArguments { _typeArguments :: [a] } newtype TypeArguments a = TypeArguments { _typeArguments :: [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 ToJSONFields1 TypeArguments
instance Eq1 TypeArguments where liftEq = genericLiftEq instance Eq1 TypeArguments where liftEq = genericLiftEq
instance Ord1 TypeArguments where liftCompare = genericLiftCompare instance Ord1 TypeArguments where liftCompare = genericLiftCompare
@ -622,9 +540,7 @@ instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeArguments instance Evaluatable TypeArguments
newtype ThisType a = ThisType ByteString newtype ThisType a = ThisType 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 ToJSONFields1 ThisType
instance Eq1 ThisType where liftEq = genericLiftEq instance Eq1 ThisType where liftEq = genericLiftEq
instance Ord1 ThisType where liftCompare = genericLiftCompare instance Ord1 ThisType where liftCompare = genericLiftCompare
@ -632,9 +548,7 @@ instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ThisType instance Evaluatable ThisType
newtype ExistentialType a = ExistentialType ByteString newtype ExistentialType a = ExistentialType 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 ToJSONFields1 ExistentialType
instance Eq1 ExistentialType where liftEq = genericLiftEq instance Eq1 ExistentialType where liftEq = genericLiftEq
instance Ord1 ExistentialType where liftCompare = genericLiftCompare instance Ord1 ExistentialType where liftCompare = genericLiftCompare
@ -642,9 +556,7 @@ instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExistentialType instance Evaluatable ExistentialType
newtype LiteralType a = LiteralType { _literalTypeSubject :: a } newtype LiteralType a = LiteralType { _literalTypeSubject :: 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 ToJSONFields1 LiteralType
instance Eq1 LiteralType where liftEq = genericLiftEq instance Eq1 LiteralType where liftEq = genericLiftEq
instance Ord1 LiteralType where liftCompare = genericLiftCompare instance Ord1 LiteralType where liftCompare = genericLiftCompare
@ -652,9 +564,7 @@ instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LiteralType instance Evaluatable LiteralType
data PropertySignature a = PropertySignature { _modifiers :: ![a], _propertySignaturePropertyName :: !a } data PropertySignature a = PropertySignature { _modifiers :: ![a], _propertySignaturePropertyName :: !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 ToJSONFields1 PropertySignature
instance Eq1 PropertySignature where liftEq = genericLiftEq instance Eq1 PropertySignature where liftEq = genericLiftEq
instance Ord1 PropertySignature where liftCompare = genericLiftCompare instance Ord1 PropertySignature where liftCompare = genericLiftCompare
@ -662,9 +572,7 @@ instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertySignature instance Evaluatable PropertySignature
data CallSignature a = CallSignature { _callSignatureTypeParameters :: !a, _callSignatureParameters :: ![a], _callSignatureType :: !a } data CallSignature a = CallSignature { _callSignatureTypeParameters :: !a, _callSignatureParameters :: ![a], _callSignatureType :: !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 ToJSONFields1 CallSignature
instance Eq1 CallSignature where liftEq = genericLiftEq instance Eq1 CallSignature where liftEq = genericLiftEq
instance Ord1 CallSignature where liftCompare = genericLiftCompare instance Ord1 CallSignature where liftCompare = genericLiftCompare
@ -673,9 +581,7 @@ instance Evaluatable CallSignature
-- | Todo: Move type params and type to context -- | Todo: Move type params and type to context
data ConstructSignature a = ConstructSignature { _constructSignatureTypeParameters :: !a, _constructSignatureParameters :: ![a], _constructSignatureType :: !a } data ConstructSignature a = ConstructSignature { _constructSignatureTypeParameters :: !a, _constructSignatureParameters :: ![a], _constructSignatureType :: !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 ToJSONFields1 ConstructSignature
instance Eq1 ConstructSignature where liftEq = genericLiftEq instance Eq1 ConstructSignature where liftEq = genericLiftEq
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
@ -683,9 +589,7 @@ instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructSignature instance Evaluatable ConstructSignature
data IndexSignature a = IndexSignature { _indexSignatureSubject :: a, _indexSignatureType :: a } data IndexSignature a = IndexSignature { _indexSignatureSubject :: a, _indexSignatureType :: 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 ToJSONFields1 IndexSignature
instance Eq1 IndexSignature where liftEq = genericLiftEq instance Eq1 IndexSignature where liftEq = genericLiftEq
instance Ord1 IndexSignature where liftCompare = genericLiftCompare instance Ord1 IndexSignature where liftCompare = genericLiftCompare
@ -693,9 +597,7 @@ instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexSignature instance Evaluatable IndexSignature
data AbstractMethodSignature a = AbstractMethodSignature { _abstractMethodSignatureContext :: ![a], _abstractMethodSignatureName :: !a, _abstractMethodSignatureParameters :: ![a] } data AbstractMethodSignature a = AbstractMethodSignature { _abstractMethodSignatureContext :: ![a], _abstractMethodSignatureName :: !a, _abstractMethodSignatureParameters :: ![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 ToJSONFields1 AbstractMethodSignature
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
@ -703,9 +605,7 @@ instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPre
instance Evaluatable AbstractMethodSignature instance Evaluatable AbstractMethodSignature
data Debugger a = Debugger data Debugger a = Debugger
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 ToJSONFields1 Debugger
instance Eq1 Debugger where liftEq = genericLiftEq instance Eq1 Debugger where liftEq = genericLiftEq
instance Ord1 Debugger where liftCompare = genericLiftCompare instance Ord1 Debugger where liftCompare = genericLiftCompare
@ -713,9 +613,7 @@ instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Debugger instance Evaluatable Debugger
data ForOf a = ForOf { _forOfBinding :: !a, _forOfSubject :: !a, _forOfBody :: !a } data ForOf a = ForOf { _forOfBinding :: !a, _forOfSubject :: !a, _forOfBody :: !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 ToJSONFields1 ForOf
instance Eq1 ForOf where liftEq = genericLiftEq instance Eq1 ForOf where liftEq = genericLiftEq
instance Ord1 ForOf where liftCompare = genericLiftCompare instance Ord1 ForOf where liftCompare = genericLiftCompare
@ -723,9 +621,7 @@ instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ForOf instance Evaluatable ForOf
data This a = This data This a = This
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 ToJSONFields1 This
instance Eq1 This where liftEq = genericLiftEq instance Eq1 This where liftEq = genericLiftEq
instance Ord1 This where liftCompare = genericLiftCompare instance Ord1 This where liftCompare = genericLiftCompare
@ -733,9 +629,7 @@ instance Show1 This where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable This instance Evaluatable This
data LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: !a, _labeledStatementSubject :: !a } data LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: !a, _labeledStatementSubject :: !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 ToJSONFields1 LabeledStatement
instance Eq1 LabeledStatement where liftEq = genericLiftEq instance Eq1 LabeledStatement where liftEq = genericLiftEq
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
@ -743,9 +637,7 @@ instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LabeledStatement instance Evaluatable LabeledStatement
newtype Update a = Update { _updateSubject :: a } newtype Update a = Update { _updateSubject :: 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 ToJSONFields1 Update
instance Eq1 Update where liftEq = genericLiftEq instance Eq1 Update where liftEq = genericLiftEq
instance Ord1 Update where liftCompare = genericLiftCompare instance Ord1 Update where liftCompare = genericLiftCompare
@ -753,14 +645,12 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Update instance Evaluatable Update
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } 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 Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Module
instance Evaluatable Module where instance Evaluatable Module where
eval (Module iden xs) = do eval (Module iden xs) = do
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
@ -770,14 +660,12 @@ instance Evaluatable Module where
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] } 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 Eq1 InternalModule where liftEq = genericLiftEq
instance Ord1 InternalModule where liftCompare = genericLiftCompare instance Ord1 InternalModule where liftCompare = genericLiftCompare
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 InternalModule
instance Evaluatable InternalModule where instance Evaluatable InternalModule where
eval (InternalModule iden xs) = do eval (InternalModule iden xs) = do
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) 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 } data ImportAlias a = ImportAlias { _importAliasSubject :: !a, _importAlias :: !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 ToJSONFields1 ImportAlias
instance Eq1 ImportAlias where liftEq = genericLiftEq instance Eq1 ImportAlias where liftEq = genericLiftEq
instance Ord1 ImportAlias where liftCompare = genericLiftCompare instance Ord1 ImportAlias where liftCompare = genericLiftCompare
@ -799,9 +685,7 @@ instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportAlias instance Evaluatable ImportAlias
data Super a = Super data Super a = Super
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 ToJSONFields1 Super
instance Eq1 Super where liftEq = genericLiftEq instance Eq1 Super where liftEq = genericLiftEq
instance Ord1 Super where liftCompare = genericLiftCompare instance Ord1 Super where liftCompare = genericLiftCompare
@ -809,9 +693,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Super instance Evaluatable Super
data Undefined a = Undefined data Undefined a = Undefined
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 ToJSONFields1 Undefined
instance Eq1 Undefined where liftEq = genericLiftEq instance Eq1 Undefined where liftEq = genericLiftEq
instance Ord1 Undefined where liftCompare = genericLiftCompare instance Ord1 Undefined where liftCompare = genericLiftCompare
@ -819,9 +701,7 @@ instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Undefined instance Evaluatable Undefined
data ClassHeritage a = ClassHeritage { _classHeritageExtendsClause :: !a, _implementsClause :: !a } data ClassHeritage a = ClassHeritage { _classHeritageExtendsClause :: !a, _implementsClause :: !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 ToJSONFields1 ClassHeritage
instance Eq1 ClassHeritage where liftEq = genericLiftEq instance Eq1 ClassHeritage where liftEq = genericLiftEq
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
@ -829,7 +709,7 @@ instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassHeritage instance Evaluatable ClassHeritage
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, _abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a } 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 Eq1 AbstractClass where liftEq = genericLiftEq
instance Ord1 AbstractClass where liftCompare = genericLiftCompare instance Ord1 AbstractClass where liftCompare = genericLiftCompare
@ -837,8 +717,6 @@ instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec
instance Declarations a => Declarations (AbstractClass a) where instance Declarations a => Declarations (AbstractClass a) where
declaredName AbstractClass{..} = declaredName abstractClassIdentifier declaredName AbstractClass{..} = declaredName abstractClassIdentifier
instance ToJSONFields1 AbstractClass
instance Evaluatable AbstractClass where instance Evaluatable AbstractClass where
eval AbstractClass{..} = do eval AbstractClass{..} = do
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm abstractClassIdentifier) 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 } data JsxElement a = JsxElement { _jsxOpeningElement :: !a, _jsxElements :: ![a], _jsxClosingElement :: !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 ToJSONFields1 JsxElement
instance Eq1 JsxElement where liftEq = genericLiftEq instance Eq1 JsxElement where liftEq = genericLiftEq
instance Ord1 JsxElement where liftCompare = genericLiftCompare instance Ord1 JsxElement where liftCompare = genericLiftCompare
@ -861,9 +737,7 @@ instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxElement instance Evaluatable JsxElement
newtype JsxText a = JsxText ByteString newtype JsxText a = JsxText 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 ToJSONFields1 JsxText
instance Eq1 JsxText where liftEq = genericLiftEq instance Eq1 JsxText where liftEq = genericLiftEq
instance Ord1 JsxText where liftCompare = genericLiftCompare instance Ord1 JsxText where liftCompare = genericLiftCompare
@ -871,9 +745,7 @@ instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxText instance Evaluatable JsxText
newtype JsxExpression a = JsxExpression { _jsxExpression :: a } newtype JsxExpression a = JsxExpression { _jsxExpression :: 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 ToJSONFields1 JsxExpression
instance Eq1 JsxExpression where liftEq = genericLiftEq instance Eq1 JsxExpression where liftEq = genericLiftEq
instance Ord1 JsxExpression where liftCompare = genericLiftCompare instance Ord1 JsxExpression where liftCompare = genericLiftCompare
@ -881,9 +753,7 @@ instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxExpression instance Evaluatable JsxExpression
data JsxOpeningElement a = JsxOpeningElement { _jsxOpeningElementIdentifier :: !a, _jsxAttributes :: ![a] } data JsxOpeningElement a = JsxOpeningElement { _jsxOpeningElementIdentifier :: !a, _jsxAttributes :: ![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 ToJSONFields1 JsxOpeningElement
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
@ -891,9 +761,7 @@ instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxOpeningElement instance Evaluatable JsxOpeningElement
newtype JsxClosingElement a = JsxClosingElement { _jsxClosingElementIdentifier :: a } newtype JsxClosingElement a = JsxClosingElement { _jsxClosingElementIdentifier :: 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 ToJSONFields1 JsxClosingElement
instance Eq1 JsxClosingElement where liftEq = genericLiftEq instance Eq1 JsxClosingElement where liftEq = genericLiftEq
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
@ -901,9 +769,7 @@ instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxClosingElement instance Evaluatable JsxClosingElement
data JsxSelfClosingElement a = JsxSelfClosingElement { _jsxSelfClosingElementIdentifier :: !a, _jsxSelfClosingElementAttributes :: ![a] } data JsxSelfClosingElement a = JsxSelfClosingElement { _jsxSelfClosingElementIdentifier :: !a, _jsxSelfClosingElementAttributes :: ![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 ToJSONFields1 JsxSelfClosingElement
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
@ -911,9 +777,7 @@ instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxSelfClosingElement instance Evaluatable JsxSelfClosingElement
data JsxAttribute a = JsxAttribute { _jsxAttributeTarget :: !a, _jsxAttributeValue :: !a } data JsxAttribute a = JsxAttribute { _jsxAttributeTarget :: !a, _jsxAttributeValue :: !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 ToJSONFields1 JsxAttribute
instance Eq1 JsxAttribute where liftEq = genericLiftEq instance Eq1 JsxAttribute where liftEq = genericLiftEq
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
@ -921,9 +785,7 @@ instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxAttribute instance Evaluatable JsxAttribute
newtype ImplementsClause a = ImplementsClause { _implementsClauseTypes :: [a] } newtype ImplementsClause a = ImplementsClause { _implementsClauseTypes :: [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 ToJSONFields1 ImplementsClause
instance Eq1 ImplementsClause where liftEq = genericLiftEq instance Eq1 ImplementsClause where liftEq = genericLiftEq
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
@ -931,9 +793,7 @@ instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImplementsClause instance Evaluatable ImplementsClause
data OptionalParameter a = OptionalParameter { _optionalParameterContext :: ![a], _optionalParameterSubject :: !a } data OptionalParameter a = OptionalParameter { _optionalParameterContext :: ![a], _optionalParameterSubject :: !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 ToJSONFields1 OptionalParameter
instance Eq1 OptionalParameter where liftEq = genericLiftEq instance Eq1 OptionalParameter where liftEq = genericLiftEq
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
@ -941,9 +801,7 @@ instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable OptionalParameter instance Evaluatable OptionalParameter
data RequiredParameter a = RequiredParameter { _requiredParameterContext :: ![a], _requiredParameterSubject :: !a } data RequiredParameter a = RequiredParameter { _requiredParameterContext :: ![a], _requiredParameterSubject :: !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 ToJSONFields1 RequiredParameter
instance Eq1 RequiredParameter where liftEq = genericLiftEq instance Eq1 RequiredParameter where liftEq = genericLiftEq
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
@ -951,9 +809,7 @@ instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RequiredParameter instance Evaluatable RequiredParameter
data RestParameter a = RestParameter { _restParameterContext :: ![a], _restParameterSubject :: !a } data RestParameter a = RestParameter { _restParameterContext :: ![a], _restParameterSubject :: !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 ToJSONFields1 RestParameter
instance Eq1 RestParameter where liftEq = genericLiftEq instance Eq1 RestParameter where liftEq = genericLiftEq
instance Ord1 RestParameter where liftCompare = genericLiftCompare instance Ord1 RestParameter where liftCompare = genericLiftCompare
@ -961,9 +817,7 @@ instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RestParameter instance Evaluatable RestParameter
newtype JsxFragment a = JsxFragment [a] newtype JsxFragment a = JsxFragment [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 ToJSONFields1 JsxFragment
instance Eq1 JsxFragment where liftEq = genericLiftEq instance Eq1 JsxFragment where liftEq = genericLiftEq
instance Ord1 JsxFragment where liftCompare = genericLiftCompare instance Ord1 JsxFragment where liftCompare = genericLiftCompare
@ -971,9 +825,7 @@ instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxFragment instance Evaluatable JsxFragment
data JsxNamespaceName a = JsxNamespaceName a a data JsxNamespaceName a = JsxNamespaceName 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 ToJSONFields1 JsxNamespaceName
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare

View File

@ -1,6 +1,7 @@
module Semantic.CLI.Spec (spec) where module Semantic.CLI.Spec (spec) where
import Control.Monad (when) import Control.Monad (when)
import qualified Data.ByteString as B
import Data.ByteString.Builder import Data.ByteString.Builder
import Data.Foldable (for_) import Data.Foldable (for_)
import Semantic.CLI import Semantic.CLI
@ -24,38 +25,30 @@ spec = parallel $ do
output <- runTask $ readBlobs (Right files) >>= runParse output <- runTask $ readBlobs (Right files) >>= runParse
runBuilder output `shouldBe'` expected runBuilder output `shouldBe'` expected
where where
shouldBe' actual expected = do shouldBe' actual' expectedFile = do
when (actual /= expected) $ print actual let actual = verbatim actual'
expected <- verbatim <$> B.readFile expectedFile
actual `shouldBe` expected actual `shouldBe` expected
parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], ByteString)] parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], FilePath)]
parseFixtures = parseFixtures =
[ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, pathMode, sExpressionParseTreeOutput) [ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, path, "test/fixtures/ruby/corpus/and-or.parseA.txt")
, (show JSONTermRenderer, runParse JSONTermRenderer, pathMode, jsonParseTreeOutput) , (show JSONTermRenderer, runParse JSONTermRenderer, path, prefix </> "parse-tree.json")
, (show JSONTermRenderer, runParse JSONTermRenderer, pathMode', jsonParseTreeOutput') , (show JSONTermRenderer, runParse JSONTermRenderer, path', prefix </> "parse-trees.json")
, (show JSONTermRenderer, runParse JSONTermRenderer, [], emptyJsonParseTreeOutput) , (show JSONTermRenderer, runParse JSONTermRenderer, [], prefix </> "parse-tree-empty.json")
, (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], symbolsOutput) , (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), path'', prefix </> "parse-tree.symbols.json")
, (show TagsTermRenderer, runParse TagsTermRenderer, [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], tagsOutput) , (show TagsTermRenderer, runParse TagsTermRenderer, path'', prefix </> "parse-tree.tags.json")
] ]
where pathMode = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby)] where path = [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)] 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" diffFixtures :: [(String, [BlobPair] -> TaskEff Builder, [Both File], FilePath)]
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 = diffFixtures =
[ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, jsonOutput) [ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, prefix </> "diff-tree.json")
, (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, sExpressionOutput) , (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, "test/fixtures/ruby/corpus/method-declaration.diffA-B.txt")
, (show ToCDiffRenderer, runDiff ToCDiffRenderer, pathMode, tocOutput) , (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))] 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))]
prefix = "test/fixtures/cli"
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"

View File

@ -18,6 +18,6 @@ spec = parallel $ do
it "renders with the specified renderer" $ do it "renders with the specified renderer" $ do
output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [methodsBlob] output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [methodsBlob]
output `shouldBe` "(Program\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n" output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n"
where where
methodsBlob = Blob "def foo\nend\n" "methods.rb" (Just Ruby) methodsBlob = Blob "def foo\nend\n" "methods.rb" (Just Ruby)

198
test/fixtures/cli/diff-tree.json vendored Normal file
View File

@ -0,0 +1,198 @@
{
"diffs": [
{
"diff":
{
"merge":
{
"term": "Statements",
"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
View 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":
{}
}

View File

@ -0,0 +1,3 @@
{
"trees": []
}

74
test/fixtures/cli/parse-tree.json vendored Normal file
View File

@ -0,0 +1,74 @@
{
"trees": [
{
"tree":
{
"term": "Statements",
"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"
}]
}

View 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
View 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
View File

@ -0,0 +1,234 @@
{
"trees": [
{
"tree":
{
"term": "Statements",
"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": "Statements",
"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"
}]
}

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -17,27 +17,39 @@
->(Integer) }) ->(Integer) })
{ (Identifier) { (Identifier)
->(Identifier) }))) ->(Identifier) })))
(Statements {+(Statements
(Type {+(Type
{ (Identifier) {+(Identifier)+}
->(Identifier) } {+(Array
(Array {+(Integer)+}
{ (Integer) {+(Array
->(Integer) } {+(Integer)+}
(Array {+(Identifier)+})+})+})+})+}
{ (Integer) {+(Statements
->(Integer) } {+(Type
(Identifier))))) {+(Identifier)+}
(Statements {+(Array
(Type {+(Integer)+}
{ (Identifier) {+(Array
->(Identifier) } {+(Integer)+}
(Array {+(Array
{ (Integer) {+(Integer)+}
->(Integer) } {+(Identifier)+})+})+})+})+})+}
(Array {-(Statements
(Integer) {-(Type
(Array {-(Identifier)-}
{ (Integer) {-(Array
->(Integer) } {-(Integer)-}
(Identifier))))))))) {-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-})-})))

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -17,27 +17,39 @@
->(Integer) }) ->(Integer) })
{ (Identifier) { (Identifier)
->(Identifier) }))) ->(Identifier) })))
(Statements {+(Statements
(Type {+(Type
{ (Identifier) {+(Identifier)+}
->(Identifier) } {+(Array
(Array {+(Integer)+}
{ (Integer) {+(Array
->(Integer) } {+(Integer)+}
(Array {+(Identifier)+})+})+})+})+}
{ (Integer) {+(Statements
->(Integer) } {+(Type
(Identifier))))) {+(Identifier)+}
(Statements {+(Array
(Type {+(Integer)+}
{ (Identifier) {+(Array
->(Identifier) } {+(Integer)+}
(Array {+(Array
{ (Integer) {+(Integer)+}
->(Integer) } {+(Identifier)+})+})+})+})+})+}
(Array {-(Statements
(Integer) {-(Type
(Array {-(Identifier)-}
{ (Integer) {-(Array
->(Integer) } {-(Integer)-}
(Identifier))))))))) {-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-})-})))

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -35,11 +35,15 @@
{+(Plus {+(Plus
{+(Identifier)+} {+(Identifier)+}
{+(Integer)+})+})+} {+(Integer)+})+})+}
{+(Assignment (Assignment
{ (Identifier)
->(Identifier) }
{ (Times
{-(Identifier)-}
{-(Integer)-})
->(LShift
{+(Identifier)+} {+(Identifier)+}
{+(LShift {+(Integer)+}) })
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment {+(Assignment
{+(Identifier)+} {+(Identifier)+}
{+(RShift {+(RShift
@ -78,11 +82,6 @@
{+(KeyValue {+(KeyValue
{+(Identifier)+} {+(Identifier)+}
{+(Integer)+})+})+})+})+})+})+} {+(Integer)+})+})+})+})+})+})+}
{-(Assignment
{-(Identifier)-}
{-(Times
{-(Identifier)-}
{-(Integer)-})-})-}
{-(Assignment {-(Assignment
{-(Identifier)-} {-(Identifier)-}
{-(Plus {-(Plus

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -22,17 +22,13 @@
->(Identifier) } ->(Identifier) }
{ (Identifier) { (Identifier)
->(Identifier) })) ->(Identifier) }))
(Equal {+(Equal
{ (Identifier) {+(Identifier)+}
->(Identifier) } {+(Identifier)+})+}
{ (Identifier) {+(Not
->(Identifier) }) {+(Equal
(Not {+(Identifier)+}
(Equal {+(Identifier)+})+})+}
{ (Identifier)
->(Identifier) }
{ (Identifier)
->(Identifier) }))
{+(LessThan {+(LessThan
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+} {+(Identifier)+})+}
@ -78,6 +74,13 @@
{+(BAnd {+(BAnd
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+} {+(Identifier)+})+}
{-(Equal
{-(Identifier)-}
{-(Identifier)-})-}
{-(Not
{-(Equal
{-(Identifier)-}
{-(Identifier)-})-})-}
{-(LessThan {-(LessThan
{-(Identifier)-} {-(Identifier)-}
{-(Identifier)-})-} {-(Identifier)-})-}

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -22,17 +22,13 @@
->(Identifier) } ->(Identifier) }
{ (Identifier) { (Identifier)
->(Identifier) })) ->(Identifier) }))
(Equal {+(Equal
{ (Identifier) {+(Identifier)+}
->(Identifier) } {+(Identifier)+})+}
{ (Identifier) {+(Not
->(Identifier) }) {+(Equal
(Not {+(Identifier)+}
(Equal {+(Identifier)+})+})+}
{ (Identifier)
->(Identifier) }
{ (Identifier)
->(Identifier) }))
{+(LessThan {+(LessThan
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+} {+(Identifier)+})+}
@ -78,6 +74,13 @@
{+(BAnd {+(BAnd
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+} {+(Identifier)+})+}
{-(Equal
{-(Identifier)-}
{-(Identifier)-})-}
{-(Not
{-(Equal
{-(Identifier)-}
{-(Identifier)-})-})-}
{-(LessThan {-(LessThan
{-(Identifier)-} {-(Identifier)-}
{-(Identifier)-})-} {-(Identifier)-})-}

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -21,20 +21,14 @@
(Identifier) (Identifier)
(Identifier)) (Identifier))
(Empty)) (Empty))
{+(Call (Call
{+(Identifier)+} { (Identifier)
{+(Statements ->(Identifier) }
{+(Identifier)+} (Statements
{+(Variadic (Identifier)
{+(Identifier)+})+})+} (Variadic
{+(Empty)+})+} (Identifier)))
{-(Call (Empty))
{-(Identifier)-}
{-(Statements
{-(Identifier)-}
{-(Variadic
{-(Identifier)-})-})-}
{-(Empty)-})-}
{-(Call {-(Call
{-(Identifier)-} {-(Identifier)-}
{-(Statements)-} {-(Statements)-}

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -21,19 +21,15 @@
(Identifier) (Identifier)
(Identifier)) (Identifier))
(Empty)) (Empty))
{+(Call
{+(Identifier)+}
{+(Statements
{+(Identifier)+}
{+(Variadic
{+(Identifier)+})+})+}
{+(Empty)+})+}
(Call (Call
{ (Identifier) { (Identifier)
->(Identifier) } ->(Identifier) }
(Statements
(Identifier)
(Variadic
(Identifier)))
(Empty))
{+(Call
{+(Identifier)+}
{+(Statements)+} {+(Statements)+}
{-(Statements {+(Empty)+})+})))
{-(Identifier)-}
{-(Variadic
{-(Identifier)-})-})-}
(Empty)))))

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -18,15 +18,11 @@
{+(Constructor {+(Constructor
{+(Empty)+} {+(Empty)+}
{+(Statements)+})+})+})+})+} {+(Statements)+})+})+})+})+}
(Type {+(Type
{ (Identifier) {+(Identifier)+}
->(Identifier) } {+(SendChannel
{ (BidirectionalChannel
{-(ReceiveChannel
{-(Identifier)-})-})
->(SendChannel
{+(ReceiveChannel {+(ReceiveChannel
{+(Identifier)+})+}) }) {+(Identifier)+})+})+})+}
{+(Type {+(Type
{+(Identifier)+} {+(Identifier)+}
{+(ReceiveChannel {+(ReceiveChannel
@ -38,6 +34,11 @@
{+(Parenthesized {+(Parenthesized
{+(ReceiveChannel {+(ReceiveChannel
{+(Identifier)+})+})+})+})+} {+(Identifier)+})+})+})+})+}
{-(Type
{-(Identifier)-}
{-(BidirectionalChannel
{-(ReceiveChannel
{-(Identifier)-})-})-})-}
{-(Type {-(Type
{-(Identifier)-} {-(Identifier)-}
{-(SendChannel {-(SendChannel

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -6,20 +6,15 @@
(Identifier) (Identifier)
(Statements) (Statements)
(Statements (Statements
{+(Assignment
{+(Identifier)+}
{+(Identifier)+})+}
(Assignment (Assignment
{ (Identifier) { (Identifier)
->(Identifier) } ->(Identifier) }
(Identifier))
(Assignment
{ (Identifier) { (Identifier)
->(Statements) }) ->(Identifier) }
{+(Assignment (Statements))
{+(Identifier)+} (Assignment
{+(Statements)+})+} { (Identifier)
{-(Assignment ->(Identifier) }
{-(Identifier)-} (Statements)))))
{-(Statements)-})-}
{-(Assignment
{-(Identifier)-}
{-(Statements)-})-})))

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function
@ -6,20 +6,15 @@
(Identifier) (Identifier)
(Statements) (Statements)
(Statements (Statements
{+(Assignment
{+(Identifier)+}
{+(Identifier)+})+}
(Assignment (Assignment
{ (Identifier) { (Identifier)
->(Identifier) } ->(Identifier) }
(Identifier))
(Assignment
{ (Identifier) { (Identifier)
->(Statements) }) ->(Identifier) }
{+(Assignment (Statements))
{+(Identifier)+} (Assignment
{+(Statements)+})+} { (Identifier)
{-(Assignment ->(Identifier) }
{-(Identifier)-} (Statements)))))
{-(Statements)-})-}
{-(Assignment
{-(Identifier)-}
{-(Statements)-})-})))

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

View File

@ -1,4 +1,4 @@
(Program (Statements
(Package (Package
(Identifier)) (Identifier))
(Function (Function

Some files were not shown because too many files have changed in this diff Show More