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

Represent errors for error nodes distinct from end of input.

This commit is contained in:
Rob Rix 2017-05-17 15:15:11 -04:00
parent 107921f62a
commit 588ff85c54

View File

@ -151,7 +151,7 @@ data Error symbol where
:: HasCallStack
=> { errorPos :: Info.SourcePos
, errorExpected :: [symbol]
, errorActual :: Maybe symbol
, errorActual :: Maybe (Maybe symbol) -- ^ @Just x@ if there is a current node, where @x@ is the current nodes symbol (i.e. @Just s@ for symbols in the grammar, @Nothing@ for error nodes); @Nothing@ otherwise.
} -> Error symbol
deriving instance Eq symbol => Eq (Error symbol)
@ -190,7 +190,7 @@ assignAllFrom :: (Symbol grammar, Enum grammar, Eq grammar, Show grammar, HasCal
assignAllFrom assignment state = case runAssignment assignment state of
Result es (Just (state, a)) -> case stateNodes (dropAnonymous state) of
[] -> Result [] (Just (state, a))
Rose (s :. _) _ :_ -> Result (if null es then [ Error (statePos state) [] s ] else es) Nothing
Rose (s :. _) _ :_ -> Result (if null es then [ Error (statePos state) [] (Just s) ] else es) Nothing
r -> r
-- | Run an assignment of nodes in a grammar onto terms in a syntax.
@ -198,7 +198,7 @@ runAssignment :: forall grammar a. (Symbol grammar, Enum grammar, Eq grammar, Sh
runAssignment = iterFreer run . fmap (\ a state -> Result [] (Just (state, a)))
where run :: AssignmentF (Node grammar) x -> (x -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a)) -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a)
run assignment yield initialState = case (assignment, stateNodes) of
(_, Rose (Nothing :. _ :. nodeSpan :. Nil) _ : _) -> Result [ Error (Info.spanStart nodeSpan) expectedSymbols Nothing ] Nothing
(_, Rose (Nothing :. _ :. nodeSpan :. Nil) _ : _) -> Result [ Error (Info.spanStart nodeSpan) expectedSymbols (Just Nothing) ] Nothing
(Location, Rose (_ :. location) _ : _) -> yield location state
(Location, []) -> yield (Info.Range stateOffset stateOffset :. Info.SourceSpan statePos statePos :. Nil) state
(Source, Rose (_ :. range :. _) _ : _) -> yield (Source.sourceText (Source.slice (offsetRange range (negate stateOffset)) stateSource)) (advanceState state)
@ -209,7 +209,7 @@ runAssignment = iterFreer run . fmap (\ a state -> Result [] (Just (state, a)))
-- 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, _) -> yield a state <|> yield b state
(_, []) -> Result [ Error statePos expectedSymbols Nothing ] Nothing
(_, Rose (symbol :. _ :. nodeSpan :. Nil) _:_) -> Result [ Error (Info.spanStart nodeSpan) expectedSymbols symbol ] Nothing
(_, Rose (symbol :. _ :. nodeSpan :. Nil) _:_) -> Result [ Error (Info.spanStart nodeSpan) expectedSymbols (Just symbol) ] Nothing
where state@AssignmentState{..} = case assignment of
Choose choices | all ((== Regular) . symbolType) (choiceSymbols choices) -> dropAnonymous initialState
_ -> initialState
@ -276,7 +276,7 @@ instance (Show symbol, Show a) => Show (Result symbol a) where
showsPrec = showsPrec2
instance Show1 Error where
liftShowsPrec sp sl d (Error p e a) = showsTernaryWith showsPrec (liftShowsPrec sp sl) (liftShowsPrec sp sl) "Error" d p e a
liftShowsPrec sp sl d (Error p e a) = showsTernaryWith showsPrec (liftShowsPrec sp sl) (liftShowsPrec (liftShowsPrec sp sl) (liftShowList sp sl)) "Error" d p e a
where showsTernaryWith sp1 sp2 sp3 name d x y z = showParen (d > 10) $
showString name . showChar ' ' . sp1 11 x . showChar ' ' . sp2 11 y . showChar ' ' . sp3 11 z