@ -6,10 +6,9 @@ module Language.TypeScript.Assignment
, Term
) where
import Data.Maybe ( fromMaybe )
import Data.Maybe ( fromMaybe , catMaybes )
import Data.Record
import Data.Maybe ( catMaybes )
import Data.Syntax ( emptyTerm , handleError , parseError , infixContext , makeTerm , makeTerm' , makeTerm1 , postContextualize )
import Data.Syntax ( emptyTerm , handleError , parseError , infixContext , makeTerm , makeTerm' , makeTerm1 , contextualize , postContextualize )
import qualified Data.Syntax as Syntax
import Data.Syntax.Assignment hiding ( Assignment , Error )
import qualified Data.Syntax.Assignment as Assignment
@ -20,13 +19,13 @@ import qualified Data.Syntax.Literal as Literal
import qualified Data.Syntax.Statement as Statement
import qualified Data.Syntax.Type as Type
import Data.Union
import GHC.Stack
import Language.TypeScript.Grammar as Grammar
import qualified Language.TypeScript.Syntax as TypeScript.Syntax
import qualified Data.Term as Term
import Data.List.NonEmpty ( some1 )
import Data.Function ( on )
import Data.Foldable ( toList )
import Data.List.NonEmpty ( nonEmpty )
-- | The type of TypeScript syntax.
type Syntax = ' [
@ -99,6 +98,7 @@ type Syntax = '[
, TypeScript . Syntax . TypeParameter
, TypeScript . Syntax . Constraint
, TypeScript . Syntax . ParenthesizedType
, TypeScript . Syntax . DefaultType
, TypeScript . Syntax . PredefinedType
, TypeScript . Syntax . TypeIdentifier
, TypeScript . Syntax . NestedIdentifier
@ -109,12 +109,14 @@ type Syntax = '[
, TypeScript . Syntax . CallSignature
, TypeScript . Syntax . ConstructSignature
, TypeScript . Syntax . ArrayType
, TypeScript . Syntax . LookupType
, TypeScript . Syntax . FlowMaybeType
, TypeScript . Syntax . TypeQuery
, TypeScript . Syntax . IndexTypeQuery
, TypeScript . Syntax . ThisType
, TypeScript . Syntax . ExistentialType
, TypeScript . Syntax . MethodSignature
, TypeScript . Syntax . AbstractMethodSignature
, TypeScript . Syntax . IndexSignature
, TypeScript . Syntax . ObjectType
, TypeScript . Syntax . LiteralType
@ -168,18 +170,21 @@ type Syntax = '[
]
type Term = Term . Term ( Data . Union . Union Syntax ) ( Record Location )
type Assignment = HasCallStack => Assignment. Assignment [] Grammar Term
type Assignment = Assignment. Assignment [] Grammar Term
-- | Assignment from AST in Ruby ’ s grammar onto a program in TypeScript’ s syntax.
-- | Assignment from AST in TypeScript ’ s grammar onto a program in TypeScript’ s syntax.
assignment :: Assignment
assignment = makeTerm <$> symbol Program <*> children ( Syntax . Program <$> many statement ) <|> parseError
assignment = makeTerm <$> symbol Program <*> children ( Syntax . Program <$> many Term statement ) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment . Assignment [] Grammar [ Term ]
manyTerm term = many ( contextualize comment term <|> makeTerm1 <$> ( Syntax . Context <$> some1 comment <*> emptyTerm ) )
term :: Assignment -> Assignment
term term = many comment *> term <|> makeTerm1 <$> ( Syntax . Context <$> some1 comment <*> emptyTerm )
term term = contextualize comment ( postContextualize comment t erm)
expression :: Assignment
expression = term ( handleError everything )
expression = handleError everything
where
everything = choice [
typeAssertion ,
@ -209,7 +214,7 @@ expression = term (handleError everything)
parenthesizedExpression ,
subscriptExpression ,
yieldExpression ,
this Expression ,
this ,
number ,
string ,
templateString ,
@ -225,7 +230,7 @@ undefined' :: Assignment
undefined' = makeTerm <$> symbol Grammar . Undefined <*> ( TypeScript . Syntax . Undefined <$ source )
assignmentExpression :: Assignment
assignmentExpression = makeTerm <$> symbol AssignmentExpression <*> children ( Statement . Assignment [] <$> ( memberExpression <|> subscriptExpression <|> identifier <|> destructuringPattern ) <*> expression )
assignmentExpression = makeTerm <$> symbol AssignmentExpression <*> children ( Statement . Assignment [] <$> term ( memberExpression <|> subscriptExpression <|> identifier <|> destructuringPattern ) <*> expression )
augmentedAssignmentExpression :: Assignment
augmentedAssignmentExpression = makeTerm' <$> symbol AugmentedAssignmentExpression <*> children ( infixTerm ( memberExpression <|> subscriptExpression <|> identifier <|> destructuringPattern ) expression [
@ -236,39 +241,41 @@ augmentedAssignmentExpression = makeTerm' <$> symbol AugmentedAssignmentExpressi
, assign Expression . Modulo <$ symbol AnonPercentEqual
, assign Expression . BXOr <$ symbol AnonCaretEqual
, assign Expression . BAnd <$ symbol AnonAmpersandEqual
, assign Expression . RShift <$ symbol AnonRAngleRAngleEqual
, assign Expression . UnsignedRShift <$ symbol AnonRAngleRAngleRAngleEqual
, assign Expression . BOr <$ symbol AnonPipeEqual ] )
where assign :: f :< Syntax => ( Term -> Term -> f Term ) -> Term -> Term -> Data . Union . Union Syntax Term
assign c l r = inj ( Statement . Assignment [] l ( makeTerm1 ( c l r ) ) )
awaitExpression :: Assignment
awaitExpression = makeTerm <$> symbol Grammar . AwaitExpression <*> children ( Expression . Await <$> expression)
awaitExpression = makeTerm <$> symbol Grammar . AwaitExpression <*> children ( Expression . Await <$> term expression)
unaryExpression :: Assignment
unaryExpression = symbol Grammar . UnaryExpression >>= \ loc ->
makeTerm loc . Expression . Not <$> children ( ( symbol AnonTilde <|> symbol AnonBang ) *> expression)
<|> makeTerm loc . Expression . Negate <$> children ( ( symbol AnonMinus <|> symbol AnonPlus ) *> expression)
<|> makeTerm loc . Expression . Typeof <$> children ( symbol AnonTypeof *> expression)
<|> makeTerm loc . Expression . Void <$> children ( symbol AnonVoid *> expression)
<|> makeTerm loc . Expression . Delete <$> children ( symbol AnonDelete *> expression)
makeTerm loc . Expression . Not <$> children ( ( symbol AnonTilde <|> symbol AnonBang ) *> term expression)
<|> makeTerm loc . Expression . Negate <$> children ( ( symbol AnonMinus <|> symbol AnonPlus ) *> term expression)
<|> makeTerm loc . Expression . Typeof <$> children ( symbol AnonTypeof *> term expression)
<|> makeTerm loc . Expression . Void <$> children ( symbol AnonVoid *> term expression)
<|> makeTerm loc . Expression . Delete <$> children ( symbol AnonDelete *> term expression)
ternaryExpression :: Assignment
ternaryExpression = makeTerm <$> symbol Grammar . TernaryExpression <*> children ( Statement . If <$> expression <*> expression <*> expression )
ternaryExpression = makeTerm <$> symbol Grammar . TernaryExpression <*> children ( Statement . If <$> term expression <*> term expression <*> term expression )
memberExpression :: Assignment
memberExpression = makeTerm <$> ( symbol Grammar . MemberExpression <|> symbol Grammar . MemberExpression' ) <*> children ( Expression . MemberAccess <$> postContextualize comment expression <*> propertyIdentifier )
memberExpression = makeTerm <$> ( symbol Grammar . MemberExpression <|> symbol Grammar . MemberExpression' ) <*> children ( Expression . MemberAccess <$> term expression <*> term propertyIdentifier )
newExpression :: Assignment
newExpression = makeTerm <$> symbol Grammar . NewExpression <*> children ( Expression . New <$> expression)
newExpression = makeTerm <$> symbol Grammar . NewExpression <*> children ( Expression . New <$> term expression)
updateExpression :: Assignment
updateExpression = makeTerm <$> symbol Grammar . UpdateExpression <*> children ( TypeScript . Syntax . Update <$> expression)
updateExpression = makeTerm <$> symbol Grammar . UpdateExpression <*> children ( TypeScript . Syntax . Update <$> term expression)
yieldExpression :: Assignment
yieldExpression = makeTerm <$> symbol Grammar . YieldExpression <*> children ( Statement . Yield <$> ( expression <|> emptyTerm ) )
yieldExpression = makeTerm <$> symbol Grammar . YieldExpression <*> children ( Statement . Yield <$> term ( expression <|> emptyTerm ) )
this Expression :: Assignment
this Expression = makeTerm <$> symbol Grammar . This Expression <*> ( TypeScript . Syntax . This <$ source )
this :: Assignment
this = makeTerm <$> symbol Grammar . This <*> ( TypeScript . Syntax . This <$ source )
regex :: Assignment
regex = makeTerm <$> symbol Grammar . Regex <*> ( Literal . Regex <$> source )
@ -280,37 +287,44 @@ anonymousClass :: Assignment
anonymousClass = makeTerm <$> symbol Grammar . AnonymousClass <*> children ( Declaration . Class <$> pure [] <*> emptyTerm <*> ( classHeritage' <|> pure [] ) <*> classBodyStatements )
abstractClass :: Assignment
abstractClass = makeTerm <$> symbol Grammar . AbstractClass <*> ( TypeScript . Syntax . AbstractClass <$> identifier <*> ( typeParameters <|> emptyTerm ) <*> ( classHeritage' <|> pure [] ) <*> classBodyStatements )
abstractClass = makeTerm <$> symbol Grammar . AbstractClass <*> children ( TypeScript . Syntax . AbstractClass <$> term identifier <*> ( term typeParameters <|> emptyTerm ) <*> ( classHeritage' <|> pure [] ) <*> classBodyStatements )
classHeritage' :: HasCallStack => Assignment . Assignment [] Grammar [ Term ]
classHeritage' = symbol Grammar . ClassHeritage *> children ( ( ( ++ ) ` on ` toList ) <$> optional extendsClause' <*> optional implementsClause' )
abstractMethodSignature :: Assignment
abstractMethodSignature = makeSignature <$> symbol Grammar . AbstractMethodSignature <*> children ( ( , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> term propertyName <*> callSignatureParts )
where makeSignature loc ( modifier , propertyName , ( typeParams , params , annotation ) ) = makeTerm loc ( TypeScript . Syntax . AbstractMethodSignature [ modifier , typeParams , annotation ] propertyName params )
extendsClause' :: Assignment
extendsClause' = makeTerm <$> symbol Grammar . ExtendsClause <*> children ( TypeScript . Syntax . ExtendsClause <$> many ty )
classHeritage' :: Assignment . Assignment [] Grammar [ Term ]
classHeritage' = symbol Grammar . ClassHeritage *> children ( ( ( ++ ) ` on ` toList ) <$> optional ( term extendsClause ) <*> optional ( term implementsClause' ) )
extendsClause :: Assignment
extendsClause = makeTerm <$> symbol Grammar . ExtendsClause <*> children ( TypeScript . Syntax . ExtendsClause <$> manyTerm ( typeReference <|> expression ) )
typeReference :: Assignment
typeReference = typeIdentifier <|> nestedTypeIdentifier <|> genericType
implementsClause' :: Assignment
implementsClause' = makeTerm <$> symbol Grammar . ImplementsClause <*> children ( TypeScript . Syntax . ImplementsClause <$> many ty )
implementsClause' = makeTerm <$> symbol Grammar . ImplementsClause <*> children ( TypeScript . Syntax . ImplementsClause <$> many Term ty )
super :: Assignment
super = makeTerm <$> symbol Grammar . Super <*> ( TypeScript . Syntax . Super <$ source )
typeAssertion :: Assignment
typeAssertion = makeTerm <$> symbol Grammar . TypeAssertion <*> children ( TypeScript . Syntax . TypeAssertion <$> t ypeArguments' <*> expression )
typeAssertion = makeTerm <$> symbol Grammar . TypeAssertion <*> children ( TypeScript . Syntax . TypeAssertion <$> t erm t ypeArguments' <*> term expression )
asExpression :: Assignment
asExpression = makeTerm <$> symbol AsExpression <*> children ( Expression . Cast <$> expression <*> ( ty <|> templateString ) )
asExpression = makeTerm <$> symbol AsExpression <*> children ( Expression . Cast <$> term expression <*> term ( ty <|> templateString ) )
templateString :: Assignment
templateString = makeTerm <$> symbol TemplateString <*> children ( Literal . String <$> many ( term templateSubstitution ) )
templateString = makeTerm <$> symbol TemplateString <*> children ( Literal . String <$> many Term templateSubstitution )
templateSubstitution :: Assignment
templateSubstitution = symbol TemplateSubstitution *> children expression
templateSubstitution = symbol TemplateSubstitution *> children ( term expression s)
nonNullExpression' :: Assignment
nonNullExpression' = makeTerm <$> symbol Grammar . NonNullExpression <*> children ( Expression . NonNullExpression <$> expression)
nonNullExpression' = makeTerm <$> symbol Grammar . NonNullExpression <*> children ( Expression . NonNullExpression <$> term expression)
importAlias' :: Assignment
importAlias' = makeTerm <$> symbol Grammar . ImportAlias <*> children ( TypeScript . Syntax . ImportAlias <$> identifier <*> ( identifier <|> nestedIdentifier ) )
importAlias' = makeTerm <$> symbol Grammar . ImportAlias <*> children ( TypeScript . Syntax . ImportAlias <$> term identifier <*> term ( identifier <|> nestedIdentifier ) )
number :: Assignment
number = makeTerm <$> symbol Grammar . Number <*> ( Literal . Float <$> source )
@ -328,41 +342,44 @@ identifier :: Assignment
identifier = ( makeTerm <$> symbol Identifier' <*> ( Syntax . Identifier <$> source ) ) <|> ( makeTerm <$> symbol Identifier <*> ( Syntax . Identifier <$> source ) )
class' :: Assignment
class' = makeClass <$> symbol Class <*> children ( ( , , , , ) <$> many ( term decorator ) <*> identifier <*> ( ( symbol TypeParameters *> children ( many ( term typeParameter' ) ) ) <|> pure [] ) <*> ( classHeritage' <|> pure [] ) <*> classBodyStatements )
class' = makeClass <$> symbol Class <*> children ( ( , , , , ) <$> many Term decorator <*> term identifier <*> ( symbol TypeParameters *> children ( many Term typeParameter' ) <|> pure [] ) <*> ( classHeritage' <|> pure [] ) <*> classBodyStatements )
where makeClass loc ( decorators , expression , typeParams , classHeritage , statements ) = makeTerm loc ( Declaration . Class ( decorators ++ typeParams ) expression classHeritage statements )
object :: Assignment
object = ( makeTerm <$> ( symbol Object <|> symbol ObjectPattern ) <*> children ( Literal . Hash <$> many ( term ( ( pair <|> spreadElement <|> methodDefinition <|> assignmentPattern <|> shorthandPropertyIdentifier ) ) ) ) )
object = makeTerm <$> ( symbol Object <|> symbol ObjectPattern ) <*> children ( Literal . Hash <$> many Term ( pair <|> spreadElement <|> methodDefinition <|> assignmentPattern <|> shorthandPropertyIdentifier ) )
array :: Assignment
array = makeTerm <$> ( symbol Array <|> symbol ArrayPattern ) <*> children ( Literal . Array <$> many ( t erm ( expression <|> spreadElement ) ) )
array = makeTerm <$> ( symbol Array <|> symbol ArrayPattern ) <*> children ( Literal . Array <$> many T erm ( expression <|> spreadElement ) )
jsxElement :: Assignment
jsxElement = makeTerm <$> symbol Grammar . JsxElement <*> children ( TypeScript . Syntax . JsxElement <$> jsxOpeningElement' <*> many ( t erm ( jsxElement <|> jsxSelfClosingElement <|> jsxExpression' <|> jsxText ) ) <*> jsxClosingElement' )
jsxElement = makeTerm <$> symbol Grammar . JsxElement <*> children ( TypeScript . Syntax . JsxElement <$> term jsxOpeningElement' <*> many T erm ( jsxElement <|> jsxSelfClosingElement <|> jsxExpression' <|> jsxText ) <*> term jsxClosingElement' )
jsxSelfClosingElement :: Assignment
jsxSelfClosingElement = makeTerm <$> symbol Grammar . JsxSelfClosingElement <*> children ( TypeScript . Syntax . JsxSelfClosingElement <$> identifier <*> many ( t erm ( jsxAttribute <|> jsxExpression' ) ) )
jsxSelfClosingElement = makeTerm <$> symbol Grammar . JsxSelfClosingElement <*> children ( TypeScript . Syntax . JsxSelfClosingElement <$> term identifier <*> manyT erm ( jsxAttribute <|> jsxExpression' ) )
jsxOpeningElement' :: Assignment
jsxOpeningElement' = makeTerm <$> symbol Grammar . JsxOpeningElement <*> children ( TypeScript . Syntax . JsxOpeningElement <$> identifier <*> many ( t erm ( jsxAttribute <|> jsxExpression' ) ) )
jsxOpeningElement' = makeTerm <$> symbol Grammar . JsxOpeningElement <*> children ( TypeScript . Syntax . JsxOpeningElement <$> term identifier <*> manyT erm ( jsxAttribute <|> jsxExpression' ) )
jsxExpression' :: Assignment
jsxExpression' = makeTerm <$> symbol Grammar . JsxExpression <*> children ( TypeScript . Syntax . JsxExpression <$> ( expression <|> sequenceExpression <|> spreadElement ) )
jsxExpression' = makeTerm <$> symbol Grammar . JsxExpression <*> children ( TypeScript . Syntax . JsxExpression <$> term ( expressions <|> spreadElement ) )
jsxText :: Assignment
jsxText = makeTerm <$> symbol Grammar . JsxText <*> ( TypeScript . Syntax . JsxText <$> source )
jsxClosingElement' :: Assignment
jsxClosingElement' = makeTerm <$> symbol Grammar . JsxClosingElement <*> children ( TypeScript . Syntax . JsxClosingElement <$> identifier)
jsxClosingElement' = makeTerm <$> symbol Grammar . JsxClosingElement <*> children ( TypeScript . Syntax . JsxClosingElement <$> term identifier)
jsxAttribute :: Assignment
jsxAttribute = makeTerm <$> symbol Grammar . JsxAttribute <*> children ( TypeScript . Syntax . JsxAttribute <$> propertyIdentifier <*> ( number <|> string <|> jsxExpression' ) )
jsxAttribute = makeTerm <$> symbol Grammar . JsxAttribute <*> children ( TypeScript . Syntax . JsxAttribute <$> term propertyIdentifier <*> term ( number <|> string <|> jsxExpression' ) )
propertyIdentifier :: Assignment
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> ( Syntax . Identifier <$> source )
sequenceExpression :: Assignment
sequenceExpression = makeTerm <$> symbol Grammar . SequenceExpression <*> children ( Expression . SequenceExpression <$> expression <*> ( sequenceExpression <|> expression ) )
sequenceExpression = makeTerm <$> symbol Grammar . SequenceExpression <*> children ( Expression . SequenceExpression <$> term expression <*> term expressions )
expressions :: Assignment
expressions = expression <|> sequenceExpression
parameter :: Assignment
parameter =
@ -377,7 +394,7 @@ destructuringPattern :: Assignment
destructuringPattern = object <|> array
spreadElement :: Assignment
spreadElement = symbol SpreadElement *> children expression
spreadElement = symbol SpreadElement *> children ( term expression )
readonly' :: Assignment
readonly' = makeTerm <$> symbol Readonly <*> ( Type . Readonly <$ source )
@ -385,60 +402,79 @@ readonly' = makeTerm <$> symbol Readonly <*> (Type.Readonly <$ source)
methodDefinition :: Assignment
methodDefinition = makeMethod <$>
symbol MethodDefinition
<*> children ( ( , , , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> emptyTerm <*> propertyName <*> callSignatureParts <*> statementBlock )
<*> children ( ( , , , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> emptyTerm <*> term propertyName <*> callSignatureParts <*> term statementBlock )
where
makeMethod loc ( modifier , readonly , receiver , propertyName' , ( typeParameters' , params , ty' ) , statements ) = makeTerm loc ( Declaration . Method [ modifier , readonly , typeParameters' , ty' ] receiver propertyName' params statements )
callSignatureParts :: HasCallStack => Assignment . Assignment [] Grammar ( Term , [ Term ] , Term )
callSignatureParts = symbol Grammar . CallSignature *> children ( ( , , ) <$> ( fromMaybe <$> emptyTerm <*> optional typeParameters ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional typeAnnotation' ) )
callSignatureParts :: Assignment . Assignment [] Grammar ( Term , [ Term ] , Term )
callSignatureParts = contextualize' <$> Assignment . manyThrough comment ( postContextualize'
<$> ( symbol Grammar . CallSignature *> children ( ( , , ) <$> ( fromMaybe <$> emptyTerm <*> optional ( term typeParameters ) ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional ( term typeAnnotation' ) ) ) ) <*> many comment )
where
contextualize' ( cs , ( typeParams , formalParams , annotation ) ) = case nonEmpty cs of
Just cs -> ( makeTerm1 ( Syntax . Context cs typeParams ) , formalParams , annotation )
Nothing -> ( typeParams , formalParams , annotation )
postContextualize' ( typeParams , formalParams , annotation ) cs = case nonEmpty cs of
Just cs -> ( typeParams , formalParams , makeTerm1 ( Syntax . Context cs annotation ) )
Nothing -> ( typeParams , formalParams , annotation )
callSignature :: Assignment
callSignature = makeTerm <$> symbol Grammar . CallSignature <*> children ( TypeScript . Syntax . CallSignature <$> ( fromMaybe <$> emptyTerm <*> optional typeParameters ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional typeAnnotation' ) )
callSignature = makeTerm <$> symbol Grammar . CallSignature <*> children ( TypeScript . Syntax . CallSignature <$> ( fromMaybe <$> emptyTerm <*> optional ( term typeParameters ) ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional ( term typeAnnotation' ) ) )
constructSignature :: Assignment
constructSignature = makeTerm <$> symbol Grammar . ConstructSignature <*> children ( TypeScript . Syntax . ConstructSignature <$> ( fromMaybe <$> emptyTerm <*> optional typeParameters ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional typeAnnotation' ) )
constructSignature = makeTerm <$> symbol Grammar . ConstructSignature <*> children ( TypeScript . Syntax . ConstructSignature <$> ( fromMaybe <$> emptyTerm <*> optional ( term typeParameters ) ) <*> formalParameters <*> ( fromMaybe <$> emptyTerm <*> optional ( term typeAnnotation' ) ) )
indexSignature :: Assignment
indexSignature = makeTerm <$> symbol Grammar . IndexSignature <*> children ( TypeScript . Syntax . IndexSignature <$> ( identifier <|> typeAnnotation' ) )
indexSignature = makeTerm <$> symbol Grammar . IndexSignature <*> children ( TypeScript . Syntax . IndexSignature <$> term identifier <*> term typeAnnotation' )
methodSignature :: Assignment
methodSignature = makeMethodSignature <$> symbol Grammar . MethodSignature <*> children ( ( , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> propertyName <*> callSignatureParts )
methodSignature = makeMethodSignature <$> symbol Grammar . MethodSignature <*> children ( ( , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> term propertyName <*> callSignatureParts )
where makeMethodSignature loc ( modifier , readonly , propertyName , ( typeParams , params , annotation ) ) = makeTerm loc ( TypeScript . Syntax . MethodSignature [ modifier , readonly , typeParams , annotation ] propertyName params )
formalParameters :: HasCallStack => Assignment . Assignment [] Grammar [ Term ]
formalParameters = symbol FormalParameters *> children ( concat <$> many ( ( \ as b -> as ++ [ b ] ) <$> many ( term decorator ) <*> term parameter ) )
formalParameters :: Assignment . Assignment [] Grammar [ Term ]
formalParameters = symbol FormalParameters *> children ( contextualize' <$> Assignment . manyThrough comment ( postContextualize' <$> ( concat <$> many ( ( \ as b -> as ++ [ b ] ) <$> manyTerm decorator <*> term parameter ) ) <*> many comment ) )
where
contextualize' ( cs , formalParams ) = case nonEmpty cs of
Just cs -> toList cs ++ formalParams
Nothing -> formalParams
postContextualize' formalParams cs = case nonEmpty cs of
Just cs -> formalParams ++ toList cs
Nothing -> formalParams
decorator :: Assignment
decorator = makeTerm <$> symbol Grammar . Decorator <*> children ( TypeScript . Syntax . Decorator <$> ( identifier <|> memberExpression <|> callExpression ) )
decorator = makeTerm <$> symbol Grammar . Decorator <*> children ( TypeScript . Syntax . Decorator <$> term ( identifier <|> memberExpression <|> callExpression ) )
typeParameters :: Assignment
typeParameters = makeTerm <$> symbol TypeParameters <*> children ( Type . TypeParameters <$> many ( term typeParameter' ) )
typeParameters = makeTerm <$> symbol TypeParameters <*> children ( Type . TypeParameters <$> many Term typeParameter' )
typeAnnotation' :: Assignment
typeAnnotation' = makeTerm <$> symbol TypeAnnotation <*> children ( TypeScript . Syntax . Annotation <$> t y)
typeAnnotation' = makeTerm <$> symbol TypeAnnotation <*> children ( TypeScript . Syntax . Annotation <$> t erm t y)
typeParameter' :: Assignment
typeParameter' = makeTerm <$> symbol Grammar . TypeParameter <*> children ( TypeScript . Syntax . TypeParameter <$> identifier <*> ( constraint <|> emptyTerm ) )
typeParameter' = makeTerm <$> symbol Grammar . TypeParameter <*> children ( TypeScript . Syntax . TypeParameter <$> term identifier <*> term ( constraint <|> emptyTerm ) <*> term ( defaultType <|> emptyTerm ) )
defaultType :: Assignment
defaultType = makeTerm <$> symbol Grammar . DefaultType <*> children ( TypeScript . Syntax . DefaultType <$> term ty )
constraint :: Assignment
constraint = makeTerm <$> symbol Grammar . Constraint <*> children ( TypeScript . Syntax . Constraint <$> ty )
constraint = makeTerm <$> symbol Grammar . Constraint <*> children ( TypeScript . Syntax . Constraint <$> t erm t y)
function :: Assignment
function = makeFunction <$> ( symbol Grammar . Function <|> symbol Grammar . GeneratorFunction ) <*> children ( ( , , ) <$> ( identifier <|> emptyTerm ) <*> callSignatureParts <*> statementBlock )
function = makeFunction <$> ( symbol Grammar . Function <|> symbol Grammar . GeneratorFunction ) <*> children ( ( , , ) <$> term ( identifier <|> emptyTerm ) <*> callSignatureParts <*> term statementBlock )
where makeFunction loc ( id , ( typeParams , params , annotation ) , statements ) = makeTerm loc ( Declaration . Function [ typeParams , annotation ] id params statements )
ambientFunction :: Assignment
ambientFunction = makeAmbientFunction <$> symbol Grammar . AmbientFunction <*> children ( ( , ) <$> identifier <*> callSignatureParts )
ambientFunction = makeAmbientFunction <$> symbol Grammar . AmbientFunction <*> children ( ( , ) <$> term identifier <*> callSignatureParts )
where makeAmbientFunction loc ( id , ( typeParams , params , annotation ) ) = makeTerm loc ( TypeScript . Syntax . AmbientFunction [ typeParams , annotation ] id params )
ty :: Assignment
ty = primaryType <|> unionType <|> intersectionType <|> functionTy <|> constructorTy
primaryType :: Assignment
primaryType = parenthesizedTy <|> predefinedTy <|> typeIdentifier <|> nestedTypeIdentifier <|> genericType <|> typePredicate <|> objectType <|> arrayTy <|> tupleType <|> flowMaybeTy <|> typeQuery <|> indexTypeQuery <|> thisType <|> existentialType <|> literalType
primaryType = parenthesizedTy <|> predefinedTy <|> typeIdentifier <|> nestedTypeIdentifier <|> genericType <|> typePredicate <|> objectType <|> arrayTy <|> tupleType <|> flowMaybeTy <|> typeQuery <|> indexTypeQuery <|> thisType <|> existentialType <|> literalType <|> lookupType
parenthesizedTy :: Assignment
parenthesizedTy = makeTerm <$> symbol Grammar . ParenthesizedType <*> children ( TypeScript . Syntax . ParenthesizedType <$> t y)
parenthesizedTy = makeTerm <$> symbol Grammar . ParenthesizedType <*> children ( TypeScript . Syntax . ParenthesizedType <$> t erm t y)
predefinedTy :: Assignment
predefinedTy = makeTerm <$> symbol Grammar . PredefinedType <*> ( TypeScript . Syntax . PredefinedType <$> source )
@ -447,34 +483,37 @@ typeIdentifier :: Assignment
typeIdentifier = makeTerm <$> symbol Grammar . TypeIdentifier <*> ( TypeScript . Syntax . TypeIdentifier <$> source )
nestedIdentifier :: Assignment
nestedIdentifier = makeTerm <$> symbol Grammar . NestedIdentifier <*> children ( TypeScript . Syntax . NestedIdentifier <$> ( identifier <|> nestedIdentifier ) <*> identifier )
nestedIdentifier = makeTerm <$> symbol Grammar . NestedIdentifier <*> children ( TypeScript . Syntax . NestedIdentifier <$> term ( identifier <|> nestedIdentifier ) <*> term identifier )
nestedTypeIdentifier :: Assignment
nestedTypeIdentifier = makeTerm <$> symbol Grammar . NestedTypeIdentifier <*> children ( TypeScript . Syntax . NestedTypeIdentifier <$> ( identifier <|> nestedIdentifier ) <*> typeIdentifier )
nestedTypeIdentifier = makeTerm <$> symbol Grammar . NestedTypeIdentifier <*> children ( TypeScript . Syntax . NestedTypeIdentifier <$> term ( identifier <|> nestedIdentifier ) <*> term typeIdentifier )
genericType :: Assignment
genericType = makeTerm <$> symbol Grammar . GenericType <*> children ( TypeScript . Syntax . GenericType <$> ( typeIdentifier <|> nestedTypeIdentifier ) <*> typeArguments' )
genericType = makeTerm <$> symbol Grammar . GenericType <*> children ( TypeScript . Syntax . GenericType <$> term ( typeIdentifier <|> nestedTypeIdentifier ) <*> term typeArguments' )
typeArguments' :: Assignment
typeArguments' = makeTerm <$> symbol Grammar . TypeArguments <*> children ( TypeScript . Syntax . TypeArguments <$> some ( term ty ) )
typePredicate :: Assignment
typePredicate = makeTerm <$> symbol Grammar . TypePredicate <*> children ( TypeScript . Syntax . TypePredicate <$> identifier <*> ty )
typePredicate = makeTerm <$> symbol Grammar . TypePredicate <*> children ( TypeScript . Syntax . TypePredicate <$> term identifier <*> term ty )
objectType :: Assignment
objectType = makeTerm <$> symbol Grammar . ObjectType <*> children ( TypeScript . Syntax . ObjectType <$> many ( t erm ( exportStatement <|> propertySignature <|> callSignature <|> constructSignature <|> indexSignature <|> methodSignature ) ) )
objectType = makeTerm <$> symbol Grammar . ObjectType <*> children ( TypeScript . Syntax . ObjectType <$> many T erm ( exportStatement <|> propertySignature <|> callSignature <|> constructSignature <|> indexSignature <|> methodSignature ) )
arrayTy :: Assignment
arrayTy = makeTerm <$> symbol Grammar . ArrayType <*> children ( TypeScript . Syntax . ArrayType <$> ty )
arrayTy = makeTerm <$> symbol Grammar . ArrayType <*> children ( TypeScript . Syntax . ArrayType <$> term ty )
lookupType :: Assignment
lookupType = makeTerm <$> symbol Grammar . LookupType <*> children ( TypeScript . Syntax . LookupType <$> term ( identifier <|> nestedTypeIdentifier ) <*> term ty )
flowMaybeTy :: Assignment
flowMaybeTy = makeTerm <$> symbol Grammar . FlowMaybeType <*> children ( TypeScript . Syntax . FlowMaybeType <$> primaryType )
flowMaybeTy = makeTerm <$> symbol Grammar . FlowMaybeType <*> children ( TypeScript . Syntax . FlowMaybeType <$> term primaryType)
typeQuery :: Assignment
typeQuery = makeTerm <$> symbol Grammar . TypeQuery <*> children ( TypeScript . Syntax . TypeQuery <$> ( identifier <|> nestedIdentifier ) )
typeQuery = makeTerm <$> symbol Grammar . TypeQuery <*> children ( TypeScript . Syntax . TypeQuery <$> term ( identifier <|> nestedIdentifier ) )
indexTypeQuery :: Assignment
indexTypeQuery = makeTerm <$> symbol Grammar . IndexTypeQuery <*> children ( TypeScript . Syntax . IndexTypeQuery <$> ( identifier <|> nestedIdentifier ) )
indexTypeQuery = makeTerm <$> symbol Grammar . IndexTypeQuery <*> children ( TypeScript . Syntax . IndexTypeQuery <$> term ( identifier <|> nestedIdentifier ) )
thisType :: Assignment
thisType = makeTerm <$> symbol Grammar . ThisType <*> ( TypeScript . Syntax . ThisType <$> source )
@ -483,36 +522,43 @@ existentialType :: Assignment
existentialType = makeTerm <$> symbol Grammar . ExistentialType <*> ( TypeScript . Syntax . ExistentialType <$> source )
literalType :: Assignment
literalType = makeTerm <$> symbol Grammar . LiteralType <*> children ( TypeScript . Syntax . LiteralType <$> ( number <|> string <|> true <|> false ) )
literalType = makeTerm <$> symbol Grammar . LiteralType <*> children ( TypeScript . Syntax . LiteralType <$> term ( number <|> string <|> true <|> false ) )
unionType :: Assignment
unionType = makeTerm <$> symbol UnionType <*> children ( TypeScript . Syntax . Union <$> ty < *> ty )
unionType = makeTerm <$> symbol UnionType <*> children ( TypeScript . Syntax . Union <$> ( term ty < |> emptyTerm ) < *> term ty )
intersectionType :: Assignment
intersectionType = makeTerm <$> symbol IntersectionType <*> children ( TypeScript . Syntax . Intersection <$> t y <*> ty )
intersectionType = makeTerm <$> symbol IntersectionType <*> children ( TypeScript . Syntax . Intersection <$> t erm t y <*> term ty )
functionTy :: Assignment
functionTy = makeTerm <$> symbol Grammar . FunctionType <*> children ( TypeScript . Syntax . FunctionType <$> ( fromMaybe <$> emptyTerm <*> optional typeParameters ) <*> formalParameters <*> ty )
functionTy = makeTerm <$> symbol Grammar . FunctionType <*> children ( TypeScript . Syntax . FunctionType <$> ( fromMaybe <$> emptyTerm <*> optional ( term typeParameters ) ) <*> formalParameters <*> term ty )
tupleType :: Assignment
tupleType = makeTerm <$> symbol TupleType <*> children ( TypeScript . Syntax . Tuple <$> many ( term ty ) )
tupleType = makeTerm <$> symbol TupleType <*> children ( TypeScript . Syntax . Tuple <$> many Term ty )
constructorTy :: Assignment
constructorTy = makeTerm <$> symbol ConstructorType <*> children ( TypeScript . Syntax . Constructor <$> ( fromMaybe <$> emptyTerm <*> optional typeParameters ) <*> formalParameters <*> ty )
constructorTy = makeTerm <$> symbol ConstructorType <*> children ( TypeScript . Syntax . Constructor <$> ( fromMaybe <$> emptyTerm <*> optional ( term typeParameters ) ) <*> formalParameters <*> term ty )
statementBlock :: Assignment
statementBlock = makeTerm <$> symbol StatementBlock <*> children ( many statement )
statementBlock = makeTerm <$> symbol StatementBlock <*> children ( many Term statement )
classBodyStatements :: HasCallStack => Assignment . Assignment [] Grammar [ Term ]
classBodyStatements = symbol ClassBody *> children ( concat <$> many ( ( \ as b -> as ++ [ b ] ) <$> many ( term decorator ) <*> term ( methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature ) ) )
classBodyStatements :: Assignment . Assignment [] Grammar [ Term ]
classBodyStatements = symbol ClassBody *> children ( contextualize' <$> Assignment . manyThrough comment ( postContextualize' <$> ( concat <$> many ( ( \ as b -> as ++ [ b ] ) <$> manyTerm decorator <*> term ( methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature ) ) ) <*> many comment ) )
where
contextualize' ( cs , formalParams ) = case nonEmpty cs of
Just cs -> toList cs ++ formalParams
Nothing -> formalParams
postContextualize' formalParams cs = case nonEmpty cs of
Just cs -> formalParams ++ toList cs
Nothing -> formalParams
publicFieldDefinition :: Assignment
publicFieldDefinition = makeField <$> symbol Grammar . PublicFieldDefinition <*> children ( ( , , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> propertyName <*> ( typeAnnotation' <|> emptyTerm ) <*> ( expression <|> emptyTerm ) )
publicFieldDefinition = makeField <$> symbol Grammar . PublicFieldDefinition <*> children ( ( , , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> term propertyName <*> ( term typeAnnotation' <|> emptyTerm ) <*> ( term expression <|> emptyTerm ) )
where makeField loc ( modifier , readonly , propertyName , annotation , expression ) = makeTerm loc ( Declaration . PublicFieldDefinition [ modifier , readonly , annotation ] propertyName expression )
statement :: Assignment
statement = term ( handleError everything )
statement = handleError everything
where
everything = choice [
exportStatement
@ -538,52 +584,55 @@ statement = term (handleError everything)
, labeledStatement ]
forOfStatement :: Assignment
forOfStatement = makeTerm <$> symbol ForOfStatement <*> children ( TypeScript . Syntax . ForOf <$> expression <*> expression <*> statement )
forOfStatement = makeTerm <$> symbol ForOfStatement <*> children ( TypeScript . Syntax . ForOf <$> term expression <*> term expressions <*> term statement )
forInStatement :: Assignment
forInStatement = makeTerm <$> symbol ForInStatement <*> children ( Statement . ForEach <$> expression <*> expression <*> statement )
forInStatement = makeTerm <$> symbol ForInStatement <*> children ( Statement . ForEach <$> term expression <*> term expression <*> term statement )
doStatement :: Assignment
doStatement = makeTerm <$> symbol DoStatement <*> children ( flip Statement . DoWhile <$> statement <*> parenthesizedExpression )
doStatement = makeTerm <$> symbol DoStatement <*> children ( flip Statement . DoWhile <$> term statement <*> term parenthesizedExpression )
continueStatement :: Assignment
continueStatement = makeTerm <$> symbol ContinueStatement <*> children ( Statement . Continue <$> ( ( s ymbol S tatementIdentifier *> identifier ) <|> emptyTerm ) )
continueStatement = makeTerm <$> symbol ContinueStatement <*> children ( Statement . Continue <$> ( s tatementIdentifier <|> emptyTerm ) )
breakStatement :: Assignment
breakStatement = makeTerm <$> symbol BreakStatement <*> children ( Statement . Break <$> ( ( s ymbol S tatementIdentifier *> identifier ) <|> emptyTerm ) )
breakStatement = makeTerm <$> symbol BreakStatement <*> children ( Statement . Break <$> ( s tatementIdentifier <|> emptyTerm ) )
withStatement :: Assignment
withStatement = makeTerm <$> symbol WithStatement <*> children ( TypeScript . Syntax . With <$> parenthesizedExpression <*> statement )
withStatement = makeTerm <$> symbol WithStatement <*> children ( TypeScript . Syntax . With <$> term parenthesizedExpression <*> term statement )
returnStatement :: Assignment
returnStatement = makeTerm <$> symbol ReturnStatement <*> children ( Statement . Return <$> ( expression <|> sequenceExpression <|> emptyTerm ) )
returnStatement = makeTerm <$> symbol ReturnStatement <*> children ( Statement . Return <$> ( term expressions <|> emptyTerm ) )
throwStatement :: Assignment
throwStatement = makeTerm <$> symbol Grammar . ThrowStatement <*> children ( Statement . Throw <$> ( expression <|> sequenceExpression ) )
throwStatement = makeTerm <$> symbol Grammar . ThrowStatement <*> children ( Statement . Throw <$> term expressions )
labeledStatement :: Assignment
labeledStatement = makeTerm <$> symbol Grammar . LabeledStatement <*> children ( TypeScript . Syntax . LabeledStatement <$> ( symbol StatementIdentifier *> children identifier ) <*> statement )
labeledStatement = makeTerm <$> symbol Grammar . LabeledStatement <*> children ( TypeScript . Syntax . LabeledStatement <$> statementIdentifier <*> term statement )
statementIdentifier :: Assignment
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> ( Syntax . Identifier <$> source )
importStatement :: Assignment
importStatement = makeTerm <$> symbol Grammar . ImportStatement <*> children ( Declaration . Import <$> ( ( ( \ a b -> [ a , b ] ) <$> importClause <*> fromClause ) <|> ( pure <$> ( importRequireClause <|> string ) ) ) )
importStatement = makeTerm <$> symbol Grammar . ImportStatement <*> children ( Declaration . Import <$> ( ( ( \ a b -> [ a , b ] ) <$> term importClause <*> term fromClause) <|> ( pure <$> term ( importRequireClause <|> string ) ) ) )
importClause :: Assignment
importClause = makeTerm <$> symbol Grammar . ImportClause <*> children ( TypeScript . Syntax . ImportClause <$> ( ( ( \ a b -> [ a , b ] ) <$> identifier <*> ( namespaceImport <|> namedImports ) ) <|> ( pure <$> ( namespaceImport <|> namedImports <|> identifier ) ) ) )
importClause = makeTerm <$> symbol Grammar . ImportClause <*> children ( TypeScript . Syntax . ImportClause <$> ( ( ( \ a b -> [ a , b ] ) <$> term identifier <*> term ( namespaceImport <|> namedImports ) ) <|> ( pure <$> term ( namespaceImport <|> namedImports <|> identifier ) ) ) )
namedImports :: Assignment
namedImports = makeTerm <$> symbol Grammar . NamedImports <*> children ( TypeScript . Syntax . NamedImports <$> many ( term importExportSpecifier ) )
namedImports = makeTerm <$> symbol Grammar . NamedImports <*> children ( TypeScript . Syntax . NamedImports <$> many Term importExportSpecifier )
namespaceImport :: Assignment
namespaceImport = makeTerm <$> symbol Grammar . NamespaceImport <*> children ( TypeScript . Syntax . NamespaceImport <$> identifier)
namespaceImport = makeTerm <$> symbol Grammar . NamespaceImport <*> children ( TypeScript . Syntax . NamespaceImport <$> term identifier)
importRequireClause :: Assignment
importRequireClause = makeTerm <$> symbol Grammar . ImportRequireClause <*> children ( TypeScript . Syntax . ImportRequireClause <$> identifier <*> string )
importRequireClause = makeTerm <$> symbol Grammar . ImportRequireClause <*> children ( TypeScript . Syntax . ImportRequireClause <$> term identifier <*> term string )
debuggerStatement :: Assignment
debuggerStatement = makeTerm <$> symbol Grammar . DebuggerStatement <*> ( TypeScript . Syntax . Debugger <$ source )
expressionStatement' :: Assignment
expressionStatement' = symbol ExpressionStatement *> children ( expression <|> sequenceExpression )
expressionStatement' = symbol ExpressionStatement *> children ( term expressions )
declaration :: Assignment
declaration = everything
@ -605,128 +654,125 @@ declaration = everything
]
typeAliasDeclaration :: Assignment
typeAliasDeclaration = makeTypeAliasDecl <$> symbol Grammar . TypeAliasDeclaration <*> children ( ( , , ) <$> identifier <*> ( typeParameters <|> emptyTerm ) <*> ty )
typeAliasDeclaration = makeTypeAliasDecl <$> symbol Grammar . TypeAliasDeclaration <*> children ( ( , , ) <$> term identifier <*> ( term typeParameters <|> emptyTerm ) <*> term ty )
where makeTypeAliasDecl loc ( identifier , typeParams , body ) = makeTerm loc ( Declaration . TypeAliasDeclaration [ typeParams ] identifier body )
enumDeclaration :: Assignment
enumDeclaration = makeTerm <$> symbol Grammar . EnumDeclaration <*> children ( TypeScript . Syntax . EnumDeclaration <$> identifier <*> many ( t erm ( propertyName <|> enumAssignment ) ) )
enumDeclaration = makeTerm <$> symbol Grammar . EnumDeclaration <*> children ( TypeScript . Syntax . EnumDeclaration <$> term identifier <*> ( symbol EnumBody *> children ( manyT erm ( propertyName <|> enumAssignment ) ) ) )
enumAssignment :: Assignment
enumAssignment = makeTerm <$> symbol Grammar . EnumAssignment <*> children ( Statement . Assignment [] <$> propertyName <*> expression )
enumAssignment = makeTerm <$> symbol Grammar . EnumAssignment <*> children ( Statement . Assignment [] <$> term propertyName <*> term expression )
interfaceDeclaration :: Assignment
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar . InterfaceDeclaration <*> children ( ( , , , ) <$> identifier <*> ( typeParameters <|> emptyTerm ) <*> ( extendsClause <|> emptyTerm ) <*> objectType )
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar . InterfaceDeclaration <*> children ( ( , , , ) <$> term identifier <*> ( term typeParameters <|> emptyTerm ) <*> ( term extendsClause <|> emptyTerm ) <*> term objectType )
where makeInterfaceDecl loc ( identifier , typeParams , clause , objectType ) = makeTerm loc ( Declaration . InterfaceDeclaration [ typeParams , clause ] identifier objectType )
extendsClause :: Assignment
extendsClause = makeTerm <$> symbol Grammar . ExtendsClause <*> children ( TypeScript . Syntax . ExtendsClause <$> many ( term ty ) )
ambientDeclaration :: Assignment
ambientDeclaration = makeTerm <$> symbol Grammar . AmbientDeclaration <*> children ( TypeScript . Syntax . AmbientDeclaration <$> choice [ declaration , statementBlock ] )
ambientDeclaration = makeTerm <$> symbol Grammar . AmbientDeclaration <*> children ( TypeScript . Syntax . AmbientDeclaration <$> term ( choice [ declaration , statementBlock ] ) )
exportStatement :: Assignment
exportStatement = makeTerm <$> symbol Grammar . ExportStatement <*> children ( TypeScript . Syntax . Export <$> ( ( ( \ a b -> [ a , b ] ) <$> exportClause <*> fromClause ) <|> ( ( ++ ) <$> many ( term decorator ) <*> ( pure <$> ( fromClause <|> exportClause <|> declaration <|> expression <|> identifier <|> importAlias' ) ) ) ) )
exportStatement = makeTerm <$> symbol Grammar . ExportStatement <*> children ( TypeScript . Syntax . Export <$> ( ( ( \ a b -> [ a , b ] ) <$> term exportClause <*> term fromClause ) <|> ( ( ++ ) <$> many Term decorator <*> ( pure <$> term ( fromClause <|> exportClause <|> declaration <|> expression <|> identifier <|> importAlias' ) ) ) ) )
fromClause :: Assignment
fromClause = string
exportClause :: Assignment
exportClause = makeTerm <$> symbol Grammar . ExportClause <*> children ( TypeScript . Syntax . ExportClause <$> many ( term importExportSpecifier ) )
exportClause = makeTerm <$> symbol Grammar . ExportClause <*> children ( TypeScript . Syntax . ExportClause <$> many Term importExportSpecifier )
importExportSpecifier :: Assignment
importExportSpecifier = makeTerm <$> ( symbol Grammar . ExportSpecifier <|> symbol Grammar . ImportSpecifier ) <*> children ( TypeScript . Syntax . ImportExportSpecifier <$> identifier <*> ( identifier <|> emptyTerm ) )
importExportSpecifier = makeTerm <$> ( symbol Grammar . ExportSpecifier <|> symbol Grammar . ImportSpecifier ) <*> children ( TypeScript . Syntax . ImportExportSpecifier <$> term identifier <*> ( term identifier <|> emptyTerm ) )
propertySignature :: Assignment
propertySignature = makePropertySignature <$> symbol Grammar . PropertySignature <*> children ( ( , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> propertyName <*> ( typeAnnotation' <|> emptyTerm ) )
propertySignature = makePropertySignature <$> symbol Grammar . PropertySignature <*> children ( ( , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> term propertyName <*> ( term typeAnnotation' <|> emptyTerm ) )
where makePropertySignature loc ( modifier , readonly , propertyName , annotation ) = makeTerm loc ( TypeScript . Syntax . PropertySignature [ modifier , readonly , annotation ] propertyName )
propertyName :: Assignment
propertyName = ( makeTerm <$> symbol PropertyIdentifier <*> ( Syntax . Identifier <$> source ) ) <|> string <|> number <|> computedPropertyName
propertyName = ( makeTerm <$> symbol PropertyIdentifier <*> ( Syntax . Identifier <$> source ) ) <|> term string <|> term number <|> term computedPropertyName
computedPropertyName :: Assignment
computedPropertyName = makeTerm <$> symbol Grammar . ComputedPropertyName <*> children ( TypeScript . Syntax . ComputedPropertyName <$> expression)
computedPropertyName = makeTerm <$> symbol Grammar . ComputedPropertyName <*> children ( TypeScript . Syntax . ComputedPropertyName <$> term expression)
assignmentPattern :: Assignment
assignmentPattern = makeTerm <$> symbol AssignmentPattern <*> children ( Statement . Assignment [] <$> shorthandPropertyIdentifier <*> expression )
assignmentPattern = makeTerm <$> symbol AssignmentPattern <*> children ( Statement . Assignment [] <$> term shorthandPropertyIdentifier <*> term expression )
shorthandPropertyIdentifier :: Assignment
shorthandPropertyIdentifier = makeTerm <$> symbol Grammar . ShorthandPropertyIdentifier <*> ( TypeScript . Syntax . ShorthandPropertyIdentifier <$> source )
requiredParameter :: Assignment
requiredParameter = makeRequiredParameter <$> symbol Grammar . RequiredParameter <*> children ( ( , , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> ( identifier <|> destructuringPattern ) <*> ( typeAnnotation' <|> emptyTerm ) <*> ( expression <|> emptyTerm ) )
requiredParameter = makeRequiredParameter <$> symbol Grammar . RequiredParameter <*> children ( ( , , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> term ( identifier <|> destructuringPattern <|> this ) <*> ( term typeAnnotation' <|> emptyTerm ) <*> ( term expression <|> emptyTerm ) )
where makeRequiredParameter loc ( modifier , readonly , identifier , annotation , initializer ) = makeTerm loc ( TypeScript . Syntax . RequiredParameter [ modifier , readonly , annotation ] ( makeTerm loc ( Statement . Assignment [] identifier initializer ) ) )
restParameter :: Assignment
restParameter = makeRestParameter <$> symbol Grammar . RestParameter <*> children ( ( , ) <$> identifier <*> ( typeAnnotation' <|> emptyTerm ) )
restParameter = makeRestParameter <$> symbol Grammar . RestParameter <*> children ( ( , ) <$> term identifier <*> ( term typeAnnotation' <|> emptyTerm ) )
where makeRestParameter loc ( identifier , annotation ) = makeTerm loc ( TypeScript . Syntax . RestParameter [ annotation ] identifier )
optionalParameter :: Assignment
optionalParameter = makeOptionalParam <$> symbol Grammar . OptionalParameter <*> children ( ( , , , , ) <$> ( accessibilityModifier' <|> emptyTerm ) <*> ( readonly' <|> emptyTerm ) <*> ( identifier <|> destructuringPattern ) <*> ( t ypeAnnotation' <|> emptyTerm ) <*> ( expression <|> emptyTerm ) )
optionalParameter = makeOptionalParam <$> symbol Grammar . OptionalParameter <*> children ( ( , , , , ) <$> ( term accessibilityModifier' <|> emptyTerm ) <*> ( term readonly' <|> emptyTerm ) <*> ( term identifier <|> destructuringPattern ) <*> ( t erm t ypeAnnotation' <|> emptyTerm ) <*> ( term expression <|> emptyTerm ) )
where makeOptionalParam loc ( modifier , readonly , subject , annotation , initializer ) = makeTerm loc ( TypeScript . Syntax . OptionalParameter [ modifier , readonly , annotation ] ( makeTerm loc ( Statement . Assignment [] subject initializer ) ) )
internalModule :: Assignment
internalModule = makeTerm <$> symbol Grammar . InternalModule <*> children ( TypeScript . Syntax . InternalModule <$> ( string <|> identifier <|> nestedIdentifier ) <*> statements )
internalModule = makeTerm <$> symbol Grammar . InternalModule <*> children ( TypeScript . Syntax . InternalModule <$> term ( string <|> identifier <|> nestedIdentifier ) <*> statements )
module ' : : Assignment
module ' = m a k e Term <$> symbol Module <*> children ( Declaration . Module <$> ( string <|> identifier <|> nestedIdentifier ) <*> ( ( s ymbol S tatementBlock *> children ( many statement) ) <|> pure [] ) )
module ' = m a k e Term <$> symbol Module <*> children ( Declaration . Module <$> term ( string <|> identifier <|> nestedIdentifier ) <*> ( s tatements <|> pure [] ) )
statements :: HasCallStack => Assignment. Assignment [] Grammar [ Term ]
statements = symbol StatementBlock *> children ( many statement )
statements :: Assignment. Assignment [] Grammar [ Term ]
statements = symbol StatementBlock *> children ( many Term statement )
arrowFunction :: Assignment
arrowFunction = makeArrowFun <$> symbol ArrowFunction <*> children ( ( , , ) <$> emptyTerm <*> ( ( ( \ a b c -> ( a , [ b ] , c ) ) <$> emptyTerm <*> identifier <*> emptyTerm ) <|> callSignatureParts ) <*> ( expression <|> statementBlock ) )
arrowFunction = makeArrowFun <$> symbol ArrowFunction <*> children ( ( , , ) <$> emptyTerm <*> ( ( ( \ a b c -> ( a , [ b ] , c ) ) <$> emptyTerm <*> term identifier <*> emptyTerm ) <|> callSignatureParts ) <*> term ( expression <|> statementBlock ) )
where makeArrowFun loc ( identifier , ( typeParams , params , returnTy ) , body ) = makeTerm loc ( Declaration . Function [ typeParams , returnTy ] identifier params body )
comment :: Assignment
comment = makeTerm <$> symbol Comment <*> ( Comment . Comment <$> source )
ifStatement :: Assignment
ifStatement = makeTerm <$> symbol IfStatement <*> children ( Statement . If <$> parenthesizedExpression <*> statement <*> ( statement <|> emptyTerm ) )
ifStatement = makeTerm <$> symbol IfStatement <*> children ( Statement . If <$> term parenthesizedExpression <*> term statement <*> ( term statement <|> emptyTerm ) )
whileStatement :: Assignment
whileStatement = makeTerm <$> symbol WhileStatement <*> children ( Statement . While <$> expression <*> statement )
whileStatement = makeTerm <$> symbol WhileStatement <*> children ( Statement . While <$> term expression <*> term statement )
forStatement :: Assignment
forStatement = makeTerm <$> symbol ForStatement <*> children ( Statement . For <$> ( variableDeclaration <|> expressionStatement' <|> emptyStatement ) <*> ( expressionStatement' <|> emptyStatement ) <*> ( expression <|> emptyTerm ) <*> statement )
forStatement = makeTerm <$> symbol ForStatement <*> children ( Statement . For <$> term ( variableDeclaration <|> expressionStatement' <|> emptyStatement ) <*> term ( expressionStatement' <|> emptyStatement ) <*> term ( expression s <|> emptyTerm ) <*> term statement )
variableDeclaration :: Assignment
variableDeclaration = ( makeTerm <$> ( symbol Grammar . VariableDeclaration <|> symbol Grammar . LexicalDeclaration ) <*> children ( Declaration . VariableDeclaration <$> many ( term variableDeclarator ) ) )
variableDeclaration = makeTerm <$> ( symbol Grammar . VariableDeclaration <|> symbol Grammar . LexicalDeclaration ) <*> children ( Declaration . VariableDeclaration <$> many Term variableDeclarator )
variableDeclarator :: Assignment
variableDeclarator = makeVarDecl <$> symbol VariableDeclarator <*> children ( ( , , ) <$> ( identifier <|> destructuringPattern ) <*> ( t ypeAnnotation' <|> emptyTerm ) <*> ( expression <|> emptyTerm ) )
variableDeclarator = makeVarDecl <$> symbol VariableDeclarator <*> children ( ( , , ) <$> term ( identifier <|> destructuringPattern ) <*> ( t erm t ypeAnnotation' <|> emptyTerm ) <*> ( term expression <|> emptyTerm ) )
where makeVarDecl loc ( subject , annotations , value ) = makeTerm loc ( Statement . Assignment [ annotations ] subject value )
parenthesizedExpression :: Assignment
parenthesizedExpression = symbol ParenthesizedExpression *> children ( expression <|> sequenceExpression )
parenthesizedExpression = symbol ParenthesizedExpression *> children ( term expressions )
switchStatement :: Assignment
switchStatement = makeTerm <$> symbol SwitchStatement <*> children ( Statement . Match <$> parenthesizedExpression <*> switchBody )
switchStatement = makeTerm <$> symbol SwitchStatement <*> children ( Statement . Match <$> term parenthesizedExpression <*> term switchBody )
where
switchBody = symbol SwitchBody *> children ( makeTerm <$> location <*> many ( term switchCase ) )
switchCase = makeTerm <$> ( symbol SwitchCase <|> symbol SwitchDefault ) <*> children ( Statement . Pattern <$> ( expression <|> emptyTerm ) <*> ( makeTerm <$> location <*> many statement ) )
switchBody = symbol SwitchBody *> children ( makeTerm <$> location <*> many Term switchCase )
switchCase = makeTerm <$> ( symbol SwitchCase <|> symbol SwitchDefault ) <*> children ( Statement . Pattern <$> ( term expressions <|> emptyTerm ) <*> ( makeTerm <$> location <*> many Term statement ) )
subscriptExpression :: Assignment
subscriptExpression = makeTerm <$> symbol SubscriptExpression <*> children ( Expression . Subscript <$> expression <*> ( pure <$> expression) )
subscriptExpression = makeTerm <$> symbol SubscriptExpression <*> children ( Expression . Subscript <$> term expression <*> ( pure <$> term expressions ) )
pair :: Assignment
pair = makeTerm <$> symbol Pair <*> children ( Literal . KeyValue <$> propertyName <*> expression )
pair = makeTerm <$> symbol Pair <*> children ( Literal . KeyValue <$> term propertyName <*> term expression )
callExpression :: Assignment
callExpression = makeCall <$> ( symbol CallExpression <|> symbol CallExpression' ) <*> children ( ( , , , ) <$> ( expression <|> super <|> function ) <*> ( typeArguments <|> pure [] ) <*> ( arguments <|> ( pure <$> templateString ) ) <*> emptyTerm )
callExpression = makeCall <$> ( symbol CallExpression <|> symbol CallExpression' ) <*> children ( ( , , , ) <$> term ( expression <|> super <|> function ) <*> ( typeArguments <|> pure [] ) <*> ( arguments <|> ( pure <$> term templateString ) ) <*> emptyTerm )
where makeCall loc ( subject , typeArgs , args , body ) = makeTerm loc ( Expression . Call typeArgs subject args body )
arguments = symbol Arguments *> children ( many ( t erm ( expression <|> spreadElement ) ) )
arguments = symbol Arguments *> children ( many T erm ( expression <|> spreadElement ) )
typeArguments = symbol Grammar . TypeArguments *> children ( some ( term ty ) )
tryStatement :: Assignment
tryStatement = makeTry <$> symbol TryStatement <*> children ( ( , , ) <$> statementBlock <*> optional catchClause <*> optional finallyClause )
tryStatement = makeTry <$> symbol TryStatement <*> children ( ( , , ) <$> term statementBlock <*> optional ( term catchClause ) <*> optional ( term finallyClause ) )
where
makeTry loc ( statementBlock' , catch , finally ) = makeTerm loc ( Statement . Try statementBlock' ( catMaybes [ catch , finally ] ) )
catchClause = makeTerm <$> symbol CatchClause <*> children ( Statement . Catch <$> ( identifier <|> emptyTerm ) <*> statementBlock )
finallyClause = makeTerm <$> symbol FinallyClause <*> children ( Statement . Finally <$> statementBlock )
binaryExpression :: Assignment
binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children ( infixTerm expression expression
binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children ( infixTerm expression ( term expression )
[ ( inj . ) . Expression . Plus <$ symbol AnonPlus
, ( inj . ) . Expression . Minus <$ symbol AnonMinus
, ( inj . ) . Expression . Times <$ symbol AnonStar
@ -743,6 +789,7 @@ binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm
, ( inj . ) . invert Expression . Equal <$ ( symbol AnonBangEqual <|> symbol AnonBangEqualEqual )
, ( inj . ) . Expression . LShift <$ symbol AnonLAngleLAngle
, ( inj . ) . Expression . RShift <$ symbol AnonRAngleRAngle
, ( inj . ) . Expression . UnsignedRShift <$ symbol AnonRAngleRAngleRAngle
, ( inj . ) . Expression . LessThan <$ symbol AnonLAngle
, ( inj . ) . Expression . GreaterThan <$ symbol AnonRAngle
, ( inj . ) . Expression . LessThanEqual <$ symbol AnonLAngleEqual
@ -754,8 +801,7 @@ emptyStatement :: Assignment
emptyStatement = makeTerm <$> symbol EmptyStatement <*> ( Syntax . Empty <$ source <|> pure Syntax . Empty )
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
infixTerm :: HasCallStack
=> Assignment
infixTerm :: Assignment
-> Assignment
-> [ Assignment . Assignment [] Grammar ( Term -> Term -> Data . Union . Union Syntax Term ) ]
-> Assignment . Assignment [] Grammar ( Data . Union . Union Syntax Term )