mirror of
https://github.com/github/semantic.git
synced 2024-12-01 09:15:01 +03:00
Merge remote-tracking branch 'origin/master' into ruby-assignment-ftw
This commit is contained in:
commit
5b6eab8539
@ -133,7 +133,6 @@ data AssignmentF ast grammar a where
|
||||
CurrentNode :: AssignmentF ast grammar (CofreeF.CofreeF ast (Node grammar) ())
|
||||
Source :: AssignmentF ast grammar ByteString
|
||||
Children :: Assignment ast grammar a -> AssignmentF ast grammar a
|
||||
Advance :: AssignmentF ast grammar ()
|
||||
Choose :: Table.Table grammar (Assignment ast grammar a) -> Maybe (Assignment ast grammar a) -> Maybe (Error (Either String grammar) -> Assignment ast grammar a) -> AssignmentF ast grammar a
|
||||
Many :: Assignment ast grammar a -> AssignmentF ast grammar [a]
|
||||
Alt :: [a] -> AssignmentF ast grammar a
|
||||
@ -176,7 +175,7 @@ children child = tracing (Children child) `Then` return
|
||||
|
||||
-- | Advance past the current node.
|
||||
advance :: HasCallStack => Assignment ast grammar ()
|
||||
advance = tracing Advance `Then` return
|
||||
advance = () <$ source
|
||||
|
||||
-- | Construct a committed choice table from a list of alternatives. Use this to efficiently select between long lists of rules.
|
||||
choice :: (Enum grammar, Eq (ast (AST ast grammar)), Ix grammar, HasCallStack) => [Assignment ast grammar a] -> Assignment ast grammar a
|
||||
@ -270,7 +269,7 @@ runAssignment source = \ assignment state -> go assignment state >>= requireExha
|
||||
-> (x -> State ast grammar -> Either (Error (Either String grammar)) (result, State ast grammar))
|
||||
-> State ast grammar
|
||||
-> Either (Error (Either String grammar)) (result, State ast grammar)
|
||||
run t yield initialState = expectedSymbols `seq` state `seq` maybe (anywhere Nothing) atNode (listToMaybe stateNodes)
|
||||
run t yield initialState = state `seq` maybe (anywhere Nothing) atNode (listToMaybe stateNodes)
|
||||
where atNode (node :< f) = case runTracing t of
|
||||
Location -> yield (nodeLocation node) state
|
||||
CurrentNode -> yield (node CofreeF.:< (() <$ f)) state
|
||||
@ -278,7 +277,6 @@ runAssignment source = \ assignment state -> go assignment state >>= requireExha
|
||||
Children child -> do
|
||||
(a, state') <- go child state { stateNodes = toList f, stateCallSites = maybe id (:) (tracingCallSite t) stateCallSites } >>= requireExhaustive (tracingCallSite t)
|
||||
yield a (advanceState state' { stateNodes = stateNodes, stateCallSites = stateCallSites })
|
||||
Advance -> yield () (advanceState state)
|
||||
Choose choices _ handler | Just choice <- Table.lookup (nodeSymbol node) choices -> (go choice state `catchError` (maybe throwError (flip go state .) handler)) >>= uncurry yield
|
||||
_ -> anywhere (Just node)
|
||||
|
||||
@ -292,7 +290,9 @@ runAssignment source = \ assignment state -> go assignment state >>= requireExha
|
||||
Choose _ (Just atEnd) _ | Nothing <- node -> go atEnd state >>= uncurry yield
|
||||
_ -> Left (makeError node)
|
||||
|
||||
state@State{..} = if not (null expectedSymbols) && all ((== Regular) . symbolType) expectedSymbols then skipTokens initialState else initialState
|
||||
state@State{..} = case (runTracing t, initialState) of
|
||||
(Choose table _ _, State { stateNodes = (node :< _) : _ }) | symbolType (nodeSymbol node) /= Regular, symbols@(_:_) <- Table.tableAddresses table, all ((== Regular) . symbolType) symbols -> skipTokens initialState
|
||||
_ -> initialState
|
||||
expectedSymbols = firstSet (t `Then` return)
|
||||
makeError = withStateCallStack (tracingCallSite t) state $ maybe (Error (Info.Span statePos statePos) (fmap Right expectedSymbols) Nothing) (nodeError (fmap Right expectedSymbols))
|
||||
|
||||
@ -398,7 +398,6 @@ instance Show1 f => Show1 (Tracing f) where
|
||||
instance (Enum grammar, Ix grammar, Show grammar, Show (ast (AST ast grammar))) => Show1 (AssignmentF ast grammar) where
|
||||
liftShowsPrec sp sl d a = case a of
|
||||
End -> showString "End" . showChar ' ' . sp d ()
|
||||
Advance -> showString "Advance" . showChar ' ' . sp d ()
|
||||
Location -> showString "Location" . sp d (Info.Range 0 0 :. Info.Span (Info.Pos 1 1) (Info.Pos 1 1) :. Nil)
|
||||
CurrentNode -> showString "CurrentNode"
|
||||
Source -> showString "Source" . showChar ' ' . sp d ""
|
||||
|
Loading…
Reference in New Issue
Block a user