mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Merge branch 'master' into ghc-8.2.1
This commit is contained in:
commit
d891836307
3
.gitmodules
vendored
3
.gitmodules
vendored
@ -37,3 +37,6 @@
|
||||
[submodule "languages/json/vendor/tree-sitter-json"]
|
||||
path = languages/json/vendor/tree-sitter-json
|
||||
url = https://github.com/tree-sitter/tree-sitter-json
|
||||
[submodule "vendor/freer-cofreer"]
|
||||
path = vendor/freer-cofreer
|
||||
url = https://github.com/robrix/freer-cofreer.git
|
||||
|
@ -270,9 +270,10 @@ runAssignment :: forall grammar a ast. (Symbol grammar, Enum grammar, Eq grammar
|
||||
-> Assignment ast grammar a -- ^ The 'Assignment' to run.
|
||||
-> State ast grammar -- ^ The current state.
|
||||
-> Either (Error grammar) (a, State ast grammar) -- ^ 'Either' an 'Error' or the pair of the assigned value & updated state.
|
||||
runAssignment toNode source = (requireExhaustive <=<) . go
|
||||
runAssignment toNode source = (\ assignment state -> go assignment state >>= requireExhaustive)
|
||||
-- Note: We explicitly bind toNode & source above in order to ensure that the where clause can close over them; they don’t change through the course of the run, so holding one reference is sufficient. On the other hand, we don’t want to accidentally capture the assignment and state in the where clause, since they change at every step—and capturing when you meant to shadow is an easy mistake to make, & results in hard-to-debug errors. Binding them in a lambda avoids that problem while also being easier to follow than a pointfree definition.
|
||||
where go :: Assignment ast grammar result -> State ast grammar -> Either (Error grammar) (result, State ast grammar)
|
||||
go = iterFreer run . fmap ((pure .) . (,))
|
||||
go assignment = iterFreer run ((pure .) . (,) <$> assignment)
|
||||
{-# INLINE go #-}
|
||||
|
||||
run :: AssignmentF ast grammar x
|
||||
@ -293,7 +294,7 @@ runAssignment toNode source = (requireExhaustive <=<) . go
|
||||
anywhere node = case assignment of
|
||||
Location -> yield (Info.Range (stateOffset state) (stateOffset state) :. Info.Span (statePos state) (statePos state) :. Nil) state
|
||||
Many rule -> uncurry yield (runMany rule state)
|
||||
Alt a b -> yield a state `catchError` (yield b . setStateError state . Just)
|
||||
Alt a b -> yield a state `catchError` (\ err -> yield b state { stateError = Just err })
|
||||
Throw e -> Left e
|
||||
Catch during handler -> yield during state `catchError` (flip yield state . handler)
|
||||
_ -> Left (maybe (Error (statePos state) expectedSymbols Nothing) (nodeError expectedSymbols . toNode) node)
|
||||
@ -337,9 +338,6 @@ data State ast grammar = State
|
||||
makeState :: [ast] -> State ast grammar
|
||||
makeState = State 0 (Info.Pos 1 1) Nothing 0
|
||||
|
||||
setStateError :: State ast grammar -> Maybe (Error grammar) -> State ast grammar
|
||||
setStateError state error = state { stateError = error }
|
||||
|
||||
|
||||
-- Instances
|
||||
|
||||
|
1
vendor/freer-cofreer
vendored
Submodule
1
vendor/freer-cofreer
vendored
Submodule
@ -0,0 +1 @@
|
||||
Subproject commit f18b723579f700674dda90ed1519f6e7298e2117
|
Loading…
Reference in New Issue
Block a user