Copyright | © 2016–present Mark Karpov |
---|---|
License | BSD 3 clause |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | GHC2021 |
Test.Hspec.Megaparsec
Description
Utility functions for testing Megaparsec parsers with Hspec.
Synopsis
- shouldParse :: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq a) => Either (ParseErrorBundle s e) a -> a -> Expectation
- parseSatisfies :: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq a) => Either (ParseErrorBundle s e) a -> (a -> Bool) -> Expectation
- shouldSucceedOn :: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a) => (s -> Either (ParseErrorBundle s e) a) -> s -> Expectation
- shouldFailOn :: (HasCallStack, Show a) => (s -> Either (ParseErrorBundle s e) a) -> s -> Expectation
- shouldFailWith :: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq e) => Either (ParseErrorBundle s e) a -> ParseError s e -> Expectation
- shouldFailWithM :: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq e) => Either (ParseErrorBundle s e) a -> [ParseError s e] -> Expectation
- failsLeaving :: (HasCallStack, Show a, Eq s, Show s) => (State s e, Either (ParseErrorBundle s e) a) -> s -> Expectation
- succeedsLeaving :: (HasCallStack, Show a, Eq s, Show s, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s) => (State s e, Either (ParseErrorBundle s e) a) -> s -> Expectation
- initialState :: s -> State s e
- initialPosState :: s -> PosState s
- err :: Int -> ET s -> ParseError s e
- data EF e
- data ET s
- eeof :: ET s
- elabel :: String -> ET s
- errFancy :: Int -> EF e -> ParseError s e
- etok :: Token s -> ET s
- etoks :: Stream s => Tokens s -> ET s
- fancy :: ErrorFancy e -> EF e
- ueof :: ET s
- ulabel :: String -> ET s
- utok :: Token s -> ET s
- utoks :: Stream s => Tokens s -> ET s
Basic expectations
Arguments
:: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq a) | |
=> Either (ParseErrorBundle s e) a | Result of parsing as returned by function like |
-> a | Desired result |
-> Expectation |
Create an expectation by saying what the result should be.
parse letterChar "" "x" `shouldParse` 'x'
Arguments
:: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq a) | |
=> Either (ParseErrorBundle s e) a | Result of parsing as returned by function like |
-> (a -> Bool) | Predicate |
-> Expectation |
Create an expectation by saying that the parser should successfully parse a value and that the value should satisfy some predicate.
parse (many punctuationChar) "" "?!!" `parseSatisfies` ((== 3) . length)
Arguments
:: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a) | |
=> (s -> Either (ParseErrorBundle s e) a) | Parser that takes stream and produces result or error message |
-> s | Input that the parser should succeed on |
-> Expectation |
Check that a parser succeeds on a given input.
parse (char 'x') "" `shouldSucceedOn` "x"
Arguments
:: (HasCallStack, Show a) | |
=> (s -> Either (ParseErrorBundle s e) a) | Parser that takes stream and produces result or error message |
-> s | Input that the parser should fail on |
-> Expectation |
Check that a parser fails on a given input.
parse (char 'x') "" `shouldFailOn` "a"
Testing of error messages
Arguments
:: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq e) | |
=> Either (ParseErrorBundle s e) a | The result of parsing |
-> ParseError s e | Expected parse errors |
-> Expectation |
Create an expectation that parser should fail producing certain
ParseError
. Use the err
function from this module to construct a
ParseError
to compare with.
parse (char 'x') "" "b" `shouldFailWith` err posI (utok 'b' <> etok 'x')
Arguments
:: (HasCallStack, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s, Show a, Eq e) | |
=> Either (ParseErrorBundle s e) a | The result of parsing |
-> [ParseError s e] | Expected parse errors, the argument is a normal linked list (as
opposed to the more correct |
-> Expectation |
Similar to shouldFailWith
, but allows us to check parsers that can
report more than one parse error at a time.
Since: 2.0.0
Incremental parsing
Arguments
:: (HasCallStack, Show a, Eq s, Show s) | |
=> (State s e, Either (ParseErrorBundle s e) a) | Parser that takes stream and produces result along with actual state information |
-> s | Part of input that should be left unconsumed |
-> Expectation |
Check that a parser fails and leaves a certain part of input
unconsumed. Use it with functions like runParser'
and runParserT'
that support incremental parsing.
runParser' (many (char 'x') <* eof) (initialState "xxa") `failsLeaving` "a"
See also: initialState
.
Arguments
:: (HasCallStack, Show a, Eq s, Show s, ShowErrorComponent e, Stream s, VisualStream s, TraversableStream s) | |
=> (State s e, Either (ParseErrorBundle s e) a) | Parser that takes stream and produces result along with actual state information |
-> s | Part of input that should be left unconsumed |
-> Expectation |
Check that a parser succeeds and leaves certain part of input
unconsumed. Use it with functions like runParser'
and runParserT'
that support incremental parsing.
runParser' (many (char 'x')) (initialState "xxa") `succeedsLeaving` "a"
See also: initialState
.
initialState :: s -> State s e Source #
Given input for parsing, construct initial state for parser.
initialPosState :: s -> PosState s Source #
Given input for parsing, construct initial positional state.
Since: 2.0.0
Re-exports
Instances
(Data e, Ord e) => Data (EF e) | |||||
Defined in Text.Megaparsec.Error.Builder Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EF e -> c (EF e) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EF e) dataTypeOf :: EF e -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EF e)) dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (EF e)) gmapT :: (forall b. Data b => b -> b) -> EF e -> EF e gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EF e -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EF e -> r gmapQ :: (forall d. Data d => d -> u) -> EF e -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> EF e -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> EF e -> m (EF e) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EF e -> m (EF e) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EF e -> m (EF e) | |||||
Ord e => Monoid (EF e) | |||||
Ord e => Semigroup (EF e) | |||||
Generic (EF e) | |||||
Defined in Text.Megaparsec.Error.Builder Associated Types
| |||||
Eq e => Eq (EF e) | |||||
Ord e => Ord (EF e) | |||||
type Rep (EF e) | |||||
Defined in Text.Megaparsec.Error.Builder type Rep (EF e) = D1 ('MetaData "EF" "Text.Megaparsec.Error.Builder" "megaparsec-9.6.1-GgMu3914B4eCMh8AqdLTvE" 'True) (C1 ('MetaCons "EF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorFancy e))))) |
Instances
(Data s, Data (Token s), Ord (Token s)) => Data (ET s) | |||||
Defined in Text.Megaparsec.Error.Builder Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ET s -> c (ET s) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ET s) dataTypeOf :: ET s -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ET s)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ET s)) gmapT :: (forall b. Data b => b -> b) -> ET s -> ET s gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ET s -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ET s -> r gmapQ :: (forall d. Data d => d -> u) -> ET s -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> ET s -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> ET s -> m (ET s) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ET s -> m (ET s) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ET s -> m (ET s) | |||||
Stream s => Monoid (ET s) | |||||
Stream s => Semigroup (ET s) | |||||
Generic (ET s) | |||||
Defined in Text.Megaparsec.Error.Builder Associated Types
| |||||
Eq (Token s) => Eq (ET s) | |||||
Ord (Token s) => Ord (ET s) | |||||
type Rep (ET s) | |||||
Defined in Text.Megaparsec.Error.Builder type Rep (ET s) = D1 ('MetaData "ET" "Text.Megaparsec.Error.Builder" "megaparsec-9.6.1-GgMu3914B4eCMh8AqdLTvE" 'False) (C1 ('MetaCons "ET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ErrorItem (Token s)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorItem (Token s)))))) |