mirror of
https://github.com/github/semantic.git
synced 2024-11-24 17:04:47 +03:00
Helpers at the bottom of assignment file, use emptyStatements and manyStatements
This commit is contained in:
parent
f7b6ba3734
commit
40ea6d0767
@ -113,7 +113,7 @@ assignment :: Assignment
|
||||
assignment = handleError program <|> parseError
|
||||
|
||||
program :: Assignment
|
||||
program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program . fromList <$> manyTerm expression)
|
||||
program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyStatements expression)
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
@ -360,7 +360,7 @@ defaultExpressionCase :: Assignment
|
||||
defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ source <*> (expressions <|> emptyTerm))
|
||||
|
||||
callExpression :: Assignment
|
||||
callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> expression <*> manyTerm expression <*> emptyTerm)
|
||||
callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call [] <$> expression <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
expressionCase :: Assignment
|
||||
expressionCase = makeTerm <$> symbol ExpressionCase <*> (Statement.Pattern <$> children expressions <*> expressions)
|
||||
@ -606,11 +606,14 @@ manyTermsTill step end = manyTill (step <|> comment) end
|
||||
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTerm = many . term
|
||||
|
||||
-- | Match a term and contextualize any comments preceeding or proceeding the term.
|
||||
term :: Assignment -> Assignment
|
||||
term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
|
||||
manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
manyStatements expr = fromList <$> (manyTerm expr)
|
||||
|
||||
emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
emptyStatements = pure (fromList [])
|
||||
|
||||
-- | Match a term and contextualize any comments preceeding or proceeding the term.
|
||||
term :: Assignment -> Assignment
|
||||
term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
|
||||
|
||||
{-# ANN module ("HLint: ignore Eta reduce" :: String) #-}
|
||||
|
@ -128,37 +128,16 @@ type Syntax = '[
|
||||
, Syntax.UseClause
|
||||
, Syntax.VariableName
|
||||
, Type.Annotation
|
||||
, [] ]
|
||||
, []
|
||||
]
|
||||
|
||||
type Term = Term.Term (Sum Syntax) (Record Location)
|
||||
type Assignment = Assignment.Assignment [] Grammar Term
|
||||
|
||||
append :: a -> [a] -> [a]
|
||||
append x xs = xs ++ [x]
|
||||
|
||||
bookend :: a -> [a] -> a -> [a]
|
||||
bookend head list last = head : append last list
|
||||
|
||||
-- | Assignment from AST in PHP's grammar onto a program in PHP's syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term)
|
||||
|
||||
commentedTerm :: Assignment -> Assignment
|
||||
commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm)
|
||||
|
||||
-- | 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 = many . commentedTerm
|
||||
|
||||
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
someTerm = fmap NonEmpty.toList . someTerm'
|
||||
|
||||
someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term)
|
||||
someTerm' = NonEmpty.some1 . commentedTerm
|
||||
|
||||
text :: Assignment
|
||||
text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source)
|
||||
|
||||
@ -763,6 +742,31 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
string :: Assignment
|
||||
string = makeTerm <$> (symbol Grammar.String <|> symbol Heredoc) <*> (Literal.TextElement <$> source)
|
||||
|
||||
|
||||
-- Helpers
|
||||
|
||||
append :: a -> [a] -> [a]
|
||||
append x xs = xs ++ [x]
|
||||
|
||||
bookend :: a -> [a] -> a -> [a]
|
||||
bookend head list last = head : append last list
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term)
|
||||
|
||||
commentedTerm :: Assignment -> Assignment
|
||||
commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm)
|
||||
|
||||
-- | 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 = many . commentedTerm
|
||||
|
||||
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
someTerm = fmap NonEmpty.toList . someTerm'
|
||||
|
||||
someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term)
|
||||
someTerm' = NonEmpty.some1 . commentedTerm
|
||||
|
||||
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
||||
infixTerm :: Assignment
|
||||
-> Assignment
|
||||
|
@ -91,17 +91,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
||||
|
||||
-- | Assignment from AST in Python's grammar onto a program in Python's syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . fromList <$> manyTerm expression) <|> 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))
|
||||
|
||||
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program <$> manyStatements expression) <|> parseError
|
||||
|
||||
expression :: Assignment
|
||||
expression = handleError (choice expressionChoices)
|
||||
@ -484,6 +474,19 @@ ifClause = symbol IfClause *> children expressions
|
||||
conditionalExpression :: Assignment
|
||||
conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (flip Statement.If <$> term expression <*> term expression <*> expressions)
|
||||
|
||||
|
||||
-- Helpers
|
||||
-- | 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))
|
||||
|
||||
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
|
||||
|
||||
-- | Match a left-associated infix chain of terms, optionally followed by comments. Like 'chainl1' but assigning comment nodes automatically.
|
||||
chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> Term) -> Assignment
|
||||
chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op
|
||||
@ -492,6 +495,9 @@ chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty)
|
||||
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTermsTill step end = manyTill (step <|> comment) end
|
||||
|
||||
manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
manyStatements expr = fromList <$> (manyTerm expr)
|
||||
|
||||
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
||||
infixTerm :: HasCallStack
|
||||
=> Assignment
|
||||
|
@ -482,7 +482,7 @@ emptyStatement :: Assignment
|
||||
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)
|
||||
|
||||
|
||||
-- Helper functions
|
||||
-- Helpers
|
||||
|
||||
invert :: Assignment -> Assignment
|
||||
invert term = makeTerm <$> location <*> fmap Expression.Not term
|
||||
|
@ -177,20 +177,7 @@ type Assignment = Assignment.Assignment [] Grammar Term
|
||||
|
||||
-- | Assignment from AST in TypeScript’s grammar onto a program in TypeScript’s syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> manyTerm 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))
|
||||
|
||||
manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
manyStatements expr = fromList <$> (manyTerm expr)
|
||||
|
||||
emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
emptyStatements = pure (fromList [])
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyStatements statement) <|> parseError
|
||||
|
||||
expression :: Assignment
|
||||
expression = handleError everything
|
||||
@ -866,6 +853,22 @@ binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm
|
||||
])
|
||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
|
||||
-- Helpers
|
||||
|
||||
-- | 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))
|
||||
|
||||
manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
manyStatements expr = fromList <$> (manyTerm expr)
|
||||
|
||||
emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
emptyStatements = pure (fromList [])
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
|
||||
emptyStatement :: Assignment
|
||||
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user