Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lang.Crucible.Syntax.ExprParse
Contents
Synopsis
- data SyntaxParse atom a
- syntaxParseIO :: IsAtom atom => SyntaxParse atom a -> Syntax atom -> IO (Either (SyntaxError atom) a)
- data SyntaxError atom = SyntaxError (NonEmpty (Reason atom))
- printSyntaxError :: IsAtom atom => SyntaxError atom -> Text
- newtype TrivialAtom = TrivialAtom Text
- test :: (HasCallStack, Show a) => Text -> SyntaxParse TrivialAtom a -> IO ()
Documentation
data SyntaxParse atom a Source #
The default parsing monad. Use its MonadSyntax
instance to write parsers.
Instances
syntaxParseIO :: IsAtom atom => SyntaxParse atom a -> Syntax atom -> IO (Either (SyntaxError atom) a) Source #
Attempt to parse the given piece of syntax, returning the first success found, or the error(s) with the greatest progress otherwise.
Errors
data SyntaxError atom Source #
Syntax errors explain why the error occurred.
Constructors
SyntaxError (NonEmpty (Reason atom)) |
Instances
Show atom => Show (SyntaxError atom) Source # | |
Defined in Lang.Crucible.Syntax.ExprParse Methods showsPrec :: Int -> SyntaxError atom -> ShowS # show :: SyntaxError atom -> String # showList :: [SyntaxError atom] -> ShowS # | |
Eq atom => Eq (SyntaxError atom) Source # | |
Defined in Lang.Crucible.Syntax.ExprParse Methods (==) :: SyntaxError atom -> SyntaxError atom -> Bool # (/=) :: SyntaxError atom -> SyntaxError atom -> Bool # |
printSyntaxError :: IsAtom atom => SyntaxError atom -> Text Source #
Convert an internal error structure into a form suitable for humans to read.
Testing utilities
newtype TrivialAtom Source #
A trivial atom, which is a wrapper around Text
, for use when testing the library.
Constructors
TrivialAtom Text |
Instances
IsString TrivialAtom Source # | |
Defined in Lang.Crucible.Syntax.ExprParse Methods fromString :: String -> TrivialAtom # | |
Show TrivialAtom Source # | |
Defined in Lang.Crucible.Syntax.ExprParse Methods showsPrec :: Int -> TrivialAtom -> ShowS # show :: TrivialAtom -> String # showList :: [TrivialAtom] -> ShowS # | |
IsAtom TrivialAtom Source # | |
Defined in Lang.Crucible.Syntax.ExprParse Methods showAtom :: TrivialAtom -> Text Source # | |
Eq TrivialAtom Source # | |
Defined in Lang.Crucible.Syntax.ExprParse |
test :: (HasCallStack, Show a) => Text -> SyntaxParse TrivialAtom a -> IO () Source #
Test a parser on some input, displaying the result.