mirror of
https://github.com/github/semantic.git
synced 2024-11-24 00:42:33 +03:00
Mini Ruby
This commit is contained in:
parent
80ee53ed9d
commit
1d751ef79a
@ -5,6 +5,11 @@ module Language.Ruby.Assignment
|
||||
, Syntax
|
||||
, Grammar
|
||||
, Term
|
||||
|
||||
-- Small version of Ruby to enable internal framework development.
|
||||
, miniAssignment
|
||||
, MiniSyntax
|
||||
, MiniTerm
|
||||
) where
|
||||
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
@ -40,6 +45,146 @@ import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||
import Prologue hiding (for)
|
||||
import Proto3.Suite (Named (..), Named1 (..))
|
||||
|
||||
|
||||
-- | Small version of Ruby syntax for testing the code rewriting pipeline.
|
||||
type MiniSyntax = '[
|
||||
Literal.Integer
|
||||
, Comment.Comment
|
||||
, Declaration.Method
|
||||
-- , Declaration.Function
|
||||
-- , Expression.Call
|
||||
, Ruby.Syntax.Send
|
||||
-- , Ruby.Syntax.Load
|
||||
-- , Ruby.Syntax.Require
|
||||
, Statement.Statements
|
||||
, Syntax.Context
|
||||
, Syntax.Empty
|
||||
, Syntax.Error
|
||||
, Syntax.Identifier
|
||||
, []
|
||||
]
|
||||
|
||||
type MiniTerm = Term.Term (Sum MiniSyntax) (Record Location)
|
||||
|
||||
miniAssignment :: Assignment MiniTerm
|
||||
miniAssignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> many expression) <|> parseError
|
||||
where
|
||||
expression :: Assignment MiniTerm
|
||||
expression = term . handleError $
|
||||
choice [ number
|
||||
, identifier
|
||||
, method ]
|
||||
-- , methodCall ]
|
||||
|
||||
expressions :: Assignment MiniTerm
|
||||
expressions = makeTerm'' <$> location <*> many expression
|
||||
|
||||
number :: Assignment MiniTerm
|
||||
number = makeTerm <$> symbol Grammar.Integer <*> (Literal.Integer <$> source)
|
||||
|
||||
identifier :: Assignment MiniTerm
|
||||
identifier =
|
||||
vcallOrLocal
|
||||
<|> mk Constant
|
||||
<|> mk InstanceVariable
|
||||
<|> mk ClassVariable
|
||||
<|> mk GlobalVariable
|
||||
<|> mk Operator
|
||||
<|> mk Super
|
||||
<|> mk Setter
|
||||
<|> mk SplatArgument
|
||||
<|> mk HashSplatArgument
|
||||
<|> mk BlockArgument
|
||||
<|> mk Uninterpreted
|
||||
where
|
||||
mk s = makeTerm <$> symbol s <*> (Syntax.Identifier . name <$> source)
|
||||
vcallOrLocal = do
|
||||
(loc, ident, locals) <- identWithLocals
|
||||
let identTerm = makeTerm loc (Syntax.Identifier (name ident))
|
||||
if ident `elem` locals
|
||||
then pure identTerm
|
||||
else pure $ makeTerm loc (Ruby.Syntax.Send Nothing (Just identTerm) [] Nothing)
|
||||
|
||||
method :: Assignment MiniTerm
|
||||
method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method [] <$> emptyTerm <*> methodSelector <*> params <*> expressions')
|
||||
where params = symbol MethodParameters *> children (many parameter) <|> pure []
|
||||
expressions' = makeTerm <$> location <*> many expression
|
||||
|
||||
methodSelector :: Assignment MiniTerm
|
||||
methodSelector = makeTerm <$> symbols <*> (Syntax.Identifier <$> (name <$> source))
|
||||
where
|
||||
symbols = symbol Identifier
|
||||
<|> symbol Constant
|
||||
<|> symbol Operator
|
||||
<|> symbol Setter
|
||||
<|> symbol Super -- TODO(@charliesome): super calls are *not* method calls and need to be assigned into their own syntax terms
|
||||
|
||||
parameter :: Assignment MiniTerm
|
||||
parameter = postContextualize comment (term uncontextualizedParameter)
|
||||
where
|
||||
uncontextualizedParameter =
|
||||
lhsIdent
|
||||
<|> splatParameter
|
||||
<|> hashSplatParameter
|
||||
<|> blockParameter
|
||||
<|> keywordParameter
|
||||
<|> optionalParameter
|
||||
<|> makeTerm <$> symbol DestructuredParameter <*> children (many parameter)
|
||||
-- splat and hash splat arguments can be unnamed. we don't currently
|
||||
-- support unnamed arguments in the term syntax, so the use of emptyTerm
|
||||
-- here is a huge hack. what we should be able to do is return a Nothing
|
||||
-- for the argument name for splats and hash splats. TODO fix me:
|
||||
mkSplat s = symbol s *> children (lhsIdent <|> emptyTerm)
|
||||
splatParameter = mkSplat SplatParameter
|
||||
hashSplatParameter = mkSplat HashSplatParameter
|
||||
blockParameter = symbol BlockParameter *> children lhsIdent
|
||||
-- we don't yet care about default expressions for optional (including
|
||||
-- keyword) parameters, but we need to match on them to prevent errors:
|
||||
keywordParameter = symbol KeywordParameter *> children (lhsIdent <* optional expression)
|
||||
optionalParameter = symbol OptionalParameter *> children (lhsIdent <* expression)
|
||||
|
||||
lhsIdent :: Assignment MiniTerm
|
||||
lhsIdent = do
|
||||
(loc, ident, locals) <- identWithLocals
|
||||
putLocals (ident : locals)
|
||||
pure $ makeTerm loc (Syntax.Identifier (name ident))
|
||||
|
||||
methodCall :: Assignment MiniTerm
|
||||
methodCall = makeTerm' <$> symbol MethodCall <*> children send -- (require <|> load <|> send)
|
||||
where
|
||||
send = inject <$> ((regularCall <|> funcCall <|> scopeCall <|> dotCall) <*> pure Nothing {- optional block -})
|
||||
|
||||
funcCall = Ruby.Syntax.Send Nothing <$> selector <*> args
|
||||
regularCall = symbol Call *> children (Ruby.Syntax.Send <$> (Just <$> expression) <*> selector) <*> args
|
||||
scopeCall = symbol ScopeResolution *> children (Ruby.Syntax.Send <$> (Just <$> expression) <*> selector) <*> args
|
||||
dotCall = symbol Call *> children (Ruby.Syntax.Send <$> (Just <$> term expression) <*> pure Nothing <*> args)
|
||||
|
||||
selector = Just <$> term methodSelector
|
||||
-- require = inject <$> (symbol Identifier *> do
|
||||
-- s <- rawSource
|
||||
-- guard (s `elem` ["require", "require_relative"])
|
||||
-- Ruby.Syntax.Require (s == "require_relative") <$> nameExpression)
|
||||
-- load = inject <$ symbol Identifier <*> do
|
||||
-- s <- rawSource
|
||||
-- guard (s == "load")
|
||||
-- (symbol ArgumentList <|> symbol ArgumentListWithParens) *> children (Ruby.Syntax.Load <$> expression <*> optional expression)
|
||||
nameExpression = (symbol ArgumentList <|> symbol ArgumentListWithParens) *> children expression
|
||||
|
||||
args :: Assignment [MiniTerm]
|
||||
args = (symbol ArgumentList <|> symbol ArgumentListWithParens) *> children (many expression) <|> many expression
|
||||
|
||||
-- block :: Assignment MiniTerm
|
||||
-- block = makeTerm <$> symbol DoBlock <*> scopedBlockChildren
|
||||
-- <|> makeTerm <$> symbol Block <*> scopedBlockChildren
|
||||
-- where scopedBlockChildren = withExtendedScope blockChildren
|
||||
-- blockChildren = children (Declaration.Function [] <$> emptyTerm <*> params <*> expressions)
|
||||
-- params = symbol BlockParameters *> children (many parameter) <|> pure []
|
||||
|
||||
comment :: Assignment MiniTerm
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
term :: Assignment MiniTerm -> Assignment MiniTerm
|
||||
term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
|
||||
|
||||
-- | The type of Ruby syntax.
|
||||
type Syntax = '[
|
||||
Comment.Comment
|
||||
|
@ -21,6 +21,7 @@ module Parsing.Parser
|
||||
, markdownParser
|
||||
, pythonParser
|
||||
, rubyParser
|
||||
, miniRubyParser
|
||||
, typescriptParser
|
||||
, phpParser
|
||||
, haskellParser
|
||||
@ -159,6 +160,9 @@ goParser = AssignmentParser (ASTParser tree_sitter_go) Go.assignment
|
||||
rubyParser :: Parser Ruby.Term
|
||||
rubyParser = AssignmentParser (ASTParser tree_sitter_ruby) Ruby.assignment
|
||||
|
||||
miniRubyParser :: Parser Ruby.MiniTerm
|
||||
miniRubyParser = AssignmentParser (ASTParser tree_sitter_ruby) Ruby.miniAssignment
|
||||
|
||||
phpParser :: Parser PHP.Term
|
||||
phpParser = AssignmentParser (ASTParser tree_sitter_php) PHP.assignment
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user