Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Parsable
Synopsis
- data ParseCoverage
- parsableQuickCheck :: forall proxy a. (Parsable a Identity () String, Printable a, Arbitrary a, Eq a, Show a, Typeable a) => proxy a -> STM TestTree
- parsableProp :: forall a. (Parsable a Identity () String, Printable a, Eq a, Show a) => TChan ParseError -> a -> Property
- wordGen :: [Char -> Bool] -> [Char -> Bool] -> Gen String
- parsableHUnit :: forall proxy a. (Parsable a Identity () String, Printable a, Show a) => proxy a -> String -> TestTree
- printableHUnit :: forall a. (Parsable a Identity () String, Printable a, Show a, Eq a) => a -> TestTree
- parsableAssertion :: forall proxy a. (Parsable a Identity () String, Printable a, Show a) => proxy a -> String -> Assertion
- printableAssertion :: forall a. (Parsable a Identity () String, Printable a, Show a, Eq a) => a -> Assertion
- runCheckParsable :: Parsable a Identity () String => String -> Either ParseError (ParseCoverage, a)
- checkParsable :: forall a s u m. (Stream s m Char, Parsable a m u s) => ParsecT s u m (ParseCoverage, a)
- checkCoverage :: Stream s m Char => ParsecT s u m a -> ParsecT s u m (ParseCoverage, a)
- data ParseError
- module Control.Monad.STM
- module Data.Void
Partial parses
data ParseCoverage Source #
If a parse succeeds for the beginning of the input, but then fails, we
choose the PartialParse
constructor. If the entire parse was successful,
we choose CompleteParse
.
This is mostly useful for testing parsers where we need to test them
individually (must end with CompleteParse
) and also composed together
(individual parsers may end with PartialParse
if they do not conclude
the larger parse).
Constructors
PartialParse String | |
CompleteParse |
Instances
Semigroup ParseCoverage Source # | |
Defined in Test.Parsable Methods (<>) :: ParseCoverage -> ParseCoverage -> ParseCoverage # sconcat :: NonEmpty ParseCoverage -> ParseCoverage # stimes :: Integral b => b -> ParseCoverage -> ParseCoverage # | |
Show ParseCoverage Source # | |
Defined in Test.Parsable Methods showsPrec :: Int -> ParseCoverage -> ShowS # show :: ParseCoverage -> String # showList :: [ParseCoverage] -> ShowS # | |
Eq ParseCoverage Source # | |
Defined in Test.Parsable Methods (==) :: ParseCoverage -> ParseCoverage -> Bool # (/=) :: ParseCoverage -> ParseCoverage -> Bool # | |
Ord ParseCoverage Source # | |
Defined in Test.Parsable Methods compare :: ParseCoverage -> ParseCoverage -> Ordering # (<) :: ParseCoverage -> ParseCoverage -> Bool # (<=) :: ParseCoverage -> ParseCoverage -> Bool # (>) :: ParseCoverage -> ParseCoverage -> Bool # (>=) :: ParseCoverage -> ParseCoverage -> Bool # max :: ParseCoverage -> ParseCoverage -> ParseCoverage # min :: ParseCoverage -> ParseCoverage -> ParseCoverage # |
QuickCheck
parsableQuickCheck :: forall proxy a. (Parsable a Identity () String, Printable a, Arbitrary a, Eq a, Show a, Typeable a) => proxy a -> STM TestTree Source #
QuickCheck tests for any Parsable
type. Currently this only checks
parsableProp
.
parsableProp :: forall a. (Parsable a Identity () String, Printable a, Eq a, Show a) => TChan ParseError -> a -> Property Source #
Generators
wordGen :: [Char -> Bool] -> [Char -> Bool] -> Gen String Source #
Generator which takes two lists of predicates which specify valid characters.
- The first list is specifically for characters that start the string.
- The second list is for any subsequent characters.
This generator always creates a non-empty string.
HUnit
parsableHUnit :: forall proxy a. (Parsable a Identity () String, Printable a, Show a) => proxy a -> String -> TestTree Source #
HUnit tests for a string which should be parsed as a Parsable
Currently this checks:
printableHUnit :: forall a. (Parsable a Identity () String, Printable a, Show a, Eq a) => a -> TestTree Source #
parsableAssertion :: forall proxy a. (Parsable a Identity () String, Printable a, Show a) => proxy a -> String -> Assertion Source #
printableAssertion :: forall a. (Parsable a Identity () String, Printable a, Show a, Eq a) => a -> Assertion Source #
Generic functions
runCheckParsable :: Parsable a Identity () String => String -> Either ParseError (ParseCoverage, a) Source #
Parses a string as the given Parsable
value
checkParsable :: forall a s u m. (Stream s m Char, Parsable a m u s) => ParsecT s u m (ParseCoverage, a) Source #
Convenience function that runs checkCoverage
on a Parsable
parser.
checkCoverage :: Stream s m Char => ParsecT s u m a -> ParsecT s u m (ParseCoverage, a) Source #
Run the specified parser, then return CompleteParse
if we are at
eof
, otherwise PartialParse
.
Re-exports
data ParseError #
The abstract data type ParseError
represents parse errors. It
provides the source position (SourcePos
) of the error
and a list of error messages (Message
). A ParseError
can be returned by the function parse
. ParseError
is an
instance of the Show
and Eq
classes.
Instances
Show ParseError | |
Defined in Text.Parsec.Error Methods showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Eq ParseError | |
Defined in Text.Parsec.Error |
module Control.Monad.STM
module Data.Void