mirror of
https://github.com/github/semantic.git
synced 2024-12-19 21:01:35 +03:00
Give explicit (generic) definitions of liftPretty for all the syntax types.
This commit is contained in:
parent
13df366dcd
commit
622a7b714a
@ -111,10 +111,11 @@ instance Pretty1 Leaf where
|
||||
liftPretty _ _ (Leaf s) = pretty ("Leaf" :: String) <+> prettyBytes s
|
||||
|
||||
newtype Branch a = Branch { branchElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Branch where liftEq = genericLiftEq
|
||||
instance Show1 Branch where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Branch where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Common
|
||||
@ -130,20 +131,22 @@ instance Pretty1 Identifier where
|
||||
liftPretty _ _ (Identifier s) = pretty ("Identifier" :: String) <+> prettyBytes s
|
||||
|
||||
newtype Program a = Program [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Program where liftEq = genericLiftEq
|
||||
instance Show1 Program where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Program where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | Empty syntax, with essentially no-op semantics.
|
||||
--
|
||||
-- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'.
|
||||
data Empty a = Empty
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Empty where liftEq _ _ _ = True
|
||||
instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty"
|
||||
instance Pretty1 Empty where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | Syntax representing a parsing or assignment error.
|
||||
@ -164,10 +167,11 @@ unError span Error{..} = Error.withCallStack (freezeCallStack (fromCallSiteList
|
||||
|
||||
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Context where liftEq = genericLiftEq
|
||||
instance Show1 Context where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Context where liftPretty = genericLiftPretty
|
||||
|
||||
prettyBytes :: ByteString -> Doc ann
|
||||
prettyBytes = pretty . decodeUtf8With (\ _ -> ('\xfffd' <$))
|
||||
|
@ -9,79 +9,89 @@ import Data.Functor.Classes.Show.Generic
|
||||
import GHC.Generics
|
||||
|
||||
data Function a = Function { functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Function where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: How should we represent function types, where applicable?
|
||||
|
||||
data Method a = Method { methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Method where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: Should we replace this with Function and differentiate by context?
|
||||
-- TODO: How should we distinguish class/instance methods?
|
||||
|
||||
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Variable where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
data Class a = Class { classIdentifier :: !a, classSuperclasses :: ![a], classBody :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Class where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleScope :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Module where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | A decorator in Python
|
||||
data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Decorator where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: Generics, constraints.
|
||||
|
||||
|
||||
-- | An ADT, i.e. a disjoint sum of products, like 'data' in Haskell, or 'enum' in Rust or Swift.
|
||||
data Datatype a = Datatype { datatypeName :: !a, datatypeConstructors :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
|
||||
instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Data.Syntax.Declaration.Datatype where liftPretty = genericLiftPretty
|
||||
|
||||
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
|
||||
data Constructor a = Constructor { constructorName :: !a, constructorFields :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
||||
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Data.Syntax.Declaration.Constructor where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | Comprehension (e.g. ((a for b in c if a()) in Python)
|
||||
data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Comprehension where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | Import declarations.
|
||||
data Import a = Import { importContent :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Import where liftPretty = genericLiftPretty
|
||||
|
@ -10,10 +10,11 @@ import GHC.Generics
|
||||
|
||||
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
|
||||
data Call a = Call { callFunction :: !a, callParams :: ![a], callBlock :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Call where liftEq = genericLiftEq
|
||||
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Call where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
data Comparison a
|
||||
@ -23,10 +24,11 @@ data Comparison a
|
||||
| GreaterThanEqual !a !a
|
||||
| Equal !a !a
|
||||
| Comparison !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Comparison where liftEq = genericLiftEq
|
||||
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Comparison where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | Binary arithmetic operators.
|
||||
@ -38,20 +40,22 @@ data Arithmetic a
|
||||
| Modulo !a !a
|
||||
| Power !a !a
|
||||
| Negate !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Arithmetic where liftEq = genericLiftEq
|
||||
instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Arithmetic where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Boolean operators.
|
||||
data Boolean a
|
||||
= Or !a !a
|
||||
| And !a !a
|
||||
| Not !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Boolean where liftEq = genericLiftEq
|
||||
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Boolean where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Bitwise operators.
|
||||
data Bitwise a
|
||||
@ -61,39 +65,44 @@ data Bitwise a
|
||||
| LShift !a !a
|
||||
| RShift !a !a
|
||||
| Complement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Bitwise where liftEq = genericLiftEq
|
||||
instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Bitwise where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Member Access (e.g. a.b)
|
||||
data MemberAccess a
|
||||
= MemberAccess !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 MemberAccess where liftEq = genericLiftEq
|
||||
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 MemberAccess where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Subscript (e.g a[1])
|
||||
data Subscript a
|
||||
= Subscript !a ![a]
|
||||
| Member !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Subscript where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Enumeration (e.g. a[1:10:1] in Python (start at index 1, stop at index 10, step 1 element from start to stop))
|
||||
data Enumeration a = Enumeration { enumerationStart :: !a, enumerationEnd :: !a, enumerationStep :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Enumeration where liftEq = genericLiftEq
|
||||
instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Enumeration where liftPretty = genericLiftPretty
|
||||
|
||||
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
|
||||
data ScopeResolution a
|
||||
= ScopeResolution ![a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 ScopeResolution where liftPretty = genericLiftPretty
|
||||
|
@ -14,7 +14,7 @@ import Prelude
|
||||
-- Boolean
|
||||
|
||||
newtype Boolean a = Boolean Bool
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
true :: Boolean a
|
||||
true = Boolean True
|
||||
@ -24,6 +24,7 @@ false = Boolean False
|
||||
|
||||
instance Eq1 Boolean where liftEq = genericLiftEq
|
||||
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Boolean where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Numeric
|
||||
@ -76,19 +77,21 @@ instance Pretty1 Complex where
|
||||
-- Strings, symbols
|
||||
|
||||
newtype String a = String { stringElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
|
||||
instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Data.Syntax.Literal.String where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: Should string literal bodies include escapes too?
|
||||
|
||||
-- | An interpolation element within a string literal.
|
||||
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 InterpolationElement where liftEq = genericLiftEq
|
||||
instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 InterpolationElement where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | A sequence of textual contents within a string literal.
|
||||
@ -102,10 +105,11 @@ instance Pretty1 TextElement where
|
||||
liftPretty _ _ (TextElement s) = pretty ("TextElement" :: Prelude.String) <+> prettyBytes s
|
||||
|
||||
data Null a = Null
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Null where liftEq = genericLiftEq
|
||||
instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Null where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Symbol a = Symbol { symbolContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
@ -124,38 +128,42 @@ instance Pretty1 Symbol where
|
||||
-- Collections
|
||||
|
||||
newtype Array a = Array { arrayElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Array where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Hash where liftEq = genericLiftEq
|
||||
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Pretty1 Hash where liftPretty = genericLiftPretty
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 KeyValue where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a]}
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Tuple where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
newtype Set a = Set { setElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Set where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”?
|
||||
-- TODO: Function literals (lambdas, procs, anonymous functions, what have you).
|
||||
|
@ -7,60 +7,69 @@ import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Pretty.Generic
|
||||
import Data.Functor.Classes.Show.Generic
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Text.Encoding (decodeUtf8With)
|
||||
import GHC.Generics
|
||||
|
||||
|
||||
newtype Document a = Document [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Document where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Block elements
|
||||
|
||||
newtype Paragraph a = Paragraph [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Paragraph where liftEq = genericLiftEq
|
||||
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Paragraph where liftPretty = genericLiftPretty
|
||||
|
||||
data Section a = Section { sectionLevel :: Int, sectionHeading :: a, sectionContent :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Section where liftEq = genericLiftEq
|
||||
instance Show1 Section where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Section where liftPretty = genericLiftPretty
|
||||
|
||||
data Heading a = Heading { headingLevel :: Int, headingContent :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Heading where liftPretty = genericLiftPretty
|
||||
|
||||
newtype UnorderedList a = UnorderedList [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 UnorderedList where liftEq = genericLiftEq
|
||||
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 UnorderedList where liftPretty = genericLiftPretty
|
||||
|
||||
newtype OrderedList a = OrderedList [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 OrderedList where liftEq = genericLiftEq
|
||||
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 OrderedList where liftPretty = genericLiftPretty
|
||||
|
||||
newtype BlockQuote a = BlockQuote [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 BlockQuote where liftEq = genericLiftEq
|
||||
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 BlockQuote where liftPretty = genericLiftPretty
|
||||
|
||||
data ThematicBreak a = ThematicBreak
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 ThematicBreak where liftEq = genericLiftEq
|
||||
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 ThematicBreak where liftPretty = genericLiftPretty
|
||||
|
||||
data HTMLBlock a = HTMLBlock ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
@ -72,37 +81,42 @@ instance Pretty1 HTMLBlock where
|
||||
liftPretty _ _ (HTMLBlock s) = pretty ("HTMLBlock" :: String) <+> prettyBytes s
|
||||
|
||||
newtype Table a = Table [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Table where liftPretty = genericLiftPretty
|
||||
|
||||
newtype TableRow a = TableRow [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 TableRow where liftPretty = genericLiftPretty
|
||||
|
||||
newtype TableCell a = TableCell [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 TableCell where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Inline elements
|
||||
|
||||
newtype Strong a = Strong [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Strong where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Emphasis a = Emphasis [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Emphasis where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
@ -136,18 +150,22 @@ data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString
|
||||
|
||||
instance Eq1 Code where liftEq = genericLiftEq
|
||||
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Code where
|
||||
liftPretty _ _ (Code l c) = nest 2 (vsep (catMaybes [Just (pretty ("Code" :: String)), fmap prettyBytes l, Just (prettyBytes c)]))
|
||||
|
||||
data LineBreak a = LineBreak
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 LineBreak where liftEq = genericLiftEq
|
||||
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 LineBreak where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Strikethrough a = Strikethrough [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Strikethrough where liftEq = genericLiftEq
|
||||
instance Show1 Strikethrough where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Strikethrough where liftPretty = genericLiftPretty
|
||||
|
||||
prettyBytes :: ByteString -> Doc ann
|
||||
prettyBytes = pretty . decodeUtf8With (\ _ -> ('\xfffd' <$))
|
||||
|
@ -10,156 +10,178 @@ import GHC.Generics
|
||||
|
||||
-- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted.
|
||||
data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 If where liftEq = genericLiftEq
|
||||
instance Show1 If where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 If where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python.
|
||||
data Else a = Else { elseCondition :: !a, elseBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Else where liftEq = genericLiftEq
|
||||
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Else where liftPretty = genericLiftPretty
|
||||
|
||||
-- TODO: Alternative definition would flatten if/else if/else chains: data If a = If ![(a, a)] !(Maybe a)
|
||||
|
||||
-- | A pattern-matching or computed jump control-flow statement, like 'switch' in C or JavaScript, or 'case' in Ruby or Haskell.
|
||||
data Match a = Match { matchSubject :: !a, matchPatterns :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Match where liftPretty = genericLiftPretty
|
||||
|
||||
-- | A pattern in a pattern-matching or computed jump control-flow statement, like 'case' in C or JavaScript, 'when' in Ruby, or the left-hand side of '->' in the body of Haskell 'case' expressions.
|
||||
data Pattern a = Pattern { pattern :: !a, patternBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Pattern where liftEq = genericLiftEq
|
||||
instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Pattern where liftPretty = genericLiftPretty
|
||||
|
||||
-- | A let statement or local binding, like 'a as b' or 'let a = b'.
|
||||
data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Let where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Assignment
|
||||
|
||||
-- | Assignment to a variable or other lvalue.
|
||||
data Assignment a = Assignment { assignmentTarget :: !a, assignmentValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Assignment where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Returns
|
||||
|
||||
newtype Return a = Return a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Return where liftEq = genericLiftEq
|
||||
instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Return where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Yield a = Yield a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Yield where liftEq = genericLiftEq
|
||||
instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Yield where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Break a = Break a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Break where liftEq = genericLiftEq
|
||||
instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Break where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Continue a = Continue a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Continue where liftEq = genericLiftEq
|
||||
instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Continue where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Retry a = Retry a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Retry where liftEq = genericLiftEq
|
||||
instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Retry where liftPretty = genericLiftPretty
|
||||
|
||||
newtype NoOp a = NoOp a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 NoOp where liftEq = genericLiftEq
|
||||
instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 NoOp where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Loops
|
||||
|
||||
data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 For where liftEq = genericLiftEq
|
||||
instance Show1 For where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 For where liftPretty = genericLiftPretty
|
||||
|
||||
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 ForEach where liftEq = genericLiftEq
|
||||
instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 ForEach where liftPretty = genericLiftPretty
|
||||
|
||||
data While a = While { whileCondition :: !a, whileBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 While where liftEq = genericLiftEq
|
||||
instance Show1 While where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 While where liftPretty = genericLiftPretty
|
||||
|
||||
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 DoWhile where liftEq = genericLiftEq
|
||||
instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 DoWhile where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- Exception handling
|
||||
|
||||
newtype Throw a = Throw a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Throw where liftEq = genericLiftEq
|
||||
instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Throw where liftPretty = genericLiftPretty
|
||||
|
||||
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Try where liftEq = genericLiftEq
|
||||
instance Show1 Try where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Try where liftPretty = genericLiftPretty
|
||||
|
||||
data Catch a = Catch { catchException :: !a, catchBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Catch where liftEq = genericLiftEq
|
||||
instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Catch where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Finally a = Finally a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Finally where liftEq = genericLiftEq
|
||||
instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Finally where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl).
|
||||
newtype ScopeEntry a = ScopeEntry [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 ScopeEntry where liftEq = genericLiftEq
|
||||
instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 ScopeEntry where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
-- | ScopeExit (e.g. `END {}` block in Ruby or Perl).
|
||||
newtype ScopeExit a = ScopeExit [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 ScopeExit where liftPretty = genericLiftPretty
|
||||
|
@ -9,13 +9,15 @@ import Data.Functor.Classes.Show.Generic
|
||||
import GHC.Generics
|
||||
|
||||
data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Annotation where liftPretty = genericLiftPretty
|
||||
|
||||
newtype Product a = Product { productElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Product where liftEq = genericLiftEq
|
||||
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Product where liftPretty = genericLiftPretty
|
||||
|
@ -90,17 +90,19 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
||||
|
||||
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||
data Ellipsis a = Ellipsis
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Ellipsis where liftPretty = genericLiftPretty
|
||||
|
||||
|
||||
data Redirect a = Redirect !a !a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Pretty1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Redirect where liftEq = genericLiftEq
|
||||
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Pretty1 Redirect where liftPretty = genericLiftPretty
|
||||
|
||||
-- | Assignment from AST in Python's grammar onto a program in Python's syntax.
|
||||
assignment :: Assignment
|
||||
|
Loading…
Reference in New Issue
Block a user