| Copyright | © 2016–2017 Mark Karpov |
|---|---|
| License | BSD 3 clause |
| Maintainer | Mark Karpov <markkarpov92@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Hspec.Megaparsec
Description
Utility functions for testing Megaparsec parsers with Hspec.
- shouldParse :: (Ord t, ShowToken t, ShowErrorComponent e, Eq a, Show a) => Either (ParseError t e) a -> a -> Expectation
- parseSatisfies :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) => Either (ParseError t e) a -> (a -> Bool) -> Expectation
- shouldSucceedOn :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) => (s -> Either (ParseError t e) a) -> s -> Expectation
- shouldFailOn :: Show a => (s -> Either (ParseError t e) a) -> s -> Expectation
- shouldFailWith :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) => Either (ParseError t e) a -> ParseError t e -> Expectation
- failsLeaving :: (Show a, Eq s, Show s, Stream s) => (State s, Either (ParseError (Token s) e) a) -> s -> Expectation
- succeedsLeaving :: (ShowToken (Token s), ShowErrorComponent e, Show a, Eq s, Show s, Stream s) => (State s, Either (ParseError (Token s) e) a) -> s -> Expectation
- initialState :: s -> State s
- module Text.Megaparsec.Error.Builder
Basic expectations
Arguments
| :: (Ord t, ShowToken t, ShowErrorComponent e, Eq a, Show a) | |
| => Either (ParseError t 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
| :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) | |
| => Either (ParseError t 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
| :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) | |
| => (s -> Either (ParseError t 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
| :: Show a | |
| => (s -> Either (ParseError t 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
shouldFailWith :: (Ord t, ShowToken t, ShowErrorComponent e, Show a) => Either (ParseError t e) a -> ParseError t e -> Expectation Source #
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')
Incremental parsing
Arguments
| :: (Show a, Eq s, Show s, Stream s) | |
| => (State s, Either (ParseError (Token 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
| :: (ShowToken (Token s), ShowErrorComponent e, Show a, Eq s, Show s, Stream s) | |
| => (State s, Either (ParseError (Token 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 Source #
Given input for parsing, construct initial state for parser (that is, with empty file name, default tab width and position at 1 line and 1 column).