| Copyright | © 2016 Mark Karpov |
|---|---|
| License | BSD 3 clause |
| Maintainer | Mark Karpov <markkarpov@openmailbox.org> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Hspec.Megaparsec
Description
Utility functions for testing Megaparsec parsers with Hspec.
- shouldParse :: (Eq a, Show a) => Either ParseError a -> a -> Expectation
- parseSatisfies :: Show a => Either ParseError a -> (a -> Bool) -> Expectation
- shouldSucceedOn :: (Show a, Stream s t) => (s -> Either ParseError a) -> s -> Expectation
- shouldFailOn :: (Show a, Stream s t) => (s -> Either ParseError a) -> s -> Expectation
- shouldFailWith :: Show a => Either ParseError a -> ParseError -> Expectation
- failsLeaving :: (Show a, Eq s, Show s, Stream s t) => (State s, Either ParseError a) -> s -> Expectation
- succeedsLeaving :: (Show a, Eq s, Show s, Stream s t) => (State s, Either ParseError a) -> s -> Expectation
- initialState :: Stream s t => s -> State s
Basic expectations
Arguments
| :: (Eq a, Show a) | |
| => Either ParseError 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
| :: Show a | |
| => Either ParseError 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
| :: (Show a, Stream s t) | |
| => (s -> Either ParseError 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 some given input.
parse (char 'x') "" `shouldSucceedOn` "x"
Arguments
| :: (Show a, Stream s t) | |
| => (s -> Either ParseError 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 some given input.
parse (char 'x') "" `shouldFailOn` "a"
Testing of error messages
shouldFailWith :: Show a => Either ParseError a -> ParseError -> Expectation Source
Create an expectation that parser should fail producing certain
ParseError. Use functions from Text.Megaparsec.Error to construct
parse errors to check against. See Text.Megaparsec.Pos for functions to
construct textual positions.
parse (char 'x') "" "b" `shouldFailWith` newErrorMessages [Unexpected "'b'", Expected "'x'"] (initialPos "")
Incremental parsing
Arguments
| :: (Show a, Eq s, Show s, Stream s t) | |
| => (State s, Either ParseError 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 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` "xxa"
See also: initialState.
Arguments
| :: (Show a, Eq s, Show s, Stream s t) | |
| => (State s, Either ParseError 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 :: Stream s t => 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).