mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Merge pull request #1933 from github/haskell-assignment
Haskell assignment #5
This commit is contained in:
commit
c04f3179e4
@ -194,7 +194,7 @@ instance Evaluatable Data.Syntax.Declaration.Datatype
|
||||
|
||||
|
||||
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
|
||||
data Constructor a = Constructor { constructorName :: !a, constructorFields :: !a }
|
||||
data Constructor a = Constructor { constructorContext :: a, constructorName :: a, constructorFields :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
||||
|
@ -316,7 +316,7 @@ sliceType :: Assignment
|
||||
sliceType = makeTerm <$> symbol SliceType <*> children (Type.Slice <$> expression)
|
||||
|
||||
structType :: Assignment
|
||||
structType = makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> expressions)
|
||||
structType = makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> emptyTerm <*> expressions)
|
||||
|
||||
typeAlias :: Assignment
|
||||
typeAlias = makeTerm <$> symbol TypeAlias <*> children (Declaration.TypeAlias [] <$> expression <*> expression)
|
||||
|
@ -33,6 +33,7 @@ type Syntax = '[
|
||||
, Literal.Float
|
||||
, Literal.Integer
|
||||
, Literal.TextElement
|
||||
, Syntax.AnnotatedTypeVariable
|
||||
, Syntax.Class
|
||||
, Syntax.Context
|
||||
, Syntax.Context'
|
||||
@ -41,15 +42,25 @@ type Syntax = '[
|
||||
, Syntax.Error
|
||||
, Syntax.Field
|
||||
, Syntax.FunctionConstructor
|
||||
, Syntax.FunctionType
|
||||
, Syntax.GADT
|
||||
, Syntax.GADTConstructor
|
||||
, Syntax.Identifier
|
||||
, Syntax.Kind
|
||||
, Syntax.KindFunctionType
|
||||
, Syntax.KindListType
|
||||
, Syntax.KindSignature
|
||||
, Syntax.ListConstructor
|
||||
, Syntax.Module
|
||||
, Syntax.Pragma
|
||||
, Syntax.QualifiedTypeConstructorIdentifier
|
||||
, Syntax.RecordDataConstructor
|
||||
, Syntax.Star
|
||||
, Syntax.StrictType
|
||||
, Syntax.StrictTypeVariable
|
||||
, Syntax.TupleConstructor
|
||||
, Syntax.Type
|
||||
, Syntax.TypeSignature
|
||||
, Syntax.TypeSynonym
|
||||
, Syntax.UnitConstructor
|
||||
, Type.TypeParameters
|
||||
@ -63,68 +74,34 @@ type Assignment' a = HasCallStack => Assignment.Assignment [] Grammar a
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ module' <|> parseError
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm
|
||||
<$> symbol Module
|
||||
<*> children (Syntax.Module <$> (moduleIdentifier <|> emptyTerm) <*> pure [] <*> (where' <|> expressions <|> emptyTerm))
|
||||
|
||||
|
||||
expressions :: Assignment
|
||||
expressions = makeTerm'' <$> location <*> many expression
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
|
||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices = [
|
||||
algebraicDatatypeDeclaration
|
||||
, character
|
||||
, comment
|
||||
, context'
|
||||
, constructorIdentifier
|
||||
, derivingClause
|
||||
, float
|
||||
, functionConstructor
|
||||
, functionDeclaration
|
||||
, integer
|
||||
, listConstructor
|
||||
, listExpression
|
||||
, listType
|
||||
, moduleIdentifier
|
||||
, strictType
|
||||
, string
|
||||
, type'
|
||||
, typeConstructorIdentifier
|
||||
, typeSynonymDeclaration
|
||||
, typeVariableIdentifier
|
||||
, tuplingConstructor
|
||||
, unitConstructor
|
||||
, variableIdentifier
|
||||
, where'
|
||||
]
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize (comment <|> pragma) (postContextualize (comment <|> pragma) term)
|
||||
|
||||
algebraicDatatypeDeclaration :: Assignment
|
||||
algebraicDatatypeDeclaration = makeTerm
|
||||
<$> symbol AlgebraicDatatypeDeclaration
|
||||
<*> children (Declaration.Datatype
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> (makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParameters))
|
||||
<*> (makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParameters <*> (kindSignature <|> emptyTerm)))
|
||||
<*> ((symbol Constructors *> children (many constructor))
|
||||
<|> pure [])
|
||||
<*> (derivingClause <|> emptyTerm))
|
||||
|
||||
annotatedTypeVariable :: Assignment
|
||||
annotatedTypeVariable = makeTerm <$> symbol AnnotatedTypeVariable <*> children (Syntax.AnnotatedTypeVariable <$> typeVariableIdentifier <* token Annotation <*> (kind <|> type'))
|
||||
|
||||
character :: Assignment
|
||||
character = makeTerm <$> symbol Char <*> (Literal.Character <$> source)
|
||||
|
||||
class' :: Assignment
|
||||
class' = makeTerm <$> symbol Class <*> children (Syntax.Class <$> typeConstructor <*> typeParameters)
|
||||
|
||||
comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
constructor :: Assignment
|
||||
constructor = (makeTerm <$> symbol DataConstructor <*> children (Declaration.Constructor <$> typeConstructor <*> typeParameters))
|
||||
constructor = (makeTerm <$> symbol DataConstructor <*> children (Declaration.Constructor <$> (context' <|> emptyTerm) <*> typeConstructor <*> typeParameters))
|
||||
<|> (makeTerm <$> symbol RecordDataConstructor <*> children (Syntax.RecordDataConstructor <$> constructorIdentifier <*> fields))
|
||||
|
||||
class' :: Assignment
|
||||
class' = makeTerm <$> symbol Class <*> children (Syntax.Class <$> typeConstructor <*> typeParameters)
|
||||
constructorIdentifier :: Assignment
|
||||
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
context' :: Assignment
|
||||
context' = makeTerm <$> symbol Context <*> children (Syntax.Context' <$> many (type' <|> contextPattern))
|
||||
@ -135,35 +112,64 @@ contextPattern = symbol ContextPattern *> children type'
|
||||
derivingClause :: Assignment
|
||||
derivingClause = makeTerm <$> symbol Deriving <*> children (Syntax.Deriving <$> many typeConstructor)
|
||||
|
||||
expressions :: Assignment
|
||||
expressions = makeTerm'' <$> location <*> many expression
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
|
||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices = [
|
||||
algebraicDatatypeDeclaration
|
||||
, annotatedTypeVariable
|
||||
, character
|
||||
, comment
|
||||
, context'
|
||||
, constructorIdentifier
|
||||
, derivingClause
|
||||
, float
|
||||
, functionConstructor
|
||||
, functionDeclaration
|
||||
, functionType
|
||||
, gadtConstructor
|
||||
, gadtDeclaration
|
||||
, integer
|
||||
, kind
|
||||
, kindSignature
|
||||
, listConstructor
|
||||
, listExpression
|
||||
, listType
|
||||
, moduleIdentifier
|
||||
, qualifiedTypeConstructorIdentifier
|
||||
, star
|
||||
, strictType
|
||||
, string
|
||||
, type'
|
||||
, typeConstructorIdentifier
|
||||
, typeSignature
|
||||
, typeSynonymDeclaration
|
||||
, typeVariableIdentifier
|
||||
, tuplingConstructor
|
||||
, unitConstructor
|
||||
, variableIdentifier
|
||||
, where'
|
||||
]
|
||||
|
||||
fields :: Assignment
|
||||
fields = makeTerm <$> symbol Fields <*> children (many field)
|
||||
|
||||
field :: Assignment
|
||||
field = makeTerm <$> symbol Field <*> children (Syntax.Field <$> variableIdentifiers <* token Annotation <*> term type')
|
||||
field = makeTerm
|
||||
<$> symbol Field
|
||||
<*> children (Syntax.Field
|
||||
<$> variableIdentifiers
|
||||
<* token Annotation
|
||||
<*> fieldType)
|
||||
where
|
||||
fieldType = makeTerm <$> location <*> (Syntax.Type <$> term (type' <|> typeVariableIdentifier) <*> typeParameters <*> (kindSignature <|> emptyTerm))
|
||||
|
||||
variableIdentifier :: Assignment
|
||||
variableIdentifier = makeTerm <$> symbol VariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
variableIdentifiers :: Assignment
|
||||
variableIdentifiers = makeTerm <$> location <*> many variableIdentifier
|
||||
|
||||
constructorIdentifier :: Assignment
|
||||
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
moduleIdentifier :: Assignment
|
||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
typeClassIdentifier :: Assignment
|
||||
typeClassIdentifier = makeTerm <$> symbol TypeClassIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
typeConstructorIdentifier :: Assignment
|
||||
typeConstructorIdentifier = makeTerm <$> symbol TypeConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
typeVariableIdentifier :: Assignment
|
||||
typeVariableIdentifier = makeTerm <$> symbol TypeVariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
where' :: Assignment
|
||||
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (many expression)
|
||||
float :: Assignment
|
||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||
|
||||
functionBody :: Assignment
|
||||
functionBody = makeTerm <$> symbol FunctionBody <*> children (many expression)
|
||||
@ -180,18 +186,52 @@ functionDeclaration = makeTerm
|
||||
<*> (manyTermsTill expression (symbol FunctionBody) <|> pure [])
|
||||
<*> functionBody)
|
||||
|
||||
functionType :: Assignment
|
||||
functionType = makeTerm <$> symbol FunctionType <*> children (Syntax.FunctionType <$> type' <*> type')
|
||||
|
||||
gadtConstructor :: Assignment
|
||||
gadtConstructor = makeTerm
|
||||
<$> symbol GadtConstructor
|
||||
<*> children (Syntax.GADTConstructor
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> typeConstructor
|
||||
<* token Annotation
|
||||
<*> term type')
|
||||
|
||||
gadtDeclaration :: Assignment
|
||||
gadtDeclaration = makeTerm
|
||||
<$> symbol GadtDeclaration
|
||||
<*> children (Syntax.GADT
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> (makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParameters' <*> (kindSignature <|> emptyTerm)))
|
||||
<*> where')
|
||||
where
|
||||
typeParameters' = makeTerm <$> location <*> manyTermsTill expression (symbol KindSignature <|> symbol Where')
|
||||
|
||||
integer :: Assignment
|
||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||
|
||||
kind :: Assignment
|
||||
kind = kind'
|
||||
<|> kindFunctionType
|
||||
<|> kindListType
|
||||
<|> star
|
||||
|
||||
kind' :: Assignment
|
||||
kind' = makeTerm <$> symbol Kind <*> children (Syntax.Kind <$> kind)
|
||||
|
||||
kindFunctionType :: Assignment
|
||||
kindFunctionType = makeTerm <$> symbol KindFunctionType <*> children (Syntax.KindFunctionType <$> kind <*> kind)
|
||||
|
||||
kindListType :: Assignment
|
||||
kindListType = makeTerm <$> symbol KindListType <*> children (Syntax.KindListType <$> kind)
|
||||
|
||||
kindSignature :: Assignment
|
||||
kindSignature = makeTerm <$> symbol KindSignature <*> children (Syntax.KindSignature <$ token Annotation <*> kind)
|
||||
|
||||
listConstructor :: Assignment
|
||||
listConstructor = makeTerm <$> token ListConstructor <*> pure Syntax.ListConstructor
|
||||
|
||||
pragma :: Assignment
|
||||
pragma = makeTerm <$> symbol Pragma <*> (Syntax.Pragma <$> source)
|
||||
|
||||
unitConstructor :: Assignment
|
||||
unitConstructor = makeTerm <$> token UnitConstructor <*> pure Syntax.UnitConstructor
|
||||
|
||||
listExpression :: Assignment
|
||||
listExpression = makeTerm <$> symbol ListExpression <*> children (Literal.Array <$> many listElement)
|
||||
where listElement = symbol Expression *> children expression
|
||||
@ -199,12 +239,46 @@ listExpression = makeTerm <$> symbol ListExpression <*> children (Literal.Array
|
||||
listType :: Assignment
|
||||
listType = makeTerm <$> symbol ListType <*> children (Literal.Array <$> many type')
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm
|
||||
<$> symbol Module
|
||||
<*> children (Syntax.Module <$> (moduleIdentifier <|> emptyTerm) <*> pure [] <*> (where' <|> expressions <|> emptyTerm))
|
||||
|
||||
moduleIdentifier :: Assignment
|
||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
parenthesizedTypePattern :: Assignment
|
||||
parenthesizedTypePattern = symbol ParenthesizedTypePattern *> children typeParameters
|
||||
|
||||
pragma :: Assignment
|
||||
pragma = makeTerm <$> symbol Pragma <*> (Syntax.Pragma <$> source)
|
||||
|
||||
qualifiedTypeConstructorIdentifier :: Assignment
|
||||
qualifiedTypeConstructorIdentifier = makeTerm <$> symbol QualifiedTypeConstructorIdentifier <*> children (Syntax.QualifiedTypeConstructorIdentifier <$> many expression)
|
||||
|
||||
star :: Assignment
|
||||
star = makeTerm <$> token Star <*> pure Syntax.Star
|
||||
|
||||
strictType :: Assignment
|
||||
strictType = makeTerm' <$> symbol StrictType <*> children ((inject <$> (Syntax.StrictType <$> typeConstructor <*> typeParameters))
|
||||
<|> (inject <$> (Syntax.StrictTypeVariable <$> typeVariableIdentifier)))
|
||||
strictType = makeTerm'
|
||||
<$> symbol StrictType
|
||||
<*> children ( (inject <$> (Syntax.StrictType <$> typeConstructor <*> typeParameters))
|
||||
<|> (inject <$> (Syntax.StrictTypeVariable <$> typeVariableIdentifier)))
|
||||
|
||||
string :: Assignment
|
||||
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||
|
||||
typeClassIdentifier :: Assignment
|
||||
typeClassIdentifier = makeTerm <$> symbol TypeClassIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
typeConstructorIdentifier :: Assignment
|
||||
typeConstructorIdentifier = makeTerm <$> symbol TypeConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
typeSignature :: Assignment
|
||||
typeSignature = makeTerm <$> symbol TypeSignature <*> children (Syntax.TypeSignature <$> variableIdentifier <* token Annotation <*> type')
|
||||
|
||||
typeVariableIdentifier :: Assignment
|
||||
typeVariableIdentifier = makeTerm <$> symbol TypeVariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
tuplingConstructor :: Assignment
|
||||
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> rawSource)
|
||||
@ -212,30 +286,32 @@ tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity
|
||||
where tupleWithArity = Syntax.TupleConstructor . succ . count ','
|
||||
|
||||
type' :: Assignment
|
||||
type' = (makeTerm <$> symbol Type <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
|
||||
<|> (makeTerm <$> symbol TypePattern <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
|
||||
type' = class'
|
||||
<|> fields
|
||||
<|> functionType
|
||||
<|> parenthesizedTypePattern
|
||||
<|> strictType
|
||||
<|> type''
|
||||
<|> typeConstructor
|
||||
<|> class'
|
||||
<|> typePattern
|
||||
|
||||
type'' :: Assignment
|
||||
type'' = makeTerm
|
||||
<$> symbol Type
|
||||
<*> children (Syntax.Type <$> (typeConstructor <|> typeVariableIdentifier <|> type') <*> typeParameters <*> (kindSignature <|> emptyTerm))
|
||||
|
||||
typeParameters :: Assignment
|
||||
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> many expression)
|
||||
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> (manyTermsTill expression (symbol Annotation) <|> many expression))
|
||||
|
||||
float :: Assignment
|
||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||
|
||||
character :: Assignment
|
||||
character = makeTerm <$> symbol Char <*> (Literal.Character <$> source)
|
||||
|
||||
string :: Assignment
|
||||
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||
typePattern :: Assignment
|
||||
typePattern = makeTerm <$> symbol TypePattern <*> children (Syntax.Type <$> typeConstructor <*> typeParameters <*> (kindSignature <|> emptyTerm))
|
||||
|
||||
typeConstructor :: Assignment
|
||||
typeConstructor = constructorIdentifier
|
||||
<|> functionConstructor
|
||||
<|> listConstructor
|
||||
<|> listType
|
||||
<|> qualifiedTypeConstructorIdentifier
|
||||
<|> typeClassIdentifier
|
||||
<|> typeConstructorIdentifier
|
||||
<|> tuplingConstructor
|
||||
@ -246,10 +322,27 @@ typeSynonymDeclaration = makeTerm
|
||||
<$> symbol TypeSynonymDeclaration
|
||||
<*> children (Syntax.TypeSynonym <$> typeLeft <*> typeRight)
|
||||
where
|
||||
typeLeft = makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParametersLeft)
|
||||
typeLeft = makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParametersLeft <*> (kindSignature <|> emptyTerm))
|
||||
typeParametersLeft = makeTerm <$> location <*> (Type.TypeParameters <$> manyTill expression (symbol TypeSynonymBody))
|
||||
typeRight = symbol TypeSynonymBody *> children type'
|
||||
|
||||
unitConstructor :: Assignment
|
||||
unitConstructor = makeTerm <$> token UnitConstructor <*> pure Syntax.UnitConstructor
|
||||
|
||||
variableIdentifier :: Assignment
|
||||
variableIdentifier = makeTerm <$> symbol VariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
variableIdentifiers :: Assignment
|
||||
variableIdentifiers = makeTerm <$> location <*> many variableIdentifier
|
||||
|
||||
where' :: Assignment
|
||||
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (many expression)
|
||||
|
||||
-- | Helpers
|
||||
|
||||
-- | Match a series of terms or comments until a delimiter is matched.
|
||||
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTermsTill step = manyTill (step <|> comment)
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize (comment <|> pragma) (postContextualize (comment <|> pragma) term)
|
||||
|
@ -37,7 +37,7 @@ instance Show1 StrictTypeVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable StrictTypeVariable
|
||||
|
||||
data Type a = Type { typeIdentifier :: !a, typeParameters :: !a }
|
||||
data Type a = Type { typeIdentifier :: a, typeParameters :: a, typeKindSignature :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
@ -144,3 +144,102 @@ instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Class
|
||||
|
||||
data GADT a = GADT { gadtContext :: a, gadtName :: a, gadtConstructors :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GADT where liftEq = genericLiftEq
|
||||
instance Ord1 GADT where liftCompare = genericLiftCompare
|
||||
instance Show1 GADT where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable GADT
|
||||
|
||||
data GADTConstructor a = GADTConstructor { gadtConstructorContext :: a, gadtConstructorName :: a, gadtConstructorTypeSignature :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GADTConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 GADTConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 GADTConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable GADTConstructor
|
||||
|
||||
data FunctionType a = FunctionType { functionTypeLeft :: a, functionTypeRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionType
|
||||
|
||||
data TypeSignature a = TypeSignature { typeSignatureName :: a, typeSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeSignature
|
||||
|
||||
newtype KindSignature a = KindSignature { kindSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KindSignature where liftEq = genericLiftEq
|
||||
instance Ord1 KindSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 KindSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KindSignature
|
||||
|
||||
data KindFunctionType a = KindFunctionType { kindFunctionTypeLeft :: a, kindFunctionTypeRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KindFunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 KindFunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindFunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KindFunctionType
|
||||
|
||||
newtype Kind a = Kind { kindKind :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Kind where liftEq = genericLiftEq
|
||||
instance Ord1 Kind where liftCompare = genericLiftCompare
|
||||
instance Show1 Kind where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Kind
|
||||
|
||||
newtype KindListType a = KindListType { kindListTypeKind :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KindListType where liftEq = genericLiftEq
|
||||
instance Ord1 KindListType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindListType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KindListType
|
||||
|
||||
data Star a = Star
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Star where liftEq = genericLiftEq
|
||||
instance Ord1 Star where liftCompare = genericLiftCompare
|
||||
instance Show1 Star where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Star
|
||||
|
||||
newtype QualifiedTypeConstructorIdentifier a = QualifiedTypeConstructorIdentifier { qualifiedTypeConstructorIdentifierName :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedTypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedTypeConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedTypeConstructorIdentifier
|
||||
|
||||
data AnnotatedTypeVariable a = AnnotatedTypeVariable { annotatedTypeVariableIdentifier :: a, annotatedTypeVariableannotation :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AnnotatedTypeVariable where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedTypeVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotatedTypeVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AnnotatedTypeVariable
|
||||
|
@ -16,6 +16,7 @@
|
||||
{+(SendChannel
|
||||
{+(SendChannel
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Statements)+})+})+})+})+}
|
||||
{+(Type
|
||||
@ -44,6 +45,7 @@
|
||||
{-(SendChannel
|
||||
{-(SendChannel
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Statements)-})-})-})-})-}
|
||||
{-(Type
|
||||
|
@ -16,6 +16,7 @@
|
||||
{+(SendChannel
|
||||
{+(SendChannel
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Statements)+})+})+})+})+}
|
||||
{+(Type
|
||||
@ -44,6 +45,7 @@
|
||||
{-(SendChannel
|
||||
{-(SendChannel
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Statements)-})-})-})-})-}
|
||||
{-(Type
|
||||
|
@ -16,6 +16,7 @@
|
||||
(SendChannel
|
||||
(SendChannel
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements)))))
|
||||
(Type
|
||||
|
@ -16,6 +16,7 @@
|
||||
(SendChannel
|
||||
(SendChannel
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements)))))
|
||||
(Type
|
||||
|
@ -9,6 +9,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -9,6 +9,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -9,6 +9,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -9,6 +9,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -22,6 +22,7 @@
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
{ (Identifier)
|
||||
|
@ -22,6 +22,7 @@
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
{ (Identifier)
|
||||
|
@ -21,6 +21,7 @@
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -21,6 +21,7 @@
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
|
@ -11,6 +11,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements))))
|
||||
(Statements
|
||||
@ -18,6 +19,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -27,6 +29,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -38,6 +41,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -11,6 +11,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements))))
|
||||
(Statements
|
||||
@ -18,6 +19,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -27,6 +29,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -38,6 +41,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -10,12 +10,14 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements))))
|
||||
(Statements
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -24,6 +26,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -34,6 +37,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -10,12 +10,14 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements))))
|
||||
(Statements
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -24,6 +26,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Field
|
||||
(Identifier)
|
||||
@ -34,6 +37,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -30,6 +30,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -30,6 +30,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -23,6 +23,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -23,6 +23,7 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Field
|
||||
|
@ -23,3 +23,6 @@ data N = N deriving (Eq, Ord, Enum, Bounded, Show, Read)
|
||||
data Show a => N a = N a
|
||||
data (Eq a, Show a, Eq b) => N a b = N a b
|
||||
data (Eq (f a), Functor f) => N f a = N f a
|
||||
|
||||
data Foo bar = HasCallStack => Foo bar
|
||||
data Baz foo = Show foo => Baz foo
|
||||
|
@ -23,3 +23,6 @@ data N = N deriving (Functor, Ord, Enum, Bounded, Show, Read)
|
||||
data Monad a => N a = N a
|
||||
data (Ord a, Show a, Eq b) => N a b = N a b
|
||||
data (Eq (f a), Applicative f) => N f a = N f a
|
||||
|
||||
data Foo bar = HasCallStack => Wiz bar
|
||||
data Baz a = Show a => Baz a
|
||||
|
@ -6,7 +6,8 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
@ -14,8 +15,10 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -27,8 +30,10 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -42,8 +47,10 @@
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -55,38 +62,40 @@
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
{+(Constructor
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
(Constructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
{+(Constructor
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
{-(Constructor
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
(Empty))
|
||||
@ -95,7 +104,8 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -103,14 +113,18 @@
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -119,14 +133,18 @@
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -134,104 +152,140 @@
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Context
|
||||
(Pragma)
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Type
|
||||
(Context
|
||||
(Pragma)
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
{-(Datatype
|
||||
{-(Empty)-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(RecordDataConstructor
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Field
|
||||
{-(Statements
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-})-})-}
|
||||
{-(RecordDataConstructor
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Field
|
||||
{-(Statements
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-})-})-}
|
||||
{-(Empty)-})-}
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
{+(Datatype
|
||||
{+(Empty)+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(RecordDataConstructor
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Field
|
||||
{+(Statements
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
{+(RecordDataConstructor
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Field
|
||||
{+(Statements
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
{+(Empty)+})+}
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -240,8 +294,10 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -262,8 +318,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -287,8 +345,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
@ -311,10 +371,47 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Identifier))
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Class
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Empty))))
|
||||
|
@ -6,7 +6,8 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
@ -14,8 +15,10 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -27,8 +30,10 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -42,8 +47,10 @@
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
@ -56,37 +63,42 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
{+(Constructor
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
(Empty))
|
||||
@ -95,7 +107,8 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -103,14 +116,18 @@
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -119,14 +136,18 @@
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
@ -134,104 +155,140 @@
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Context
|
||||
(Pragma)
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Type
|
||||
(Context
|
||||
(Pragma)
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
{+(Datatype
|
||||
{+(Empty)+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(RecordDataConstructor
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Field
|
||||
{+(Statements
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
{+(RecordDataConstructor
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Field
|
||||
{+(Statements
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
{+(Empty)+})+}
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
{-(Datatype
|
||||
{-(Empty)-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(RecordDataConstructor
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Field
|
||||
{-(Statements
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-})-})-}
|
||||
{-(RecordDataConstructor
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Field
|
||||
{-(Statements
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-})-})-}
|
||||
{-(Empty)-})-}
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -240,8 +297,10 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -262,8 +321,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -287,8 +348,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
@ -311,10 +374,47 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Identifier))
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Class
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Empty))))
|
||||
|
@ -5,15 +5,18 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -23,8 +26,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(StrictTypeVariable
|
||||
@ -36,8 +41,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(StrictTypeVariable
|
||||
@ -48,23 +55,30 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Empty))
|
||||
@ -72,20 +86,25 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
@ -93,95 +112,128 @@
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Context
|
||||
(Pragma)
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Type
|
||||
(Context
|
||||
(Pragma)
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -190,8 +242,10 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -210,8 +264,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -234,8 +290,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
@ -257,10 +315,43 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Class
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
|
@ -5,15 +5,18 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -23,8 +26,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(StrictTypeVariable
|
||||
@ -36,8 +41,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(StrictTypeVariable
|
||||
@ -48,23 +55,30 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Empty))
|
||||
@ -72,20 +86,25 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
@ -93,95 +112,128 @@
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Context
|
||||
(Pragma)
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Type
|
||||
(Context
|
||||
(Pragma)
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Identifier))))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(RecordDataConstructor
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -190,8 +242,10 @@
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(Deriving
|
||||
@ -210,8 +264,10 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
@ -234,8 +290,10 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
@ -257,10 +315,43 @@
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))
|
||||
(Datatype
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Constructor
|
||||
(Context'
|
||||
(Class
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
|
15
test/fixtures/haskell/corpus/gadt-declarations.A.hs
vendored
Normal file
15
test/fixtures/haskell/corpus/gadt-declarations.A.hs
vendored
Normal file
@ -0,0 +1,15 @@
|
||||
data Foo a b c where
|
||||
Baz :: a -> b -> c -> Foo a b c
|
||||
|
||||
data Foo f a where
|
||||
Bar :: { jolo :: Maybe String, runJolo :: f a } -> Foo f a
|
||||
|
||||
data Foo a :: [*] -> * where
|
||||
|
||||
data Number a where
|
||||
Integer :: !Prelude.Integer -> Number Prelude.Integer
|
||||
Ratio :: !Prelude.Rational -> Number Prelude.Rational
|
||||
Decimal :: !Scientific -> Number Scientific
|
||||
|
||||
data Union (r :: [ * -> * ]) (v :: *) where
|
||||
Union :: {-# UNPACK #-} !Int -> t v -> Union r v
|
15
test/fixtures/haskell/corpus/gadt-declarations.B.hs
vendored
Normal file
15
test/fixtures/haskell/corpus/gadt-declarations.B.hs
vendored
Normal file
@ -0,0 +1,15 @@
|
||||
data Bar a b c where
|
||||
Baz :: a -> b -> c -> Bar a b c
|
||||
|
||||
data Bar f a where
|
||||
Baz :: { jolo :: Maybe String, runJolo :: f a } -> Bar f a
|
||||
|
||||
data Bar a :: [*] -> [*] where
|
||||
|
||||
data Number' a where
|
||||
Integer' :: !Prelude.Integer -> Number Prelude.Integer
|
||||
Ratio' :: !Prelude.Rational -> Number Prelude.Rational
|
||||
Decimal' :: !Scientific -> Number Scientific
|
||||
|
||||
data Union (r :: [ * -> * ]) (v :: *) where
|
||||
Union :: {-# UNPACK #-} !Integer -> t v -> Union r v
|
207
test/fixtures/haskell/corpus/gadt-declarations.diffA-B.txt
vendored
Normal file
207
test/fixtures/haskell/corpus/gadt-declarations.diffA-B.txt
vendored
Normal file
@ -0,0 +1,207 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier))
|
||||
(KindSignature
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(Star)))
|
||||
(Kind
|
||||
{ (Star)
|
||||
->(KindListType
|
||||
{+(Star)+}) }))))
|
||||
(Statements))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(Star)))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Context
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))))
|
207
test/fixtures/haskell/corpus/gadt-declarations.diffB-A.txt
vendored
Normal file
207
test/fixtures/haskell/corpus/gadt-declarations.diffB-A.txt
vendored
Normal file
@ -0,0 +1,207 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier))
|
||||
(KindSignature
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(Star)))
|
||||
(Kind
|
||||
{ (KindListType
|
||||
{-(Star)-})
|
||||
->(Star) }))))
|
||||
(Statements))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(Star)))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Context
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))))
|
194
test/fixtures/haskell/corpus/gadt-declarations.parseA.txt
vendored
Normal file
194
test/fixtures/haskell/corpus/gadt-declarations.parseA.txt
vendored
Normal file
@ -0,0 +1,194 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier))
|
||||
(KindSignature
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(Star)))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Statements))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(Star)))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Context
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))))
|
195
test/fixtures/haskell/corpus/gadt-declarations.parseB.txt
vendored
Normal file
195
test/fixtures/haskell/corpus/gadt-declarations.parseB.txt
vendored
Normal file
@ -0,0 +1,195 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Field
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier))
|
||||
(KindSignature
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(Star)))
|
||||
(Kind
|
||||
(KindListType
|
||||
(Star))))))
|
||||
(Statements))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(QualifiedTypeConstructorIdentifier
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Empty))))
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
(GADT
|
||||
(Empty)
|
||||
(Type
|
||||
(Identifier)
|
||||
(Statements
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(AnnotatedTypeVariable
|
||||
(Identifier)
|
||||
(Star)))
|
||||
(Empty))
|
||||
(Statements
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Context
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
(StrictType
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))))))
|
@ -49,10 +49,12 @@
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Float)+})+})+}
|
||||
{+(Function
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Float)+})+})+}
|
||||
(Function
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
{+(Float)+}
|
||||
{-(Integer)-}))
|
||||
{+(Function
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
@ -283,10 +285,6 @@
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
|
2
test/fixtures/haskell/corpus/type-signatures.A.hs
vendored
Normal file
2
test/fixtures/haskell/corpus/type-signatures.A.hs
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
bar :: a -> b -> c -> Int -> Maybe Int
|
||||
bar :: a -> b -> c -> [Int] -> Maybe Int
|
1
test/fixtures/haskell/corpus/type-signatures.B.hs
vendored
Normal file
1
test/fixtures/haskell/corpus/type-signatures.B.hs
vendored
Normal file
@ -0,0 +1 @@
|
||||
foo :: a -> b -> c -> Int -> Maybe Int
|
88
test/fixtures/haskell/corpus/type-signatures.diffA-B.txt
vendored
Normal file
88
test/fixtures/haskell/corpus/type-signatures.diffA-B.txt
vendored
Normal file
@ -0,0 +1,88 @@
|
||||
(Module
|
||||
(Empty)
|
||||
{ (Statements
|
||||
{-(TypeSignature
|
||||
{-(Identifier)-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})-})-})-})-}
|
||||
{-(TypeSignature
|
||||
{-(Identifier)-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Array
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})-})-})-})-})
|
||||
->(TypeSignature
|
||||
{+(Identifier)+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+})+})+}) })
|
88
test/fixtures/haskell/corpus/type-signatures.diffB-A.txt
vendored
Normal file
88
test/fixtures/haskell/corpus/type-signatures.diffB-A.txt
vendored
Normal file
@ -0,0 +1,88 @@
|
||||
(Module
|
||||
(Empty)
|
||||
{ (TypeSignature
|
||||
{-(Identifier)-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})-})-})-})
|
||||
->(Statements
|
||||
{+(TypeSignature
|
||||
{+(Identifier)+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+})+})+})+}
|
||||
{+(TypeSignature
|
||||
{+(Identifier)+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(Array
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+})+})+})+}) })
|
61
test/fixtures/haskell/corpus/type-signatures.parseA.txt
vendored
Normal file
61
test/fixtures/haskell/corpus/type-signatures.parseA.txt
vendored
Normal file
@ -0,0 +1,61 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))))))
|
||||
(TypeSignature
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty)))))))))
|
29
test/fixtures/haskell/corpus/type-signatures.parseB.txt
vendored
Normal file
29
test/fixtures/haskell/corpus/type-signatures.parseB.txt
vendored
Normal file
@ -0,0 +1,29 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(TypeSignature
|
||||
(Identifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))
|
||||
(Empty))))))))
|
@ -5,77 +5,96 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(ListConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
{+(Identifier)+}))
|
||||
{+(Identifier)+})
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
{+(Identifier)+})))
|
||||
{+(Identifier)+})
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(TypeParameters)))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(UnitConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
{-(TypeSynonym
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(TupleConstructor)-}
|
||||
{-(TypeParameters)-})-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-}
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (FunctionConstructor)
|
||||
->(TupleConstructor) }
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
{+(TypeSynonym
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(FunctionConstructor)+}
|
||||
{+(TypeParameters)+})+})+}))
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+}))
|
||||
|
@ -5,77 +5,96 @@
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(ListConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
{-(Identifier)-}))
|
||||
{-(Identifier)-})
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
{-(Identifier)-})))
|
||||
{-(Identifier)-})
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(TypeParameters)))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(UnitConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
{+(TypeSynonym
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(TupleConstructor)+}
|
||||
{+(TypeParameters)+})+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+}
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TupleConstructor)
|
||||
->(FunctionConstructor) }
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
{-(TypeSynonym
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(FunctionConstructor)-}
|
||||
{-(TypeParameters)-})-})-}))
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-}))
|
||||
|
@ -4,63 +4,80 @@
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(ListConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(TypeParameters)))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(UnitConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(FunctionConstructor)
|
||||
(TypeParameters)))))
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
|
@ -4,65 +4,82 @@
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(ListConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters
|
||||
(Identifier))))
|
||||
(TypeParameters)))
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(UnitConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TupleConstructor)
|
||||
(TypeParameters)))
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeSynonym
|
||||
(Type
|
||||
(Identifier)
|
||||
(TypeParameters))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(FunctionConstructor)
|
||||
(TypeParameters)))))
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
|
Loading…
Reference in New Issue
Block a user