mirror of
https://github.com/github/semantic.git
synced 2024-12-27 00:44:57 +03:00
Merge branch 'master' into abstract-assign-and-gc
This commit is contained in:
commit
7956917c58
@ -118,6 +118,17 @@ instance Evaluatable Data.Syntax.Literal.String
|
|||||||
|
|
||||||
instance ToJSONFields1 Data.Syntax.Literal.String
|
instance ToJSONFields1 Data.Syntax.Literal.String
|
||||||
|
|
||||||
|
newtype Character a = Character { characterContent :: ByteString }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Data.Syntax.Literal.Character where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable Data.Syntax.Literal.Character
|
||||||
|
|
||||||
|
instance ToJSONFields1 Data.Syntax.Literal.Character
|
||||||
|
|
||||||
-- | An interpolation element within a string literal.
|
-- | An interpolation element within a string literal.
|
||||||
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
@ -176,7 +187,6 @@ instance Ord1 Regex where liftCompare = genericLiftCompare
|
|||||||
instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
-- TODO: Heredoc-style string literals?
|
-- TODO: Heredoc-style string literals?
|
||||||
-- TODO: Character literals.
|
|
||||||
|
|
||||||
instance ToJSONFields1 Regex where
|
instance ToJSONFields1 Regex where
|
||||||
toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r]
|
toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r]
|
||||||
|
@ -6,7 +6,8 @@ module Language.Haskell.Assignment
|
|||||||
, Term
|
, Term
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Assigning.Assignment hiding (Assignment, Error)
|
import Assigning.Assignment hiding (Assignment, Error, count)
|
||||||
|
import Data.ByteString.Char8 (count)
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Sum
|
import Data.Sum
|
||||||
import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm'', contextualize, postContextualize)
|
import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm'', contextualize, postContextualize)
|
||||||
@ -17,6 +18,7 @@ import qualified Data.Syntax as Syntax
|
|||||||
import qualified Data.Syntax.Comment as Comment
|
import qualified Data.Syntax.Comment as Comment
|
||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
import qualified Data.Syntax.Literal as Literal
|
import qualified Data.Syntax.Literal as Literal
|
||||||
|
import qualified Data.Syntax.Type as Type
|
||||||
import qualified Data.Term as Term
|
import qualified Data.Term as Term
|
||||||
import qualified Language.Haskell.Syntax as Syntax
|
import qualified Language.Haskell.Syntax as Syntax
|
||||||
import Prologue
|
import Prologue
|
||||||
@ -24,13 +26,23 @@ import Prologue
|
|||||||
type Syntax = '[
|
type Syntax = '[
|
||||||
Comment.Comment
|
Comment.Comment
|
||||||
, Declaration.Function
|
, Declaration.Function
|
||||||
|
, Literal.Array
|
||||||
|
, Literal.Character
|
||||||
, Literal.Float
|
, Literal.Float
|
||||||
, Literal.Integer
|
, Literal.Integer
|
||||||
|
, Literal.TextElement
|
||||||
, Syntax.Context
|
, Syntax.Context
|
||||||
, Syntax.Empty
|
, Syntax.Empty
|
||||||
, Syntax.Error
|
, Syntax.Error
|
||||||
|
, Syntax.FunctionConstructor
|
||||||
, Syntax.Identifier
|
, Syntax.Identifier
|
||||||
|
, Syntax.ListConstructor
|
||||||
, Syntax.Module
|
, Syntax.Module
|
||||||
|
, Syntax.TupleConstructor
|
||||||
|
, Syntax.Type
|
||||||
|
, Syntax.TypeSynonym
|
||||||
|
, Syntax.UnitConstructor
|
||||||
|
, Type.TypeParameters
|
||||||
, []
|
, []
|
||||||
]
|
]
|
||||||
|
|
||||||
@ -55,12 +67,24 @@ expression = term (handleError (choice expressionChoices))
|
|||||||
|
|
||||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||||
expressionChoices = [
|
expressionChoices = [
|
||||||
comment
|
character
|
||||||
|
, comment
|
||||||
, constructorIdentifier
|
, constructorIdentifier
|
||||||
, float
|
, float
|
||||||
|
, functionConstructor
|
||||||
, functionDeclaration
|
, functionDeclaration
|
||||||
, integer
|
, integer
|
||||||
|
, listConstructor
|
||||||
|
, listExpression
|
||||||
|
, listType
|
||||||
, moduleIdentifier
|
, moduleIdentifier
|
||||||
|
, string
|
||||||
|
, type'
|
||||||
|
, typeConstructorIdentifier
|
||||||
|
, typeSynonymDeclaration
|
||||||
|
, typeVariableIdentifier
|
||||||
|
, tuplingConstructor
|
||||||
|
, unitConstructor
|
||||||
, variableIdentifier
|
, variableIdentifier
|
||||||
, where'
|
, where'
|
||||||
]
|
]
|
||||||
@ -80,12 +104,21 @@ constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Id
|
|||||||
moduleIdentifier :: Assignment
|
moduleIdentifier :: Assignment
|
||||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||||
|
|
||||||
|
typeConstructorIdentifier :: Assignment
|
||||||
|
typeConstructorIdentifier = makeTerm <$> symbol TypeConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||||
|
|
||||||
|
typeVariableIdentifier :: Assignment
|
||||||
|
typeVariableIdentifier = makeTerm <$> symbol TypeVariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||||
|
|
||||||
where' :: Assignment
|
where' :: Assignment
|
||||||
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (many expression)
|
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (many expression)
|
||||||
|
|
||||||
functionBody :: Assignment
|
functionBody :: Assignment
|
||||||
functionBody = makeTerm <$> symbol FunctionBody <*> children (many expression)
|
functionBody = makeTerm <$> symbol FunctionBody <*> children (many expression)
|
||||||
|
|
||||||
|
functionConstructor :: Assignment
|
||||||
|
functionConstructor = makeTerm <$> token FunctionConstructor <*> pure Syntax.FunctionConstructor
|
||||||
|
|
||||||
functionDeclaration :: Assignment
|
functionDeclaration :: Assignment
|
||||||
functionDeclaration = makeTerm
|
functionDeclaration = makeTerm
|
||||||
<$> symbol FunctionDeclaration
|
<$> symbol FunctionDeclaration
|
||||||
@ -98,9 +131,57 @@ functionDeclaration = makeTerm
|
|||||||
integer :: Assignment
|
integer :: Assignment
|
||||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||||
|
|
||||||
|
listConstructor :: Assignment
|
||||||
|
listConstructor = makeTerm <$> token ListConstructor <*> pure Syntax.ListConstructor
|
||||||
|
|
||||||
|
unitConstructor :: Assignment
|
||||||
|
unitConstructor = makeTerm <$> token UnitConstructor <*> pure Syntax.UnitConstructor
|
||||||
|
|
||||||
|
listExpression :: Assignment
|
||||||
|
listExpression = makeTerm <$> symbol ListExpression <*> children (Literal.Array <$> many listElement)
|
||||||
|
where listElement = symbol Expression *> children expression
|
||||||
|
|
||||||
|
listType :: Assignment
|
||||||
|
listType = makeTerm <$> symbol ListType <*> children (Literal.Array <$> many type')
|
||||||
|
|
||||||
|
tuplingConstructor :: Assignment
|
||||||
|
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> source)
|
||||||
|
-- a tuple (,) has arity two, but only one comma, so apply the successor to the count of commas for the correct arity.
|
||||||
|
where tupleWithArity = Syntax.TupleConstructor . succ . count ','
|
||||||
|
|
||||||
|
type' :: Assignment
|
||||||
|
type' = (makeTerm <$> symbol Type <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
|
||||||
|
<|> (makeTerm <$> symbol TypePattern <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
|
||||||
|
|
||||||
|
typeParameters :: Assignment
|
||||||
|
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> many expression)
|
||||||
|
|
||||||
float :: Assignment
|
float :: Assignment
|
||||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||||
|
|
||||||
|
character :: Assignment
|
||||||
|
character = makeTerm <$> symbol Char <*> (Literal.Character <$> source)
|
||||||
|
|
||||||
|
string :: Assignment
|
||||||
|
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||||
|
|
||||||
|
typeConstructor :: Assignment
|
||||||
|
typeConstructor = typeConstructorIdentifier
|
||||||
|
<|> functionConstructor
|
||||||
|
<|> listConstructor
|
||||||
|
<|> listType
|
||||||
|
<|> tuplingConstructor
|
||||||
|
<|> unitConstructor
|
||||||
|
|
||||||
|
typeSynonymDeclaration :: Assignment
|
||||||
|
typeSynonymDeclaration = makeTerm
|
||||||
|
<$> symbol TypeSynonymDeclaration
|
||||||
|
<*> children (Syntax.TypeSynonym <$> typeLeft <*> typeRight)
|
||||||
|
where
|
||||||
|
typeLeft = makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParametersLeft)
|
||||||
|
typeParametersLeft = makeTerm <$> location <*> (Type.TypeParameters <$> manyTill expression (symbol TypeSynonymBody))
|
||||||
|
typeRight = symbol TypeSynonymBody *> children type'
|
||||||
|
|
||||||
-- | Match a series of terms or comments until a delimiter is matched.
|
-- | Match a series of terms or comments until a delimiter is matched.
|
||||||
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
||||||
manyTermsTill step = manyTill (step <|> comment)
|
manyTermsTill step = manyTill (step <|> comment)
|
||||||
|
@ -19,4 +19,66 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
instance ToJSONFields1 Module
|
instance ToJSONFields1 Module
|
||||||
|
|
||||||
instance Evaluatable Module where
|
instance Evaluatable Module
|
||||||
|
|
||||||
|
data Type a = Type { typeIdentifier :: !a, typeParameters :: !a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 Type where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 Type
|
||||||
|
|
||||||
|
instance Evaluatable Type
|
||||||
|
|
||||||
|
data TypeSynonym a = TypeSynonym { typeSynonymLeft :: !a, typeSynonymRight :: !a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 TypeSynonym where liftEq = genericLiftEq
|
||||||
|
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 TypeSynonym
|
||||||
|
|
||||||
|
instance Evaluatable TypeSynonym
|
||||||
|
|
||||||
|
data UnitConstructor a = UnitConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 UnitConstructor where liftEq = genericLiftEq
|
||||||
|
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 UnitConstructor
|
||||||
|
|
||||||
|
instance Evaluatable UnitConstructor
|
||||||
|
|
||||||
|
newtype TupleConstructor a = TupleConstructor { tupleConstructorArity :: Int } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 TupleConstructor where liftEq = genericLiftEq
|
||||||
|
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 TupleConstructor
|
||||||
|
|
||||||
|
instance Evaluatable TupleConstructor
|
||||||
|
|
||||||
|
data ListConstructor a = ListConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 ListConstructor where liftEq = genericLiftEq
|
||||||
|
instance Ord1 ListConstructor where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 ListConstructor
|
||||||
|
|
||||||
|
instance Evaluatable ListConstructor
|
||||||
|
|
||||||
|
data FunctionConstructor a = FunctionConstructor deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
|
instance Eq1 FunctionConstructor where liftEq = genericLiftEq
|
||||||
|
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance ToJSONFields1 FunctionConstructor
|
||||||
|
|
||||||
|
instance Evaluatable FunctionConstructor
|
||||||
|
69
test/fixtures/haskell/corpus/literals.A.hs
vendored
69
test/fixtures/haskell/corpus/literals.A.hs
vendored
@ -35,3 +35,72 @@ aZ' = undefined
|
|||||||
|
|
||||||
a = True
|
a = True
|
||||||
a = False
|
a = False
|
||||||
|
|
||||||
|
a = 'a'
|
||||||
|
a = 'b'
|
||||||
|
|
||||||
|
a = '0'
|
||||||
|
a = '1'
|
||||||
|
|
||||||
|
a = '_'
|
||||||
|
|
||||||
|
a = 'A'
|
||||||
|
a = 'B'
|
||||||
|
|
||||||
|
a = ','
|
||||||
|
|
||||||
|
a = '!'
|
||||||
|
a = '#'
|
||||||
|
a = '$'
|
||||||
|
a = '%'
|
||||||
|
a = '&'
|
||||||
|
a = '⋆'
|
||||||
|
a = '+'
|
||||||
|
a = '.'
|
||||||
|
a = '/'
|
||||||
|
a = '<'
|
||||||
|
a = '='
|
||||||
|
a = '>'
|
||||||
|
a = '?'
|
||||||
|
a = '^'
|
||||||
|
a = '|'
|
||||||
|
a = '-'
|
||||||
|
a = '~'
|
||||||
|
a = ':'
|
||||||
|
a = '"'
|
||||||
|
|
||||||
|
a = [ "\NUL"
|
||||||
|
, "\SOH"
|
||||||
|
, "\STX"
|
||||||
|
, "\ETX"
|
||||||
|
, "\EOT"
|
||||||
|
, "\ENQ"
|
||||||
|
, "\ACK"
|
||||||
|
, "\BEL"
|
||||||
|
, "\BS"
|
||||||
|
, "\HT"
|
||||||
|
, "\LF"
|
||||||
|
, "\VT"
|
||||||
|
, "\FF"
|
||||||
|
, "\CR"
|
||||||
|
, "\SO"
|
||||||
|
, "\SI"
|
||||||
|
, "\DLE"
|
||||||
|
, "\DC1"
|
||||||
|
, "\DC2"
|
||||||
|
, "\DC3"
|
||||||
|
, "\DC4"
|
||||||
|
, "\NAK"
|
||||||
|
, "\SYN"
|
||||||
|
, "\ETB"
|
||||||
|
, "\CAN"
|
||||||
|
, "\EM"
|
||||||
|
, "\SUB"
|
||||||
|
, "\ESC"
|
||||||
|
, "\FS"
|
||||||
|
, "\GS"
|
||||||
|
, "\RS"
|
||||||
|
, "\US"
|
||||||
|
, "\SP"
|
||||||
|
, "\DEL"
|
||||||
|
]
|
||||||
|
69
test/fixtures/haskell/corpus/literals.B.hs
vendored
69
test/fixtures/haskell/corpus/literals.B.hs
vendored
@ -35,3 +35,72 @@ bZ' = undefined
|
|||||||
|
|
||||||
b = True
|
b = True
|
||||||
b = False
|
b = False
|
||||||
|
|
||||||
|
b = 'a'
|
||||||
|
b = 'b'
|
||||||
|
|
||||||
|
b = '0'
|
||||||
|
b = '1'
|
||||||
|
|
||||||
|
b = '_'
|
||||||
|
|
||||||
|
b = 'A'
|
||||||
|
b = 'B'
|
||||||
|
|
||||||
|
b = ','
|
||||||
|
|
||||||
|
b = '!'
|
||||||
|
b = '#'
|
||||||
|
b = '$'
|
||||||
|
b = '%'
|
||||||
|
b = '&'
|
||||||
|
b = '⋆'
|
||||||
|
b = '+'
|
||||||
|
b = '.'
|
||||||
|
b = '/'
|
||||||
|
b = '<'
|
||||||
|
b = '='
|
||||||
|
b = '>'
|
||||||
|
b = '?'
|
||||||
|
b = '^'
|
||||||
|
b = '|'
|
||||||
|
b = '-'
|
||||||
|
b = '~'
|
||||||
|
b = ':'
|
||||||
|
b = '"'
|
||||||
|
|
||||||
|
b = [ "\NUL"
|
||||||
|
, "\SOH"
|
||||||
|
, "\STX"
|
||||||
|
, "\ETX"
|
||||||
|
, "\EOT"
|
||||||
|
, "\ENQ"
|
||||||
|
, "\ACK"
|
||||||
|
, "\BEL"
|
||||||
|
, "\BS"
|
||||||
|
, "\HT"
|
||||||
|
, "\LF"
|
||||||
|
, "\VT"
|
||||||
|
, "\FF"
|
||||||
|
, "\CR"
|
||||||
|
, "\SO"
|
||||||
|
, "\SI"
|
||||||
|
, "\DLE"
|
||||||
|
, "\DC1"
|
||||||
|
, "\DC2"
|
||||||
|
, "\DC3"
|
||||||
|
, "\DC4"
|
||||||
|
, "\NAK"
|
||||||
|
, "\SYN"
|
||||||
|
, "\ETB"
|
||||||
|
, "\CAN"
|
||||||
|
, "\EM"
|
||||||
|
, "\SUB"
|
||||||
|
, "\ESC"
|
||||||
|
, "\FS"
|
||||||
|
, "\GS"
|
||||||
|
, "\RS"
|
||||||
|
, "\US"
|
||||||
|
, "\SP"
|
||||||
|
, "\DEL"
|
||||||
|
]
|
||||||
|
307
test/fixtures/haskell/corpus/literals.diffA-B.txt
vendored
307
test/fixtures/haskell/corpus/literals.diffA-B.txt
vendored
@ -1,11 +1,10 @@
|
|||||||
(Module
|
(Module
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(
|
(
|
||||||
(Function
|
{+(Function
|
||||||
{ (Identifier)
|
{+(Identifier)+}
|
||||||
->(Identifier) }
|
{+(
|
||||||
(
|
{+(Integer)+})+})+}
|
||||||
(Integer)))
|
|
||||||
{+(Function
|
{+(Function
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(
|
{+(
|
||||||
@ -118,6 +117,156 @@
|
|||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(
|
{+(
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Array
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+})+})+})+}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Integer)-})-})-}
|
||||||
{-(Function
|
{-(Function
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(
|
{-(
|
||||||
@ -229,4 +378,150 @@
|
|||||||
{-(Function
|
{-(Function
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(
|
{-(
|
||||||
{-(Identifier)-})-})-}))
|
{-(Identifier)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Array
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-})-})-})-}))
|
||||||
|
501
test/fixtures/haskell/corpus/literals.diffB-A.txt
vendored
501
test/fixtures/haskell/corpus/literals.diffB-A.txt
vendored
@ -1,113 +1,92 @@
|
|||||||
(Module
|
(Module
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(
|
(
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
(Function
|
(Function
|
||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(Identifier) }
|
->(Identifier) }
|
||||||
(
|
(
|
||||||
(Integer)))
|
{+(Float)+}
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Integer)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Integer)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Integer)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Integer)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Integer)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Float)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
{+(Function
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(
|
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
(Function
|
|
||||||
{ (Identifier)
|
|
||||||
->(Identifier) }
|
|
||||||
(
|
|
||||||
{+(Identifier)+}
|
|
||||||
{-(Integer)-}))
|
{-(Integer)-}))
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Float)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
{+(Function
|
{+(Function
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(
|
{+(
|
||||||
@ -120,6 +99,176 @@
|
|||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(
|
{+(
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Identifier)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Character)+})+})+}
|
||||||
|
{+(Function
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Array
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+}
|
||||||
|
{+(TextElement)+})+})+})+}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Integer)-})-})-}
|
||||||
{-(Function
|
{-(Function
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(
|
{-(
|
||||||
@ -227,4 +376,150 @@
|
|||||||
{-(Function
|
{-(Function
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(
|
{-(
|
||||||
{-(Identifier)-})-})-}))
|
{-(Identifier)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Character)-})-})-}
|
||||||
|
{-(Function
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(
|
||||||
|
{-(Array
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(TextElement)-})-})-})-}))
|
||||||
|
148
test/fixtures/haskell/corpus/literals.parseA.txt
vendored
148
test/fixtures/haskell/corpus/literals.parseA.txt
vendored
@ -116,4 +116,150 @@
|
|||||||
(Function
|
(Function
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(
|
(
|
||||||
(Identifier)))))
|
(Identifier)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Array
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement))))))
|
||||||
|
148
test/fixtures/haskell/corpus/literals.parseB.txt
vendored
148
test/fixtures/haskell/corpus/literals.parseB.txt
vendored
@ -116,4 +116,150 @@
|
|||||||
(Function
|
(Function
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(
|
(
|
||||||
(Identifier)))))
|
(Identifier)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Character)))
|
||||||
|
(Function
|
||||||
|
(Identifier)
|
||||||
|
(
|
||||||
|
(Array
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement)
|
||||||
|
(TextElement))))))
|
||||||
|
8
test/fixtures/haskell/corpus/type-synonyms.A.hs
vendored
Normal file
8
test/fixtures/haskell/corpus/type-synonyms.A.hs
vendored
Normal file
@ -0,0 +1,8 @@
|
|||||||
|
type Foo = Bar
|
||||||
|
type List = []
|
||||||
|
type Foo a = Bar a
|
||||||
|
type Rec a = [Circ a]
|
||||||
|
type V = ()
|
||||||
|
type X = (,)
|
||||||
|
type Y = (,,)
|
||||||
|
type Z = (->)
|
8
test/fixtures/haskell/corpus/type-synonyms.B.hs
vendored
Normal file
8
test/fixtures/haskell/corpus/type-synonyms.B.hs
vendored
Normal file
@ -0,0 +1,8 @@
|
|||||||
|
type Bar = Foo
|
||||||
|
type List' = []
|
||||||
|
type Foo a b = Bar a b
|
||||||
|
type Rec a = [Triangle a]
|
||||||
|
type X = ()
|
||||||
|
type Y = (,,)
|
||||||
|
type Z = (,)
|
||||||
|
type T = (->)
|
81
test/fixtures/haskell/corpus/type-synonyms.diffA-B.txt
vendored
Normal file
81
test/fixtures/haskell/corpus/type-synonyms.diffA-B.txt
vendored
Normal file
@ -0,0 +1,81 @@
|
|||||||
|
(Module
|
||||||
|
(Empty)
|
||||||
|
(
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(ListConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
{+(Identifier)+}))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
{+(Identifier)+})))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Array
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier))))
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(UnitConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
{-(TypeSynonym
|
||||||
|
{-(Type
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(TypeParameters)-})-}
|
||||||
|
{-(Type
|
||||||
|
{-(TupleConstructor)-}
|
||||||
|
{-(TypeParameters)-})-})-}
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
{ (FunctionConstructor)
|
||||||
|
->(TupleConstructor) }
|
||||||
|
(TypeParameters)))
|
||||||
|
{+(TypeSynonym
|
||||||
|
{+(Type
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(TypeParameters)+})+}
|
||||||
|
{+(Type
|
||||||
|
{+(FunctionConstructor)+}
|
||||||
|
{+(TypeParameters)+})+})+}))
|
81
test/fixtures/haskell/corpus/type-synonyms.diffB-A.txt
vendored
Normal file
81
test/fixtures/haskell/corpus/type-synonyms.diffB-A.txt
vendored
Normal file
@ -0,0 +1,81 @@
|
|||||||
|
(Module
|
||||||
|
(Empty)
|
||||||
|
(
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(ListConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
{-(Identifier)-}))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
{-(Identifier)-})))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Array
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier))))
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(UnitConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
{+(TypeSynonym
|
||||||
|
{+(Type
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(TypeParameters)+})+}
|
||||||
|
{+(Type
|
||||||
|
{+(TupleConstructor)+}
|
||||||
|
{+(TypeParameters)+})+})+}
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
{ (TupleConstructor)
|
||||||
|
->(FunctionConstructor) }
|
||||||
|
(TypeParameters)))
|
||||||
|
{-(TypeSynonym
|
||||||
|
{-(Type
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(TypeParameters)-})-}
|
||||||
|
{-(Type
|
||||||
|
{-(FunctionConstructor)-}
|
||||||
|
{-(TypeParameters)-})-})-}))
|
66
test/fixtures/haskell/corpus/type-synonyms.parseA.txt
vendored
Normal file
66
test/fixtures/haskell/corpus/type-synonyms.parseA.txt
vendored
Normal file
@ -0,0 +1,66 @@
|
|||||||
|
(Module
|
||||||
|
(Empty)
|
||||||
|
(
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(ListConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier))))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Array
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier))))
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(UnitConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(FunctionConstructor)
|
||||||
|
(TypeParameters)))))
|
68
test/fixtures/haskell/corpus/type-synonyms.parseB.txt
vendored
Normal file
68
test/fixtures/haskell/corpus/type-synonyms.parseB.txt
vendored
Normal file
@ -0,0 +1,68 @@
|
|||||||
|
(Module
|
||||||
|
(Empty)
|
||||||
|
(
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(ListConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)
|
||||||
|
(Identifier))))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier)))
|
||||||
|
(Type
|
||||||
|
(Array
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters
|
||||||
|
(Identifier))))
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(UnitConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(TupleConstructor)
|
||||||
|
(TypeParameters)))
|
||||||
|
(TypeSynonym
|
||||||
|
(Type
|
||||||
|
(Identifier)
|
||||||
|
(TypeParameters))
|
||||||
|
(Type
|
||||||
|
(FunctionConstructor)
|
||||||
|
(TypeParameters)))))
|
Loading…
Reference in New Issue
Block a user