mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Basic use of Statements in assignment and eval
This commit is contained in:
parent
85257f5622
commit
c0ca3df3d1
@ -22,6 +22,7 @@ import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import Data.Sum
|
||||
import GHC.Exts (fromList)
|
||||
import qualified Data.Term as Term
|
||||
import Prologue
|
||||
|
||||
@ -91,6 +92,7 @@ type Syntax =
|
||||
, Syntax.Empty
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Syntax.Statements
|
||||
, Type.Annotation
|
||||
, Type.Array
|
||||
, Type.Function
|
||||
@ -111,7 +113,7 @@ assignment :: Assignment
|
||||
assignment = handleError program <|> parseError
|
||||
|
||||
program :: Assignment
|
||||
program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyTerm expression)
|
||||
program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program . fromList <$> manyTerm expression)
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
|
@ -9,6 +9,7 @@ import Data.Aeson
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import Data.Syntax (Statements)
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
@ -299,7 +300,7 @@ instance ToJSONFields1 Field
|
||||
instance Evaluatable Field
|
||||
|
||||
|
||||
data Package a = Package { packageName :: !a, packageContents :: ![a] }
|
||||
data Package a = Package { packageName :: !a, packageContents :: Statements a }
|
||||
deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
|
@ -23,6 +23,7 @@ import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import qualified Language.PHP.Syntax as Syntax
|
||||
import GHC.Exts (fromList)
|
||||
import Prologue
|
||||
|
||||
type Syntax = '[
|
||||
@ -140,7 +141,7 @@ 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 <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError
|
||||
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)
|
||||
|
@ -25,6 +25,7 @@ import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import GHC.Exts (fromList)
|
||||
import Prologue
|
||||
|
||||
|
||||
@ -90,7 +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 <$> manyTerm expression) <|> parseError
|
||||
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]
|
||||
|
@ -23,6 +23,7 @@ import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Term as Term
|
||||
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||
import GHC.Exts (fromList)
|
||||
import Prologue hiding (for)
|
||||
|
||||
-- | The type of Ruby syntax.
|
||||
@ -77,6 +78,7 @@ type Syntax = '[
|
||||
, Syntax.Error
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Syntax.Statements
|
||||
, Ruby.Syntax.Class
|
||||
, Ruby.Syntax.Load
|
||||
, Ruby.Syntax.LowPrecedenceBoolean
|
||||
@ -92,7 +94,7 @@ type Assignment = Assignment' Term
|
||||
|
||||
-- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> many expression) <|> parseError
|
||||
assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> many expression) <|> parseError
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
@ -230,7 +232,7 @@ singletonClass :: Assignment
|
||||
singletonClass = makeTerm <$> symbol SingletonClass <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> pure Nothing <*> expressions)
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression)
|
||||
module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> manyStatements expression)
|
||||
|
||||
scopeResolution :: Assignment
|
||||
scopeResolution = makeTerm <$> symbol ScopeResolution <*> children (Expression.ScopeResolution <$> many expression)
|
||||
@ -494,6 +496,9 @@ term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> som
|
||||
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 <$> (many expr)
|
||||
|
||||
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
||||
infixTerm :: HasCallStack
|
||||
=> Assignment
|
||||
|
@ -8,6 +8,7 @@ import Data.Abstract.Path
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import Data.Syntax (Statements)
|
||||
import Diffing.Algorithm
|
||||
import Prelude hiding (fail)
|
||||
import Prologue
|
||||
@ -146,7 +147,7 @@ instance Evaluatable Class where
|
||||
Rval <$> letrec' name (\addr ->
|
||||
subtermValue classBody <* makeNamespace name addr super)
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
|
@ -22,6 +22,7 @@ import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import Language.TypeScript.Grammar as Grammar
|
||||
import qualified Language.TypeScript.Syntax as TypeScript.Syntax
|
||||
import GHC.Exts (fromList)
|
||||
import Prologue
|
||||
|
||||
-- | The type of TypeScript syntax.
|
||||
@ -89,6 +90,7 @@ type Syntax = '[
|
||||
, Syntax.Error
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Syntax.Statements
|
||||
, Syntax.Context
|
||||
, Type.Readonly
|
||||
, Type.TypeParameters
|
||||
@ -175,12 +177,15 @@ 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 <$> manyTerm statement) <|> parseError
|
||||
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)
|
||||
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
|
||||
@ -763,11 +768,11 @@ internalModule :: Assignment
|
||||
internalModule = makeTerm <$> symbol Grammar.InternalModule <*> children (TypeScript.Syntax.InternalModule <$> term (string <|> identifier <|> nestedIdentifier) <*> statements)
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure []))
|
||||
module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure (fromList [])))
|
||||
|
||||
|
||||
statements :: Assignment.Assignment [] Grammar [Term]
|
||||
statements = symbol StatementBlock *> children (manyTerm statement)
|
||||
statements :: Assignment.Assignment [] Grammar (Syntax.Statements Term)
|
||||
statements = symbol StatementBlock *> children (manyStatements statement)
|
||||
|
||||
arrowFunction :: Assignment
|
||||
arrowFunction = makeArrowFun <$> symbol ArrowFunction <*> children ((,,) <$> emptyTerm <*> (((\a b c -> (a, [b], c)) <$> emptyTerm <*> term identifier <*> emptyTerm) <|> callSignatureParts) <*> term (expression <|> statementBlock))
|
||||
|
@ -13,6 +13,7 @@ import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.Map as Map
|
||||
import Data.Semigroup.Reducer (Reducer)
|
||||
import Data.Syntax (Statements)
|
||||
import Diffing.Algorithm
|
||||
import Prelude
|
||||
import Prologue
|
||||
@ -758,7 +759,7 @@ instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Update
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
@ -775,7 +776,7 @@ instance Evaluatable Module where
|
||||
|
||||
|
||||
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: Statements a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 InternalModule where liftEq = genericLiftEq
|
||||
|
Loading…
Reference in New Issue
Block a user