mirror of
https://github.com/github/semantic.git
synced 2025-01-03 13:02:37 +03:00
Define state assignments.
This commit is contained in:
parent
96affb1f05
commit
25ebe64d83
@ -2,6 +2,7 @@
|
||||
module Data.Syntax.Assignment
|
||||
( Assignment
|
||||
, get
|
||||
, state
|
||||
, symbol
|
||||
, range
|
||||
, sourceSpan
|
||||
@ -23,9 +24,9 @@ import Data.Functor.Foldable hiding (Nil)
|
||||
import Data.Record
|
||||
import Data.Text (unpack)
|
||||
import qualified Info
|
||||
import Prologue hiding (Alt, get)
|
||||
import Prologue hiding (Alt, get, state)
|
||||
import Range (offsetRange)
|
||||
import Source (Source(), drop, slice, sourceText)
|
||||
import qualified Source (Source(..), drop, slice, sourceText)
|
||||
import Text.Parser.TreeSitter.Language
|
||||
import Text.Show hiding (show)
|
||||
|
||||
@ -36,6 +37,7 @@ type Assignment node = Freer (AssignmentF node)
|
||||
|
||||
data AssignmentF node a where
|
||||
Get :: AssignmentF node node
|
||||
State :: AssignmentF (Node grammar) (AssignmentState grammar)
|
||||
Source :: AssignmentF symbol ByteString
|
||||
Children :: Assignment symbol a -> AssignmentF symbol a
|
||||
Alt :: a -> a -> AssignmentF symbol a
|
||||
@ -47,6 +49,12 @@ data AssignmentF node a where
|
||||
get :: Assignment (Record fields) (Record fields)
|
||||
get = Get `Then` return
|
||||
|
||||
-- | Zero-width production of the current state.
|
||||
--
|
||||
-- Since this is zero-width, care must be taken not to repeat it without chaining on other rules. I.e. 'many (state *> b)' is fine, but 'many state' is not.
|
||||
state :: Assignment (Node grammar) (AssignmentState grammar)
|
||||
state = State `Then` return
|
||||
|
||||
-- | Zero-width match of a node with the given symbol.
|
||||
--
|
||||
-- Since this is zero-width, care must be taken not to repeat it without chaining on other rules. I.e. 'many (symbol A *> b)' is fine, but 'many (symbol A)' is not.
|
||||
@ -89,7 +97,7 @@ data Result a = Result a | Error [Text]
|
||||
|
||||
|
||||
-- | Run an assignment of nodes in a grammar onto terms in a syntax, discarding any unparsed nodes.
|
||||
assignAll :: (Symbol grammar, Eq grammar, Show grammar) => Assignment (Node grammar) a -> Source -> [AST grammar] -> Result a
|
||||
assignAll :: (Symbol grammar, Eq grammar, Show grammar) => Assignment (Node grammar) a -> Source.Source -> [AST grammar] -> Result a
|
||||
assignAll assignment = (assignAllFrom assignment .) . AssignmentState 0 (Info.SourcePos 0 0)
|
||||
|
||||
assignAllFrom :: (Symbol grammar, Eq grammar, Show grammar) => Assignment (Node grammar) a -> AssignmentState grammar -> Result a
|
||||
@ -104,9 +112,10 @@ runAssignment :: (Symbol grammar, Eq grammar, Show grammar) => Assignment (Node
|
||||
runAssignment = iterFreer (\ assignment yield state -> case (assignment, dropAnonymous state) of
|
||||
-- Nullability: some rules, e.g. 'pure a' and 'many a', should match at the end of input. Either side of an alternation may be nullable, ergo Alt can match at the end of input.
|
||||
(Alt a b, state) -> yield a state <|> yield b state -- FIXME: Symbol `Alt` Symbol `Alt` Symbol is inefficient, should build and match against an IntMap instead.
|
||||
(State, state) -> yield state state
|
||||
(assignment, AssignmentState offset _ source (subtree@(Rose node@(_ :. range :. _) children) : _)) -> case assignment of
|
||||
Get -> yield node state
|
||||
Source -> yield (sourceText (slice (offsetRange range (negate offset)) source)) (advanceState state)
|
||||
Source -> yield (Source.sourceText (Source.slice (offsetRange range (negate offset)) source)) (advanceState state)
|
||||
Children childAssignment -> do
|
||||
c <- assignAllFrom childAssignment state { stateNodes = children }
|
||||
yield c (advanceState state)
|
||||
@ -125,7 +134,7 @@ advanceState state@AssignmentState{..}
|
||||
| Rose (_ :. range :. span :. _) _ : rest <- stateNodes = AssignmentState (Info.end range) (Info.spanEnd span) (Source.drop (Info.end range - stateOffset) stateSource) rest
|
||||
| otherwise = state
|
||||
|
||||
data AssignmentState grammar = AssignmentState { stateOffset :: Int, statePos :: Info.SourcePos, stateSource :: Source, stateNodes :: [AST grammar] }
|
||||
data AssignmentState grammar = AssignmentState { stateOffset :: Int, statePos :: Info.SourcePos, stateSource :: Source.Source, stateNodes :: [AST grammar] }
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Alternative (Assignment symbol) where
|
||||
@ -135,6 +144,7 @@ instance Alternative (Assignment symbol) where
|
||||
instance Show symbol => Show1 (AssignmentF symbol) where
|
||||
liftShowsPrec sp sl d a = case a of
|
||||
Get -> showString "Get"
|
||||
State -> showString "State" . sp d (AssignmentState 0 (Info.SourcePos 0 0) (Source.Source "") [])
|
||||
Source -> showString "Source" . showChar ' ' . sp d ""
|
||||
Children a -> showsUnaryWith (liftShowsPrec sp sl) "Children" d a
|
||||
Alt a b -> showsBinaryWith sp sp "Alt" d a b
|
||||
|
Loading…
Reference in New Issue
Block a user