mirror of
https://github.com/github/semantic.git
synced 2024-12-01 00:33:59 +03:00
Merge pull request #1139 from github/python-expression-statements
Python expression statements
This commit is contained in:
commit
ef442e9a14
@ -55,8 +55,16 @@ instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
|||||||
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
|
-- | Comprehension (e.g. ((a for b in c) in Python)
|
||||||
|
data Comprehension a = Comprehension { comprehensionMap :: !a, comprehensionBindings :: ![a], comprehensionContext :: !a }
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||||
|
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
-- | Import declarations.
|
-- | Import declarations.
|
||||||
data Import a = Import { importContent :: ByteString }
|
data Import a = Import { importContent :: ![a] }
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Import where liftEq = genericLiftEq
|
instance Eq1 Import where liftEq = genericLiftEq
|
||||||
|
@ -8,21 +8,34 @@ import GHC.Generics
|
|||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
|
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
|
||||||
data Call a = Call { callFunction :: a, callParams :: [a] }
|
data Call a = Call { callFunction :: !a, callParams :: ![a] }
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Call where liftEq = genericLiftEq
|
instance Eq1 Call where liftEq = genericLiftEq
|
||||||
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
|
data Comparison a
|
||||||
|
= LessThan !a !a
|
||||||
|
| LessThanEqual !a !a
|
||||||
|
| GreaterThan !a !a
|
||||||
|
| GreaterThanEqual !a !a
|
||||||
|
| Equal !a !a
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 Comparison where liftEq = genericLiftEq
|
||||||
|
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
-- | Binary arithmetic operators.
|
-- | Binary arithmetic operators.
|
||||||
data Arithmetic a
|
data Arithmetic a
|
||||||
= Plus a a
|
= Plus !a !a
|
||||||
| Minus a a
|
| Minus !a !a
|
||||||
| Times a a
|
| Times !a !a
|
||||||
| DividedBy a a
|
| DividedBy !a !a
|
||||||
| Modulo a a
|
| Modulo !a !a
|
||||||
| Power a a
|
| Power !a !a
|
||||||
| Negate a
|
| Negate !a
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Arithmetic where liftEq = genericLiftEq
|
instance Eq1 Arithmetic where liftEq = genericLiftEq
|
||||||
@ -30,9 +43,9 @@ instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
-- | Boolean operators.
|
-- | Boolean operators.
|
||||||
data Boolean a
|
data Boolean a
|
||||||
= Or a a
|
= Or !a !a
|
||||||
| And a a
|
| And !a !a
|
||||||
| Not a
|
| Not !a
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Boolean where liftEq = genericLiftEq
|
instance Eq1 Boolean where liftEq = genericLiftEq
|
||||||
@ -40,13 +53,38 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
-- | Bitwise operators.
|
-- | Bitwise operators.
|
||||||
data Bitwise a
|
data Bitwise a
|
||||||
= BOr a a
|
= BOr !a !a
|
||||||
| BAnd a a
|
| BAnd !a !a
|
||||||
| BXOr a a
|
| BXOr !a !a
|
||||||
| LShift a a
|
| LShift !a !a
|
||||||
| RShift a a
|
| RShift !a !a
|
||||||
| Complement a
|
| Complement a
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Bitwise where liftEq = genericLiftEq
|
instance Eq1 Bitwise where liftEq = genericLiftEq
|
||||||
instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- | Member Access (e.g. a.b)
|
||||||
|
data MemberAccess a
|
||||||
|
= MemberAccess !a !a
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 MemberAccess where liftEq = genericLiftEq
|
||||||
|
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- | Subscript (e.g a[1])
|
||||||
|
data Subscript a
|
||||||
|
= Subscript !a ![a]
|
||||||
|
| Member !a !a
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||||
|
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
|
||||||
|
data ScopeResolution a
|
||||||
|
= ScopeResolution ![a]
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||||
|
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
@ -4,10 +4,9 @@ module Data.Syntax.Literal where
|
|||||||
import Data.Align.Generic
|
import Data.Align.Generic
|
||||||
import Data.Functor.Classes.Eq.Generic
|
import Data.Functor.Classes.Eq.Generic
|
||||||
import Data.Functor.Classes.Show.Generic
|
import Data.Functor.Classes.Show.Generic
|
||||||
import Data.Syntax.Comment
|
|
||||||
import Data.Functor.Union
|
import Data.Functor.Union
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
import Prologue
|
import Prologue hiding (Set)
|
||||||
|
|
||||||
-- Boolean
|
-- Boolean
|
||||||
|
|
||||||
@ -45,8 +44,7 @@ instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
|
|||||||
instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
|
data Range a = Range { rangeStart :: !a, rangeEnd :: !a }
|
||||||
data Range a = Range { rangeStart :: a, rangeEnd :: a }
|
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Range where liftEq = genericLiftEq
|
instance Eq1 Range where liftEq = genericLiftEq
|
||||||
@ -97,14 +95,14 @@ instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
-- Collections
|
-- Collections
|
||||||
|
|
||||||
newtype Array a = Array { arrayElements :: [Union '[Identity, Comment] a] }
|
newtype Array a = Array { arrayElements :: [a] }
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Array where liftEq = genericLiftEq
|
instance Eq1 Array where liftEq = genericLiftEq
|
||||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
newtype Hash a = Hash { hashElements :: [Union '[KeyValue, Comment] a] }
|
newtype Hash a = Hash { hashElements :: [a] }
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Hash where liftEq = genericLiftEq
|
instance Eq1 Hash where liftEq = genericLiftEq
|
||||||
@ -117,12 +115,21 @@ data KeyValue a = KeyValue { key :: !a, value :: !a }
|
|||||||
instance Eq1 KeyValue where liftEq = genericLiftEq
|
instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||||
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
data Tuple a = Tuple { tupleContents :: ![a]}
|
|
||||||
|
newtype Tuple a = Tuple { tupleContents :: [a]}
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
|
newtype Set a = Set { setElements :: [a] }
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 Set where liftEq = genericLiftEq
|
||||||
|
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
-- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”?
|
-- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”?
|
||||||
-- TODO: Function literals (lambdas, procs, anonymous functions, what have you).
|
-- TODO: Function literals (lambdas, procs, anonymous functions, what have you).
|
||||||
-- TODO: Regexp literals.
|
-- TODO: Regexp literals.
|
||||||
|
|
||||||
|
@ -26,16 +26,26 @@ import Term
|
|||||||
type Syntax = Union Syntax'
|
type Syntax = Union Syntax'
|
||||||
type Syntax' =
|
type Syntax' =
|
||||||
'[ Comment.Comment
|
'[ Comment.Comment
|
||||||
|
, Declaration.Comprehension
|
||||||
|
, Declaration.Function
|
||||||
, Declaration.Import
|
, Declaration.Import
|
||||||
, Declaration.Variable
|
, Declaration.Variable
|
||||||
, Expression.Arithmetic
|
, Expression.Arithmetic
|
||||||
, Expression.Boolean
|
, Expression.Boolean
|
||||||
, Expression.Bitwise
|
, Expression.Bitwise
|
||||||
, Expression.Call
|
, Expression.Call
|
||||||
|
, Expression.Comparison
|
||||||
|
, Expression.ScopeResolution
|
||||||
|
, Expression.MemberAccess
|
||||||
|
, Expression.Subscript
|
||||||
|
, Literal.Array
|
||||||
, Literal.Boolean
|
, Literal.Boolean
|
||||||
, Literal.Float
|
, Literal.Float
|
||||||
|
, Literal.Hash
|
||||||
, Literal.Integer
|
, Literal.Integer
|
||||||
|
, Literal.KeyValue
|
||||||
, Literal.Null
|
, Literal.Null
|
||||||
|
, Literal.Set
|
||||||
, Literal.String
|
, Literal.String
|
||||||
, Literal.TextElement
|
, Literal.TextElement
|
||||||
, Literal.Tuple
|
, Literal.Tuple
|
||||||
@ -44,12 +54,21 @@ type Syntax' =
|
|||||||
, Statement.If
|
, Statement.If
|
||||||
, Statement.Return
|
, Statement.Return
|
||||||
, Statement.Yield
|
, Statement.Yield
|
||||||
|
, Language.Python.Syntax.Ellipsis
|
||||||
, Syntax.Empty
|
, Syntax.Empty
|
||||||
, Syntax.Error [Error Grammar]
|
, Syntax.Error [Error Grammar]
|
||||||
, Syntax.Identifier
|
, Syntax.Identifier
|
||||||
, []
|
, []
|
||||||
]
|
]
|
||||||
|
|
||||||
|
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||||
|
data Ellipsis a = Ellipsis
|
||||||
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
|
instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||||
|
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
|
||||||
data Redirect a = Redirect !a !a
|
data Redirect a = Redirect !a !a
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||||
|
|
||||||
@ -60,28 +79,75 @@ instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
|||||||
assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
assignment = makeTerm <$> symbol Module <*> children (many declaration)
|
assignment = makeTerm <$> symbol Module <*> children (many declaration)
|
||||||
|
|
||||||
|
|
||||||
declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
declaration = comment <|> literal <|> statement <|> import' <|> importFrom
|
declaration = handleError $ comment <|> statement <|> expression
|
||||||
|
|
||||||
|
|
||||||
statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
statement = expressionStatement
|
statement = assertStatement
|
||||||
<|> ifStatement
|
|
||||||
<|> returnStatement
|
|
||||||
<|> identifier
|
|
||||||
<|> assignment'
|
<|> assignment'
|
||||||
<|> augmentedAssignment
|
<|> augmentedAssignment
|
||||||
<|> printStatement
|
<|> expressionStatement
|
||||||
<|> assertStatement
|
|
||||||
<|> globalStatement
|
<|> globalStatement
|
||||||
|
<|> ifStatement
|
||||||
|
<|> identifier
|
||||||
|
<|> import'
|
||||||
|
<|> importFrom
|
||||||
|
<|> printStatement
|
||||||
|
<|> returnStatement
|
||||||
|
|
||||||
|
expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
expressionStatement = symbol ExpressionStatement *> children expression
|
||||||
|
|
||||||
|
expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
expression = await
|
||||||
|
<|> binaryOperator
|
||||||
|
<|> booleanOperator
|
||||||
|
<|> call
|
||||||
|
<|> comparisonOperator
|
||||||
|
<|> comprehension
|
||||||
|
<|> conditionalExpression
|
||||||
|
<|> dottedName
|
||||||
|
<|> ellipsis
|
||||||
|
<|> lambda
|
||||||
|
<|> keywordIdentifier
|
||||||
|
<|> literal
|
||||||
|
<|> memberAccess
|
||||||
|
<|> notOperator
|
||||||
|
<|> subscript
|
||||||
|
<|> statement
|
||||||
|
<|> tuple
|
||||||
|
<|> unaryOperator
|
||||||
|
|
||||||
|
dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression)
|
||||||
|
|
||||||
|
ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
ellipsis = makeTerm <$> symbol Grammar.Ellipsis <*> (Language.Python.Syntax.Ellipsis <$ source)
|
||||||
|
|
||||||
|
comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression >>= \ lexpression -> makeComparison loc lexpression)
|
||||||
|
where
|
||||||
|
makeComparison loc lexpression = makeTerm loc <$ symbol AnonLAngle <*> (Expression.LessThan lexpression <$> expression)
|
||||||
|
<|> makeTerm loc <$ symbol AnonLAngleEqual <*> (Expression.LessThanEqual lexpression <$> expression)
|
||||||
|
<|> makeTerm loc <$ symbol AnonRAngle <*> (Expression.GreaterThan lexpression <$> expression)
|
||||||
|
<|> makeTerm loc <$ symbol AnonRAngleEqual <*> (Expression.GreaterThanEqual lexpression <$> expression)
|
||||||
|
<|> makeTerm loc <$ symbol AnonEqualEqual <*> (Expression.Equal lexpression <$> expression)
|
||||||
|
<|> makeTerm loc <$ symbol AnonBangEqual <*> (Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression)))
|
||||||
|
<|> makeTerm loc <$ symbol AnonNot <*> (Expression.Not <$> (makeTerm <$> location <*> (Expression.Member lexpression <$> expression)))
|
||||||
|
<|> makeTerm loc <$ symbol AnonIn <*> (Expression.Member lexpression <$> expression)
|
||||||
|
-- source is used here to push the cursor to the next node to enable matching against `AnonNot`
|
||||||
|
<|> symbol AnonIs *> source *> (symbol AnonNot *> (makeTerm loc <$> Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression)))
|
||||||
|
<|> (makeTerm loc <$> Expression.Equal lexpression <$> expression))
|
||||||
|
|
||||||
|
notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression)
|
||||||
|
|
||||||
|
keywordIdentifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
keywordIdentifier = makeTerm <$> symbol KeywordIdentifier <*> children (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression))
|
tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression))
|
||||||
|
|
||||||
expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
|
||||||
expression = identifier <|> statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal
|
|
||||||
|
|
||||||
-- TODO: Consider flattening single element lists
|
-- TODO: Consider flattening single element lists
|
||||||
expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
expressionList = makeTerm <$> symbol ExpressionList <*> children (many expression)
|
expressionList = makeTerm <$> symbol ExpressionList <*> children (many expression)
|
||||||
@ -145,7 +211,17 @@ identifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
|||||||
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
literal :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
literal :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString
|
literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary <|> set
|
||||||
|
|
||||||
|
set :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> many expression)
|
||||||
|
|
||||||
|
dictionary :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
dictionary = makeTerm <$> symbol Dictionary <*> children (Literal.Hash <$> many pairs)
|
||||||
|
where pairs = makeTerm <$> symbol Pair <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||||
|
|
||||||
|
list' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
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 (Node Grammar) (Term Syntax Location)
|
string :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
@ -163,17 +239,13 @@ integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
|||||||
comment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
comment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||||
|
|
||||||
expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
|
||||||
expressionStatement = symbol ExpressionStatement *> children (statement <|> literal <|> expression)
|
|
||||||
|
|
||||||
|
|
||||||
-- TODO Possibly match against children for dotted name and identifiers
|
-- TODO Possibly match against children for dotted name and identifiers
|
||||||
import' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
import' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
import' = makeTerm <$> symbol ImportStatement <*> (Declaration.Import <$> source)
|
import' = makeTerm <$> symbol ImportStatement <*> children (Declaration.Import <$> many expression)
|
||||||
|
|
||||||
-- TODO Possibly match against children nodes
|
-- TODO Possibly match against children nodes
|
||||||
importFrom :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
importFrom :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
importFrom = makeTerm <$> symbol ImportFromStatement <*> (Declaration.Import <$> source)
|
importFrom = makeTerm <$> symbol ImportFromStatement <*> children (Declaration.Import <$> many expression)
|
||||||
|
|
||||||
assertStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
assertStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax 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)
|
||||||
@ -192,18 +264,29 @@ printStatement = do
|
|||||||
globalStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
globalStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax 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 (Node Grammar) (Term Syntax Location)
|
||||||
|
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> many expression)
|
||||||
|
|
||||||
returnStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
returnStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expressionList)
|
returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expressionList)
|
||||||
|
|
||||||
|
|
||||||
ifStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
ifStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> condition <*> 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 <$> condition <*> statement)
|
elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> expression <*> statement)
|
||||||
condition = boolean
|
|
||||||
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 (Node Grammar) (Term Syntax Location)
|
||||||
|
memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> expression <*> expression)
|
||||||
|
|
||||||
|
subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression)
|
||||||
|
|
||||||
|
call :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (symbol ArgumentList *> children (many expression)
|
||||||
|
<|> some comprehension))
|
||||||
|
|
||||||
boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
||||||
@ -212,8 +295,33 @@ boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
|
|||||||
none :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
none :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
none = makeTerm <$> symbol None <*> (Literal.Null <$ source)
|
none = makeTerm <$> symbol None <*> (Literal.Null <$ source)
|
||||||
|
|
||||||
|
lambda :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambdaIdentifier <*> lambdaParameters <*> lambdaBody)
|
||||||
|
where lambdaIdentifier = makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source)
|
||||||
|
lambdaParameters = many identifier
|
||||||
|
lambdaBody = expression
|
||||||
|
|
||||||
|
comprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionDeclaration expression)
|
||||||
|
<|> makeTerm <$> symbol ListComprehension <*> children (comprehensionDeclaration expression)
|
||||||
|
<|> makeTerm <$> symbol SetComprehension <*> children (comprehensionDeclaration expression)
|
||||||
|
<|> makeTerm <$> symbol DictionaryComprehension <*> children (comprehensionDeclaration keyValue)
|
||||||
|
where
|
||||||
|
keyValue = makeTerm <$> location <*> (Literal.KeyValue <$> expression <*> expression)
|
||||||
|
comprehensionDeclaration preceeding = Declaration.Comprehension <$> preceeding <* symbol Variables <*> children (many expression) <*> (flip (foldr makeComprehension) <$> many nestedComprehension <*> expression)
|
||||||
|
makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest)
|
||||||
|
nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression))
|
||||||
|
|
||||||
|
conditionalExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
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 Syntax' f => a -> f (Term Syntax a) -> Term Syntax a
|
||||||
makeTerm a f = cofree (a :< inj f)
|
makeTerm a f = cofree (a :< inj f)
|
||||||
|
|
||||||
emptyTerm :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
emptyTerm :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location)
|
||||||
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
emptyTerm = makeTerm <$> location <*> pure Syntax.Empty
|
||||||
|
|
||||||
|
handleError :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -> Assignment (Node Grammar) (Term Syntax Location)
|
||||||
|
handleError = flip catchError $ \ error -> case errorCause error of
|
||||||
|
UnexpectedEndOfInput _ -> throwError error
|
||||||
|
_ -> makeTerm <$> location <*> (Syntax.Error [error] <$ source)
|
||||||
|
Loading…
Reference in New Issue
Block a user