1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 14:54:16 +03:00

EvalCollect instances

This commit is contained in:
Timothy Clem 2017-11-22 10:19:22 -08:00
parent ce1581553b
commit 08318707d9
7 changed files with 18 additions and 0 deletions

View File

@ -41,6 +41,11 @@ instance ( Monad m
=> EvalCollect l v m s a (Union fs) where => EvalCollect l v m s a (Union fs) where
evalCollect ev = apply (Proxy :: Proxy (EvalCollect l v m s a)) (evalCollect @l ev) evalCollect ev = apply (Proxy :: Proxy (EvalCollect l v m s a)) (evalCollect @l ev)
instance ( Monad m
, EvalCollect l v m s a s
)
=> EvalCollect l v m s a (TermF s a) where
evalCollect ev In{..} = evalCollect @l ev termOut
class Monad m => MonadGC l a m where class Monad m => MonadGC l a m where
askRoots :: m (Set (Address l a)) askRoots :: m (Set (Address l a))

View File

@ -119,6 +119,7 @@ instance Eq1 Identifier where liftEq = genericLiftEq
instance Ord1 Identifier where liftCompare = genericLiftCompare instance Ord1 Identifier where liftCompare = genericLiftCompare
instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Identifier -- TODO: Implement Eval instance for Identifier
instance (Monad m) => EvalCollect l (Value s a l) m s a Identifier
instance (Monad m) => Eval (Value s a l) m s a Identifier instance (Monad m) => Eval (Value s a l) m s a Identifier
newtype Program a = Program [a] newtype Program a = Program [a]
@ -128,6 +129,7 @@ instance Eq1 Program where liftEq = genericLiftEq
instance Ord1 Program where liftCompare = genericLiftCompare instance Ord1 Program where liftCompare = genericLiftCompare
instance Show1 Program where liftShowsPrec = genericLiftShowsPrec instance Show1 Program where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Program -- TODO: Implement Eval instance for Program
instance (Monad m) => EvalCollect l (Value s a l) m s a Program
instance (Monad m) => Eval (Value s a l) m s a Program where instance (Monad m) => Eval (Value s a l) m s a Program where
eval ev (Program xs) = foldl (\_ a -> ev a) (pure (I PNoOp)) xs eval ev (Program xs) = foldl (\_ a -> ev a) (pure (I PNoOp)) xs
@ -150,6 +152,7 @@ instance Eq1 Empty where liftEq _ _ _ = True
instance Ord1 Empty where liftCompare _ _ _ = EQ instance Ord1 Empty where liftCompare _ _ _ = EQ
instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty" instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty"
-- TODO: Define Value semantics for Empty -- TODO: Define Value semantics for Empty
instance (Monad m) => EvalCollect l (Value s a l) m s a Empty
instance (Monad m) => Eval (Value s a l) m s a Empty where instance (Monad m) => Eval (Value s a l) m s a Empty where
eval _ _ = pure (I PNoOp) eval _ _ = pure (I PNoOp)
@ -162,6 +165,7 @@ instance Eq1 Error where liftEq = genericLiftEq
instance Ord1 Error where liftCompare = genericLiftCompare instance Ord1 Error where liftCompare = genericLiftCompare
instance Show1 Error where liftShowsPrec = genericLiftShowsPrec instance Show1 Error where liftShowsPrec = genericLiftShowsPrec
-- TODO: Define Value semantics for Error -- TODO: Define Value semantics for Error
instance (Monad m) => EvalCollect l (Value s a l) m s a Error
instance (Monad m) => Eval (Value s a l) m s a Error instance (Monad m) => Eval (Value s a l) m s a Error
errorSyntax :: Error.Error String -> [a] -> Error a errorSyntax :: Error.Error String -> [a] -> Error a
@ -197,10 +201,12 @@ instance Diffable Context where
instance Eq1 Context where liftEq = genericLiftEq instance Eq1 Context where liftEq = genericLiftEq
instance Ord1 Context where liftCompare = genericLiftCompare instance Ord1 Context where liftCompare = genericLiftCompare
instance Show1 Context where liftShowsPrec = genericLiftShowsPrec instance Show1 Context where liftShowsPrec = genericLiftShowsPrec
instance (Monad m) => EvalCollect l (Value s a l) m s a Context
instance (Monad m) => Eval (Value s a l) m s a Context where instance (Monad m) => Eval (Value s a l) m s a Context where
eval ev Context{..} = ev contextSubject eval ev Context{..} = ev contextSubject
-- TODO: Find a better place for this -- TODO: Find a better place for this
-- TODO: Define Value semantics for [] -- TODO: Define Value semantics for []
instance Monad m => EvalCollect l (Value s a l) m s a []
instance Monad m => Eval (Value s a l) m s a [] where instance Monad m => Eval (Value s a l) m s a [] where
eval _ _ = pure (I PNoOp) eval _ _ = pure (I PNoOp)

View File

@ -20,6 +20,7 @@ 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 (Monad m) => EvalCollect l (Value s a l) m s a Comment
instance (Monad m) => Eval (Value s a l) m s a Comment instance (Monad m) => Eval (Value s a l) m s a Comment
-- TODO: nested comment types -- TODO: nested comment types

View File

@ -20,6 +20,7 @@ instance Diffable Function where
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 (Monad m) => EvalCollect l (Value s a l) m s a Function
instance (Monad m) => Eval (Value s a l) m s a Function instance (Monad m) => Eval (Value s a l) m s a Function
-- TODO: How should we represent function types, where applicable? -- TODO: How should we represent function types, where applicable?

View File

@ -18,6 +18,7 @@ data Call a = Call { callContext :: ![a], callFunction :: !a, callParams :: ![a]
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 (Monad m) => EvalCollect l (Value s a l) m s a Call
instance (Monad m) => Eval (Value s a l) m s a Call instance (Monad m) => Eval (Value s a l) m s a Call

View File

@ -28,6 +28,7 @@ false = Boolean False
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 (Monad m) => EvalCollect l (Value s a l) m s a Boolean
instance (Monad m) => Eval (Value s a l) m s a Boolean where instance (Monad m) => Eval (Value s a l) m s a Boolean where
eval _ (Boolean x) = pure (I (PBool x)) eval _ (Boolean x) = pure (I (PBool x))
@ -41,6 +42,7 @@ newtype Integer a = Integer { integerContent :: ByteString }
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
instance Show1 Data.Syntax.Literal.Integer where liftShowsPrec = genericLiftShowsPrec instance Show1 Data.Syntax.Literal.Integer where liftShowsPrec = genericLiftShowsPrec
instance (Monad m) => EvalCollect l (Value s a l) m s a Data.Syntax.Literal.Integer
instance (Monad m) => Eval (Value s a l) m s a Data.Syntax.Literal.Integer instance (Monad m) => Eval (Value s a l) m s a Data.Syntax.Literal.Integer
-- TODO: Should IntegerLiteral hold an Integer instead of a ByteString? -- TODO: Should IntegerLiteral hold an Integer instead of a ByteString?
@ -99,6 +101,7 @@ newtype TextElement a = TextElement { textElementContent :: ByteString }
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 (Monad m) => EvalCollect l (Value s a l) m s a TextElement
instance (Monad m) => Eval (Value s a l) m s a TextElement where instance (Monad m) => Eval (Value s a l) m s a TextElement where
eval _ (TextElement x) = pure (I (PString x)) eval _ (TextElement x) = pure (I (PString x))

View File

@ -17,6 +17,7 @@ data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a }
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 (Monad m) => EvalCollect l (Value s a l) m s a Annotation
instance (Monad m) => Eval (Value s a l) m s a Annotation instance (Monad m) => Eval (Value s a l) m s a Annotation
newtype Product a = Product { productElements :: [a] } newtype Product a = Product { productElements :: [a] }