1
1
mirror of https://github.com/github/semantic.git synced 2024-12-03 00:16:52 +03:00

Parameterize AssignmentState by the term type.

This commit is contained in:
Rob Rix 2017-06-07 15:01:24 -04:00
parent 698b0ac5fe
commit f7c1992db1

View File

@ -196,7 +196,7 @@ assign = assignBy (rhead . headF)
assignBy :: (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> Source.Source -> Cofree [] (Record '[node, Info.Range, Info.SourceSpan]) -> Result grammar a assignBy :: (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> Source.Source -> Cofree [] (Record '[node, Info.Range, Info.SourceSpan]) -> Result grammar a
assignBy toSymbol assignment source = fmap fst . assignAllFrom toSymbol assignment . makeState source . pure assignBy toSymbol assignment source = fmap fst . assignAllFrom toSymbol assignment . makeState source . pure
assignAllFrom :: (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> AssignmentState node -> Result grammar (a, AssignmentState node) assignAllFrom :: (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> AssignmentState (Cofree [] (Record (node ': Location))) -> Result grammar (a, AssignmentState (Cofree [] (Record (node ': Location))))
assignAllFrom toSymbol assignment state = case runAssignment toSymbol assignment state of assignAllFrom toSymbol assignment state = case runAssignment toSymbol assignment state of
Result err (Just (a, state)) -> case stateNodes (dropAnonymous toSymbol state) of Result err (Just (a, state)) -> case stateNodes (dropAnonymous toSymbol state) of
[] -> pure (a, state) [] -> pure (a, state)
@ -204,9 +204,9 @@ assignAllFrom toSymbol assignment state = case runAssignment toSymbol assignment
r -> r r -> r
-- | Run an assignment of nodes in a grammar onto terms in a syntax. -- | Run an assignment of nodes in a grammar onto terms in a syntax.
runAssignment :: forall grammar node a. (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> AssignmentState node -> Result grammar (a, AssignmentState node) runAssignment :: forall grammar node a. (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> Assignment grammar a -> AssignmentState (Cofree [] (Record (node ': Location))) -> Result grammar (a, AssignmentState (Cofree [] (Record (node ': Location))))
runAssignment toSymbol = iterFreer run . fmap ((pure .) . (,)) runAssignment toSymbol = iterFreer run . fmap ((pure .) . (,))
where run :: AssignmentF grammar x -> (x -> AssignmentState node -> Result grammar (a, AssignmentState node)) -> AssignmentState node -> Result grammar (a, AssignmentState node) where run :: AssignmentF grammar x -> (x -> AssignmentState (Cofree [] (Record (node ': Location))) -> Result grammar (a, AssignmentState (Cofree [] (Record (node ': Location))))) -> AssignmentState (Cofree [] (Record (node ': Location))) -> Result grammar (a, AssignmentState (Cofree [] (Record (node ': Location))))
run assignment yield initialState = case (assignment, stateNodes) of run assignment yield initialState = case (assignment, stateNodes) of
(Location, node : _) -> yield (rtail (extract node)) state (Location, node : _) -> yield (rtail (extract node)) state
(Location, []) -> yield (Info.Range stateOffset stateOffset :. Info.SourceSpan statePos statePos :. Nil) state (Location, []) -> yield (Info.Range stateOffset stateOffset :. Info.SourceSpan statePos statePos :. Nil) state
@ -231,25 +231,25 @@ runAssignment toSymbol = iterFreer run . fmap ((pure .) . (,))
_ -> [] _ -> []
choiceSymbols choices = (toEnum :: Int -> grammar) <$> IntMap.keys choices choiceSymbols choices = (toEnum :: Int -> grammar) <$> IntMap.keys choices
dropAnonymous :: Symbol grammar => (forall x. CofreeF [] (Record (node ': Location)) x -> Maybe grammar) -> AssignmentState node -> AssignmentState node dropAnonymous :: Symbol grammar => (forall x. CofreeF f a x -> Maybe grammar) -> AssignmentState (Cofree f a) -> AssignmentState (Cofree f a)
dropAnonymous toSymbol state = state { stateNodes = dropWhile ((`notElem` [Just Regular, Nothing]) . fmap symbolType . toSymbol . runCofree) (stateNodes state) } dropAnonymous toSymbol state = state { stateNodes = dropWhile ((`notElem` [Just Regular, Nothing]) . fmap symbolType . toSymbol . runCofree) (stateNodes state) }
-- | Advances the state past the current (head) node (if any), dropping it off stateNodes & its corresponding bytes off of stateSource, and updating stateOffset & statePos to its end. Exhausted 'AssignmentState's (those without any remaining nodes) are returned unchanged. -- | Advances the state past the current (head) node (if any), dropping it off stateNodes & its corresponding bytes off of stateSource, and updating stateOffset & statePos to its end. Exhausted 'AssignmentState's (those without any remaining nodes) are returned unchanged.
advanceState :: AssignmentState node -> AssignmentState node advanceState :: AssignmentState (Cofree [] (Record (node ': Location))) -> AssignmentState (Cofree [] (Record (node ': Location)))
advanceState state@AssignmentState{..} advanceState state@AssignmentState{..}
| node : rest <- stateNodes, (_ :. range :. span :. _) :< _ <- runCofree node = AssignmentState (Info.end range) (Info.spanEnd span) (Source.drop (Info.end range - stateOffset) stateSource) rest | node : rest <- stateNodes, (_ :. range :. span :. _) :< _ <- runCofree node = AssignmentState (Info.end range) (Info.spanEnd span) (Source.drop (Info.end range - stateOffset) stateSource) rest
| otherwise = state | otherwise = state
-- | State kept while running 'Assignment's. -- | State kept while running 'Assignment's.
data AssignmentState node = AssignmentState data AssignmentState term = AssignmentState
{ stateOffset :: Int -- ^ The offset into the Source thus far reached, measured in bytes. { stateOffset :: Int -- ^ The offset into the Source thus far reached, measured in bytes.
, statePos :: Info.SourcePos -- ^ The (1-indexed) line/column position in the Source thus far reached. , statePos :: Info.SourcePos -- ^ The (1-indexed) line/column position in the Source thus far reached.
, stateSource :: Source.Source -- ^ The remaining Source. Equal to dropping 'stateOffset' bytes off the original input Source. , stateSource :: Source.Source -- ^ The remaining Source. Equal to dropping 'stateOffset' bytes off the original input Source.
, stateNodes :: [Cofree [] (Record (node ': Location))] -- ^ The remaining nodes to assign. Note that 'children' rules recur into subterms, and thus this does not necessarily reflect all of the terms remaining to be assigned in the overall algorithm, only those “in scope.” , stateNodes :: [term] -- ^ The remaining nodes to assign. Note that 'children' rules recur into subterms, and thus this does not necessarily reflect all of the terms remaining to be assigned in the overall algorithm, only those “in scope.”
} }
deriving (Eq, Show) deriving (Eq, Show)
makeState :: Source.Source -> [Cofree [] (Record (node ': Location))] -> AssignmentState node makeState :: Source.Source -> [Cofree [] (Record (node ': Location))] -> AssignmentState (Cofree [] (Record (node ': Location)))
makeState source nodes = AssignmentState 0 (Info.SourcePos 1 1) source nodes makeState source nodes = AssignmentState 0 (Info.SourcePos 1 1) source nodes