hspec-megaparsec-0.1.1: Utility functions for testing Megaparsec parsers with Hspec

Copyright© 2016 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov@openmailbox.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Megaparsec

Contents

Description

Utility functions for testing Megaparsec parsers with Hspec.

Synopsis

Basic expectations

shouldParse Source

Arguments

:: (Eq a, Show a) 
=> Either ParseError a

Result of parsing as returned by function like parse

-> a

Desired result

-> Expectation 

Create an expectation by saying what the result should be.

parse letterChar "" "x" `shouldParse` 'x'

parseSatisfies Source

Arguments

:: Show a 
=> Either ParseError a

Result of parsing as returned by function like parse

-> (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)

shouldSucceedOn Source

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"

shouldFailOn Source

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

failsLeaving Source

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` "a"

See also: initialState.

succeedsLeaving Source

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).