mirror of
https://github.com/github/semantic.git
synced 2024-12-01 00:33:59 +03:00
Redefine the Syntax type synonyms as just the list of type constructors.
This commit is contained in:
parent
c0763f7a23
commit
a8bf5b5e71
@ -2,7 +2,6 @@
|
|||||||
module Language.Python.Syntax
|
module Language.Python.Syntax
|
||||||
( assignment
|
( assignment
|
||||||
, Syntax
|
, Syntax
|
||||||
, Syntax'
|
|
||||||
, Grammar
|
, Grammar
|
||||||
, Error
|
, Error
|
||||||
) where
|
) where
|
||||||
@ -26,8 +25,7 @@ import Language.Python.Grammar as Grammar
|
|||||||
import Prologue hiding (Location)
|
import Prologue hiding (Location)
|
||||||
import Term
|
import Term
|
||||||
|
|
||||||
type Syntax = Union Syntax'
|
type Syntax =
|
||||||
type Syntax' =
|
|
||||||
'[ Comment.Comment
|
'[ Comment.Comment
|
||||||
, Declaration.Comprehension
|
, Declaration.Comprehension
|
||||||
, Declaration.Function
|
, Declaration.Function
|
||||||
@ -81,13 +79,13 @@ instance Eq1 Redirect where liftEq = genericLiftEq
|
|||||||
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
-- | Assignment from AST in Python's grammar onto a program in Python's syntax.
|
-- | Assignment from AST in Python's grammar onto a program in Python's syntax.
|
||||||
assignment :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
assignment :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
assignment = makeTerm <$> symbol Module <*> children (many declaration)
|
assignment = makeTerm <$> symbol Module <*> children (many declaration)
|
||||||
|
|
||||||
declaration :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
declaration :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
declaration = handleError $ comment <|> statement <|> expression
|
declaration = handleError $ comment <|> statement <|> expression
|
||||||
|
|
||||||
statement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
statement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
statement = assertStatement
|
statement = assertStatement
|
||||||
<|> assignment'
|
<|> assignment'
|
||||||
<|> augmentedAssignment
|
<|> augmentedAssignment
|
||||||
@ -100,10 +98,10 @@ statement = assertStatement
|
|||||||
<|> printStatement
|
<|> printStatement
|
||||||
<|> returnStatement
|
<|> returnStatement
|
||||||
|
|
||||||
expressionStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
expressionStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
expressionStatement = symbol ExpressionStatement *> children expression
|
expressionStatement = symbol ExpressionStatement *> children expression
|
||||||
|
|
||||||
expression :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
expression :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
expression = await
|
expression = await
|
||||||
<|> binaryOperator
|
<|> binaryOperator
|
||||||
<|> booleanOperator
|
<|> booleanOperator
|
||||||
@ -123,13 +121,13 @@ expression = await
|
|||||||
<|> tuple
|
<|> tuple
|
||||||
<|> unaryOperator
|
<|> unaryOperator
|
||||||
|
|
||||||
dottedName :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
dottedName :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression)
|
dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression)
|
||||||
|
|
||||||
ellipsis :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
ellipsis :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
ellipsis = makeTerm <$> symbol Grammar.Ellipsis <*> (Language.Python.Syntax.Ellipsis <$ source)
|
ellipsis = makeTerm <$> symbol Grammar.Ellipsis <*> (Language.Python.Syntax.Ellipsis <$ source)
|
||||||
|
|
||||||
comparisonOperator :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
comparisonOperator :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression >>= \ lexpression -> makeComparison loc lexpression)
|
comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression >>= \ lexpression -> makeComparison loc lexpression)
|
||||||
where
|
where
|
||||||
makeComparison loc lexpression = makeTerm loc <$ symbol AnonLAngle <*> (Expression.LessThan lexpression <$> expression)
|
makeComparison loc lexpression = makeTerm loc <$ symbol AnonLAngle <*> (Expression.LessThan lexpression <$> expression)
|
||||||
@ -144,26 +142,26 @@ comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression
|
|||||||
<|> symbol AnonIs *> source *> (symbol AnonNot *> (makeTerm loc <$> Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression)))
|
<|> symbol AnonIs *> source *> (symbol AnonNot *> (makeTerm loc <$> Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression)))
|
||||||
<|> (makeTerm loc <$> Expression.Equal lexpression <$> expression))
|
<|> (makeTerm loc <$> Expression.Equal lexpression <$> expression))
|
||||||
|
|
||||||
notOperator :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
notOperator :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression)
|
notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression)
|
||||||
|
|
||||||
keywordIdentifier :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
keywordIdentifier :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
keywordIdentifier = makeTerm <$> symbol KeywordIdentifier <*> children (Syntax.Identifier <$> source)
|
keywordIdentifier = makeTerm <$> symbol KeywordIdentifier <*> children (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
tuple :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
tuple :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression))
|
tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression))
|
||||||
|
|
||||||
-- TODO: Consider flattening single element lists
|
-- TODO: Consider flattening single element lists
|
||||||
expressionList :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
expressionList :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
expressionList = makeTerm <$> symbol ExpressionList <*> children (many expression)
|
expressionList = makeTerm <$> symbol ExpressionList <*> children (many expression)
|
||||||
|
|
||||||
unaryOperator :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
unaryOperator :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
unaryOperator = symbol UnaryOperator >>= \ location -> arithmetic location <|> bitwise location <|> children ( symbol AnonPlus *> expression )
|
unaryOperator = symbol UnaryOperator >>= \ location -> arithmetic location <|> bitwise location <|> children ( symbol AnonPlus *> expression )
|
||||||
where
|
where
|
||||||
arithmetic location = makeTerm location . Expression.Negate <$> children ( symbol AnonMinus *> expression )
|
arithmetic location = makeTerm location . Expression.Negate <$> children ( symbol AnonMinus *> expression )
|
||||||
bitwise location = makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
bitwise location = makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
||||||
|
|
||||||
binaryOperator :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
binaryOperator :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
binaryOperator = symbol BinaryOperator >>= \ location -> children (expression >>= \ lexpression ->
|
binaryOperator = symbol BinaryOperator >>= \ location -> children (expression >>= \ lexpression ->
|
||||||
makeTerm location <$> arithmetic lexpression
|
makeTerm location <$> arithmetic lexpression
|
||||||
<|> makeTerm location <$> bitwise lexpression)
|
<|> makeTerm location <$> bitwise lexpression)
|
||||||
@ -181,17 +179,17 @@ binaryOperator = symbol BinaryOperator >>= \ location -> children (expression >>
|
|||||||
<|> symbol AnonLAngleLAngle *> (Expression.LShift lexpression <$> expression)
|
<|> symbol AnonLAngleLAngle *> (Expression.LShift lexpression <$> expression)
|
||||||
<|> symbol AnonRAngleRAngle *> (Expression.RShift lexpression <$> expression)
|
<|> symbol AnonRAngleRAngle *> (Expression.RShift lexpression <$> expression)
|
||||||
|
|
||||||
booleanOperator :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
booleanOperator :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
booleanOperator = makeTerm <$> symbol BooleanOperator <*> children ( expression >>= booleanOperator' )
|
booleanOperator = makeTerm <$> symbol BooleanOperator <*> children ( expression >>= booleanOperator' )
|
||||||
where
|
where
|
||||||
booleanOperator' lexpression = symbol AnonAnd *> (Expression.And lexpression <$> expression)
|
booleanOperator' lexpression = symbol AnonAnd *> (Expression.And lexpression <$> expression)
|
||||||
<|> symbol AnonOr *> (Expression.Or lexpression <$> expression)
|
<|> symbol AnonOr *> (Expression.Or lexpression <$> expression)
|
||||||
|
|
||||||
assignment' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
assignment' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
assignment' =
|
assignment' =
|
||||||
makeTerm <$> symbol Assignment <*> children (Statement.Assignment <$> expressionList <*> rvalue)
|
makeTerm <$> symbol Assignment <*> children (Statement.Assignment <$> expressionList <*> rvalue)
|
||||||
|
|
||||||
augmentedAssignment :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
augmentedAssignment :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
augmentedAssignment = makeTerm <$> symbol AugmentedAssignment <*> children (expressionList >>= \ lvalue -> Statement.Assignment lvalue <$>
|
augmentedAssignment = makeTerm <$> symbol AugmentedAssignment <*> children (expressionList >>= \ lvalue -> Statement.Assignment lvalue <$>
|
||||||
(makeTerm <$> symbol AnonPlusEqual <*> (Expression.Plus lvalue <$> rvalue)
|
(makeTerm <$> symbol AnonPlusEqual <*> (Expression.Plus lvalue <$> rvalue)
|
||||||
<|> makeTerm <$> symbol AnonMinusEqual <*> (Expression.Minus lvalue <$> rvalue)
|
<|> makeTerm <$> symbol AnonMinusEqual <*> (Expression.Minus lvalue <$> rvalue)
|
||||||
@ -206,56 +204,56 @@ augmentedAssignment = makeTerm <$> symbol AugmentedAssignment <*> children (expr
|
|||||||
<|> makeTerm <$> symbol AnonLAngleLAngleEqual <*> (Expression.LShift lvalue <$> rvalue)
|
<|> makeTerm <$> symbol AnonLAngleLAngleEqual <*> (Expression.LShift lvalue <$> rvalue)
|
||||||
<|> makeTerm <$> symbol AnonCaretEqual <*> (Expression.BXOr lvalue <$> rvalue)))
|
<|> makeTerm <$> symbol AnonCaretEqual <*> (Expression.BXOr lvalue <$> rvalue)))
|
||||||
|
|
||||||
yield :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
yield :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children ( expression <|> expressionList <|> emptyTerm ))
|
yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children ( expression <|> expressionList <|> emptyTerm ))
|
||||||
|
|
||||||
rvalue :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
rvalue :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
rvalue = expressionList <|> assignment' <|> augmentedAssignment <|> yield
|
rvalue = expressionList <|> assignment' <|> augmentedAssignment <|> yield
|
||||||
|
|
||||||
identifier :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
identifier :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
literal :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
literal :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary <|> set
|
literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary <|> set
|
||||||
|
|
||||||
set :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
set :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> many expression)
|
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> many expression)
|
||||||
|
|
||||||
dictionary :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
dictionary :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
dictionary = makeTerm <$> symbol Dictionary <*> children (Literal.Hash <$> many pairs)
|
dictionary = makeTerm <$> symbol Dictionary <*> children (Literal.Hash <$> many pairs)
|
||||||
where pairs = makeTerm <$> symbol Pair <*> children (Literal.KeyValue <$> expression <*> expression)
|
where pairs = makeTerm <$> symbol Pair <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||||
|
|
||||||
list' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
list' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
list' = makeTerm <$> symbol List <*> children (Literal.Array <$> many expression)
|
list' = makeTerm <$> symbol List <*> children (Literal.Array <$> many expression)
|
||||||
|
|
||||||
-- TODO: Wrap `Literal.TextElement` with a `Literal.String`
|
-- TODO: Wrap `Literal.TextElement` with a `Literal.String`
|
||||||
string :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
string :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||||
|
|
||||||
concatenatedString :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
concatenatedString :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
concatenatedString = makeTerm <$> symbol ConcatenatedString <*> children (Literal.TextElement . mconcat <$> many (symbol String *> source))
|
concatenatedString = makeTerm <$> symbol ConcatenatedString <*> children (Literal.TextElement . mconcat <$> many (symbol String *> source))
|
||||||
|
|
||||||
float :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
float :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||||
|
|
||||||
integer :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
integer :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||||
|
|
||||||
comment :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
comment :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||||
|
|
||||||
-- TODO Possibly match against children for dotted name and identifiers
|
-- TODO Possibly match against children for dotted name and identifiers
|
||||||
import' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
import' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
import' = makeTerm <$> symbol ImportStatement <*> children (Declaration.Import <$> many expression)
|
import' = makeTerm <$> symbol ImportStatement <*> children (Declaration.Import <$> many expression)
|
||||||
|
|
||||||
-- TODO Possibly match against children nodes
|
-- TODO Possibly match against children nodes
|
||||||
importFrom :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
importFrom :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
importFrom = makeTerm <$> symbol ImportFromStatement <*> children (Declaration.Import <$> many expression)
|
importFrom = makeTerm <$> symbol ImportFromStatement <*> children (Declaration.Import <$> many expression)
|
||||||
|
|
||||||
assertStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
assertStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
assertStatement = makeTerm <$ symbol AssertStatement <*> location <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> source)) <*> many expression)
|
assertStatement = makeTerm <$ symbol AssertStatement <*> location <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> source)) <*> many expression)
|
||||||
|
|
||||||
printStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
printStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
printStatement = do
|
printStatement = do
|
||||||
location <- symbol PrintStatement
|
location <- symbol PrintStatement
|
||||||
children $ do
|
children $ do
|
||||||
@ -266,47 +264,47 @@ printStatement = do
|
|||||||
redirectCallTerm location keyword = makeTerm location <$ symbol Chevron <*> (flip Redirect <$> children expression <*> printCallTerm location keyword)
|
redirectCallTerm location keyword = makeTerm location <$ symbol Chevron <*> (flip Redirect <$> children expression <*> printCallTerm location keyword)
|
||||||
printCallTerm location keyword = makeTerm location . Expression.Call keyword <$> many expression
|
printCallTerm location keyword = makeTerm location . Expression.Call keyword <$> many expression
|
||||||
|
|
||||||
globalStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
globalStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> source)) <*> many identifier)
|
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> source)) <*> many identifier)
|
||||||
|
|
||||||
await :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
await :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> many expression)
|
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> many expression)
|
||||||
|
|
||||||
returnStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
returnStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expressionList)
|
returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expressionList)
|
||||||
|
|
||||||
|
|
||||||
ifStatement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
ifStatement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> expression <*> statement <*> (flip (foldr makeElif) <$> many elifClause <*> optionalElse))
|
ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> expression <*> statement <*> (flip (foldr makeElif) <$> many elifClause <*> optionalElse))
|
||||||
where elseClause = symbol ElseClause *> children statement
|
where elseClause = symbol ElseClause *> children statement
|
||||||
elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> expression <*> statement)
|
elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> expression <*> statement)
|
||||||
optionalElse = fromMaybe <$> emptyTerm <*> optional elseClause
|
optionalElse = fromMaybe <$> emptyTerm <*> optional elseClause
|
||||||
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
||||||
|
|
||||||
memberAccess :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
memberAccess :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> expression <*> expression)
|
memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> expression <*> expression)
|
||||||
|
|
||||||
subscript :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
subscript :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression)
|
subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression)
|
||||||
|
|
||||||
call :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
call :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (symbol ArgumentList *> children (many expression)
|
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (symbol ArgumentList *> children (many expression)
|
||||||
<|> some comprehension))
|
<|> some comprehension))
|
||||||
|
|
||||||
boolean :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
boolean :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
||||||
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
||||||
|
|
||||||
none :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
none :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
none = makeTerm <$> symbol None <*> (Literal.Null <$ source)
|
none = makeTerm <$> symbol None <*> (Literal.Null <$ source)
|
||||||
|
|
||||||
lambda :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
lambda :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambdaIdentifier <*> lambdaParameters <*> lambdaBody)
|
lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambdaIdentifier <*> lambdaParameters <*> lambdaBody)
|
||||||
where lambdaIdentifier = makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source)
|
where lambdaIdentifier = makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source)
|
||||||
lambdaParameters = many identifier
|
lambdaParameters = many identifier
|
||||||
lambdaBody = expression
|
lambdaBody = expression
|
||||||
|
|
||||||
comprehension :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
comprehension :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionDeclaration expression)
|
comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionDeclaration expression)
|
||||||
<|> makeTerm <$> symbol ListComprehension <*> children (comprehensionDeclaration expression)
|
<|> makeTerm <$> symbol ListComprehension <*> children (comprehensionDeclaration expression)
|
||||||
<|> makeTerm <$> symbol SetComprehension <*> children (comprehensionDeclaration expression)
|
<|> makeTerm <$> symbol SetComprehension <*> children (comprehensionDeclaration expression)
|
||||||
@ -317,16 +315,16 @@ comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehen
|
|||||||
makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest)
|
makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest)
|
||||||
nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression))
|
nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression))
|
||||||
|
|
||||||
conditionalExpression :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
conditionalExpression :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (expression >>= \ thenBranch -> expression >>= \ conditional -> Statement.If conditional thenBranch <$> (expression <|> emptyTerm))
|
conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (expression >>= \ thenBranch -> expression >>= \ conditional -> Statement.If conditional thenBranch <$> (expression <|> emptyTerm))
|
||||||
|
|
||||||
makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a
|
makeTerm :: (HasCallStack, InUnion fs f) => a -> f (Term (Union fs) a) -> Term (Union fs) a
|
||||||
makeTerm a f = cofree (a :< inj f)
|
makeTerm a f = cofree (a :< inj f)
|
||||||
|
|
||||||
emptyTerm :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
emptyTerm :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
||||||
|
|
||||||
handleError :: HasCallStack => Assignment Grammar (Term Syntax (Record Location)) -> Assignment Grammar (Term Syntax (Record Location))
|
handleError :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location)) -> Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
handleError = flip catchError $ \ error -> case errorCause error of
|
handleError = flip catchError $ \ error -> case errorCause error of
|
||||||
UnexpectedEndOfInput _ -> throwError error
|
UnexpectedEndOfInput _ -> throwError error
|
||||||
_ -> makeTerm <$> location <*> (Syntax.Error error <$ source)
|
_ -> makeTerm <$> location <*> (Syntax.Error error <$ source)
|
||||||
|
@ -2,7 +2,6 @@
|
|||||||
module Language.Ruby.Syntax
|
module Language.Ruby.Syntax
|
||||||
( assignment
|
( assignment
|
||||||
, Syntax
|
, Syntax
|
||||||
, Syntax'
|
|
||||||
, Grammar
|
, Grammar
|
||||||
, Error
|
, Error
|
||||||
) where
|
) where
|
||||||
@ -23,8 +22,7 @@ import Prologue hiding (for, get, Location, state, unless)
|
|||||||
import Term
|
import Term
|
||||||
|
|
||||||
-- | The type of Ruby syntax.
|
-- | The type of Ruby syntax.
|
||||||
type Syntax = Union Syntax'
|
type Syntax =
|
||||||
type Syntax' =
|
|
||||||
'[Comment.Comment
|
'[Comment.Comment
|
||||||
, Declaration.Class
|
, Declaration.Class
|
||||||
, Declaration.Method
|
, Declaration.Method
|
||||||
@ -58,30 +56,30 @@ type Error = Assignment.Error Grammar
|
|||||||
|
|
||||||
|
|
||||||
-- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax.
|
-- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax.
|
||||||
assignment :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
assignment :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
assignment = makeTerm <$> symbol Program <*> children (many declaration)
|
assignment = makeTerm <$> symbol Program <*> children (many declaration)
|
||||||
|
|
||||||
declaration :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
declaration :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
declaration = handleError $ comment <|> class' <|> method
|
declaration = handleError $ comment <|> class' <|> method
|
||||||
|
|
||||||
class' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
class' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
class' = makeTerm <$> symbol Class <*> children (Declaration.Class <$> (constant <|> scopeResolution) <*> (superclass <|> pure []) <*> many declaration)
|
class' = makeTerm <$> symbol Class <*> children (Declaration.Class <$> (constant <|> scopeResolution) <*> (superclass <|> pure []) <*> many declaration)
|
||||||
where superclass = pure <$ symbol Superclass <*> children constant
|
where superclass = pure <$ symbol Superclass <*> children constant
|
||||||
scopeResolution = symbol ScopeResolution *> children (constant <|> identifier)
|
scopeResolution = symbol ScopeResolution *> children (constant <|> identifier)
|
||||||
|
|
||||||
constant :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
constant :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
constant = makeTerm <$> symbol Constant <*> (Syntax.Identifier <$> source)
|
constant = makeTerm <$> symbol Constant <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
identifier :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
identifier :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
method :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
method :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> identifier <*> pure [] <*> statements)
|
method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> identifier <*> pure [] <*> statements)
|
||||||
|
|
||||||
statements :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
statements :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
statements = makeTerm <$> location <*> many statement
|
statements = makeTerm <$> location <*> many statement
|
||||||
|
|
||||||
statement :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
statement :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
statement = handleError
|
statement = handleError
|
||||||
$ exit Statement.Return Return
|
$ exit Statement.Return Return
|
||||||
<|> exit Statement.Yield Yield
|
<|> exit Statement.Yield Yield
|
||||||
@ -96,36 +94,36 @@ statement = handleError
|
|||||||
<|> assignment'
|
<|> assignment'
|
||||||
where exit construct sym = makeTerm <$> symbol sym <*> children ((construct .) . fromMaybe <$> emptyTerm <*> optional (symbol ArgumentList *> children statement))
|
where exit construct sym = makeTerm <$> symbol sym <*> children ((construct .) . fromMaybe <$> emptyTerm <*> optional (symbol ArgumentList *> children statement))
|
||||||
|
|
||||||
lvalue :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
lvalue :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
lvalue = identifier
|
lvalue = identifier
|
||||||
|
|
||||||
expression :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
expression :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
expression = identifier <|> statement
|
expression = identifier <|> statement
|
||||||
|
|
||||||
comment :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
comment :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||||
|
|
||||||
if' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
if' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
if' = ifElsif If
|
if' = ifElsif If
|
||||||
<|> makeTerm <$> symbol IfModifier <*> children (flip Statement.If <$> statement <*> statement <*> (makeTerm <$> location <*> pure Syntax.Empty))
|
<|> makeTerm <$> symbol IfModifier <*> children (flip Statement.If <$> statement <*> statement <*> (makeTerm <$> location <*> pure Syntax.Empty))
|
||||||
where ifElsif s = makeTerm <$> symbol s <*> children (Statement.If <$> statement <*> statements <*> (fromMaybe <$> emptyTerm <*> optional (ifElsif Elsif <|> makeTerm <$> symbol Else <*> children (many statement))))
|
where ifElsif s = makeTerm <$> symbol s <*> children (Statement.If <$> statement <*> statements <*> (fromMaybe <$> emptyTerm <*> optional (ifElsif Elsif <|> makeTerm <$> symbol Else <*> children (many statement))))
|
||||||
|
|
||||||
unless :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
unless :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
unless = makeTerm <$> symbol Unless <*> children (Statement.If <$> invert statement <*> statements <*> (fromMaybe <$> emptyTerm <*> optional (makeTerm <$> symbol Else <*> children (many statement))))
|
unless = makeTerm <$> symbol Unless <*> children (Statement.If <$> invert statement <*> statements <*> (fromMaybe <$> emptyTerm <*> optional (makeTerm <$> symbol Else <*> children (many statement))))
|
||||||
<|> makeTerm <$> symbol UnlessModifier <*> children (flip Statement.If <$> statement <*> invert statement <*> (makeTerm <$> location <*> pure Syntax.Empty))
|
<|> makeTerm <$> symbol UnlessModifier <*> children (flip Statement.If <$> statement <*> invert statement <*> (makeTerm <$> location <*> pure Syntax.Empty))
|
||||||
|
|
||||||
while :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
while :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
while = makeTerm <$> symbol While <*> children (Statement.While <$> statement <*> statements)
|
while = makeTerm <$> symbol While <*> children (Statement.While <$> statement <*> statements)
|
||||||
<|> makeTerm <$> symbol WhileModifier <*> children (flip Statement.While <$> statement <*> statement)
|
<|> makeTerm <$> symbol WhileModifier <*> children (flip Statement.While <$> statement <*> statement)
|
||||||
|
|
||||||
until :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
until :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
until = makeTerm <$> symbol Until <*> children (Statement.While <$> invert statement <*> statements)
|
until = makeTerm <$> symbol Until <*> children (Statement.While <$> invert statement <*> statements)
|
||||||
<|> makeTerm <$> symbol UntilModifier <*> children (flip Statement.While <$> statement <*> invert statement)
|
<|> makeTerm <$> symbol UntilModifier <*> children (flip Statement.While <$> statement <*> invert statement)
|
||||||
|
|
||||||
for :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
for :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
for = makeTerm <$> symbol For <*> children (Statement.ForEach <$> identifier <*> statement <*> statements)
|
for = makeTerm <$> symbol For <*> children (Statement.ForEach <$> identifier <*> statement <*> statements)
|
||||||
|
|
||||||
assignment' :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
assignment' :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
assignment'
|
assignment'
|
||||||
= makeTerm <$> symbol Assignment <*> children (Statement.Assignment <$> lvalue <*> expression)
|
= makeTerm <$> symbol Assignment <*> children (Statement.Assignment <$> lvalue <*> expression)
|
||||||
<|> makeTerm <$> symbol OperatorAssignment <*> children (lvalue >>= \ var -> Statement.Assignment var <$>
|
<|> makeTerm <$> symbol OperatorAssignment <*> children (lvalue >>= \ var -> Statement.Assignment var <$>
|
||||||
@ -143,7 +141,7 @@ assignment'
|
|||||||
<|> makeTerm <$> symbol AnonLAngleLAngleEqual <*> (Expression.LShift var <$> expression)
|
<|> makeTerm <$> symbol AnonLAngleLAngleEqual <*> (Expression.LShift var <$> expression)
|
||||||
<|> makeTerm <$> symbol AnonCaretEqual <*> (Expression.BXOr var <$> expression)))
|
<|> makeTerm <$> symbol AnonCaretEqual <*> (Expression.BXOr var <$> expression)))
|
||||||
|
|
||||||
literal :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
literal :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
literal = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
literal = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
||||||
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
||||||
<|> makeTerm <$> symbol Grammar.Integer <*> (Literal.Integer <$> source)
|
<|> makeTerm <$> symbol Grammar.Integer <*> (Literal.Integer <$> source)
|
||||||
@ -156,10 +154,10 @@ invert term = makeTerm <$> location <*> fmap Expression.Not term
|
|||||||
makeTerm :: (InUnion fs f, HasCallStack) => a -> f (Term (Union fs) a) -> (Term (Union fs) a)
|
makeTerm :: (InUnion fs f, HasCallStack) => a -> f (Term (Union fs) a) -> (Term (Union fs) a)
|
||||||
makeTerm a f = cofree $ a :< inj f
|
makeTerm a f = cofree $ a :< inj f
|
||||||
|
|
||||||
emptyTerm :: HasCallStack => Assignment Grammar (Term Syntax (Record Location))
|
emptyTerm :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
||||||
|
|
||||||
handleError :: HasCallStack => Assignment Grammar (Term Syntax (Record Location)) -> Assignment Grammar (Term Syntax (Record Location))
|
handleError :: HasCallStack => Assignment Grammar (Term (Union Syntax) (Record Location)) -> Assignment Grammar (Term (Union Syntax) (Record Location))
|
||||||
handleError = flip catchError $ \ error -> case errorCause error of
|
handleError = flip catchError $ \ error -> case errorCause error of
|
||||||
UnexpectedEndOfInput _ -> throwError error
|
UnexpectedEndOfInput _ -> throwError error
|
||||||
_ -> makeTerm <$> location <*> (Syntax.Error error <$ source)
|
_ -> makeTerm <$> location <*> (Syntax.Error error <$ source)
|
||||||
|
@ -54,10 +54,10 @@ parserForLanguage (Just language) = case language of
|
|||||||
TypeScript -> TreeSitterParser TypeScript tree_sitter_typescript
|
TypeScript -> TreeSitterParser TypeScript tree_sitter_typescript
|
||||||
_ -> LineByLineParser
|
_ -> LineByLineParser
|
||||||
|
|
||||||
rubyParser :: Parser (Term (Union Ruby.Syntax') (Record Location))
|
rubyParser :: Parser (Term (Union Ruby.Syntax) (Record Location))
|
||||||
rubyParser = AssignmentParser (ASTParser tree_sitter_ruby) Ruby.assignment
|
rubyParser = AssignmentParser (ASTParser tree_sitter_ruby) Ruby.assignment
|
||||||
|
|
||||||
pythonParser :: Parser (Term (Union Python.Syntax') (Record Location))
|
pythonParser :: Parser (Term (Union Python.Syntax) (Record Location))
|
||||||
pythonParser = AssignmentParser (ASTParser tree_sitter_python) Python.assignment
|
pythonParser = AssignmentParser (ASTParser tree_sitter_python) Python.assignment
|
||||||
|
|
||||||
runParser :: Parser term -> Source -> IO term
|
runParser :: Parser term -> Source -> IO term
|
||||||
|
Loading…
Reference in New Issue
Block a user