hspec-megaparsec-0.3.0: 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

:: (Ord t, ShowToken t, ShowErrorComponent e, Eq a, Show a) 
=> Either (ParseError t e) 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

:: (Ord t, ShowToken t, ShowErrorComponent e, Show a) 
=> Either (ParseError t e) 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

:: (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 some given input.

parse (char 'x') "" `shouldSucceedOn` "x"

shouldFailOn Source #

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 some 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')

Error message construction

When you wish to test error message on failure, the need to construct a error message for comparison arises. These helpers allow to construct virtually any sort of error message easily.

err Source #

Arguments

:: NonEmpty SourcePos

ParseError position

-> EC t e

Error components

-> ParseError t e

Resulting ParseError

Assemble a ParseErorr from source position and EC t e value. To create source position, two helpers are available: posI and posN. EC t e is a monoid and can be built from primitives provided by this module, see below.

Since: 0.3.0

posI :: NonEmpty SourcePos Source #

Initial source position with empty file name.

Since: 0.3.0

posN :: forall s n. (Stream s, Integral n) => n -> s -> NonEmpty SourcePos Source #

posN n s returns source position achieved by applying updatePos method corresponding to type of stream s n times.

Since: 0.3.0

data EC t e Source #

Auxiliary type for construction of ParseErrors. Note that it's a monoid.

Since: 0.3.0

Instances

(Eq t, Eq e) => Eq (EC t e) Source # 

Methods

(==) :: EC t e -> EC t e -> Bool #

(/=) :: EC t e -> EC t e -> Bool #

(Data t, Data e, Ord t, Ord e) => Data (EC t e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EC t e -> c (EC t e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EC t e) #

toConstr :: EC t e -> Constr #

dataTypeOf :: EC t e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (EC t e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (EC t e)) #

gmapT :: (forall b. Data b => b -> b) -> EC t e -> EC t e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EC t e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EC t e -> r #

gmapQ :: (forall d. Data d => d -> u) -> EC t e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EC t e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EC t e -> m (EC t e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EC t e -> m (EC t e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EC t e -> m (EC t e) #

Generic (EC t e) Source # 

Associated Types

type Rep (EC t e) :: * -> * #

Methods

from :: EC t e -> Rep (EC t e) x #

to :: Rep (EC t e) x -> EC t e #

(Ord t, Ord e) => Semigroup (EC t e) Source # 

Methods

(<>) :: EC t e -> EC t e -> EC t e #

sconcat :: NonEmpty (EC t e) -> EC t e #

stimes :: Integral b => b -> EC t e -> EC t e #

(Ord t, Ord e) => Monoid (EC t e) Source # 

Methods

mempty :: EC t e #

mappend :: EC t e -> EC t e -> EC t e #

mconcat :: [EC t e] -> EC t e #

type Rep (EC t e) Source # 
type Rep (EC t e) = D1 (MetaData "EC" "Test.Hspec.Megaparsec" "hspec-megaparsec-0.3.0-IJpvznhdkfyDLkC45WZi8R" False) (C1 (MetaCons "EC" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "ecUnexpected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorItem t)))) ((:*:) (S1 (MetaSel (Just Symbol "ecExpected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorItem t)))) (S1 (MetaSel (Just Symbol "_ecCustom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set e))))))

utok :: (Ord t, Ord e) => t -> EC t e Source #

Construct “unexpected token” error component.

Since: 0.3.0

utoks :: (Ord t, Ord e) => [t] -> EC t e Source #

Construct “unexpected tokens” error component. Empty string produces EndOfInput.

Since: 0.3.0

ulabel :: (Ord t, Ord e) => String -> EC t e Source #

Construct “unexpected label” error component. Do not use with empty strings (for empty strings it's bottom).

Since: 0.3.0

ueof :: (Ord t, Ord e) => EC t e Source #

Construct “unexpected end of input” error component.

Since: 0.3.0

etok :: (Ord t, Ord e) => t -> EC t e Source #

Construct “expected token” error component.

Since: 0.3.0

etoks :: (Ord t, Ord e) => [t] -> EC t e Source #

Construct “expected tokens” error component. Empty string produces EndOfInput.

Since: 0.3.0

elabel :: (Ord t, Ord e) => String -> EC t e Source #

Construct “expected label” error component. Do not use with empty strings.

Since: 0.3.0

eeof :: (Ord t, Ord e) => EC t e Source #

Construct “expected end of input” error component.

Since: 0.3.0

cstm :: e -> EC t e Source #

Construct custom error component.

Since: 0.3.0

Incremental parsing

failsLeaving Source #

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

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