1
1
mirror of https://github.com/github/semantic.git synced 2024-12-01 00:33:59 +03:00

Define Ruby.Term recursively.

This commit is contained in:
Rob Rix 2019-10-18 22:34:24 -04:00
parent 2cf145c40f
commit c9db56d4a5
No known key found for this signature in database
GPG Key ID: F188A01508EA1CF7
6 changed files with 64 additions and 27 deletions

View File

@ -33,17 +33,15 @@ import qualified Data.Syntax.Directive as Directive
import qualified Data.Syntax.Expression as Expression
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 qualified Language.Ruby.Term as Ruby
import Language.Ruby.Term as Ruby
import TreeSitter.Ruby as Grammar
type Term = Term.Term (Sum Ruby.Syntax)
type Assignment = Assignment.Assignment [] Grammar
-- | Assignment from AST in Rubys grammar onto a program in Rubys syntax.
assignment :: Assignment (Ruby.Term Loc)
assignment = fmap Ruby.Term . handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> many expression) <|> parseError
assignment :: Assignment (Term Loc)
assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> many expression) <|> parseError
expression :: Assignment (Term Loc)
expression = term (handleError (choice expressionChoices))

View File

@ -8,10 +8,13 @@ import Control.Lens.Lens
import Data.Abstract.Declarations
import Data.Abstract.FreeVariables
import Data.Bifunctor
import Data.Bitraversable
import Data.Coerce
import Data.Diff
import Data.Functor.Foldable
import Data.Graph.ControlFlowVertex (VertexDeclaration)
import Data.Sum (Sum)
import Data.Foldable (fold)
import Data.Functor.Foldable (Base, Recursive(..))
import Data.Graph.ControlFlowVertex (VertexDeclaration(..), toVertex1)
import qualified Data.Sum as Sum
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Comment as Comment
import qualified Data.Syntax.Declaration as Declaration
@ -20,8 +23,10 @@ import qualified Data.Syntax.Expression as Expression
import qualified Data.Syntax.Literal as Literal
import qualified Data.Syntax.Statement as Statement
import qualified Data.Term as Term
import Data.Traversable
import Diffing.Interpreter
import qualified Language.Ruby.Syntax as Ruby.Syntax
import Source.Loc
import Source.Span
type Syntax =
@ -115,17 +120,39 @@ type Syntax =
]
newtype Term ann = Term { getTerm :: Term.Term (Sum Syntax) ann }
deriving (Eq, Declarations, Foldable, FreeVariables, Functor, Syntax.HasErrors, Ord, Show, Traversable, VertexDeclaration)
newtype Term ann = Term { getTerm :: Term.TermF (Sum.Sum Syntax) ann (Term ann) }
deriving (Eq, Declarations, FreeVariables, Ord, Show)
instance Term.IsTerm Term where
type Syntax Term = Sum.Sum Syntax
toTermF = coerce
fromTermF = coerce
instance Foldable Term where
foldMap = foldMapDefault
instance Functor Term where
fmap = fmapDefault
instance Traversable Term where
traverse f = go where go = fmap Term . bitraverse f go . getTerm
instance VertexDeclaration Term where
toVertex info (Term (Term.In ann syntax)) = toVertex1 ann info syntax
instance Syntax.HasErrors Term where
getErrors = cata $ \ (Term.In Loc{..} syntax) ->
maybe (fold syntax) (pure . Syntax.unError span) (Sum.project syntax)
instance DiffTerms Term where
type DiffFor Term = Diff (Sum Syntax)
diffTermPair = diffTermPair . bimap getTerm getTerm
type DiffFor Term = Diff (Sum.Sum Syntax)
diffTermPair = diffTermPair . bimap (cata Term.Term) (cata Term.Term)
type instance Base (Term ann) = Term.TermF (Sum Syntax) ann
type instance Base (Term ann) = Term.TermF (Sum.Sum Syntax) ann
instance Recursive (Term ann) where
project = fmap Term . project . getTerm
project = getTerm
instance HasSpan ann => HasSpan (Term ann) where
span_ = inner.span_ where inner = lens getTerm (\t i -> t { getTerm = i })

View File

@ -100,7 +100,8 @@ deriving instance DOTGraphDiff Go.Term
deriving instance DOTGraphDiff Markdown.Term
deriving instance DOTGraphDiff PHP.Term
deriving instance DOTGraphDiff Python.Term
deriving instance DOTGraphDiff Ruby.Term
instance DOTGraphDiff Ruby.Term where
dotGraphDiff = serialize (DOT (diffStyle "diffs")) . renderTreeGraph <=< diffTerms
instance DOTGraphDiff TSX.Term where
dotGraphDiff = serialize (DOT (diffStyle "diffs")) . renderTreeGraph <=< diffTerms
instance DOTGraphDiff TypeScript.Term where
@ -137,9 +138,10 @@ deriving instance JSONGraphDiff Go.Term
deriving instance JSONGraphDiff Markdown.Term
deriving instance JSONGraphDiff PHP.Term
deriving instance JSONGraphDiff Python.Term
deriving instance JSONGraphDiff Ruby.Term
instance JSONGraphDiff Ruby.Term where
jsonGraphDiff terms = toGraph (bimap fst fst terms) <$> diffTerms terms
instance JSONGraphDiff TSX.Term where
jsonGraphDiff terms = toGraph (bimap fst fst terms) <$> diffTerms terms
jsonGraphDiff terms = toGraph (bimap fst fst terms) <$> diffTerms terms
instance JSONGraphDiff TypeScript.Term where
jsonGraphDiff terms = toGraph (bimap fst fst terms) <$> diffTerms terms
@ -157,7 +159,8 @@ deriving instance JSONTreeDiff Go.Term
deriving instance JSONTreeDiff Markdown.Term
deriving instance JSONTreeDiff PHP.Term
deriving instance JSONTreeDiff Python.Term
deriving instance JSONTreeDiff Ruby.Term
instance JSONTreeDiff Ruby.Term where
jsonTreeDiff terms = renderJSONDiff (bimap fst fst terms) <$> diffTerms terms
instance JSONTreeDiff TSX.Term where
jsonTreeDiff terms = renderJSONDiff (bimap fst fst terms) <$> diffTerms terms
instance JSONTreeDiff TypeScript.Term where
@ -177,7 +180,8 @@ deriving instance SExprDiff Go.Term
deriving instance SExprDiff Markdown.Term
deriving instance SExprDiff PHP.Term
deriving instance SExprDiff Python.Term
deriving instance SExprDiff Ruby.Term
instance SExprDiff Ruby.Term where
sexprDiff = serialize (SExpression ByConstructorName) <=< diffTerms
instance SExprDiff TSX.Term where
sexprDiff = serialize (SExpression ByConstructorName) <=< diffTerms
instance SExprDiff TypeScript.Term where
@ -197,7 +201,8 @@ deriving instance ShowDiff Go.Term
deriving instance ShowDiff Markdown.Term
deriving instance ShowDiff PHP.Term
deriving instance ShowDiff Python.Term
deriving instance ShowDiff Ruby.Term
instance ShowDiff Ruby.Term where
showDiff = serialize Show <=< diffTerms
instance ShowDiff TSX.Term where
showDiff = serialize Show <=< diffTerms
instance ShowDiff TypeScript.Term where

View File

@ -123,7 +123,8 @@ deriving instance ToTags Go.Term
deriving instance ToTags Markdown.Term
deriving instance ToTags PHP.Term
deriving instance ToTags PythonALaCarte.Term
deriving instance ToTags Ruby.Term
instance ToTags Ruby.Term where
tags = runTagging
instance ToTags TSX.Term where
tags = runTagging
instance ToTags TypeScript.Term where

View File

@ -126,7 +126,8 @@ deriving instance SummarizeTerms Go.Term
deriving instance SummarizeTerms Markdown.Term
deriving instance SummarizeTerms PHP.Term
deriving instance SummarizeTerms PythonALaCarte.Term
deriving instance SummarizeTerms Ruby.Term
instance SummarizeTerms Ruby.Term where
summarizeTerms = summarizeTerms . bimap (fmap (cata Term)) (fmap (cata Term))
instance SummarizeTerms TSX.Term where
summarizeTerms = summarizeTerms . bimap (fmap (cata Term)) (fmap (cata Term))
instance SummarizeTerms TypeScript.Term where

View File

@ -128,7 +128,8 @@ deriving instance ShowTerm Go.Term
deriving instance ShowTerm Markdown.Term
deriving instance ShowTerm PHP.Term
deriving instance ShowTerm PythonALaCarte.Term
deriving instance ShowTerm Ruby.Term
instance ShowTerm Ruby.Term where
showTerm = showTerm . cata Term
instance ShowTerm TSX.Term where
showTerm = showTerm . cata Term
instance ShowTerm TypeScript.Term where
@ -157,7 +158,8 @@ deriving instance SExprTerm Go.Term
deriving instance SExprTerm Markdown.Term
deriving instance SExprTerm PHP.Term
deriving instance SExprTerm PythonALaCarte.Term
deriving instance SExprTerm Ruby.Term
instance SExprTerm Ruby.Term where
sexprTerm = SExpr.serializeSExpression ByConstructorName
instance SExprTerm TSX.Term where
sexprTerm = SExpr.serializeSExpression ByConstructorName
instance SExprTerm TypeScript.Term where
@ -177,7 +179,8 @@ deriving instance DOTGraphTerm Go.Term
deriving instance DOTGraphTerm Markdown.Term
deriving instance DOTGraphTerm PHP.Term
deriving instance DOTGraphTerm PythonALaCarte.Term
deriving instance DOTGraphTerm Ruby.Term
instance DOTGraphTerm Ruby.Term where
dotGraphTerm = serialize (DOT (termStyle "terms")) . renderTreeGraph
instance DOTGraphTerm TSX.Term where
dotGraphTerm = serialize (DOT (termStyle "terms")) . renderTreeGraph
instance DOTGraphTerm TypeScript.Term where
@ -197,7 +200,8 @@ deriving instance JSONTreeTerm Go.Term
deriving instance JSONTreeTerm Markdown.Term
deriving instance JSONTreeTerm PHP.Term
deriving instance JSONTreeTerm PythonALaCarte.Term
deriving instance JSONTreeTerm Ruby.Term
instance JSONTreeTerm Ruby.Term where
jsonTreeTerm blob = jsonTreeTerm blob . cata Term
instance JSONTreeTerm TSX.Term where
jsonTreeTerm blob = jsonTreeTerm blob . cata Term
instance JSONTreeTerm TypeScript.Term where
@ -227,7 +231,8 @@ deriving instance JSONGraphTerm Go.Term
deriving instance JSONGraphTerm Markdown.Term
deriving instance JSONGraphTerm PHP.Term
deriving instance JSONGraphTerm PythonALaCarte.Term
deriving instance JSONGraphTerm Ruby.Term
instance JSONGraphTerm Ruby.Term where
jsonGraphTerm blob = jsonGraphTerm blob . cata Term
instance JSONGraphTerm TSX.Term where
jsonGraphTerm blob = jsonGraphTerm blob . cata Term
instance JSONGraphTerm TypeScript.Term where