mirror of
https://github.com/github/semantic.git
synced 2024-12-25 07:55:12 +03:00
Merge branch 'master' into grpc-trees
This commit is contained in:
commit
5674357bae
@ -243,7 +243,7 @@ nodeError expected Node{..} = Error nodeSpan expected (Just (Right nodeSymbol))
|
||||
|
||||
firstSet :: (Enum grammar, Ix grammar) => Assignment ast grammar a -> [grammar]
|
||||
firstSet = iterFreer (\ _ (Tracing _ assignment) -> case assignment of
|
||||
Choose table _ _ -> Table.tableAddresses table
|
||||
Choose table _ _ -> Table.tableAddresses table
|
||||
Label child _ -> firstSet child
|
||||
_ -> []) . ([] <$)
|
||||
|
||||
|
@ -142,7 +142,7 @@ instance (Show1 syntax, Show ann1, Show ann2) => Show (Diff syntax ann1 ann2) wh
|
||||
instance Show1 syntax => Show3 (DiffF syntax) where
|
||||
liftShowsPrec3 sp1 sl1 sp2 sl2 spRecur slRecur d diff = case diff of
|
||||
Patch patch -> showsUnaryWith (liftShowsPrec2 (liftShowsPrec2 sp1 sl1 spRecur slRecur) (liftShowList2 sp1 sl1 spRecur slRecur) (liftShowsPrec2 sp2 sl2 spRecur slRecur) (liftShowList2 sp2 sl2 spRecur slRecur)) "Patch" d patch
|
||||
Merge term -> showsUnaryWith (liftShowsPrec2 spBoth slBoth spRecur slRecur) "Merge" d term
|
||||
Merge term -> showsUnaryWith (liftShowsPrec2 spBoth slBoth spRecur slRecur) "Merge" d term
|
||||
where spBoth = liftShowsPrec2 sp1 sl1 sp2 sl2
|
||||
slBoth = liftShowList2 sp1 sl1 sp2 sl2
|
||||
|
||||
|
@ -131,7 +131,7 @@ instance (Ord1 f, GOrd1 g) => GOrd1 (f :.: g) where
|
||||
|
||||
|
||||
instance GShow1 U1 where
|
||||
gliftShowsPrec _ _ _ _ _ = id
|
||||
gliftShowsPrec _ _ _ _ _ = id
|
||||
|
||||
instance GShow1 Par1 where
|
||||
gliftShowsPrec _ sp _ d (Par1 a) = sp d a
|
||||
@ -149,7 +149,7 @@ instance (Constructor c, GShow1Body f) => GShow1 (M1 C c f) where
|
||||
gliftShowsPrec opts sp sl d m = gliftShowsPrecBody opts (conFixity m) (conIsRecord m && optionsUseRecordSyntax opts) (conName m) sp sl d (unM1 m)
|
||||
|
||||
instance GShow1Body U1 where
|
||||
gliftShowsPrecBody _ _ _ conName _ _ _ _ = showString conName
|
||||
gliftShowsPrecBody _ _ _ conName _ _ _ _ = showString conName
|
||||
|
||||
instance (Selector s, GShow1 f) => GShow1Body (M1 S s f) where
|
||||
gliftShowsPrecBody opts _ conIsRecord conName sp sl d m = showParen (d > 10) $ showString conName . showChar ' ' . showBraces conIsRecord (foldr (.) id (gliftShowsPrecAll opts conIsRecord sp sl 11 m))
|
||||
@ -163,7 +163,7 @@ instance (GShow1Body f, GShow1Body g) => GShow1Body (f :*: g) where
|
||||
else foldr (.) id (intersperse (showString " ") (gliftShowsPrecAll opts conIsRecord sp sl 11 (a :*: b)))
|
||||
Infix _ prec -> showParen (d > prec) $ gliftShowsPrec opts sp sl (succ prec) a . showChar ' ' . showString conName . showChar ' ' . gliftShowsPrec opts sp sl (succ prec) b
|
||||
|
||||
gliftShowsPrecAll opts conIsRecord sp sl d (a :*: b) = gliftShowsPrecAll opts conIsRecord sp sl d a <> gliftShowsPrecAll opts conIsRecord sp sl d b
|
||||
gliftShowsPrecAll opts conIsRecord sp sl d (a :*: b) = gliftShowsPrecAll opts conIsRecord sp sl d a <> gliftShowsPrecAll opts conIsRecord sp sl d b
|
||||
|
||||
instance GShow1 f => GShow1 (M1 S c f) where
|
||||
gliftShowsPrec opts sp sl d (M1 a) = gliftShowsPrec opts sp sl d a
|
||||
|
@ -8,7 +8,7 @@ import Data.Term
|
||||
import Prologue
|
||||
|
||||
-- | A single step in a diffing algorithm, parameterized by the types of terms, diffs, and the result of the applicable algorithm.
|
||||
data AlgorithmF term1 term2 result partial where
|
||||
data AlgorithmF term1 term2 result partial where
|
||||
-- | Diff two terms with the choice of algorithm left to the interpreter’s discretion.
|
||||
Diff :: term1 -> term2 -> AlgorithmF term1 term2 result result
|
||||
-- | Diff two terms recursively in O(n) time, resulting in a single diff node.
|
||||
|
@ -19,6 +19,7 @@ import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import qualified Language.Haskell.Syntax as Syntax
|
||||
@ -35,69 +36,134 @@ type Syntax = '[
|
||||
, Literal.Integer
|
||||
, Literal.TextElement
|
||||
, Literal.Tuple
|
||||
, Statement.If
|
||||
, Statement.Match
|
||||
, Statement.Pattern
|
||||
, Syntax.AllConstructors
|
||||
, Syntax.AnnotatedTypeVariable
|
||||
, Syntax.App
|
||||
, Syntax.ArithmeticSequence
|
||||
, Syntax.AsPattern
|
||||
, Syntax.BindPattern
|
||||
, Syntax.CaseGuardPattern
|
||||
, Syntax.Class
|
||||
, Syntax.ConstructorIdentifier
|
||||
, Syntax.ConstructorOperator
|
||||
, Syntax.ConstructorPattern
|
||||
, Syntax.ConstructorSymbol
|
||||
, Syntax.Context
|
||||
, Syntax.Context'
|
||||
, Syntax.CPPDirective
|
||||
, Syntax.DefaultDeclaration
|
||||
, Syntax.DefaultSignature
|
||||
, Syntax.Deriving
|
||||
, Syntax.Do
|
||||
, Syntax.Empty
|
||||
, Syntax.EntityIdentifier
|
||||
, Syntax.Error
|
||||
, Syntax.EqualityConstraint
|
||||
, Syntax.Export
|
||||
, Syntax.ExpressionTypeSignature
|
||||
, Syntax.Field
|
||||
, Syntax.FieldBind
|
||||
, Syntax.FieldPattern
|
||||
, Syntax.Fixity'
|
||||
, Syntax.FunctionalDependency
|
||||
, Syntax.FunctionConstructor
|
||||
, Syntax.FunctionGuardPattern
|
||||
, Syntax.FunctionType
|
||||
, Syntax.GADT
|
||||
, Syntax.GADTConstructor
|
||||
, Syntax.Generator
|
||||
, Syntax.Guard
|
||||
, Syntax.HiddenImport
|
||||
, Syntax.Identifier
|
||||
, Syntax.InfixConstructorIdentifier
|
||||
, Syntax.InfixOperatorApp
|
||||
, Syntax.InfixVariableIdentifier
|
||||
, Syntax.ImplicitParameterIdentifier
|
||||
, Syntax.Import
|
||||
, Syntax.ImportAlias
|
||||
, Syntax.ImportDeclaration
|
||||
, Syntax.InfixDataConstructor
|
||||
, Syntax.InfixOperatorPattern
|
||||
, Syntax.Instance
|
||||
, Syntax.IrrefutablePattern
|
||||
, Syntax.Kind
|
||||
, Syntax.KindFunctionType
|
||||
, Syntax.KindListType
|
||||
, Syntax.KindParenthesizedConstructor
|
||||
, Syntax.KindSignature
|
||||
, Syntax.KindTupleType
|
||||
, Syntax.LabeledConstruction
|
||||
, Syntax.LabeledPattern
|
||||
, Syntax.LabeledUpdate
|
||||
, Syntax.Lambda
|
||||
, Syntax.LambdaCase
|
||||
, Syntax.LeftOperatorSection
|
||||
, Syntax.Let
|
||||
, Syntax.ListComprehension
|
||||
, Syntax.ListConstructor
|
||||
, Syntax.ListPattern
|
||||
, Syntax.Module
|
||||
, Syntax.ModuleExport
|
||||
, Syntax.ModuleIdentifier
|
||||
, Syntax.NamedFieldPun
|
||||
, Syntax.NegativeLiteral
|
||||
, Syntax.NewType
|
||||
, Syntax.Operator
|
||||
, Syntax.OperatorSection
|
||||
, Syntax.PatternGuard
|
||||
, Syntax.Pragma
|
||||
, Syntax.PrefixNegation
|
||||
, Syntax.QualifiedEntityIdentifier
|
||||
, Syntax.PrimitiveConstructorIdentifier
|
||||
, Syntax.PrimitiveVariableIdentifier
|
||||
, Syntax.PromotedTypeOperator
|
||||
, Syntax.QualifiedConstructorIdentifier
|
||||
, Syntax.QualifiedInfixVariableIdentifier
|
||||
, Syntax.QualifiedModuleIdentifier
|
||||
, Syntax.QualifiedImportDeclaration
|
||||
, Syntax.QualifiedTypeClassIdentifier
|
||||
, Syntax.QualifiedTypeConstructorIdentifier
|
||||
, Syntax.QualifiedVariableIdentifier
|
||||
, Syntax.QuasiQuotation
|
||||
, Syntax.QuasiQuotationDeclaration
|
||||
, Syntax.QuasiQuotationExpression
|
||||
, Syntax.QuasiQuotationExpressionBody
|
||||
, Syntax.QuasiQuotationPattern
|
||||
, Syntax.QuasiQuotationQuoter
|
||||
, Syntax.QuasiQuotationType
|
||||
, Syntax.QuotedName
|
||||
, Syntax.RecordDataConstructor
|
||||
, Syntax.RecordWildCards
|
||||
, Syntax.RightOperatorSection
|
||||
, Syntax.ScopedTypeVariables
|
||||
, Syntax.Splice
|
||||
, Syntax.StandaloneDerivingInstance
|
||||
, Syntax.Star
|
||||
, Syntax.StrictPattern
|
||||
, Syntax.StrictType
|
||||
, Syntax.StrictTypeVariable
|
||||
, Syntax.Tuple
|
||||
, Syntax.TupleConstructor
|
||||
, Syntax.TuplePattern
|
||||
, Syntax.Type
|
||||
, Syntax.TypeApp
|
||||
, Syntax.TypeClass
|
||||
, Syntax.TypeClassIdentifier
|
||||
, Syntax.TypeClassInstance
|
||||
, Syntax.TypeConstructorExport
|
||||
, Syntax.TypeConstructorIdentifier
|
||||
, Syntax.TypeFamily
|
||||
, Syntax.TypeInstance
|
||||
, Syntax.TypeOperator
|
||||
, Syntax.TypePattern
|
||||
, Syntax.TypeSignature
|
||||
, Syntax.TypeSynonym
|
||||
, Syntax.TypeVariableIdentifier
|
||||
, Syntax.UnitConstructor
|
||||
, Syntax.VariableIdentifier
|
||||
, Syntax.VariableOperator
|
||||
, Syntax.VariableSymbol
|
||||
, Syntax.ViewPattern
|
||||
, Syntax.Wildcard
|
||||
, Type.TypeParameters
|
||||
, []
|
||||
]
|
||||
@ -115,18 +181,22 @@ algebraicDatatypeDeclaration = makeTerm
|
||||
<*> children (Declaration.Datatype
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> (makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParameters <*> (kindSignature <|> emptyTerm)))
|
||||
<*> ((symbol Constructors *> children (manyTerm constructor))
|
||||
<|> pure [])
|
||||
<*> (derivingClause <|> emptyTerm))
|
||||
<*> (constructors <|> pure [])
|
||||
<*> (term derivingClause <|> emptyTerm))
|
||||
where
|
||||
constructors = symbol Constructors *> children (manyTerm constructor)
|
||||
|
||||
allConstructors :: Assignment
|
||||
allConstructors = makeTerm <$> token AllConstructors <*> pure Syntax.AllConstructors
|
||||
|
||||
alternative :: Assignment
|
||||
alternative = makeTerm <$> symbol Alternative <*> children (Statement.Pattern <$> expression <*> expressions)
|
||||
|
||||
annotatedTypeVariable :: Assignment
|
||||
annotatedTypeVariable = makeTerm <$> symbol AnnotatedTypeVariable <*> children (Syntax.AnnotatedTypeVariable <$> typeVariableIdentifier <* token Annotation <*> (kind <|> type'))
|
||||
annotatedTypeVariable = makeTerm <$> symbol AnnotatedTypeVariable <*> children (Syntax.AnnotatedTypeVariable <$> typeVariableIdentifier <* token Annotation <*> expression)
|
||||
|
||||
app :: Assignment
|
||||
app = makeTerm <$> symbol FunctionApplication <*> children (Syntax.App <$> expression <*> expression)
|
||||
app = makeTerm <$> symbol FunctionApplication <*> children (Syntax.App <$> expression <*> (typeApp <|> emptyTerm) <*> expression)
|
||||
|
||||
arithmeticSequence :: Assignment
|
||||
arithmeticSequence = symbol ArithmeticSequence *> children ( enumFrom
|
||||
@ -134,13 +204,22 @@ arithmeticSequence = symbol ArithmeticSequence *> children ( enumFrom
|
||||
<|> enumFromTo
|
||||
<|> enumFromThenTo)
|
||||
where
|
||||
enumFrom = makeTerm <$> symbol EnumFrom <*> children (Syntax.EnumFrom <$> expression)
|
||||
enumFromThen = makeTerm <$> symbol EnumFromThen <*> children (Syntax.EnumFromThen <$> expression <*> expression)
|
||||
enumFromTo = makeTerm <$> symbol EnumFromTo <*> children (Syntax.EnumFromTo <$> expression <*> expression)
|
||||
enumFromThenTo = makeTerm <$> symbol EnumFromThenTo <*> children (Syntax.EnumFromThenTo <$> expression <*> expression <*> expression)
|
||||
enumFrom = makeTerm <$> symbol EnumFrom <*> children (Syntax.ArithmeticSequence <$> expression <*> pure Nothing <*> pure Nothing)
|
||||
enumFromThen = makeTerm <$> symbol EnumFromThen <*> children (Syntax.ArithmeticSequence <$> expression <*> (fmap Just expression) <*> pure Nothing)
|
||||
enumFromTo = makeTerm <$> symbol EnumFromTo <*> children (Syntax.ArithmeticSequence <$> expression <*> (fmap Just expression) <*> pure Nothing)
|
||||
enumFromThenTo = makeTerm <$> symbol EnumFromThenTo <*> children (Syntax.ArithmeticSequence <$> expression <*> (fmap Just expression) <*> (fmap Just expression))
|
||||
|
||||
asPattern :: Assignment
|
||||
asPattern = makeTerm <$> symbol AsPattern <*> children (Syntax.AsPattern <$> expression <*> expression)
|
||||
|
||||
bindPattern :: Assignment
|
||||
bindPattern = makeTerm <$> symbol BindPattern <*> children (Syntax.BindPattern <$> expression <*> expression)
|
||||
bindPattern = makeTerm <$> symbol BindPattern <*> children (Syntax.BindPattern <$> (manyTermsTill expression (symbol AnonLAngleMinus)) <*> expression)
|
||||
|
||||
case' :: Assignment
|
||||
case' = makeTerm <$> symbol CaseExpression <*> children (Statement.Match <$> expression <*> expressions)
|
||||
|
||||
caseGuardPattern :: Assignment
|
||||
caseGuardPattern = makeTerm <$> symbol CaseGuardPattern <*> children (Syntax.CaseGuardPattern <$> manyTerm expression)
|
||||
|
||||
character :: Assignment
|
||||
character = makeTerm <$> symbol Char <*> (Literal.Character <$> source)
|
||||
@ -151,9 +230,13 @@ class' = makeTerm <$> symbol Class <*> children (Syntax.Class <$> manyTerm expre
|
||||
comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
conditionalExpression :: Assignment
|
||||
conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (Statement.If <$> expression <*> expression <*> expression)
|
||||
|
||||
constructor :: Assignment
|
||||
constructor = (makeTerm <$> symbol DataConstructor <*> children (Declaration.Constructor <$> manyTerm (context' <|> scopedTypeVariables) <*> typeConstructor <*> typeParameters))
|
||||
<|> (makeTerm <$> symbol RecordDataConstructor <*> children (Syntax.RecordDataConstructor <$> constructorIdentifier <*> fields))
|
||||
<|> term (makeTerm <$> symbol RecordDataConstructor <*> children (Syntax.RecordDataConstructor <$> manyTerm (context' <|> scopedTypeVariables) <*> constructorIdentifier <*> (term fields)))
|
||||
<|> term (makeTerm <$> symbol InfixDataConstructor <*> children (Syntax.InfixDataConstructor <$> manyTerm (context' <|> scopedTypeVariables) <*> expression <*> expression <*> expression))
|
||||
|
||||
constructorIdentifier :: Assignment
|
||||
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.ConstructorIdentifier . Name.name <$> source)
|
||||
@ -173,11 +256,17 @@ context' = makeTerm <$> symbol Context <*> children (Syntax.Context' <$> express
|
||||
contextPattern :: Assignment
|
||||
contextPattern = symbol ContextPattern *> children expressions
|
||||
|
||||
cppDirective :: Assignment
|
||||
cppDirective = makeTerm <$> symbol CppDirective <*> (Syntax.CPPDirective <$> source)
|
||||
|
||||
defaultDeclaration :: Assignment
|
||||
defaultDeclaration = makeTerm <$> symbol DefaultDeclaration <*> children (Syntax.DefaultDeclaration <$> manyTerm expression)
|
||||
|
||||
defaultSignature :: Assignment
|
||||
defaultSignature = makeTerm <$> symbol DefaultSignature <*> children (Syntax.DefaultSignature <$> manyTermsTill expression (symbol Annotation) <* token Annotation <*> manyTerm (context' <|> scopedTypeVariables) <*> expressions)
|
||||
|
||||
derivingClause :: Assignment
|
||||
derivingClause = makeTerm <$> symbol Deriving <*> children (Syntax.Deriving <$> manyTerm typeConstructor)
|
||||
derivingClause = makeTerm <$> symbol Deriving <*> children (Syntax.Deriving <$> manyTerm expression)
|
||||
|
||||
do' :: Assignment
|
||||
do' = makeTerm <$> symbol Do <*> children (Syntax.Do <$> manyTerm expression)
|
||||
@ -192,7 +281,7 @@ export :: Assignment
|
||||
export = makeTerm <$> symbol Export <*> children (Syntax.Export <$> expressions)
|
||||
|
||||
expression' :: Assignment
|
||||
expression' = symbol Expression *> children expression
|
||||
expression' = symbol Expression *> children expressions
|
||||
|
||||
expressions :: Assignment
|
||||
expressions = makeTerm'' <$> location <*> manyTerm expression
|
||||
@ -204,66 +293,113 @@ expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices = [
|
||||
algebraicDatatypeDeclaration
|
||||
, allConstructors
|
||||
, alternative
|
||||
, annotatedTypeVariable
|
||||
, app
|
||||
, arithmeticSequence
|
||||
, asPattern
|
||||
, bindPattern
|
||||
, case'
|
||||
, caseGuardPattern
|
||||
, character
|
||||
, class'
|
||||
, comment
|
||||
, conditionalExpression
|
||||
, context'
|
||||
, contextPattern
|
||||
, constructorIdentifier
|
||||
, constructorOperator
|
||||
, constructorPattern
|
||||
, constructorSymbol
|
||||
, cppDirective
|
||||
, defaultDeclaration
|
||||
, defaultSignature
|
||||
, derivingClause
|
||||
, do'
|
||||
, equalityConstraint
|
||||
, expression'
|
||||
, expressionTypeSignature
|
||||
, fields
|
||||
, fieldBind
|
||||
, fieldPattern
|
||||
, fixityDeclaration
|
||||
, float
|
||||
, functionalDependency
|
||||
, functionConstructor
|
||||
, functionDeclaration
|
||||
, functionGuardPattern
|
||||
, functionType
|
||||
, gadtConstructor
|
||||
, gadtDeclaration
|
||||
, generator
|
||||
, guard'
|
||||
, implicitParameterIdentifier
|
||||
, importAlias
|
||||
, importDeclaration
|
||||
, infixConstructorIdentifier
|
||||
, infixOperatorApp
|
||||
, infixOperatorPattern
|
||||
, infixVariableIdentifier
|
||||
, instance'
|
||||
, integer
|
||||
, irrefutablePattern
|
||||
, kind
|
||||
, kindListType
|
||||
, kindFunctionType
|
||||
, kindParenthesizedConstructor
|
||||
, kindSignature
|
||||
, kindTupleType
|
||||
, labeledConstruction
|
||||
, labeledPattern
|
||||
, labeledUpdate
|
||||
, lambda
|
||||
, lambdaCase
|
||||
, letExpression
|
||||
, letStatement
|
||||
, listConstructor
|
||||
, listComprehension
|
||||
, listExpression
|
||||
, listPattern
|
||||
, listType
|
||||
, moduleExport
|
||||
, moduleIdentifier
|
||||
, namedFieldPun
|
||||
, negativeLiteral
|
||||
, newType
|
||||
, operator
|
||||
, operatorSection
|
||||
, parenthesizedConstructorOperator
|
||||
, parenthesizedExpression
|
||||
, parenthesizedPattern
|
||||
, parenthesizedTypePattern
|
||||
, pattern'
|
||||
, patternGuard
|
||||
, pragma
|
||||
, prefixNegation
|
||||
, primitiveConstructorIdentifier
|
||||
, primitiveVariableIdentifier
|
||||
, promotedTypeOperator
|
||||
, qualifiedConstructorIdentifier
|
||||
, qualifiedImportDeclaration
|
||||
, qualifiedInfixVariableIdentifier
|
||||
, qualifiedModuleIdentifier
|
||||
, qualifiedTypeClassIdentifier
|
||||
, qualifiedTypeConstructorIdentifier
|
||||
, qualifiedVariableIdentifier
|
||||
, quasiQuotation
|
||||
, quasiQuotationDeclaration
|
||||
, quasiQuotationExpression
|
||||
, quasiQuotationExpressionBody
|
||||
, quasiQuotationPattern
|
||||
, quasiQuotationQuoter
|
||||
, quasiQuotationType
|
||||
, quotedName
|
||||
, recordWildCards
|
||||
, scopedTypeVariables
|
||||
, splice
|
||||
, standaloneDerivingInstance
|
||||
, star
|
||||
, strictPattern
|
||||
, strictType
|
||||
, string
|
||||
, tuple
|
||||
@ -271,7 +407,13 @@ expressionChoices = [
|
||||
, tupleType
|
||||
, type'
|
||||
, type''
|
||||
, typeApp
|
||||
, typeClass
|
||||
, typeClassIdentifier
|
||||
, typeClassInstance
|
||||
, typeConstructor
|
||||
, typeFamily
|
||||
, typeInstance
|
||||
, typePattern
|
||||
, typeConstructorExport
|
||||
, typeConstructorIdentifier
|
||||
@ -284,9 +426,14 @@ expressionChoices = [
|
||||
, variableIdentifier
|
||||
, variableOperator
|
||||
, variableSymbol
|
||||
, viewPattern
|
||||
, where'
|
||||
, wildcard
|
||||
]
|
||||
|
||||
expressionTypeSignature :: Assignment
|
||||
expressionTypeSignature = makeTerm <$> symbol ExpressionTypeSignature <*> children (Syntax.ExpressionTypeSignature <$> manyTermsTill expression (symbol Annotation) <* token Annotation <*> manyTerm (context' <|> scopedTypeVariables) <*> expressions)
|
||||
|
||||
fields :: Assignment
|
||||
fields = makeTerm <$> symbol Fields <*> children (manyTerm field)
|
||||
|
||||
@ -300,34 +447,49 @@ field = makeTerm
|
||||
where
|
||||
fieldType = makeTerm <$> location <*> (Syntax.Type <$> term (type' <|> typeVariableIdentifier) <*> typeParameters <*> (kindSignature <|> emptyTerm))
|
||||
|
||||
fieldBind :: Assignment
|
||||
fieldBind = makeTerm <$> symbol FieldBind <*> children (Syntax.FieldBind <$> expression <*> expression)
|
||||
|
||||
fieldPattern :: Assignment
|
||||
fieldPattern = makeTerm <$> symbol FieldPattern <*> children (Syntax.FieldPattern <$> expression <*> expressions)
|
||||
|
||||
fixityDeclaration :: Assignment
|
||||
fixityDeclaration = makeTerm <$> symbol FixityDeclaration <*> children (Syntax.Fixity' <$> (integer <|> emptyTerm) <*> manyTerm expression)
|
||||
|
||||
float :: Assignment
|
||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||
|
||||
functionalDependency :: Assignment
|
||||
functionalDependency = makeTerm <$> symbol FunctionalDependency <*> children (Syntax.FunctionalDependency <$> expressions)
|
||||
|
||||
functionBody :: Assignment
|
||||
functionBody = makeTerm <$> symbol FunctionBody <*> children (manyTerm expression)
|
||||
|
||||
functionConstructor :: Assignment
|
||||
functionConstructor = makeTerm <$> token FunctionConstructor <*> pure Syntax.FunctionConstructor
|
||||
functionConstructor = makeTerm <$> token FunctionConstructor <*> pure Syntax.FunctionConstructor
|
||||
|
||||
functionDeclaration :: Assignment
|
||||
functionDeclaration = makeTerm
|
||||
<$> symbol FunctionDeclaration
|
||||
<*> children (Declaration.Function []
|
||||
<$> variableIdentifier
|
||||
<$> term expression
|
||||
<*> (manyTermsTill expression (symbol FunctionBody) <|> pure [])
|
||||
<*> functionBody)
|
||||
|
||||
functionGuardPattern :: Assignment
|
||||
functionGuardPattern = makeTerm <$> symbol FunctionGuardPattern <*> children (Syntax.FunctionGuardPattern <$> manyTerm expression)
|
||||
|
||||
functionType :: Assignment
|
||||
functionType = makeTerm <$> symbol FunctionType <*> children (Syntax.FunctionType <$> type' <*> type')
|
||||
functionType = makeTerm <$> symbol FunctionType <*> children (Syntax.FunctionType <$> expression <*> expression)
|
||||
|
||||
gadtConstructor :: Assignment
|
||||
gadtConstructor = makeTerm
|
||||
<$> symbol GadtConstructor
|
||||
<*> children (Syntax.GADTConstructor
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> typeConstructor
|
||||
<*> expression
|
||||
<* token Annotation
|
||||
<*> term type')
|
||||
<*> expressions)
|
||||
|
||||
gadtDeclaration :: Assignment
|
||||
gadtDeclaration = makeTerm
|
||||
@ -342,12 +504,18 @@ gadtDeclaration = makeTerm
|
||||
generator :: Assignment
|
||||
generator = makeTerm <$> symbol Generator <*> children (Syntax.Generator <$> expression <*> expression)
|
||||
|
||||
guard' :: Assignment
|
||||
guard' = makeTerm <$> symbol Guard <*> children (Syntax.Guard <$> expressions)
|
||||
|
||||
hiddenImport :: Assignment
|
||||
hiddenImport = makeTerm <$> symbol Import <*> children (Syntax.HiddenImport <$> expressions)
|
||||
|
||||
hiddenImportSpec :: Assignment.Assignment [] Grammar [Term]
|
||||
hiddenImportSpec = symbol HiddenImportSpec *> children (manyTerm hiddenImport)
|
||||
|
||||
implicitParameterIdentifier :: Assignment
|
||||
implicitParameterIdentifier = makeTerm <$> symbol ImplicitParameterIdentifier <*> (Syntax.ImplicitParameterIdentifier . Name.name <$> source)
|
||||
|
||||
import' :: Assignment
|
||||
import' = makeTerm <$> symbol Import <*> children (Syntax.Import <$> expressions)
|
||||
|
||||
@ -365,8 +533,14 @@ importDeclaration = makeTerm
|
||||
importSpec :: Assignment.Assignment [] Grammar [Term]
|
||||
importSpec = symbol ImportSpec *> children (manyTerm import')
|
||||
|
||||
inClause :: Assignment
|
||||
inClause = symbol InClause *> children expressions
|
||||
|
||||
infixConstructorIdentifier :: Assignment
|
||||
infixConstructorIdentifier = makeTerm <$> symbol InfixConstructorIdentifier <*> children (Syntax.InfixConstructorIdentifier . Name.name <$> source)
|
||||
|
||||
infixOperatorApp :: Assignment
|
||||
infixOperatorApp = makeTerm <$> symbol InfixOperatorApplication <*> children (Syntax.InfixOperatorApp <$> expression <*> expression <*> expression)
|
||||
infixOperatorApp = makeTerm <$> symbol InfixOperatorApplication <*> children (Syntax.InfixOperatorApp <$> expression <*> (typeApp <|> emptyTerm) <*> expression <*> (expressions <|> emptyTerm))
|
||||
|
||||
infixOperatorPattern :: Assignment
|
||||
infixOperatorPattern = makeTerm <$> symbol InfixOperatorPattern <*> children (Syntax.InfixOperatorPattern <$> expression <*> operator <*> expression)
|
||||
@ -374,26 +548,50 @@ infixOperatorPattern = makeTerm <$> symbol InfixOperatorPattern <*> children (Sy
|
||||
infixVariableIdentifier :: Assignment
|
||||
infixVariableIdentifier = makeTerm <$> symbol InfixVariableIdentifier <*> children (Syntax.InfixVariableIdentifier . Name.name <$> source)
|
||||
|
||||
instance' :: Assignment
|
||||
instance' = makeTerm <$> symbol Instance <*> children (Syntax.Instance <$> expressions)
|
||||
|
||||
integer :: Assignment
|
||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||
|
||||
irrefutablePattern :: Assignment
|
||||
irrefutablePattern = makeTerm <$> symbol IrrefutablePattern <*> children (Syntax.IrrefutablePattern <$> expression)
|
||||
|
||||
kind :: Assignment
|
||||
kind = kind'
|
||||
<|> kindFunctionType
|
||||
<|> kindListType
|
||||
<|> kindParenthesizedConstructor
|
||||
<|> kindSignature
|
||||
<|> kindTupleType
|
||||
<|> star
|
||||
|
||||
kind' :: Assignment
|
||||
kind' = makeTerm <$> symbol Kind <*> children (Syntax.Kind <$> kind)
|
||||
kind' = makeTerm <$> symbol Kind <*> children (Syntax.Kind <$> expression)
|
||||
|
||||
kindFunctionType :: Assignment
|
||||
kindFunctionType = makeTerm <$> symbol KindFunctionType <*> children (Syntax.KindFunctionType <$> kind <*> kind)
|
||||
kindFunctionType = makeTerm <$> symbol KindFunctionType <*> children (Syntax.KindFunctionType <$> expression <*> expression)
|
||||
|
||||
kindListType :: Assignment
|
||||
kindListType = makeTerm <$> symbol KindListType <*> children (Syntax.KindListType <$> kind)
|
||||
kindListType = makeTerm <$> symbol KindListType <*> children (Syntax.KindListType <$> expression)
|
||||
|
||||
kindParenthesizedConstructor :: Assignment
|
||||
kindParenthesizedConstructor = makeTerm <$> symbol KindParenthesizedConstructor <*> children (Syntax.KindParenthesizedConstructor <$> expression)
|
||||
|
||||
kindSignature :: Assignment
|
||||
kindSignature = makeTerm <$> symbol KindSignature <*> children (Syntax.KindSignature <$ token Annotation <*> kind)
|
||||
kindSignature = makeTerm <$> symbol KindSignature <*> children (Syntax.KindSignature <$ token Annotation <*> expression)
|
||||
|
||||
kindTupleType :: Assignment
|
||||
kindTupleType = makeTerm <$> symbol KindTupleType <*> children (Syntax.KindTupleType <$> manyTerm expression)
|
||||
|
||||
labeledConstruction :: Assignment
|
||||
labeledConstruction = makeTerm <$> symbol LabeledConstruction <*> children (Syntax.LabeledConstruction <$> expression <*> manyTerm expression)
|
||||
|
||||
labeledPattern :: Assignment
|
||||
labeledPattern = makeTerm <$> symbol LabeledPattern <*> children (Syntax.LabeledPattern <$> expressions)
|
||||
|
||||
labeledUpdate :: Assignment
|
||||
labeledUpdate = makeTerm <$> symbol LabeledUpdate <*> children (Syntax.LabeledUpdate <$> manyTerm expression)
|
||||
|
||||
lambda :: Assignment
|
||||
lambda = makeTerm <$> symbol Lambda <*> children (Syntax.Lambda <$> lambdaHead <*> lambdaBody)
|
||||
@ -401,6 +599,15 @@ lambda = makeTerm <$> symbol Lambda <*> children (Syntax.Lambda <$> lambdaHead <
|
||||
lambdaHead = symbol LambdaHead *> children expressions
|
||||
lambdaBody = symbol LambdaBody *> children expressions
|
||||
|
||||
lambdaCase :: Assignment
|
||||
lambdaCase = makeTerm <$> symbol LambdaCase <*> children (Syntax.LambdaCase <$> manyTerm expression)
|
||||
|
||||
letExpression :: Assignment
|
||||
letExpression = makeTerm <$> symbol LetExpression <*> children (Syntax.Let <$> manyTermsTill expression (symbol InClause) <*> inClause)
|
||||
|
||||
letStatement :: Assignment
|
||||
letStatement = makeTerm <$> symbol LetStatement <*> children (Syntax.Let <$> manyTerm expression <*> emptyTerm)
|
||||
|
||||
listComprehension :: Assignment
|
||||
listComprehension = makeTerm <$> symbol ListComprehension <*> children (Syntax.ListComprehension <$> expression <*> manyTerm expression)
|
||||
|
||||
@ -411,19 +618,23 @@ listExpression :: Assignment
|
||||
listExpression = makeTerm <$> symbol ListExpression <*> children (Literal.Array <$> manyTerm listElement)
|
||||
where listElement = symbol Expression *> children expression
|
||||
|
||||
listPattern :: Assignment
|
||||
listPattern = makeTerm <$> symbol ListPattern <*> children (Syntax.ListPattern <$> expressions)
|
||||
|
||||
listType :: Assignment
|
||||
listType = makeTerm <$> symbol ListType <*> children (Literal.Array <$> manyTerm type')
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm
|
||||
module' = makeTerm
|
||||
<$> symbol Module
|
||||
<*> children (Syntax.Module
|
||||
<$> (term moduleIdentifier <|> emptyTerm)
|
||||
<$> manyTerm (comment <|> pragma)
|
||||
<*> term (moduleIdentifier <|> qualifiedModuleIdentifier <|> emptyTerm)
|
||||
<*> moduleExports
|
||||
<*> (where' <|> expressions <|> emptyTerm))
|
||||
<*> term (where' <|> expressions <|> emptyTerm))
|
||||
where
|
||||
moduleExports = symbol ModuleExports *> children (manyTerm export)
|
||||
<|> pure []
|
||||
moduleExports = (symbol ModuleExports *> children (manyTerm export))
|
||||
<|> (pure [])
|
||||
|
||||
moduleExport :: Assignment
|
||||
moduleExport = makeTerm <$> symbol ModuleExport <*> children (Syntax.ModuleExport <$> expressions)
|
||||
@ -431,8 +642,14 @@ moduleExport = makeTerm <$> symbol ModuleExport <*> children (Syntax.ModuleExpor
|
||||
moduleIdentifier :: Assignment
|
||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.ModuleIdentifier . Name.name <$> source)
|
||||
|
||||
namedFieldPun :: Assignment
|
||||
namedFieldPun = makeTerm <$> symbol NamedFieldPun <*> children (Syntax.NamedFieldPun <$> expression)
|
||||
|
||||
negativeLiteral :: Assignment
|
||||
negativeLiteral = makeTerm <$> symbol NegativeLiteral <*> children (Syntax.NegativeLiteral <$> expression)
|
||||
|
||||
newConstructor :: Assignment
|
||||
newConstructor = makeTerm <$> symbol NewConstructor <*> children (Declaration.Constructor <$> manyTerm (context' <|> scopedTypeVariables) <*> typeConstructor <*> typeParameters)
|
||||
newConstructor = makeTerm <$> symbol NewConstructor <*> children (Declaration.Constructor <$> manyTerm (context' <|> scopedTypeVariables) <*> expression <*> expressions)
|
||||
|
||||
newType :: Assignment
|
||||
newType = makeTerm <$> symbol NewtypeDeclaration <*> children (Syntax.NewType <$> manyTerm (context' <|> scopedTypeVariables) <*> typeLeft <*> newConstructor <*> (derivingClause <|> emptyTerm))
|
||||
@ -440,7 +657,10 @@ newType = makeTerm <$> symbol NewtypeDeclaration <*> children (Syntax.NewType <$
|
||||
typeLeft = makeTerm <$> location <*> manyTermsTill expression (symbol NewConstructor)
|
||||
|
||||
operator :: Assignment
|
||||
operator = typeOperator <|> constructorOperator <|> variableOperator
|
||||
operator = constructorOperator
|
||||
<|> typeOperator
|
||||
<|> promotedTypeOperator
|
||||
<|> variableOperator
|
||||
|
||||
operatorSection :: Assignment
|
||||
operatorSection = (makeTerm <$> symbol RightOperatorSection <*> children (Syntax.RightOperatorSection <$> expression <*> expression))
|
||||
@ -449,8 +669,11 @@ operatorSection = (makeTerm <$> symbol RightOperatorSection <*> children (Syntax
|
||||
packageQualifiedImport :: Assignment
|
||||
packageQualifiedImport = makeTerm <$> symbol PackageQualifiedImport <*> (Literal.TextElement <$> source)
|
||||
|
||||
parenthesizedConstructorOperator :: Assignment
|
||||
parenthesizedConstructorOperator = symbol ParenthesizedConstructorOperator *> children expression
|
||||
|
||||
parenthesizedExpression :: Assignment
|
||||
parenthesizedExpression = symbol ParenthesizedExpression *> children expression
|
||||
parenthesizedExpression = symbol ParenthesizedExpression *> children expressions
|
||||
|
||||
parenthesizedPattern :: Assignment
|
||||
parenthesizedPattern = symbol ParenthesizedPattern *> children expressions
|
||||
@ -459,7 +682,10 @@ parenthesizedTypePattern :: Assignment
|
||||
parenthesizedTypePattern = symbol ParenthesizedTypePattern *> children expressions
|
||||
|
||||
pattern' :: Assignment
|
||||
pattern' = symbol Pattern *> children expression
|
||||
pattern' = symbol Pattern *> children expressions
|
||||
|
||||
patternGuard :: Assignment
|
||||
patternGuard = makeTerm <$> symbol PatternGuard <*> children (Syntax.PatternGuard <$> expression <*> (expression <|> emptyTerm))
|
||||
|
||||
pragma :: Assignment
|
||||
pragma = makeTerm <$> symbol Pragma <*> (Syntax.Pragma <$> source)
|
||||
@ -473,6 +699,9 @@ primitiveConstructorIdentifier = makeTerm <$> symbol PrimitiveConstructorIdentif
|
||||
primitiveVariableIdentifier :: Assignment
|
||||
primitiveVariableIdentifier = makeTerm <$> symbol PrimitiveVariableIdentifier <*> (Syntax.PrimitiveVariableIdentifier . Name.name <$> source)
|
||||
|
||||
promotedTypeOperator :: Assignment
|
||||
promotedTypeOperator = makeTerm <$> symbol PromotedTypeOperator <*> children (Syntax.PromotedTypeOperator <$> expression)
|
||||
|
||||
qualifiedConstructorIdentifier :: Assignment
|
||||
qualifiedConstructorIdentifier = makeTerm <$> symbol QualifiedConstructorIdentifier <*> children (Syntax.QualifiedConstructorIdentifier <$> someTerm' expression)
|
||||
|
||||
@ -490,18 +719,48 @@ qualifiedInfixVariableIdentifier = makeTerm <$> symbol QualifiedInfixVariableIde
|
||||
qualifiedModuleIdentifier :: Assignment
|
||||
qualifiedModuleIdentifier = makeTerm <$> symbol QualifiedModuleIdentifier <*> children (Syntax.QualifiedModuleIdentifier <$> someTerm' expression)
|
||||
|
||||
qualifiedTypeClassIdentifier :: Assignment
|
||||
qualifiedTypeClassIdentifier = makeTerm <$> symbol QualifiedTypeClassIdentifier <*> children (Syntax.QualifiedTypeClassIdentifier <$> someTerm' expression)
|
||||
|
||||
qualifiedTypeConstructorIdentifier :: Assignment
|
||||
qualifiedTypeConstructorIdentifier = makeTerm <$> symbol QualifiedTypeConstructorIdentifier <*> children (Syntax.QualifiedTypeConstructorIdentifier <$> someTerm' expression)
|
||||
|
||||
qualifiedVariableIdentifier :: Assignment
|
||||
qualifiedVariableIdentifier = makeTerm <$> symbol QualifiedVariableIdentifier <*> children (Syntax.QualifiedVariableIdentifier <$> someTerm' expression)
|
||||
|
||||
quasiQuotation :: Assignment
|
||||
quasiQuotation = makeTerm <$> symbol QuasiQuotation <*> children (Syntax.QuasiQuotation <$> (expression <|> emptyTerm) <*> expression)
|
||||
|
||||
quasiQuotationDeclaration :: Assignment
|
||||
quasiQuotationDeclaration = makeTerm <$> token QuasiQuotationDeclaration <*> pure Syntax.QuasiQuotationDeclaration
|
||||
|
||||
quasiQuotationExpression :: Assignment
|
||||
quasiQuotationExpression = makeTerm <$> token QuasiQuotationExpression <*> pure Syntax.QuasiQuotationExpression
|
||||
|
||||
quasiQuotationExpressionBody :: Assignment
|
||||
quasiQuotationExpressionBody = makeTerm <$> symbol QuasiQuotationExpressionBody <*> (Syntax.QuasiQuotationExpressionBody . Name.name <$> source)
|
||||
|
||||
quasiQuotationPattern :: Assignment
|
||||
quasiQuotationPattern = makeTerm <$> token QuasiQuotationPattern <*> pure Syntax.QuasiQuotationPattern
|
||||
|
||||
quasiQuotationQuoter :: Assignment
|
||||
quasiQuotationQuoter = makeTerm <$> symbol QuasiQuotationQuoter <*> (Syntax.QuasiQuotationQuoter . Name.name <$> source)
|
||||
|
||||
quasiQuotationType :: Assignment
|
||||
quasiQuotationType = makeTerm <$> token QuasiQuotationType <*> pure Syntax.QuasiQuotationType
|
||||
|
||||
quotedName :: Assignment
|
||||
quotedName = makeTerm <$> symbol QuotedName <*> children (Syntax.QuotedName <$> expression)
|
||||
|
||||
recordWildCards :: Assignment
|
||||
recordWildCards = makeTerm <$> symbol RecordWildCards <*> (Syntax.RecordWildCards <$ source)
|
||||
|
||||
scopedTypeVariables :: Assignment
|
||||
scopedTypeVariables = makeTerm <$> symbol ScopedTypeVariables <*> children (Syntax.ScopedTypeVariables <$> expressions <* token Dot)
|
||||
|
||||
splice :: Assignment
|
||||
splice = makeTerm <$> symbol Splice <*> children (Syntax.Splice <$> expression)
|
||||
|
||||
standaloneDerivingInstance :: Assignment
|
||||
standaloneDerivingInstance = makeTerm <$> symbol StandaloneDerivingDeclaration <*> children (Syntax.StandaloneDerivingInstance <$> manyTerm (context' <|> scopedTypeVariables) <*> expression <*> instance')
|
||||
where
|
||||
@ -510,6 +769,9 @@ standaloneDerivingInstance = makeTerm <$> symbol StandaloneDerivingDeclaration <
|
||||
star :: Assignment
|
||||
star = makeTerm <$> token Star <*> pure Syntax.Star
|
||||
|
||||
strictPattern :: Assignment
|
||||
strictPattern = makeTerm <$> symbol StrictPattern <*> children (Syntax.StrictPattern <$> expression)
|
||||
|
||||
strictType :: Assignment
|
||||
strictType = makeTerm'
|
||||
<$> symbol StrictType
|
||||
@ -519,32 +781,14 @@ strictType = makeTerm'
|
||||
string :: Assignment
|
||||
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||
|
||||
tuple :: Assignment
|
||||
tuple = makeTerm <$> symbol TupleExpression <*> children (Syntax.Tuple <$> manyTerm expression)
|
||||
|
||||
tuplePattern :: Assignment
|
||||
tuplePattern = makeTerm <$> symbol TuplePattern <*> children (Syntax.TuplePattern <$> manyTerm expression)
|
||||
|
||||
tupleType :: Assignment
|
||||
tupleType = makeTerm <$> symbol TupleType <*> children (Literal.Tuple <$> manyTerm type')
|
||||
|
||||
typeClassIdentifier :: Assignment
|
||||
typeClassIdentifier = makeTerm <$> symbol TypeClassIdentifier <*> (Syntax.TypeClassIdentifier . Name.name <$> source)
|
||||
|
||||
typeConstructorExport :: Assignment
|
||||
typeConstructorExport = makeTerm <$> symbol TypeConstructorExport <*> children (Syntax.TypeConstructorExport <$> expression)
|
||||
|
||||
typeConstructorIdentifier :: Assignment
|
||||
typeConstructorIdentifier = makeTerm <$> symbol TypeConstructorIdentifier <*> (Syntax.TypeConstructorIdentifier . Name.name <$> source)
|
||||
|
||||
typeOperator :: Assignment
|
||||
typeOperator = makeTerm <$> symbol TypeOperator <*> (Syntax.TypeOperator . Name.name <$> source)
|
||||
|
||||
typeSignature :: Assignment
|
||||
typeSignature = makeTerm <$> symbol TypeSignature <*> children (Syntax.TypeSignature <$> variableIdentifier <* token Annotation <*> manyTerm (context' <|> scopedTypeVariables) <*> expressions)
|
||||
|
||||
typeVariableIdentifier :: Assignment
|
||||
typeVariableIdentifier = makeTerm <$> symbol TypeVariableIdentifier <*> (Syntax.TypeVariableIdentifier . Name.name <$> source)
|
||||
|
||||
tuple :: Assignment
|
||||
tuple = makeTerm <$> symbol TupleExpression <*> children (Syntax.Tuple <$> manyTerm expression)
|
||||
tupleType = makeTerm <$> symbol TupleType <*> children (Literal.Tuple <$> manyTerm expression)
|
||||
|
||||
tuplingConstructor :: Assignment
|
||||
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> rawSource)
|
||||
@ -566,11 +810,25 @@ type'' = makeTerm
|
||||
<$> symbol Type
|
||||
<*> children (Syntax.Type <$> expression <*> typeParameters <*> (kindSignature <|> emptyTerm))
|
||||
|
||||
typeParameters :: Assignment
|
||||
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> (manyTermsTill expression (symbol Annotation) <|> manyTerm expression))
|
||||
typeApp :: Assignment
|
||||
typeApp = makeTerm <$> symbol TypeApplication <*> children (Syntax.TypeApp <$> expression)
|
||||
|
||||
typePattern :: Assignment
|
||||
typePattern = makeTerm <$> symbol TypePattern <*> children (Syntax.TypePattern <$> expressions)
|
||||
typeClass :: Assignment
|
||||
typeClass = makeTerm <$> symbol TypeClassDeclaration <*> children (Syntax.TypeClass
|
||||
<$> (context' <|> emptyTerm)
|
||||
<*> expression
|
||||
<*> manyTermsTill expression (symbol Where)
|
||||
<*> where')
|
||||
|
||||
typeClassIdentifier :: Assignment
|
||||
typeClassIdentifier = makeTerm <$> symbol TypeClassIdentifier <*> (Syntax.TypeClassIdentifier . Name.name <$> source)
|
||||
|
||||
typeClassInstance :: Assignment
|
||||
typeClassInstance = makeTerm <$> symbol TypeClassInstanceDeclaration <*> children (Syntax.TypeClassInstance
|
||||
<$> manyTerm (context' <|> scopedTypeVariables)
|
||||
<*> expression
|
||||
<*> expression
|
||||
<*> (where' <|> emptyTerm))
|
||||
|
||||
typeConstructor :: Assignment
|
||||
typeConstructor = constructorIdentifier
|
||||
@ -578,6 +836,7 @@ typeConstructor = constructorIdentifier
|
||||
<|> listConstructor
|
||||
<|> listType
|
||||
<|> qualifiedModuleIdentifier
|
||||
<|> qualifiedTypeClassIdentifier
|
||||
<|> qualifiedTypeConstructorIdentifier
|
||||
<|> quotedName
|
||||
<|> tupleType
|
||||
@ -586,15 +845,54 @@ typeConstructor = constructorIdentifier
|
||||
<|> typeConstructorIdentifier
|
||||
<|> unitConstructor
|
||||
|
||||
typeConstructorExport :: Assignment
|
||||
typeConstructorExport = makeTerm <$> symbol TypeConstructorExport <*> children (Syntax.TypeConstructorExport <$> expression)
|
||||
|
||||
typeConstructorIdentifier :: Assignment
|
||||
typeConstructorIdentifier = makeTerm <$> symbol TypeConstructorIdentifier <*> (Syntax.TypeConstructorIdentifier . Name.name <$> source)
|
||||
|
||||
typeFamily :: Assignment
|
||||
typeFamily = makeTerm <$> symbol TypeFamilyDeclaration <*> children (Syntax.TypeFamily <$> expression <*> manyTermsTill expression typeFamilySeperator <*> (typeSignature <|> kindSignature <|> emptyTerm) <*> (where' <|> emptyTerm))
|
||||
where
|
||||
typeFamilySeperator = symbol TypeSignature
|
||||
<|> symbol KindSignature
|
||||
<|> symbol Where
|
||||
|
||||
typeInstance :: Assignment
|
||||
typeInstance = makeTerm <$> symbol TypeInstanceDeclaration <*> children (Syntax.TypeInstance <$> typeInstanceType <*> typeInstanceBody)
|
||||
where
|
||||
typeInstanceType = makeTerm <$> location <*> manyTermsTill expression (symbol TypeInstanceBody)
|
||||
typeInstanceBody = symbol TypeInstanceBody *> children expressions
|
||||
|
||||
typeOperator :: Assignment
|
||||
typeOperator = makeTerm <$> symbol TypeOperator <*> (Syntax.TypeOperator . Name.name <$> source)
|
||||
|
||||
typeSignature :: Assignment
|
||||
typeSignature = makeTerm <$> symbol TypeSignature <*> children (Syntax.TypeSignature <$> manyTermsTill expression (symbol Annotation) <* token Annotation <*> manyTerm (context' <|> scopedTypeVariables) <*> expressions)
|
||||
|
||||
typeParameters :: Assignment
|
||||
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> (manyTermsTill expression (symbol Annotation) <|> manyTerm expression))
|
||||
|
||||
typePattern :: Assignment
|
||||
typePattern = makeTerm <$> symbol TypePattern <*> children (Syntax.TypePattern <$> expressions)
|
||||
|
||||
typeSynonymDeclaration :: Assignment
|
||||
typeSynonymDeclaration = makeTerm
|
||||
<$> symbol TypeSynonymDeclaration
|
||||
<*> children (typeSynonym <$> typeLeft <*> typeRight)
|
||||
where
|
||||
typeLeft = makeTerm <$> location <*> manyTill expression (symbol TypeSynonymBody)
|
||||
typeRight = symbol TypeSynonymBody *> children ((,) <$> manyTerm (context' <|> scopedTypeVariables) <*> expression)
|
||||
typeLeft = makeTerm <$> location <*> manyTill expression typeRightSeperator
|
||||
typeRight = (symbol TypeSynonymBody *> children ((,) <$> manyTerm (context' <|> scopedTypeVariables) <*> expression))
|
||||
<|> ((,) [] <$> typeSignature)
|
||||
<|> ((,) [] <$> kindSignature)
|
||||
typeRightSeperator = symbol TypeSynonymBody
|
||||
<|> symbol TypeSignature
|
||||
<|> symbol KindSignature
|
||||
typeSynonym typeLeft (contexts, typeRight) = Syntax.TypeSynonym typeLeft contexts typeRight
|
||||
|
||||
typeVariableIdentifier :: Assignment
|
||||
typeVariableIdentifier = makeTerm <$> symbol TypeVariableIdentifier <*> (Syntax.TypeVariableIdentifier . Name.name <$> source)
|
||||
|
||||
unitConstructor :: Assignment
|
||||
unitConstructor = makeTerm <$> token UnitConstructor <*> pure Syntax.UnitConstructor
|
||||
|
||||
@ -610,9 +908,15 @@ variableSymbol = makeTerm <$> (symbol VariableSymbol <|> symbol VariableSymbol')
|
||||
variableIdentifiers :: Assignment
|
||||
variableIdentifiers = makeTerm <$> location <*> many variableIdentifier
|
||||
|
||||
viewPattern :: Assignment
|
||||
viewPattern = makeTerm <$> symbol ViewPattern <*> children (Syntax.ViewPattern <$> expression <*> expression)
|
||||
|
||||
where' :: Assignment
|
||||
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (manyTerm expression)
|
||||
|
||||
wildcard :: Assignment
|
||||
wildcard = makeTerm <$> token Wildcard <*> pure Syntax.Wildcard
|
||||
|
||||
-- | Helpers
|
||||
|
||||
commentedTerm :: Assignment -> Assignment
|
||||
|
@ -7,9 +7,10 @@ import Diffing.Algorithm
|
||||
import Prelude
|
||||
import Prologue
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a
|
||||
, moduleExports :: ![a]
|
||||
, moduleStatements :: !a
|
||||
data Module a = Module { moduleContext :: [a]
|
||||
, moduleIdentifier :: a
|
||||
, moduleExports :: [a]
|
||||
, moduleStatements :: a
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
@ -19,7 +20,16 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Module
|
||||
|
||||
data StrictType a = StrictType { strictTypeIdentifier :: !a, strictTypeParameters :: !a }
|
||||
newtype StrictPattern a = StrictPattern a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 StrictPattern where liftEq = genericLiftEq
|
||||
instance Ord1 StrictPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable StrictPattern
|
||||
|
||||
data StrictType a = StrictType { strictTypeIdentifier :: a, strictTypeParameters :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 StrictType where liftEq = genericLiftEq
|
||||
@ -28,7 +38,7 @@ instance Show1 StrictType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable StrictType
|
||||
|
||||
newtype StrictTypeVariable a = StrictTypeVariable { strictTypeVariableIdentifier :: a }
|
||||
newtype StrictTypeVariable a = StrictTypeVariable a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 StrictTypeVariable where liftEq = genericLiftEq
|
||||
@ -91,7 +101,7 @@ instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionConstructor
|
||||
|
||||
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorName :: !a, recordDataConstructorFields :: !a }
|
||||
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorContext :: [a], recordDataConstructorName :: !a, recordDataConstructorFields :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RecordDataConstructor where liftEq = genericLiftEq
|
||||
@ -171,7 +181,7 @@ instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionType
|
||||
|
||||
data TypeSignature a = TypeSignature { typeSignatureName :: a, typeSignatureContext :: [a], typeSignatureContent :: a }
|
||||
data TypeSignature a = TypeSignature { typeSignatureName :: [a], typeSignatureContext :: [a], typeSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeSignature where liftEq = genericLiftEq
|
||||
@ -180,6 +190,15 @@ instance Show1 TypeSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeSignature
|
||||
|
||||
data ExpressionTypeSignature a = ExpressionTypeSignature { expressionTypeSignatureName :: [a], expressionTypeSignatureContext :: [a], expressionTypeSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ExpressionTypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ExpressionTypeSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 ExpressionTypeSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ExpressionTypeSignature
|
||||
|
||||
newtype KindSignature a = KindSignature { kindSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
@ -225,19 +244,65 @@ instance Show1 Star where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Star
|
||||
|
||||
data QualifiedEntityIdentifier a = QualifiedTypeConstructorIdentifier (NonEmpty a)
|
||||
| QualifiedConstructorIdentifier (NonEmpty a)
|
||||
| QualifiedInfixVariableIdentifier (NonEmpty a)
|
||||
| QualifiedModuleIdentifier (NonEmpty a)
|
||||
| QualifiedVariableIdentifier (NonEmpty a)
|
||||
data QualifiedTypeClassIdentifier a = QualifiedTypeClassIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedEntityIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedEntityIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedEntityIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedEntityIdentifier where liftHashWithSalt = foldl
|
||||
instance Eq1 QualifiedTypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedTypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedTypeClassIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedEntityIdentifier
|
||||
instance Evaluatable QualifiedTypeClassIdentifier
|
||||
|
||||
newtype QualifiedTypeConstructorIdentifier a = QualifiedTypeConstructorIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedTypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedTypeConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedTypeConstructorIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedTypeConstructorIdentifier
|
||||
|
||||
newtype QualifiedConstructorIdentifier a = QualifiedConstructorIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedConstructorIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedConstructorIdentifier
|
||||
|
||||
newtype QualifiedInfixVariableIdentifier a = QualifiedInfixVariableIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedInfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedInfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedInfixVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedInfixVariableIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedInfixVariableIdentifier
|
||||
|
||||
newtype QualifiedModuleIdentifier a = QualifiedModuleIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedModuleIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedModuleIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedModuleIdentifier
|
||||
|
||||
newtype QualifiedVariableIdentifier a = QualifiedVariableIdentifier (NonEmpty a)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedVariableIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedVariableIdentifier
|
||||
|
||||
data AnnotatedTypeVariable a = AnnotatedTypeVariable { annotatedTypeVariableIdentifier :: a, annotatedTypeVariableannotation :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
@ -347,33 +412,140 @@ instance Show1 EqualityConstraint where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable EqualityConstraint
|
||||
|
||||
data EntityIdentifier a = TypeVariableIdentifier Name
|
||||
| TypeConstructorIdentifier Name
|
||||
| ModuleIdentifier Name
|
||||
| ConstructorIdentifier Name
|
||||
| InfixVariableIdentifier Name
|
||||
| TypeClassIdentifier Name
|
||||
| VariableIdentifier Name
|
||||
| PrimitiveConstructorIdentifier Name
|
||||
| PrimitiveVariableIdentifier Name
|
||||
newtype TypeVariableIdentifier a = TypeVariableIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 EntityIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 EntityIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 EntityIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Eq1 TypeVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable EntityIdentifier
|
||||
instance Evaluatable TypeVariableIdentifier
|
||||
|
||||
data Operator a = VariableOperator a
|
||||
| ConstructorOperator a
|
||||
| TypeOperator Name
|
||||
newtype TypeConstructorIdentifier a = TypeConstructorIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Operator where liftEq = genericLiftEq
|
||||
instance Ord1 Operator where liftCompare = genericLiftCompare
|
||||
instance Show1 Operator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Eq1 TypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Operator
|
||||
instance Evaluatable TypeConstructorIdentifier
|
||||
|
||||
newtype ModuleIdentifier a = ModuleIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ModuleIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ModuleIdentifier
|
||||
|
||||
newtype ConstructorIdentifier a = ConstructorIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ConstructorIdentifier
|
||||
|
||||
newtype ImplicitParameterIdentifier a = ImplicitParameterIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImplicitParameterIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ImplicitParameterIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ImplicitParameterIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImplicitParameterIdentifier
|
||||
|
||||
newtype InfixConstructorIdentifier a = InfixConstructorIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InfixConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable InfixConstructorIdentifier
|
||||
|
||||
newtype InfixVariableIdentifier a = InfixVariableIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable InfixVariableIdentifier
|
||||
|
||||
newtype TypeClassIdentifier a = TypeClassIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeClassIdentifier
|
||||
|
||||
newtype VariableIdentifier a = VariableIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 VariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 VariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable VariableIdentifier
|
||||
|
||||
newtype PrimitiveConstructorIdentifier a = PrimitiveConstructorIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PrimitiveConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 PrimitiveConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PrimitiveConstructorIdentifier
|
||||
|
||||
newtype PrimitiveVariableIdentifier a = PrimitiveVariableIdentifier Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PrimitiveVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 PrimitiveVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PrimitiveVariableIdentifier
|
||||
|
||||
newtype VariableOperator a = VariableOperator a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 VariableOperator where liftEq = genericLiftEq
|
||||
instance Ord1 VariableOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable VariableOperator
|
||||
|
||||
newtype ConstructorOperator a = ConstructorOperator a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstructorOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ConstructorOperator
|
||||
|
||||
newtype TypeOperator a = TypeOperator Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 TypeOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeOperator
|
||||
|
||||
newtype PromotedTypeOperator a = PromotedTypeOperator a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PromotedTypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 PromotedTypeOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 PromotedTypeOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PromotedTypeOperator
|
||||
|
||||
newtype ConstructorSymbol a = ConstructorSymbol { constructorSymbolName :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
@ -447,8 +619,7 @@ instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImportAlias
|
||||
|
||||
data App a = App { appLeft :: a, appRight :: a }
|
||||
| InfixOperatorApp { appLeft :: a, infixOperator :: a, appRight :: a }
|
||||
data App a = App { appLeft :: a, appLeftTypeApp :: a, appRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 App where liftEq = genericLiftEq
|
||||
@ -457,6 +628,24 @@ instance Show1 App where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable App
|
||||
|
||||
data InfixOperatorApp a = InfixOperatorApp { infixOperatorAppLeft :: a, infixOperatorAppLeftTypeApp :: a, infixOperatorAppOperator :: a, infixOperatorAppRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InfixOperatorApp where liftEq = genericLiftEq
|
||||
instance Ord1 InfixOperatorApp where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixOperatorApp where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable InfixOperatorApp
|
||||
|
||||
newtype TypeApp a = TypeApp { typeAppType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeApp where liftEq = genericLiftEq
|
||||
instance Ord1 TypeApp where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeApp where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeApp
|
||||
|
||||
data ListComprehension a = ListComprehension { comprehensionValue :: a, comprehensionSource :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
@ -493,10 +682,8 @@ instance Show1 TuplePattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TuplePattern
|
||||
|
||||
data ArithmeticSequence a = EnumFrom a -- e.g. [1..]
|
||||
| EnumFromThen a a -- e.g. [1,2..]
|
||||
| EnumFromTo a a -- e.g. [1..2]
|
||||
| EnumFromThenTo a a a -- e.g. [1,2..10]
|
||||
-- e.g. [1..], [1,2..], [1,2..10]
|
||||
data ArithmeticSequence a = ArithmeticSequence { from :: a, next :: Maybe a, to :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ArithmeticSequence where liftEq = genericLiftEq
|
||||
@ -505,15 +692,23 @@ instance Show1 ArithmeticSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ArithmeticSequence
|
||||
|
||||
data OperatorSection a = RightOperatorSection a a
|
||||
| LeftOperatorSection a a
|
||||
data RightOperatorSection a = RightOperatorSection a a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 OperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 OperatorSection where liftCompare = genericLiftCompare
|
||||
instance Show1 OperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Eq1 RightOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 RightOperatorSection where liftCompare = genericLiftCompare
|
||||
instance Show1 RightOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable OperatorSection
|
||||
instance Evaluatable RightOperatorSection
|
||||
|
||||
data LeftOperatorSection a = LeftOperatorSection a a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LeftOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 LeftOperatorSection where liftCompare = genericLiftCompare
|
||||
instance Show1 LeftOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LeftOperatorSection
|
||||
|
||||
newtype ConstructorPattern a = ConstructorPattern a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
@ -525,7 +720,7 @@ instance Show1 ConstructorPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructorPattern
|
||||
|
||||
-- e.g. `a <- b` in a Haskell do block.
|
||||
data BindPattern a = BindPattern { bindPatternLeft :: a, bindPatternRight :: a }
|
||||
data BindPattern a = BindPattern { bindPatternLeft :: [a], bindPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BindPattern where liftEq = genericLiftEq
|
||||
@ -561,3 +756,368 @@ instance Ord1 PrefixNegation where liftCompare = genericLiftCompare
|
||||
instance Show1 PrefixNegation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PrefixNegation
|
||||
|
||||
newtype CPPDirective a = CPPDirective Text
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CPPDirective where liftEq = genericLiftEq
|
||||
instance Ord1 CPPDirective where liftCompare = genericLiftCompare
|
||||
instance Show1 CPPDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable CPPDirective
|
||||
|
||||
data QuasiQuotation a = QuasiQuotation { quasiQuotationHead :: a, quasiQuotationBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotation where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotation where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotation
|
||||
|
||||
newtype QuasiQuotationExpressionBody a = QuasiQuotationExpressionBody Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationExpressionBody where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpressionBody where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationExpressionBody where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationExpressionBody
|
||||
|
||||
data QuasiQuotationPattern a = QuasiQuotationPattern
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationPattern where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationPattern
|
||||
|
||||
data QuasiQuotationType a = QuasiQuotationType
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationType where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationType where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationType
|
||||
|
||||
data QuasiQuotationDeclaration a = QuasiQuotationDeclaration
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationDeclaration
|
||||
|
||||
newtype QuasiQuotationQuoter a = QuasiQuotationQuoter Name
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationQuoter where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationQuoter where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationQuoter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationQuoter
|
||||
|
||||
data QuasiQuotationExpression a = QuasiQuotationExpression
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QuasiQuotationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QuasiQuotationExpression
|
||||
|
||||
newtype Splice a = Splice a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Splice where liftEq = genericLiftEq
|
||||
instance Ord1 Splice where liftCompare = genericLiftCompare
|
||||
instance Show1 Splice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Splice
|
||||
|
||||
data TypeClass a = TypeClass { typeClassContext :: a, typeClassIdentifier :: a, typeClassParameters :: [a], typeClassBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeClass where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClass where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClass where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeClass
|
||||
|
||||
data Fixity' a = Fixity' { fixityPrecedence :: a, fixityIdentifier :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Fixity' where liftEq = genericLiftEq
|
||||
instance Ord1 Fixity' where liftCompare = genericLiftCompare
|
||||
instance Show1 Fixity' where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Fixity'
|
||||
|
||||
-- The default signature of a type class. The default signature has the same shape as a TypeSignature Assignment.
|
||||
data DefaultSignature a = DefaultSignature { defaultSignatureName :: [a], defaultSignatureContext :: [a], defaultSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultSignature where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DefaultSignature
|
||||
|
||||
data TypeFamily a = TypeFamily { typeFamilyIdentifier :: a, typeFamilyParameters :: [a], typeFamilySignature :: a, typeFamilyBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeFamily where liftEq = genericLiftEq
|
||||
instance Ord1 TypeFamily where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeFamily where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeFamily
|
||||
|
||||
newtype FunctionalDependency a = FunctionalDependency { functionalDependencyContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FunctionalDependency where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionalDependency where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionalDependency where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionalDependency
|
||||
|
||||
data TypeClassInstance a = TypeClassInstance { typeClassInstanceContext :: [a], typeClassInstanceIdentifier :: a, typeClassInstanceInstance :: a, typeClassInstanceBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeClassInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassInstance where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClassInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeClassInstance
|
||||
|
||||
newtype Instance a = Instance a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Instance where liftEq = genericLiftEq
|
||||
instance Ord1 Instance where liftCompare = genericLiftCompare
|
||||
instance Show1 Instance where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Instance
|
||||
|
||||
-- e.g. The `Bar{..}` in `foo Bar{..} = baz`.
|
||||
newtype LabeledPattern a = LabeledPattern a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledPattern where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LabeledPattern
|
||||
|
||||
-- e.g. The `{..}` in `foo Bar{..} = baz`
|
||||
data RecordWildCards a = RecordWildCards
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RecordWildCards where liftEq = genericLiftEq
|
||||
instance Ord1 RecordWildCards where liftCompare = genericLiftCompare
|
||||
instance Show1 RecordWildCards where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable RecordWildCards
|
||||
|
||||
-- e.g. `type instance F [Int] = Int` where `F` is an open type family.
|
||||
data TypeInstance a = TypeInstance { typeInstanceType :: a, typeInstanceBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeInstance where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeInstance
|
||||
|
||||
newtype KindParenthesizedConstructor a = KindParenthesizedConstructor { kindParenthesizedConstructorContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KindParenthesizedConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 KindParenthesizedConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 KindParenthesizedConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KindParenthesizedConstructor
|
||||
|
||||
newtype KindTupleType a = KindTupleType { kindTupleType :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KindTupleType where liftEq = genericLiftEq
|
||||
instance Ord1 KindTupleType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindTupleType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KindTupleType
|
||||
|
||||
data Wildcard a = Wildcard
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Wildcard where liftEq = genericLiftEq
|
||||
instance Ord1 Wildcard where liftCompare = genericLiftCompare
|
||||
instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Wildcard
|
||||
|
||||
data Let a = Let { letStatements :: [a], letInClause :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Let
|
||||
|
||||
newtype ListPattern a = ListPattern a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ListPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ListPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 ListPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ListPattern
|
||||
|
||||
-- e.g. The `n@num1` in `f n@num1 x@num2 = x`
|
||||
data AsPattern a = AsPattern { asPatternLeft :: a, asPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AsPattern where liftEq = genericLiftEq
|
||||
instance Ord1 AsPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 AsPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AsPattern
|
||||
|
||||
-- e.g. The `a = 1` in `foo Bar{ a = 1 } = baz`.
|
||||
data FieldPattern a = FieldPattern { fieldPatternLeft :: a, fieldPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FieldPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FieldPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 FieldPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FieldPattern
|
||||
|
||||
-- e.g. The `start` or `end` in `f Blob{start, end} = [start, end]`.
|
||||
newtype NamedFieldPun a = NamedFieldPun a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamedFieldPun where liftEq = genericLiftEq
|
||||
instance Ord1 NamedFieldPun where liftCompare = genericLiftCompare
|
||||
instance Show1 NamedFieldPun where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NamedFieldPun
|
||||
|
||||
-- e.g. The `-(1)` in `f (-(1)) = 1`.
|
||||
newtype NegativeLiteral a = NegativeLiteral a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NegativeLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 NegativeLiteral where liftCompare = genericLiftCompare
|
||||
instance Show1 NegativeLiteral where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NegativeLiteral
|
||||
|
||||
-- e.g. The `~a` in `f ~a = 1`
|
||||
newtype IrrefutablePattern a = IrrefutablePattern a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IrrefutablePattern where liftEq = genericLiftEq
|
||||
instance Ord1 IrrefutablePattern where liftCompare = genericLiftCompare
|
||||
instance Show1 IrrefutablePattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable IrrefutablePattern
|
||||
|
||||
-- For handling guards in case alternative expressions.
|
||||
newtype CaseGuardPattern a = CaseGuardPattern [a]
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CaseGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 CaseGuardPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 CaseGuardPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable CaseGuardPattern
|
||||
|
||||
newtype Guard a = Guard a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Guard where liftEq = genericLiftEq
|
||||
instance Ord1 Guard where liftCompare = genericLiftCompare
|
||||
instance Show1 Guard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Guard
|
||||
|
||||
newtype LambdaCase a = LambdaCase [a]
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LambdaCase where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaCase where liftCompare = genericLiftCompare
|
||||
instance Show1 LambdaCase where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LambdaCase
|
||||
|
||||
-- For handling guards in function declarations.
|
||||
newtype FunctionGuardPattern a = FunctionGuardPattern [a]
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FunctionGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionGuardPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionGuardPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionGuardPattern
|
||||
|
||||
-- The `y { a = 1, b = 2} in `f y@Example = y { a = 1, b = 2 }`.
|
||||
newtype LabeledUpdate a = LabeledUpdate [a]
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledUpdate where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledUpdate where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledUpdate where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LabeledUpdate
|
||||
|
||||
-- The `a = 1` in `f y@Example = y { a = 1, b = 2 }`.
|
||||
data FieldBind a = FieldBind { fieldBindLeft :: a, fieldBindRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FieldBind where liftEq = genericLiftEq
|
||||
instance Ord1 FieldBind where liftCompare = genericLiftCompare
|
||||
instance Show1 FieldBind where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FieldBind
|
||||
|
||||
data ViewPattern a = ViewPattern { viewPatternLeft :: a, viewPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ViewPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ViewPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 ViewPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ViewPattern
|
||||
|
||||
-- The `a <- b` in `f a | a <- b = c` of a function declaration.
|
||||
data PatternGuard a = PatternGuard { patternGuardPattern :: a, patternGuardExpression :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PatternGuard where liftEq = genericLiftEq
|
||||
instance Ord1 PatternGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 PatternGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PatternGuard
|
||||
|
||||
data LabeledConstruction a = LabeledConstruction { labeledConstructionConstructor :: a, labeledConstructionFields :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledConstruction where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledConstruction where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledConstruction where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LabeledConstruction
|
||||
|
||||
data InfixDataConstructor a = InfixDataConstructor { infixDataConstructorContext :: [a], infixDataConstructorLeft :: a, infixDataConstructorOperator :: a, infixDataConstructorRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InfixDataConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 InfixDataConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixDataConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable InfixDataConstructor
|
||||
|
@ -300,7 +300,7 @@ comparisonOperator = symbol ComparisonOperator *> children (expression `chainl1T
|
||||
, (makeTerm1 .) . Expression.Member <$ symbol AnonIn
|
||||
, token AnonIs *> ((makeTerm1 .) . invert Expression.Equal <$ symbol AnonNot <|> pure ((makeTerm1 .) . Expression.Equal))
|
||||
])
|
||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
notOperator :: Assignment
|
||||
notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> term expression)
|
||||
|
@ -126,7 +126,7 @@ someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
|
||||
, ApplyAll typeclasses (Sum TypeScript.Syntax)
|
||||
, ApplyAll typeclasses (Sum PHP.Syntax)
|
||||
)
|
||||
=> Language -- ^ The 'Language' to select.
|
||||
=> Language -- ^ The 'Language' to select.
|
||||
-> Maybe (Parser (SomeTerm typeclasses (Record Location))) -- ^ A 'SomeParser' abstracting the syntax type to be produced.
|
||||
someParser Go = Just (SomeParser goParser)
|
||||
someParser Java = Just (SomeParser javaParser)
|
||||
|
@ -18,7 +18,7 @@ import Semantic.Task
|
||||
import Serializing.Format
|
||||
import qualified Language.Ruby.Assignment as Ruby
|
||||
|
||||
runParse :: (Member (Distribute WrappedTask) effs, Member Task effs) => TermRenderer output -> [Blob] -> Eff effs Builder
|
||||
runParse :: (Member (Distribute WrappedTask) effs, Member Task effs) => TermRenderer output -> [Blob] -> Eff effs Builder
|
||||
runParse JSONTermRenderer = withParsedBlobs (render . renderJSONTerm) >=> serialize JSON
|
||||
runParse SExpressionTermRenderer = withParsedBlobs (const (serialize (SExpression ByConstructorName)))
|
||||
runParse ShowTermRenderer = withParsedBlobs (const (serialize Show))
|
||||
|
@ -68,6 +68,12 @@
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
@ -75,12 +81,6 @@
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters))
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{+(Constructor
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(TypeParameters)+})+}
|
||||
{-(Constructor
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(TypeParameters)-})-}
|
||||
|
3
test/fixtures/haskell/corpus/cpp-directives.A.hs
vendored
Normal file
3
test/fixtures/haskell/corpus/cpp-directives.A.hs
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
#ifndef mingw32_HOST_OS
|
||||
import System.Posix.Signals
|
||||
#endif
|
3
test/fixtures/haskell/corpus/cpp-directives.B.hs
vendored
Normal file
3
test/fixtures/haskell/corpus/cpp-directives.B.hs
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
#ifndef mingw64_HOST_OS
|
||||
import System.Util.Posix.Signals
|
||||
#endif
|
13
test/fixtures/haskell/corpus/cpp-directives.diffA-B.txt
vendored
Normal file
13
test/fixtures/haskell/corpus/cpp-directives.diffA-B.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
{ (CPPDirective)
|
||||
->(CPPDirective) }
|
||||
(ImportDeclaration
|
||||
(Empty)
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
{+(ModuleIdentifier)+}
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)))
|
||||
(CPPDirective)))
|
13
test/fixtures/haskell/corpus/cpp-directives.diffB-A.txt
vendored
Normal file
13
test/fixtures/haskell/corpus/cpp-directives.diffB-A.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
{ (CPPDirective)
|
||||
->(CPPDirective) }
|
||||
(ImportDeclaration
|
||||
(Empty)
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
{-(ModuleIdentifier)-}
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)))
|
||||
(CPPDirective)))
|
11
test/fixtures/haskell/corpus/cpp-directives.parseA.txt
vendored
Normal file
11
test/fixtures/haskell/corpus/cpp-directives.parseA.txt
vendored
Normal file
@ -0,0 +1,11 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(CPPDirective)
|
||||
(ImportDeclaration
|
||||
(Empty)
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)))
|
||||
(CPPDirective)))
|
12
test/fixtures/haskell/corpus/cpp-directives.parseB.txt
vendored
Normal file
12
test/fixtures/haskell/corpus/cpp-directives.parseB.txt
vendored
Normal file
@ -0,0 +1,12 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(CPPDirective)
|
||||
(ImportDeclaration
|
||||
(Empty)
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier)))
|
||||
(CPPDirective)))
|
252
test/fixtures/haskell/corpus/expressions.diffA-B.txt
vendored
252
test/fixtures/haskell/corpus/expressions.diffA-B.txt
vendored
@ -7,6 +7,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -15,7 +16,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -25,8 +28,11 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -34,6 +40,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -41,6 +48,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -50,8 +58,11 @@
|
||||
(App
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -61,13 +72,13 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) })))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThen
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -75,7 +86,7 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -83,7 +94,7 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThenTo
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -167,7 +178,7 @@
|
||||
{+(Integer)+}))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
@ -188,7 +199,7 @@
|
||||
{+(Integer)+})))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
(Function
|
||||
@ -198,8 +209,10 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
{ (Integer)
|
||||
->(Integer) })
|
||||
(Empty)
|
||||
(ListComprehension
|
||||
(ListComprehension
|
||||
(Tuple
|
||||
@ -212,7 +225,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer)))))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -230,40 +243,64 @@
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(LeftOperatorSection
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(LeftOperatorSection
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(LeftOperatorSection
|
||||
{+(VariableIdentifier)+}
|
||||
{+(ConstructorOperator
|
||||
{+(ConstructorSymbol)+})+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(LeftOperatorSection
|
||||
{+(VariableIdentifier)+}
|
||||
{+(ConstructorOperator
|
||||
{+(ConstructorSymbol)+})+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(InfixVariableIdentifier)+})+}
|
||||
{+(VariableIdentifier)+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(QualifiedConstructorIdentifier
|
||||
{+(ModuleIdentifier)+}
|
||||
{+(ConstructorIdentifier)+})+})+})+}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(LeftOperatorSection
|
||||
{-(VariableIdentifier)-}
|
||||
{-(ConstructorOperator
|
||||
{-(ConstructorSymbol)-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(LeftOperatorSection
|
||||
{-(VariableIdentifier)-}
|
||||
{-(ConstructorOperator
|
||||
{-(ConstructorSymbol)-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(InfixVariableIdentifier)-})-}
|
||||
{-(VariableIdentifier)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(QualifiedConstructorIdentifier
|
||||
{-(ModuleIdentifier)-}
|
||||
{-(ConstructorIdentifier)-})-})-})-}
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
@ -276,38 +313,46 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(TextElement)))))))))))
|
||||
@ -322,6 +367,7 @@
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
{ (VariableIdentifier)
|
||||
@ -332,6 +378,7 @@
|
||||
(InfixOperatorApp
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
{ (VariableIdentifier)
|
||||
@ -361,10 +408,12 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -379,10 +428,12 @@
|
||||
(VariableIdentifier))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -398,82 +449,61 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(Integer)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(Integer))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(PrefixNegation
|
||||
{+(Integer)+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(PrefixNegation
|
||||
{+(VariableIdentifier)+})+})+})+}
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(Integer))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(App
|
||||
{+(App
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Lambda
|
||||
{+(VariableIdentifier)+}
|
||||
{+(InfixOperatorApp
|
||||
{+(Tuple
|
||||
{+(VariableIdentifier)+})+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(App
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+})+})+})+})+})+}
|
||||
{+(VariableIdentifier)+})+})+})+})+}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(PrefixNegation
|
||||
{-(VariableIdentifier)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(PrefixNegation
|
||||
{-(Integer)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(App
|
||||
{-(App
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Lambda
|
||||
{-(VariableIdentifier)-}
|
||||
{-(InfixOperatorApp
|
||||
{-(Tuple
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(App
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-})-})-})-})-})-}
|
||||
{-(VariableIdentifier)-})-})-})-})-}))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(Integer))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Lambda
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(InfixOperatorApp
|
||||
(Tuple
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))))
|
||||
(Empty)
|
||||
(VariableIdentifier)))))))
|
||||
|
234
test/fixtures/haskell/corpus/expressions.diffB-A.txt
vendored
234
test/fixtures/haskell/corpus/expressions.diffB-A.txt
vendored
@ -7,6 +7,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -15,7 +16,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -25,8 +28,11 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -34,6 +40,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -41,6 +48,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -50,8 +58,11 @@
|
||||
(App
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -61,13 +72,13 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) })))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThen
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -75,7 +86,7 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -83,7 +94,7 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThenTo
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
@ -167,7 +178,7 @@
|
||||
{-(Integer)-}))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
@ -188,7 +199,7 @@
|
||||
{-(Integer)-})))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
(Function
|
||||
@ -198,8 +209,10 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
{ (Integer)
|
||||
->(Integer) })
|
||||
(Empty)
|
||||
(ListComprehension
|
||||
(ListComprehension
|
||||
(Tuple
|
||||
@ -212,7 +225,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer)))))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
@ -230,29 +243,40 @@
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(LeftOperatorSection
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(LeftOperatorSection
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(LeftOperatorSection
|
||||
{+(VariableIdentifier)+}
|
||||
{+(ConstructorOperator
|
||||
{+(ConstructorSymbol)+})+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(LeftOperatorSection
|
||||
{+(VariableIdentifier)+}
|
||||
{+(ConstructorOperator
|
||||
{+(ConstructorSymbol)+})+})+})+})+}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(LeftOperatorSection
|
||||
{-(VariableIdentifier)-}
|
||||
{-(ConstructorOperator
|
||||
{-(ConstructorSymbol)-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(LeftOperatorSection
|
||||
{-(VariableIdentifier)-}
|
||||
{-(ConstructorOperator
|
||||
{-(ConstructorSymbol)-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(InfixVariableIdentifier)-})-}
|
||||
{-(VariableIdentifier)-})-})-})-}
|
||||
@ -273,34 +297,42 @@
|
||||
{-(Statements
|
||||
{-(InfixOperatorApp
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(TextElement)-})-})-})-})-})-})-})-})-})-})-}
|
||||
@ -309,6 +341,7 @@
|
||||
(Statements
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(InfixVariableIdentifier)+})+}
|
||||
{+(VariableIdentifier)+})+}
|
||||
@ -317,6 +350,7 @@
|
||||
{-(VariableIdentifier)-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(VariableIdentifier)-})-})-}
|
||||
@ -324,6 +358,7 @@
|
||||
{-(VariableIdentifier)-}
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(VariableIdentifier)-})-})-})-}))
|
||||
@ -344,34 +379,42 @@
|
||||
{+(Statements
|
||||
{+(InfixOperatorApp
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(TextElement)+})+})+})+})+})+})+})+})+})+})+}
|
||||
@ -383,6 +426,7 @@
|
||||
{+(VariableIdentifier)+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(VariableIdentifier)+})+})+}
|
||||
@ -390,6 +434,7 @@
|
||||
{+(VariableIdentifier)+}
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(VariableIdentifier)+})+})+})+})+})+}
|
||||
@ -418,10 +463,12 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -436,10 +483,12 @@
|
||||
(VariableIdentifier))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -455,86 +504,61 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(Integer)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(Integer))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(PrefixNegation
|
||||
{+(Integer)+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(PrefixNegation
|
||||
{+(VariableIdentifier)+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(PrefixNegation
|
||||
{+(Integer)+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(InfixOperatorApp
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(App
|
||||
{+(App
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Lambda
|
||||
{+(VariableIdentifier)+}
|
||||
{+(InfixOperatorApp
|
||||
{+(Tuple
|
||||
{+(VariableIdentifier)+})+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(InfixOperatorApp
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(VariableOperator
|
||||
{+(VariableSymbol)+})+}
|
||||
{+(App
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+})+})+})+})+})+}
|
||||
{+(VariableIdentifier)+})+})+})+})+}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(PrefixNegation
|
||||
{-(Integer)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(PrefixNegation
|
||||
{-(VariableIdentifier)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(PrefixNegation
|
||||
{-(Integer)-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(InfixOperatorApp
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(App
|
||||
{-(App
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Lambda
|
||||
{-(VariableIdentifier)-}
|
||||
{-(InfixOperatorApp
|
||||
{-(Tuple
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(InfixOperatorApp
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(VariableOperator
|
||||
{-(VariableSymbol)-})-}
|
||||
{-(App
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-})-})-})-})-})-}
|
||||
{-(VariableIdentifier)-})-})-})-})-}))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(Integer))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(PrefixNegation
|
||||
(Integer))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Lambda
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(InfixOperatorApp
|
||||
(Tuple
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Empty)
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))))
|
||||
(Empty)
|
||||
(VariableIdentifier)))))))
|
||||
|
@ -6,6 +6,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -13,7 +14,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -22,20 +25,25 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -44,8 +52,11 @@
|
||||
(App
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -54,24 +65,24 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThen
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThenTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Integer))))
|
||||
@ -137,7 +148,7 @@
|
||||
(Integer)))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))))
|
||||
(Function
|
||||
@ -155,7 +166,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -163,7 +174,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Integer))
|
||||
(Empty)
|
||||
(ListComprehension
|
||||
(ListComprehension
|
||||
(Tuple
|
||||
@ -176,7 +189,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -211,6 +224,7 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
@ -231,34 +245,42 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(TextElement)))))))))))
|
||||
@ -270,6 +292,7 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier)))
|
||||
@ -277,6 +300,7 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -302,10 +326,12 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -319,10 +345,12 @@
|
||||
(VariableIdentifier))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -336,6 +364,7 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(Integer)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(Integer))))
|
||||
@ -359,23 +388,29 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Lambda
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(Tuple
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))))
|
||||
(Empty)
|
||||
(VariableIdentifier)))))))
|
||||
|
@ -6,6 +6,7 @@
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -13,7 +14,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -22,20 +25,25 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -44,8 +52,11 @@
|
||||
(App
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -54,24 +65,24 @@
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThen
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(EnumFromThenTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Integer))))
|
||||
@ -139,7 +150,7 @@
|
||||
(Integer)))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFromTo
|
||||
(ArithmeticSequence
|
||||
(Integer)
|
||||
(Integer))))))
|
||||
(Function
|
||||
@ -157,7 +168,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -165,7 +176,9 @@
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Integer))
|
||||
(Empty)
|
||||
(ListComprehension
|
||||
(ListComprehension
|
||||
(Tuple
|
||||
@ -178,7 +191,7 @@
|
||||
(Integer))))
|
||||
(Generator
|
||||
(VariableIdentifier)
|
||||
(EnumFrom
|
||||
(ArithmeticSequence
|
||||
(Integer)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
@ -213,6 +226,7 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
@ -233,34 +247,42 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(TextElement)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(TextElement)))))))))))
|
||||
@ -272,6 +294,7 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier)))
|
||||
@ -279,6 +302,7 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -304,10 +328,12 @@
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -321,10 +347,12 @@
|
||||
(VariableIdentifier))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
@ -338,6 +366,7 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(Integer)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(Integer))))
|
||||
@ -361,23 +390,29 @@
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(Lambda
|
||||
(VariableIdentifier)
|
||||
(InfixOperatorApp
|
||||
(Tuple
|
||||
(VariableIdentifier))
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))))
|
||||
(Empty)
|
||||
(VariableIdentifier)))))))
|
||||
|
159
test/fixtures/haskell/corpus/function-declarations.A.hs
vendored
Normal file
159
test/fixtures/haskell/corpus/function-declarations.A.hs
vendored
Normal file
@ -0,0 +1,159 @@
|
||||
f num1 num2 = num2
|
||||
f (Ex 1) = Ex 1
|
||||
f n@num1 x@num2 = x
|
||||
f _ num2 = num2
|
||||
f 1 2 = 3
|
||||
f "hello" "world" = "goodbye"
|
||||
f 'a' 'b' = 'c'
|
||||
f 1.0 2.0 = 3.0
|
||||
f Ex { a = 1 } = 1
|
||||
f Ex { a = 1, b = 2 } = 2
|
||||
f Ex {} = 2
|
||||
f Blob{start, end} = [start, end]
|
||||
f Blob{..} = [start, end]
|
||||
f Blob{start, end = end', ..} = [start, end', name, path]
|
||||
f (1) = 1
|
||||
f (-(1)) = 1
|
||||
f (Example a b c) = a
|
||||
f (a :<: f) = 2
|
||||
f ([]) = 1
|
||||
f (1, 2) = 1
|
||||
f ((Just 1), Just 2) = Just 1
|
||||
f (Just a, Nothing) = Nothing
|
||||
f (Left a, Right b, -(1)) = b
|
||||
f [] = 0
|
||||
f [a] = a
|
||||
f (a:bs) = a
|
||||
f (a:b:cs) = a
|
||||
f (a:b:c:ds) = a
|
||||
f ~a = 1
|
||||
f ~(-(1)) = 1
|
||||
f ~(~(a, b), c) = c
|
||||
f x = case x of
|
||||
Just a | a < 10 -> True
|
||||
| a < 20 -> False
|
||||
| a > 19 -> True
|
||||
|
||||
g x = case x of
|
||||
Just a | a < 10, True, let b :: Int -> Int
|
||||
b x = x -> True
|
||||
Nothing -> False
|
||||
|
||||
f x = case x of
|
||||
Just _ -> x where x = True
|
||||
Nothing -> False
|
||||
|
||||
f a = case a of
|
||||
Just a -> g
|
||||
where g = h
|
||||
h = 1
|
||||
Nothing -> i
|
||||
where i = j
|
||||
j = 2
|
||||
|
||||
f a = case a of
|
||||
Just a -> g
|
||||
Nothing -> i
|
||||
where g = 1
|
||||
i = 2
|
||||
|
||||
f = (
|
||||
\ a ->
|
||||
case a of
|
||||
A -> b
|
||||
)
|
||||
a = reify tcName >>= \case
|
||||
TyConI (DataD _ _ _ _ cons _) -> do
|
||||
sigs <- filter (const makeSigs) <$> traverse genSig cons
|
||||
decs <- traverse genDecl cons
|
||||
pure $ sigs ++ decs
|
||||
|
||||
_ ->
|
||||
fail "makeEff expects a type constructor"
|
||||
|
||||
f x | x < 10, x > 2 = True
|
||||
| otherwise = False
|
||||
|
||||
f x = do
|
||||
let z = x
|
||||
y <- a
|
||||
pure y
|
||||
|
||||
f x = do
|
||||
let z = x
|
||||
a
|
||||
y
|
||||
where y = pure a
|
||||
a = 1
|
||||
|
||||
f y@Example = y { a = 1, b = 2 }
|
||||
f y@(Example { a = a', b = b' }) = y { a = a' + 1, b = b' ++ " !" }
|
||||
|
||||
f = read @Int
|
||||
f = read @Int "5"
|
||||
f = read @Prelude.Int "5"
|
||||
f = read @Int . Prelude.id
|
||||
f = read @Prelude.Int . Prelude.id
|
||||
f = read @Int . id
|
||||
f = read @Prelude.Int . Prelude.id
|
||||
f = read @Int .id
|
||||
f = read @Prelude.Int .Prelude.id
|
||||
f = read @Int. id
|
||||
f = read @Prelude.Int. Prelude.id
|
||||
f = read @(x (Bar a))
|
||||
|
||||
f = Data.List.uncons . id
|
||||
f = Data.List.uncons . Prelude.id
|
||||
f = Data.List.uncons. id
|
||||
f = Data.List.uncons. Prelude.id
|
||||
f = Data.List.uncons .id
|
||||
f = Data.List.uncons .Prelude.id
|
||||
f = Data.List.uncons.id
|
||||
f = Data.List.uncons.Prelude.id
|
||||
|
||||
f = Bar ': Baz
|
||||
f = Bar ':<: Baz
|
||||
|
||||
f = (<>)
|
||||
f = a <>
|
||||
|
||||
f = 1 where
|
||||
g = 2 where
|
||||
|
||||
f = a where
|
||||
{- comment -}
|
||||
f = a where
|
||||
{-
|
||||
-}
|
||||
f = a where
|
||||
--
|
||||
f = a where
|
||||
{-# COLUMN 42 #-}
|
||||
|
||||
b = 2
|
||||
|
||||
eval (a :< b) (fmap subtermValue -> QualifiedName name iden) = bar
|
||||
|
||||
sort :: (?cmp :: a -> a -> Bool) => [a] -> [a]
|
||||
sort = sortBy ?cmp
|
||||
|
||||
b (E (u :: Union e b) q) = a
|
||||
|
||||
ifte :: ( IvoryStore a
|
||||
, IvoryZero ('Stored a)
|
||||
, GetAlloc eff ~ 'Scope s
|
||||
) => IBool
|
||||
-> Ivory eff a
|
||||
-> Ivory eff a
|
||||
-> Ivory eff a
|
||||
|
||||
haystackClient maybeURL managerSettings appName
|
||||
| Just url <- maybeURL = do
|
||||
manager <- newManager managerSettings
|
||||
request' <- parseRequest url
|
||||
let request = request'
|
||||
{ method = "POST"
|
||||
, requestHeaders = ("Content-Type", "application/json; charset=utf-8") : requestHeaders request'
|
||||
}
|
||||
pure $ HaystackClient request manager appName
|
||||
| otherwise = pure NullHaystackClient
|
160
test/fixtures/haskell/corpus/function-declarations.B.hs
vendored
Normal file
160
test/fixtures/haskell/corpus/function-declarations.B.hs
vendored
Normal file
@ -0,0 +1,160 @@
|
||||
g num1 num2 = num2
|
||||
g (Ex 1) = Ex 1
|
||||
g n@num1 x@num2 = x
|
||||
g _ num2 = num2
|
||||
g 1 2 = 3
|
||||
g "hello" "world" = "goodbye"
|
||||
g 'a' 'b' = 'c'
|
||||
g 1.0 2.0 = 3.0
|
||||
g Ex { a = 1 } = 1
|
||||
g Ex { a = 1, b = 2 } = 2
|
||||
g Ex {} = 2
|
||||
g Blob{start, end} = [start, end]
|
||||
g Blob{..} = [start, end]
|
||||
g Blob{start, end = end', ..} = [start, end', name, path]
|
||||
g c@Ex { a = 1 } = c
|
||||
g (1) = 1
|
||||
g (-(1)) = 1
|
||||
g (Example a b c) = a
|
||||
g (a :<: f) = 2
|
||||
g ([]) = 1
|
||||
g (1, 2) = 1
|
||||
g ((Just 1), Just 2) = Just 1
|
||||
g (Just a, Nothing) = Nothing
|
||||
g (Left a, Right b, -(1)) = b
|
||||
g [] = 0
|
||||
g [a] = a
|
||||
g (a:bs) = a
|
||||
g (a:b:cs) = a
|
||||
g (a:b:c:ds) = a
|
||||
g ~a = 1
|
||||
g ~(-(1)) = 1
|
||||
g ~(~(a, b), c) = c
|
||||
g x = case x of
|
||||
Just a | a < 10 -> True
|
||||
| a < 20 -> False
|
||||
| a > 19 -> True
|
||||
|
||||
f x = case x of
|
||||
Just a | a < 10, True, let b :: Int -> Int
|
||||
b x = x -> True
|
||||
Nothing -> False
|
||||
|
||||
g x = case x of
|
||||
Just _ -> x where x = True
|
||||
Nothing -> False
|
||||
|
||||
g a = case a of
|
||||
Just a -> g
|
||||
where g = h
|
||||
h = 1
|
||||
Nothing -> i
|
||||
where i = j
|
||||
j = 2
|
||||
|
||||
g a = case a of
|
||||
Just a -> g
|
||||
Nothing -> i
|
||||
where g = 1
|
||||
i = 2
|
||||
|
||||
g = (
|
||||
\ a ->
|
||||
case a of
|
||||
A -> b
|
||||
)
|
||||
b = reify tcName >>= \case
|
||||
TyConI (DataD _ _ _ _ cons _) -> do
|
||||
sigs <- filter (const makeSigs) <$> traverse genSig cons
|
||||
decs <- traverse genDecl cons
|
||||
pure $ sigs ++ decs
|
||||
|
||||
_ ->
|
||||
fail "makeEff expects a type constructor"
|
||||
|
||||
g y | y < 10, y > 2 = True
|
||||
| otherwise = False
|
||||
|
||||
g x = do
|
||||
let z = x
|
||||
y <- a
|
||||
pure y
|
||||
|
||||
g x = do
|
||||
let z = x
|
||||
a
|
||||
y
|
||||
where y = pure a
|
||||
a = 1
|
||||
|
||||
g y@Example = y { a = 1, b = 2 }
|
||||
g y@(Example { a = a', b = b' }) = y { a = a' + 1, b = b' ++ " !" }
|
||||
|
||||
g = read @Int
|
||||
g = read @Int "5"
|
||||
g = read @Prelude.Int "5"
|
||||
g = read @Int . Prelude.id
|
||||
g = read @Prelude.Int . Prelude.id
|
||||
g = read @Int . id
|
||||
g = read @Prelude.Int . Prelude.id
|
||||
g = read @Int .id
|
||||
g = read @Prelude.Int .Prelude.id
|
||||
g = read @Int. id
|
||||
g = read @Prelude.Int. Prelude.id
|
||||
g = read @(x (Bar a))
|
||||
|
||||
g = Data.List.uncons . id
|
||||
g = Data.List.uncons . Prelude.id
|
||||
g = Data.List.uncons. id
|
||||
g = Data.List.uncons. Prelude.id
|
||||
g = Data.List.uncons .id
|
||||
g = Data.List.uncons .Prelude.id
|
||||
g = Data.List.uncons.id
|
||||
g = Data.List.uncons.Prelude.id
|
||||
|
||||
g = Bar ': Baz
|
||||
g = Bar ':<: Baz
|
||||
|
||||
g = (<>)
|
||||
g = a <>
|
||||
|
||||
g = 1 where
|
||||
h = 2 where
|
||||
|
||||
g = a where
|
||||
{- comment -}
|
||||
g = a where
|
||||
{-
|
||||
-}
|
||||
g = a where
|
||||
--
|
||||
g = a where
|
||||
{-# COLUMN 42 #-}
|
||||
|
||||
c = 2
|
||||
|
||||
eval' (a :< b) (fmap subtermValue -> QualifiedName name' iden) = foo
|
||||
|
||||
sort' :: (?cmp :: a -> a -> Bool) => [a] -> [a]
|
||||
sort' = sortBy ?cmp
|
||||
|
||||
c (F (u :: Union e b) q) = b
|
||||
|
||||
g :: ( IvoryStore a
|
||||
, IvoryZero ('Stored a)
|
||||
, GetAlloc eff ~ 'Scope s
|
||||
) => IBool
|
||||
-> Ivory eff a
|
||||
-> Ivory eff a
|
||||
-> Ivory eff a
|
||||
|
||||
needlestackClient maybeURL directorSettings appName
|
||||
| Just url <- maybeURL = do
|
||||
director <- newDirector directorSettings
|
||||
request' <- parseRequest url
|
||||
let request = request'
|
||||
{ method = "POST"
|
||||
, requestHeaders = ("Content-Type", "application/json; charset=utf-8") : requestHeaders request'
|
||||
}
|
||||
pure $ NeedlestackClient request director appName
|
||||
| otherwise = pure NullNeedlestackClient
|
2147
test/fixtures/haskell/corpus/function-declarations.diffA-B.txt
vendored
Normal file
2147
test/fixtures/haskell/corpus/function-declarations.diffA-B.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
2302
test/fixtures/haskell/corpus/function-declarations.diffB-A.txt
vendored
Normal file
2302
test/fixtures/haskell/corpus/function-declarations.diffB-A.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
1158
test/fixtures/haskell/corpus/function-declarations.parseA.txt
vendored
Normal file
1158
test/fixtures/haskell/corpus/function-declarations.parseA.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
1170
test/fixtures/haskell/corpus/function-declarations.parseB.txt
vendored
Normal file
1170
test/fixtures/haskell/corpus/function-declarations.parseB.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
@ -183,7 +183,7 @@
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(TypeConstructorIdentifier)
|
||||
(Context
|
||||
(Statements
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
|
@ -183,7 +183,7 @@
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(TypeConstructorIdentifier)
|
||||
(Context
|
||||
(Statements
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
|
@ -171,7 +171,7 @@
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(TypeConstructorIdentifier)
|
||||
(Context
|
||||
(Statements
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
|
@ -172,7 +172,7 @@
|
||||
(GADTConstructor
|
||||
(Empty)
|
||||
(TypeConstructorIdentifier)
|
||||
(Context
|
||||
(Statements
|
||||
(Pragma)
|
||||
(FunctionType
|
||||
(Type
|
||||
|
52
test/fixtures/haskell/corpus/layout.A.hs
vendored
Normal file
52
test/fixtures/haskell/corpus/layout.A.hs
vendored
Normal file
@ -0,0 +1,52 @@
|
||||
f = let y = x
|
||||
x = let g = 1
|
||||
in g
|
||||
in y
|
||||
|
||||
f = a
|
||||
where a = b
|
||||
b = 1
|
||||
|
||||
f = a
|
||||
where a = b
|
||||
b = 1
|
||||
|
||||
f = foo
|
||||
where a = b
|
||||
where c = d
|
||||
e = f
|
||||
x = w
|
||||
|
||||
g = do c
|
||||
a
|
||||
do b
|
||||
e
|
||||
do g
|
||||
g
|
||||
h
|
||||
i
|
||||
|
||||
a = do
|
||||
b
|
||||
where
|
||||
c = d
|
||||
|
||||
a = do
|
||||
b
|
||||
where
|
||||
c = d
|
||||
|
||||
a = do
|
||||
b
|
||||
where
|
||||
c = d
|
||||
|
||||
class Foo bar where
|
||||
fooVariables :: bar -> [Baz]
|
||||
{-
|
||||
-}
|
||||
class Foo1 bar where
|
||||
liftFoo = foldMap
|
||||
|
||||
freeFoo bar = case freeFoo bar of
|
||||
[n] -> Right n
|
42
test/fixtures/haskell/corpus/layout.B.hs
vendored
Normal file
42
test/fixtures/haskell/corpus/layout.B.hs
vendored
Normal file
@ -0,0 +1,42 @@
|
||||
f = let x = y
|
||||
y = let h = 1
|
||||
in h
|
||||
in x
|
||||
|
||||
f = b
|
||||
where b = a
|
||||
a = 1
|
||||
|
||||
f = c
|
||||
where c = b
|
||||
b = 1
|
||||
|
||||
f = bar
|
||||
where c = a
|
||||
where a = e
|
||||
e = f
|
||||
w = x
|
||||
|
||||
g = do a
|
||||
b
|
||||
do c
|
||||
d
|
||||
do e
|
||||
f
|
||||
g
|
||||
h
|
||||
|
||||
b = do
|
||||
a
|
||||
where
|
||||
d = c
|
||||
|
||||
b = do
|
||||
c
|
||||
where
|
||||
c = e
|
||||
|
||||
b = do
|
||||
a
|
||||
where
|
||||
a = f
|
212
test/fixtures/haskell/corpus/layout.diffA-B.txt
vendored
Normal file
212
test/fixtures/haskell/corpus/layout.diffA-B.txt
vendored
Normal file
@ -0,0 +1,212 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-}
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{+(VariableIdentifier)+}
|
||||
{-(Let
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(VariableIdentifier)-})-}))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Let
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+}
|
||||
{+(VariableIdentifier)+})+})+})+}
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-}
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{+(VariableIdentifier)+}
|
||||
{-(Integer)-}))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+})))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
{-(VariableIdentifier)-}
|
||||
(VariableIdentifier)
|
||||
{+(VariableIdentifier)+}
|
||||
(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+})+}
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(VariableIdentifier)-})
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Do
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(VariableIdentifier)+})+})+})+})+})+})+}
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Do
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))))))
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-})-})-})-})-}
|
||||
{-(TypeClass
|
||||
{-(Empty)-}
|
||||
{-(TypeClassIdentifier)-}
|
||||
{-(TypeVariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Context
|
||||
{-(Comment)-}
|
||||
{-(TypeSignature
|
||||
{-(VariableIdentifier)-}
|
||||
{-(FunctionType
|
||||
{-(Type
|
||||
{-(TypeVariableIdentifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Type
|
||||
{-(Array
|
||||
{-(Type
|
||||
{-(TypeConstructorIdentifier)-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(TypeParameters)-}
|
||||
{-(Empty)-})-})-})-})-})-})-}
|
||||
{-(TypeClass
|
||||
{-(Empty)-}
|
||||
{-(TypeClassIdentifier)-}
|
||||
{-(TypeVariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Match
|
||||
{-(App
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(Pattern
|
||||
{-(ListPattern
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(App
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(Empty)-}
|
||||
{-(VariableIdentifier)-})-})-})-})-})-}))
|
219
test/fixtures/haskell/corpus/layout.diffB-A.txt
vendored
Normal file
219
test/fixtures/haskell/corpus/layout.diffB-A.txt
vendored
Normal file
@ -0,0 +1,219 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-}
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{+(VariableIdentifier)+}
|
||||
{-(Let
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(VariableIdentifier)-})-}))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Let
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+}
|
||||
{+(VariableIdentifier)+})+})+})+}
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-}
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{+(VariableIdentifier)+}
|
||||
{-(Integer)-}))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+})))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
{+(VariableIdentifier)+}
|
||||
(VariableIdentifier)
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+})+}
|
||||
{+(VariableIdentifier)+})+}
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(VariableIdentifier)-})-}
|
||||
{-(VariableIdentifier)-})))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Do
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))))))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(VariableIdentifier)+})+})+})+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Do
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(VariableIdentifier)+})+})+})+})+})+})+}
|
||||
{+(TypeClass
|
||||
{+(Empty)+}
|
||||
{+(TypeClassIdentifier)+}
|
||||
{+(TypeVariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Context
|
||||
{+(Comment)+}
|
||||
{+(TypeSignature
|
||||
{+(VariableIdentifier)+}
|
||||
{+(FunctionType
|
||||
{+(Type
|
||||
{+(TypeVariableIdentifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Type
|
||||
{+(Array
|
||||
{+(Type
|
||||
{+(TypeConstructorIdentifier)+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(TypeParameters)+}
|
||||
{+(Empty)+})+})+})+})+})+})+}
|
||||
{+(TypeClass
|
||||
{+(Empty)+}
|
||||
{+(TypeClassIdentifier)+}
|
||||
{+(TypeVariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(VariableIdentifier)+})+})+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Match
|
||||
{+(App
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableIdentifier)+})+}
|
||||
{+(Pattern
|
||||
{+(ListPattern
|
||||
{+(VariableIdentifier)+})+}
|
||||
{+(App
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(Empty)+}
|
||||
{+(VariableIdentifier)+})+})+})+})+})+}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-})-})-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Do
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(VariableIdentifier)-})-})-})-})-})-})-}))
|
160
test/fixtures/haskell/corpus/layout.parseA.txt
vendored
Normal file
160
test/fixtures/haskell/corpus/layout.parseA.txt
vendored
Normal file
@ -0,0 +1,160 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer)))
|
||||
(VariableIdentifier))))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Context
|
||||
(Comment)
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Match
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))
|
||||
(Pattern
|
||||
(ListPattern
|
||||
(VariableIdentifier))
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(VariableIdentifier))))))))
|
113
test/fixtures/haskell/corpus/layout.parseB.txt
vendored
Normal file
113
test/fixtures/haskell/corpus/layout.parseB.txt
vendored
Normal file
@ -0,0 +1,113 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Let
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer)))
|
||||
(VariableIdentifier))))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Integer))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Do
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))))
|
@ -1,11 +1,10 @@
|
||||
(Module
|
||||
(ModuleIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Integer)))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
@ -284,6 +283,10 @@
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
|
@ -1,11 +1,10 @@
|
||||
(Module
|
||||
(ModuleIdentifier)
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(Integer)))
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
{+(Integer)+})+})+}
|
||||
{+(Function
|
||||
{+(VariableIdentifier)+}
|
||||
{+(Statements
|
||||
@ -284,6 +283,10 @@
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
{-(Integer)-})-})-}
|
||||
{-(Function
|
||||
{-(VariableIdentifier)-}
|
||||
{-(Statements
|
||||
|
@ -1,9 +1,7 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(QualifiedModuleIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) })
|
||||
(Statements)))
|
||||
(QualifiedModuleIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) })
|
||||
(Statements))
|
||||
|
@ -1,9 +1,7 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(QualifiedModuleIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) })
|
||||
(Statements)))
|
||||
(QualifiedModuleIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) })
|
||||
(Statements))
|
||||
|
@ -1,7 +1,5 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier))
|
||||
(Statements)))
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier))
|
||||
(Statements))
|
||||
|
@ -1,7 +1,5 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier))
|
||||
(Statements)))
|
||||
(QualifiedModuleIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ModuleIdentifier))
|
||||
(Statements))
|
||||
|
@ -8,8 +8,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Context'
|
||||
@ -22,8 +21,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -32,17 +30,16 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))))))
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -61,11 +58,10 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -74,8 +70,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)))
|
||||
(NewType
|
||||
@ -85,8 +80,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)
|
||||
(TypeClassIdentifier)
|
||||
|
@ -8,8 +8,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Context'
|
||||
@ -22,8 +21,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -32,17 +30,16 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))))))
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -61,11 +58,10 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -74,8 +70,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)))
|
||||
(NewType
|
||||
@ -85,8 +80,7 @@
|
||||
(Constructor
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)
|
||||
(TypeClassIdentifier)
|
||||
|
@ -6,8 +6,7 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Context'
|
||||
@ -18,24 +17,22 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(VariableIdentifier))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))))))
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(VariableIdentifier))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -52,19 +49,17 @@
|
||||
(TypeVariableIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)))
|
||||
(NewType
|
||||
@ -72,8 +67,7 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)
|
||||
(TypeClassIdentifier)
|
||||
|
@ -6,8 +6,7 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Context'
|
||||
@ -18,24 +17,22 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(VariableIdentifier))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))))))
|
||||
(Statements
|
||||
(Field
|
||||
(Statements
|
||||
(VariableIdentifier))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty)))))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
@ -52,19 +49,17 @@
|
||||
(TypeVariableIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(NewType
|
||||
(Statements
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeConstructorIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)))
|
||||
(NewType
|
||||
@ -72,8 +67,7 @@
|
||||
(TypeConstructorIdentifier))
|
||||
(Constructor
|
||||
(ConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeVariableIdentifier))
|
||||
(Deriving
|
||||
(TypeClassIdentifier)
|
||||
(TypeClassIdentifier)
|
||||
|
8
test/fixtures/haskell/corpus/statements.A.hs
vendored
Normal file
8
test/fixtures/haskell/corpus/statements.A.hs
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
f = if a then 1 else 2
|
||||
f = if a; then b; else c
|
||||
f = if (if a then b else c) then d else e
|
||||
f = if if a then b else c then d else e
|
||||
|
||||
head' :: [a] -> a
|
||||
head' [] = error "No head for empty lists!"
|
||||
head' (x:_) = x
|
8
test/fixtures/haskell/corpus/statements.B.hs
vendored
Normal file
8
test/fixtures/haskell/corpus/statements.B.hs
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
g = if b then 1 else 2
|
||||
g = if b; then c; else d
|
||||
g = if (if b then c else d) then e else f
|
||||
g = if if b then c else d then e else f
|
||||
|
||||
h' :: [a] -> a
|
||||
h' [] = error "No head for empty lists!"
|
||||
h' (x:_) = x
|
90
test/fixtures/haskell/corpus/statements.diffA-B.txt
vendored
Normal file
90
test/fixtures/haskell/corpus/statements.diffA-B.txt
vendored
Normal file
@ -0,0 +1,90 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ListConstructor)
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(TextElement))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Wildcard))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
90
test/fixtures/haskell/corpus/statements.diffB-A.txt
vendored
Normal file
90
test/fixtures/haskell/corpus/statements.diffB-A.txt
vendored
Normal file
@ -0,0 +1,90 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) })))
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(ListConstructor)
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(TextElement))))
|
||||
(Function
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Wildcard))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
69
test/fixtures/haskell/corpus/statements.parseA.txt
vendored
Normal file
69
test/fixtures/haskell/corpus/statements.parseA.txt
vendored
Normal file
@ -0,0 +1,69 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ListConstructor)
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(TextElement))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Wildcard))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
69
test/fixtures/haskell/corpus/statements.parseB.txt
vendored
Normal file
69
test/fixtures/haskell/corpus/statements.parseB.txt
vendored
Normal file
@ -0,0 +1,69 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(If
|
||||
(If
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ListConstructor)
|
||||
(Statements
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(TextElement))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Wildcard))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
42
test/fixtures/haskell/corpus/tempate-haskell.A.hs
vendored
Normal file
42
test/fixtures/haskell/corpus/tempate-haskell.A.hs
vendored
Normal file
@ -0,0 +1,42 @@
|
||||
[|example|]
|
||||
[e|example|]
|
||||
[p|example|]
|
||||
[t|example|]
|
||||
[d|example|]
|
||||
[str|example|]
|
||||
|
||||
[ | example| ]
|
||||
[ e| example| ]
|
||||
[ p| example| ]
|
||||
[ t| example| ]
|
||||
[ d| example| ]
|
||||
[ str| example| ]
|
||||
|
||||
[ | example | ]
|
||||
[ e | example | ]
|
||||
[ p | example | ]
|
||||
[ t | example | ]
|
||||
[ d | example | ]
|
||||
[ str | example | ]
|
||||
[str|integer,double,varchar,boolean,date,money,enum
|
||||
|13,3.14159,testing!,false,1900-01-01,$3.99,foo
|
||||
|12,0.1,a string,true,1929-10-01,12,bar
|
||||
|]
|
||||
|
||||
[ | [{ "ret_setof_integers": 1 },
|
||||
{ "ret_setof_integers": 2 },
|
||||
{ "ret_setof_integers": 3 }] | ]
|
||||
|
||||
[|
|
||||
[
|
||||
{ "ret_setof_integers": 1 },
|
||||
{ "ret_setof_integers": 2 },
|
||||
{ "ret_setof_integers": 3 }
|
||||
]
|
||||
|]
|
||||
|
||||
f = [|a|] `b` c
|
||||
|
||||
f = $x
|
||||
f = $(a . b $ c)
|
||||
$(makeEff ''Embedded)
|
104
test/fixtures/haskell/corpus/tempate-haskell.parseA.txt
vendored
Normal file
104
test/fixtures/haskell/corpus/tempate-haskell.parseA.txt
vendored
Normal file
@ -0,0 +1,104 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationExpression)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationPattern)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationType)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationDeclaration)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationQuoter)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationExpression)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationPattern)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationType)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationDeclaration)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationQuoter)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationExpression)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationPattern)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationType)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationDeclaration)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationQuoter)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(QuasiQuotationQuoter)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(QuasiQuotation
|
||||
(Empty)
|
||||
(QuasiQuotationExpressionBody))
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Splice
|
||||
(VariableIdentifier))))
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(Splice
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier))))))
|
||||
(Splice
|
||||
(App
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(QuotedName
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier)))))))
|
42
test/fixtures/haskell/corpus/template-haskell.B.hs
vendored
Normal file
42
test/fixtures/haskell/corpus/template-haskell.B.hs
vendored
Normal file
@ -0,0 +1,42 @@
|
||||
[|example'|]
|
||||
[e|example'|]
|
||||
[p|example'|]
|
||||
[t|example'|]
|
||||
[d|example'|]
|
||||
[str|example'|]
|
||||
|
||||
[ | example'| ]
|
||||
[ e| example'| ]
|
||||
[ p| example'| ]
|
||||
[ t| example'| ]
|
||||
[ d| example'| ]
|
||||
[ str| example'| ]
|
||||
|
||||
[ | example' | ]
|
||||
[ e | example' | ]
|
||||
[ p | example' | ]
|
||||
[ t | example' | ]
|
||||
[ d | example' | ]
|
||||
[ str | example' | ]
|
||||
[str|integer,double,varchar,boolean,date,money,enum
|
||||
|12,0.1,a string,true,1929-10-01,12,bar
|
||||
|13,3.14159,testing!,false,1900-01-01,$3.99,foo
|
||||
|]
|
||||
|
||||
[ | [{ "ret_setof_integers": 3 },
|
||||
{ "ret_setof_integers": 4 },
|
||||
{ "ret_setof_integers": 5 }] | ]
|
||||
|
||||
[|
|
||||
[
|
||||
{ "ret_setof_integers": 3 },
|
||||
{ "ret_setof_integers": 4 },
|
||||
{ "ret_setof_integers": 5 }
|
||||
]
|
||||
|]
|
||||
|
||||
g = [|a|] `b` c
|
||||
|
||||
g = $x
|
||||
g = $(a . b $ c)
|
||||
$(makeEff' ''Embedded)
|
48
test/fixtures/haskell/corpus/type-class-declarations.A.hs
vendored
Normal file
48
test/fixtures/haskell/corpus/type-class-declarations.A.hs
vendored
Normal file
@ -0,0 +1,48 @@
|
||||
class Show a where {}
|
||||
class Show a b where {}
|
||||
|
||||
class Show a => Read a where {}
|
||||
class (Show a, Eq a) => Read a where {}
|
||||
|
||||
class Foo a where {
|
||||
op :: Num b => a -> b -> a;
|
||||
op' :: (Num a, Num b) => a -> b -> a;
|
||||
}
|
||||
|
||||
class Foo a where
|
||||
infixl `op`
|
||||
infixr 7 `op`
|
||||
infix 7 `op`, `ip`, `ap`
|
||||
infix <$>
|
||||
infix 7 <$>
|
||||
infix 7 :
|
||||
infix 7 :.
|
||||
infix 7 :<:
|
||||
|
||||
class (Eq a) => Ord a where
|
||||
compare :: a -> a -> Ordering
|
||||
(<), (<=), (>=), (>) :: a -> a -> Bool
|
||||
max, min :: a -> a -> a
|
||||
id :: a
|
||||
|
||||
class Bar a b m => Baz a b m where {}
|
||||
|
||||
class Bar baz where
|
||||
foo :: wiz -> Baz
|
||||
default foo :: wiz -> Baz
|
||||
|
||||
class Bar (baz :: Foo) where
|
||||
|
||||
class Effectful (m :: [* -> *] -> * -> *) where
|
||||
|
||||
class Foo bar where
|
||||
type Baz wiz :: Wax
|
||||
|
||||
class Foo bar where
|
||||
type Baz wiz :: [* -> *]
|
||||
|
||||
class Bar baz => Foo fax where
|
||||
type family Woo a :: [* -> *]
|
||||
|
||||
class (Monad a, Show b) => Foo a b c | a -> c, b -> c where
|
||||
d :: a b
|
48
test/fixtures/haskell/corpus/type-class-declarations.B.hs
vendored
Normal file
48
test/fixtures/haskell/corpus/type-class-declarations.B.hs
vendored
Normal file
@ -0,0 +1,48 @@
|
||||
class Eq a where {}
|
||||
class Ord a b where {}
|
||||
|
||||
class Eq a => Ord a where {}
|
||||
class (Show a, Eq a) => Ord a where {}
|
||||
|
||||
class Bar a where {
|
||||
op' :: Num b => a -> b -> a;
|
||||
op :: (Num a, Num b) => a -> b -> a;
|
||||
}
|
||||
|
||||
class Bar a where
|
||||
infixl `op`
|
||||
infixr 8 `op`
|
||||
infix 8 `op`, `ip`, `ap`
|
||||
infix <$>
|
||||
infix 8 <$>
|
||||
infix 8 :
|
||||
infix 8 :.
|
||||
infix 8 :<:
|
||||
|
||||
class (Eq b) => Ord b where
|
||||
compare :: b -> b -> Ordering
|
||||
(<), (<=), (>=), (>) :: b -> b -> Bool
|
||||
max, min :: b -> b -> b
|
||||
id :: b
|
||||
|
||||
class Foo a b m => Bar a b m where {}
|
||||
|
||||
class Foo bat where
|
||||
bar :: bat -> Baz
|
||||
default bar :: bat -> Baz
|
||||
|
||||
class Foo (baz :: Bar) where
|
||||
|
||||
class Effectful' (m' :: [* -> *] -> * -> *) where
|
||||
|
||||
class Foo bar where
|
||||
type Baz wiz :: Wax
|
||||
|
||||
class Foo bar where
|
||||
type Baz wiz :: [* -> *]
|
||||
|
||||
class Foo baz => Bar fax where
|
||||
type family Woot a :: [* -> *]
|
||||
|
||||
class (Monad a, Show b) => Foo a b c | b -> d, a -> b where
|
||||
d :: a b
|
385
test/fixtures/haskell/corpus/type-class-declarations.diffA-B.txt
vendored
Normal file
385
test/fixtures/haskell/corpus/type-class-declarations.diffA-B.txt
vendored
Normal file
@ -0,0 +1,385 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }))
|
||||
(TypeClassIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) })))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(Statements
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(DefaultSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier)))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Empty))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(FunctionalDependency
|
||||
(Statements
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))))))
|
385
test/fixtures/haskell/corpus/type-class-declarations.diffB-A.txt
vendored
Normal file
385
test/fixtures/haskell/corpus/type-class-declarations.diffB-A.txt
vendored
Normal file
@ -0,0 +1,385 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }))
|
||||
(TypeClassIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) })))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(Statements
|
||||
(TypeSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(DefaultSignature
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier)))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)))
|
||||
{ (TypeClassIdentifier)
|
||||
->(TypeClassIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Empty))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(FunctionalDependency
|
||||
(Statements
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(FunctionType
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))))))
|
341
test/fixtures/haskell/corpus/type-class-declarations.parseA.txt
vendored
Normal file
341
test/fixtures/haskell/corpus/type-class-declarations.parseA.txt
vendored
Normal file
@ -0,0 +1,341 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(DefaultSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier)))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Empty))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(FunctionalDependency
|
||||
(Statements
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))))))
|
341
test/fixtures/haskell/corpus/type-class-declarations.parseB.txt
vendored
Normal file
341
test/fixtures/haskell/corpus/type-class-declarations.parseB.txt
vendored
Normal file
@ -0,0 +1,341 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier))
|
||||
(VariableOperator
|
||||
(InfixVariableIdentifier)))
|
||||
(Fixity'
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(VariableOperator
|
||||
(VariableSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))
|
||||
(Fixity'
|
||||
(Integer)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol)))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(DefaultSignature
|
||||
(VariableIdentifier)
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Statements))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier)))))
|
||||
(TypeClass
|
||||
(Empty)
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(Empty))))
|
||||
(TypeClass
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(FunctionalDependency
|
||||
(Statements
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))))))
|
76
test/fixtures/haskell/corpus/type-class-instance-declarations.A.hs
vendored
Normal file
76
test/fixtures/haskell/corpus/type-class-instance-declarations.A.hs
vendored
Normal file
@ -0,0 +1,76 @@
|
||||
instance Show Int where
|
||||
instance Show Int where {}
|
||||
instance Show Int
|
||||
instance Show Int a where
|
||||
instance Show Int a where {}
|
||||
instance Show Int a
|
||||
instance Show (Maybe a) where
|
||||
instance Show (Maybe a) where {}
|
||||
instance Show (Maybe a)
|
||||
instance Show (a, b, c) where
|
||||
instance Show (a, b, c) where {}
|
||||
instance Show (a, b, c)
|
||||
instance Show [a] where
|
||||
instance Show [a] where {}
|
||||
instance Show [a]
|
||||
instance Show (a -> b) where
|
||||
instance Show (a -> b) where {}
|
||||
instance Show (a -> b)
|
||||
instance Show Foo where
|
||||
bar (Foo Baz) (Foo Wix) = EQ
|
||||
instance Show Foo where {
|
||||
bar (Foo Baz) (Foo Wix) = EQ
|
||||
}
|
||||
instance Show (,) where
|
||||
instance Show (,) where {}
|
||||
instance Show (,)
|
||||
instance Show (Bar, Baz a b) where
|
||||
instance Show (Bar, Baz a b) where {}
|
||||
instance Show (Bar, Baz a b)
|
||||
instance Show [(Bar, Baz a b)] where
|
||||
instance Show [(Bar, Baz a b)] where {}
|
||||
instance Show [(Bar, Baz a b)]
|
||||
instance Show [Bar] where
|
||||
instance Show [Bar] where {}
|
||||
instance Show [Bar]
|
||||
instance Show [Bar a b] where
|
||||
instance Show [Bar a b] where {}
|
||||
instance Show [Bar a b]
|
||||
instance Show [Bar Baz b] where
|
||||
instance Show [Bar Baz b] where {}
|
||||
instance Show [Bar Baz b]
|
||||
|
||||
instance Show a => Read Int where {}
|
||||
instance Show a => Read (Maybe a) where {}
|
||||
instance (Show a, Eq a) => Read (Maybe a) where {}
|
||||
instance (Foo (Bar [Baz])) => Read (Bar) where {}
|
||||
instance (Foo (Bar (Baz, Baz))) => Read (Bar) where {}
|
||||
|
||||
instance Foo Bar where
|
||||
baz :: Num b => a -> b -> a
|
||||
baz' :: (Num a, Num b) => Maybe a -> Either String b -> Maybe (Either String a)
|
||||
|
||||
instance Bar a b m => Baz a b m where {}
|
||||
|
||||
instance ( Foo (Bar a b '[]) c ) => Baz a b (Bix a b c) where
|
||||
|
||||
instance (Bar baz ~ foo) => Wix baz where
|
||||
toWix = undefined
|
||||
Wix baz <> Wix baz' = Wix (baz <> baz')
|
||||
|
||||
instance Bar (f :+: g) where {}
|
||||
|
||||
instance (A :< b, B :< b) => Bar (A c) Foo where {}
|
||||
|
||||
instance Foo Bar where
|
||||
foo D.F{..} = foo
|
||||
|
||||
instance Show Foo where
|
||||
bar (Foo Baz) (Foo Baz) = EQ
|
||||
|
||||
instance forall location a b. (Show a, Monad b) => MonadError (Value a) b where
|
||||
unit = pure . Unit
|
||||
|
||||
instance Show A where b = c
|
||||
-- a
|
||||
instance Show A where b = c
|
76
test/fixtures/haskell/corpus/type-class-instance-declarations.B.hs
vendored
Normal file
76
test/fixtures/haskell/corpus/type-class-instance-declarations.B.hs
vendored
Normal file
@ -0,0 +1,76 @@
|
||||
instance Eq Int where
|
||||
instance Eq Int where {}
|
||||
instance Eq Int
|
||||
instance Eq Int a where
|
||||
instance Eq Int a where {}
|
||||
instance Eq Int a
|
||||
instance Eq (Maybe a) where
|
||||
instance Eq (Maybe a) where {}
|
||||
instance Eq (Maybe a)
|
||||
instance Eq (a, b, c) where
|
||||
instance Eq (a, b, c) where {}
|
||||
instance Eq (a, b, c)
|
||||
instance Eq [a] where
|
||||
instance Eq [a] where {}
|
||||
instance Eq [a]
|
||||
instance Eq (a -> b) where
|
||||
instance Eq (a -> b) where {}
|
||||
instance Eq (a -> b)
|
||||
instance Eq Foo where
|
||||
bar (Foo Baz) (Foo Wix) = EQ
|
||||
instance Eq Foo where {
|
||||
bar (Foo Baz) (Foo Wix) = EQ
|
||||
}
|
||||
instance Eq (,) where
|
||||
instance Eq (,) where {}
|
||||
instance Eq (,)
|
||||
instance Eq (Bar, Baz a b) where
|
||||
instance Eq (Bar, Baz a b) where {}
|
||||
instance Eq (Bar, Baz a b)
|
||||
instance Eq [(Bar, Baz a b)] where
|
||||
instance Eq [(Bar, Baz a b)] where {}
|
||||
instance Eq [(Bar, Baz a b)]
|
||||
instance Eq [Bar] where
|
||||
instance Eq [Bar] where {}
|
||||
instance Eq [Bar]
|
||||
instance Eq [Bar a b] where
|
||||
instance Eq [Bar a b] where {}
|
||||
instance Eq [Bar a b]
|
||||
instance Eq [Bar Baz b] where
|
||||
instance Eq [Bar Baz b] where {}
|
||||
instance Eq [Bar Baz b]
|
||||
|
||||
instance Show a => Read Int where {}
|
||||
instance Show a => Read (Maybe a) where {}
|
||||
instance (Show a, Eq a) => Read (Maybe a) where {}
|
||||
instance (Foo (Bar [Baz])) => Read (Bar) where {}
|
||||
instance (Foo (Bar (Baz, Baz))) => Read (Bar) where {}
|
||||
|
||||
instance Bar Foo where
|
||||
baz :: Num b => a -> b -> a
|
||||
baz' :: (Num a, Num b) => Maybe a -> Either String b -> Maybe (Either String a)
|
||||
|
||||
instance Foo a b m => Bar a b m where {}
|
||||
|
||||
instance ( Foo (Bar a b '[]) c ) => Baz a b (Bix a b c) where
|
||||
|
||||
instance (Foo baz ~ bar) => Wix baz where
|
||||
toWix = undefined
|
||||
Wix baz <> Wix baz' = Wix (baz <> baz')
|
||||
|
||||
instance Foo (f :+: g) where {}
|
||||
|
||||
instance (B :< a, A :< b) => Foo (A b) Bar where {}
|
||||
|
||||
instance Bar Foo where
|
||||
foo F.D{..} = bar
|
||||
|
||||
instance Show Bar where
|
||||
bar (Bar Baz) (Bar Baz) = EQ
|
||||
|
||||
instance forall location b c. (Show b, Monad c) => ErrorMonad (Value b) c where
|
||||
unit = pure . Unit
|
||||
|
||||
instance Show B where c = d
|
||||
-- a
|
||||
instance Show B where c = d
|
1183
test/fixtures/haskell/corpus/type-class-instance-declarations.diffA-B.txt
vendored
Normal file
1183
test/fixtures/haskell/corpus/type-class-instance-declarations.diffA-B.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
1186
test/fixtures/haskell/corpus/type-class-instance-declarations.diffB-A.txt
vendored
Normal file
1186
test/fixtures/haskell/corpus/type-class-instance-declarations.diffB-A.txt
vendored
Normal file
File diff suppressed because it is too large
Load Diff
737
test/fixtures/haskell/corpus/type-class-instance-declarations.parseA.txt
vendored
Normal file
737
test/fixtures/haskell/corpus/type-class-instance-declarations.parseA.txt
vendored
Normal file
@ -0,0 +1,737 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty)))))))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(QuotedName
|
||||
(ListConstructor)))
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(EqualityConstraint
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeVariableIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier)))))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(InfixOperatorPattern
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(TypeVariableIdentifier))
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeConstructorIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(LabeledPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(RecordWildCards)))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(ScopedTypeVariables
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(ConstructorIdentifier))))))
|
||||
(Context
|
||||
(Comment)
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
737
test/fixtures/haskell/corpus/type-class-instance-declarations.parseB.txt
vendored
Normal file
737
test/fixtures/haskell/corpus/type-class-instance-declarations.parseB.txt
vendored
Normal file
@ -0,0 +1,737 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TupleConstructor))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty)))
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))))
|
||||
(Empty))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Tuple
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty)))))
|
||||
(TypeSignature
|
||||
(VariableIdentifier)
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(FunctionType
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Empty))
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Empty)))))))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(QuotedName
|
||||
(ListConstructor)))
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(EqualityConstraint
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeVariableIdentifier)))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeVariableIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(App
|
||||
(ConstructorIdentifier)
|
||||
(Empty)
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(VariableIdentifier)))))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(InfixOperatorPattern
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(Type
|
||||
(TypeVariableIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(Context'
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(TypeVariableIdentifier))
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(ConstructorOperator
|
||||
(ConstructorSymbol))
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeConstructorIdentifier)))
|
||||
(Statements))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(LabeledPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(RecordWildCards)))
|
||||
(Statements
|
||||
(VariableIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(ConstructorIdentifier)))
|
||||
(Statements
|
||||
(ConstructorIdentifier)))))
|
||||
(TypeClassInstance
|
||||
(ScopedTypeVariables
|
||||
(Statements
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(TypeVariableIdentifier)))
|
||||
(Context'
|
||||
(Statements
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(Class
|
||||
(TypeClassIdentifier)
|
||||
(TypeVariableIdentifier))))
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(Statements
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier))
|
||||
(TypeVariableIdentifier)))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(InfixOperatorApp
|
||||
(VariableIdentifier)
|
||||
(Empty)
|
||||
(VariableOperator
|
||||
(VariableSymbol))
|
||||
(ConstructorIdentifier))))))
|
||||
(Context
|
||||
(Comment)
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier))))))
|
||||
(TypeClassInstance
|
||||
(TypeClassIdentifier)
|
||||
(Instance
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements
|
||||
(Function
|
||||
(VariableIdentifier)
|
||||
(Statements
|
||||
(VariableIdentifier)))))))
|
11
test/fixtures/haskell/corpus/type-family-declarations.A.hs
vendored
Normal file
11
test/fixtures/haskell/corpus/type-family-declarations.A.hs
vendored
Normal file
@ -0,0 +1,11 @@
|
||||
type family Foo bar where
|
||||
Bar = Wiz
|
||||
Baz = 'Custom
|
||||
Bar.Baz a = 'Custom
|
||||
Bar.Baz (A a) = 'Custom
|
||||
|
||||
type family F a :: *
|
||||
type instance F [Int] = Int
|
||||
type instance F String = Char
|
||||
|
||||
type family Bar (baz :: [(* -> *) -> Wiz]) (foo :: * -> *) :: Wiz where
|
11
test/fixtures/haskell/corpus/type-family-declarations.B.hs
vendored
Normal file
11
test/fixtures/haskell/corpus/type-family-declarations.B.hs
vendored
Normal file
@ -0,0 +1,11 @@
|
||||
type family Baz bar where
|
||||
Baz = Wiz
|
||||
Bar = 'Custom
|
||||
Baz.Bar a = 'Custom
|
||||
Baz.Bar (B b) = 'Custom
|
||||
|
||||
type family F b :: *
|
||||
type instance F [String] = Int
|
||||
type instance F Char = Char
|
||||
|
||||
type family Baz (bar :: [(* -> *) -> Waz]) (faz :: * -> *) :: Waz where
|
107
test/fixtures/haskell/corpus/type-family-declarations.diffA-B.txt
vendored
Normal file
107
test/fixtures/haskell/corpus/type-family-declarations.diffA-B.txt
vendored
Normal file
@ -0,0 +1,107 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Empty)
|
||||
(Statements
|
||||
{-(Function
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(Statements
|
||||
{-(ConstructorIdentifier)-})-})-}
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
{+(ConstructorIdentifier)+}
|
||||
{-(QuotedName
|
||||
{-(TypeConstructorIdentifier)-})-}))
|
||||
{+(Function
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(Statements
|
||||
{+(QuotedName
|
||||
{+(TypeConstructorIdentifier)+})+})+})+}
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) })
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) })
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindSignature
|
||||
(Star))
|
||||
(Empty))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindParenthesizedConstructor
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })))
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))
|
||||
(TypeSignature
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(Statements))))
|
107
test/fixtures/haskell/corpus/type-family-declarations.diffB-A.txt
vendored
Normal file
107
test/fixtures/haskell/corpus/type-family-declarations.diffB-A.txt
vendored
Normal file
@ -0,0 +1,107 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeVariableIdentifier)
|
||||
(Empty)
|
||||
(Statements
|
||||
{-(Function
|
||||
{-(ConstructorIdentifier)-}
|
||||
{-(Statements
|
||||
{-(ConstructorIdentifier)-})-})-}
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
{+(ConstructorIdentifier)+}
|
||||
{-(QuotedName
|
||||
{-(TypeConstructorIdentifier)-})-}))
|
||||
{+(Function
|
||||
{+(ConstructorIdentifier)+}
|
||||
{+(Statements
|
||||
{+(QuotedName
|
||||
{+(TypeConstructorIdentifier)+})+})+})+}
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) })
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
{ (ModuleIdentifier)
|
||||
->(ModuleIdentifier) }
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) })
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
{ (ConstructorIdentifier)
|
||||
->(ConstructorIdentifier) }
|
||||
{ (VariableIdentifier)
|
||||
->(VariableIdentifier) }))))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindSignature
|
||||
(Star))
|
||||
(Empty))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeFamily
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindParenthesizedConstructor
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })))
|
||||
(AnnotatedTypeVariable
|
||||
{ (TypeVariableIdentifier)
|
||||
->(TypeVariableIdentifier) }
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))
|
||||
(TypeSignature
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) })
|
||||
(Statements))))
|
86
test/fixtures/haskell/corpus/type-family-declarations.parseA.txt
vendored
Normal file
86
test/fixtures/haskell/corpus/type-family-declarations.parseA.txt
vendored
Normal file
@ -0,0 +1,86 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
(ConstructorIdentifier)))
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(Star))
|
||||
(Empty))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeConstructorIdentifier))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindParenthesizedConstructor
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(TypeConstructorIdentifier))))
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))))
|
86
test/fixtures/haskell/corpus/type-family-declarations.parseB.txt
vendored
Normal file
86
test/fixtures/haskell/corpus/type-family-declarations.parseB.txt
vendored
Normal file
@ -0,0 +1,86 @@
|
||||
(Module
|
||||
(Empty)
|
||||
(Statements
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(Empty)
|
||||
(Statements
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
(ConstructorIdentifier)))
|
||||
(Function
|
||||
(ConstructorIdentifier)
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(VariableIdentifier)))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))
|
||||
(Function
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(QualifiedConstructorIdentifier
|
||||
(ModuleIdentifier)
|
||||
(ConstructorIdentifier))
|
||||
(ConstructorPattern
|
||||
(Statements
|
||||
(ConstructorIdentifier)
|
||||
(VariableIdentifier)))))
|
||||
(Statements
|
||||
(QuotedName
|
||||
(TypeConstructorIdentifier))))))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeVariableIdentifier)
|
||||
(KindSignature
|
||||
(Star))
|
||||
(Empty))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(Array
|
||||
(Type
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeParameters)
|
||||
(Empty))))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeInstance
|
||||
(Statements
|
||||
(TypeConstructorIdentifier)
|
||||
(TypeConstructorIdentifier))
|
||||
(TypePattern
|
||||
(TypeConstructorIdentifier)))
|
||||
(TypeFamily
|
||||
(TypeConstructorIdentifier)
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindListType
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(KindParenthesizedConstructor
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star)))))
|
||||
(TypeConstructorIdentifier))))
|
||||
(AnnotatedTypeVariable
|
||||
(TypeVariableIdentifier)
|
||||
(KindFunctionType
|
||||
(Kind
|
||||
(Star))
|
||||
(Kind
|
||||
(Star))))
|
||||
(TypeSignature
|
||||
(TypeConstructorIdentifier))
|
||||
(Statements))))
|
@ -115,14 +115,11 @@
|
||||
{+(TypeConstructorIdentifier)+}
|
||||
{+(TypeVariableIdentifier)+})+})+}
|
||||
{+(Empty)+})+})+})+})+})+}
|
||||
(TypeSynonym
|
||||
(Statements
|
||||
{ (TypeConstructorIdentifier)
|
||||
->(TypeConstructorIdentifier) }
|
||||
{+(TypeConstructorIdentifier)+})
|
||||
{ (TypePattern
|
||||
{-(FunctionConstructor)-})
|
||||
->(TextElement) })
|
||||
{+(TypeSynonym
|
||||
{+(Statements
|
||||
{+(TypeConstructorIdentifier)+}
|
||||
{+(TypeConstructorIdentifier)+})+}
|
||||
{+(TextElement)+})+}
|
||||
{+(TypeSynonym
|
||||
{+(Statements
|
||||
{+(TypeConstructorIdentifier)+}
|
||||
@ -171,6 +168,11 @@
|
||||
{+(TypeConstructorIdentifier)+}
|
||||
{+(TypeVariableIdentifier)+}
|
||||
{+(TypeVariableIdentifier)+})+})+})+})+}
|
||||
{-(TypeSynonym
|
||||
{-(Statements
|
||||
{-(TypeConstructorIdentifier)-})-}
|
||||
{-(TypePattern
|
||||
{-(FunctionConstructor)-})-})-}
|
||||
{-(TypeSynonym
|
||||
{-(Statements
|
||||
{-(TypeConstructorIdentifier)-})-}
|
||||
|
2
vendor/haskell-tree-sitter
vendored
2
vendor/haskell-tree-sitter
vendored
@ -1 +1 @@
|
||||
Subproject commit 643f8a2856f9d9a4cf25f3b0eb844aa46aafc535
|
||||
Subproject commit 6176c8c8e7c59760a881a2487d81bcbdb26efe9c
|
Loading…
Reference in New Issue
Block a user