Safe Haskell | None |
---|---|
Language | Haskell2010 |
The only good reason to import this module is if you intend to add another instance of the classes it exports.
Synopsis
- class Alternative m => AlternativeFail m where
- failure :: String -> m a
- expectedName :: String -> m a -> m a
- class LookAheadParsing m => InputParsing m where
- type ParserInput m
- getInput :: m (ParserInput m)
- anyToken :: m (ParserInput m)
- take :: Int -> m (ParserInput m)
- satisfy :: (ParserInput m -> Bool) -> m (ParserInput m)
- notSatisfy :: (ParserInput m -> Bool) -> m ()
- scan :: state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m)
- string :: ParserInput m -> m (ParserInput m)
- takeWhile :: (ParserInput m -> Bool) -> m (ParserInput m)
- takeWhile1 :: (ParserInput m -> Bool) -> m (ParserInput m)
- concatMany :: Monoid a => m a -> m a
- class (CharParsing m, InputParsing m) => InputCharParsing m where
- satisfyCharInput :: (Char -> Bool) -> m (ParserInput m)
- notSatisfyChar :: (Char -> Bool) -> m ()
- scanChars :: state -> (state -> Char -> Maybe state) -> m (ParserInput m)
- takeCharsWhile :: (Char -> Bool) -> m (ParserInput m)
- takeCharsWhile1 :: (Char -> Bool) -> m (ParserInput m)
- class InputMappableParsing m where
- mapParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') => (s -> s') -> (s' -> s) -> m s a -> m s' a
- mapMaybeParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') => (s -> Maybe s') -> (s' -> Maybe s) -> m s a -> m s' a
- class Monad m => FixTraversable m where
- fixSequence :: (Traversable g, Applicative n) => g m -> m (g n)
- data Error = Error [String] (Maybe String)
- errorString :: Error -> String
- concatExpected :: [String] -> Maybe String
- oxfordComma :: String -> [String] -> String
Documentation
class Alternative m => AlternativeFail m where Source #
Subclass of Alternative
that carries an error message in case of failure
Nothing
failure :: String -> m a Source #
Equivalent to empty
except it takes an error message it may carry or drop on the floor. The grammatical form
of the argument be a noun representing the unexpected value.
expectedName :: String -> m a -> m a Source #
Sets or modifies the expected value.
Instances
AlternativeFail [] Source # | |
Defined in Construct.Classes | |
AlternativeFail Maybe Source # | |
AlternativeFail (Either Error) Source # | |
class LookAheadParsing m => InputParsing m where Source #
Methods for parsing factorial monoid inputs
type ParserInput m Source #
getInput :: m (ParserInput m) Source #
Always sucessful parser that returns the remaining input without consuming it.
anyToken :: m (ParserInput m) Source #
A parser that accepts any single atomic prefix of the input stream. > anyToken == satisfy (const True) > anyToken == take 1
take :: Int -> m (ParserInput m) Source #
A parser that accepts exactly the given number of input atoms.
satisfy :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser that accepts an input atom only if it satisfies the given predicate.
notSatisfy :: (ParserInput m -> Bool) -> m () Source #
A parser that succeeds exactly when satisfy doesn't, equivalent to
notFollowedBy
. satisfy
scan :: state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m) Source #
A stateful scanner. The predicate modifies a state argument, and each transformed state is passed to successive
invocations of the predicate on each token of the input until one returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the predicate returns Nothing
on the first
character.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
string :: ParserInput m -> m (ParserInput m) Source #
A parser that consumes and returns the given prefix of the input.
takeWhile :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest sequence of input atoms that match the given predicate; an optimized version of 'concatMany . satisfy'.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
takeWhile1 :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized version of 'concatSome . satisfy'.
concatMany :: Monoid a => m a -> m a Source #
Zero or more argument occurrences like many
, with concatenated monoidal results.
concatMany :: (Monoid a, Alternative m) => m a -> m a Source #
Zero or more argument occurrences like many
, with concatenated monoidal results.
string :: (Monad m, LeftReductive (ParserInput m), FactorialMonoid (ParserInput m), Show (ParserInput m)) => ParserInput m -> m (ParserInput m) Source #
A parser that consumes and returns the given prefix of the input.
scan :: (Monad m, FactorialMonoid (ParserInput m)) => state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m) Source #
A stateful scanner. The predicate modifies a state argument, and each transformed state is passed to successive
invocations of the predicate on each token of the input until one returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the predicate returns Nothing
on the first
character.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
takeWhile :: (Monad m, FactorialMonoid (ParserInput m)) => (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest sequence of input atoms that match the given predicate; an optimized version of 'concatMany . satisfy'.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
takeWhile1 :: (Monad m, FactorialMonoid (ParserInput m)) => (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized version of 'concatSome . satisfy'.
Instances
class (CharParsing m, InputParsing m) => InputCharParsing m where Source #
Methods for parsing textual monoid inputs
Nothing
satisfyCharInput :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of satisfy
on textual inputs, accepting an input character only if it satisfies the given
predicate, and returning the input atom that represents the character. Equivalent to fmap singleton
. Char.satisfy
notSatisfyChar :: (Char -> Bool) -> m () Source #
A parser that succeeds exactly when satisfy doesn't, equivalent to notFollowedBy . Char.satisfy
scanChars :: state -> (state -> Char -> Maybe state) -> m (ParserInput m) Source #
Stateful scanner like scan
, but specialized for TextualMonoid
inputs.
takeCharsWhile :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile
on TextualMonoid
inputs, accepting the longest sequence of input characters that
match the given predicate; an optimized version of fmap fromString . many . Char.satisfy
.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
takeCharsWhile1 :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile1
on TextualMonoid
inputs, accepting the longest sequence of input characters
that match the given predicate; an optimized version of fmap fromString . some . Char.satisfy
.
satisfyCharInput :: IsString (ParserInput m) => (Char -> Bool) -> m (ParserInput m) Source #
Specialization of satisfy
on textual inputs, accepting an input character only if it satisfies the given
predicate, and returning the input atom that represents the character. Equivalent to fmap singleton
. Char.satisfy
scanChars :: (Monad m, TextualMonoid (ParserInput m)) => state -> (state -> Char -> Maybe state) -> m (ParserInput m) Source #
Stateful scanner like scan
, but specialized for TextualMonoid
inputs.
takeCharsWhile :: (Monad m, TextualMonoid (ParserInput m)) => (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile
on TextualMonoid
inputs, accepting the longest sequence of input characters that
match the given predicate; an optimized version of fmap fromString . many . Char.satisfy
.
Note: Because this parser does not fail, do not use it with combinators such as many
, because such parsers
loop until a failure occurs. Careless use will thus result in an infinite loop.
takeCharsWhile1 :: (Monad m, TextualMonoid (ParserInput m)) => (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile1
on TextualMonoid
inputs, accepting the longest sequence of input characters
that match the given predicate; an optimized version of fmap fromString . some . Char.satisfy
.
Instances
class InputMappableParsing m where Source #
A subclass of InputParsing
for parsers that can switch the input stream type
mapParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') => (s -> s') -> (s' -> s) -> m s a -> m s' a Source #
Converts a parser accepting one input stream type to another. The functions forth
and back
must be inverses of
each other and they must distribute through <>
:
f (s1 <> s2) == f s1 <> f s2
mapMaybeParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') => (s -> Maybe s') -> (s' -> Maybe s) -> m s a -> m s' a Source #
Converts a parser accepting one input stream type to another just like mapParserInput
, except the argument
functions can return Nothing
to indicate they need more input.
Instances
InputMappableParsing (Parser t) Source # | |
Defined in Construct.Classes mapParserInput :: (InputParsing (Parser t s), s ~ ParserInput (Parser t s), Monoid s, Monoid s') => (s -> s') -> (s' -> s) -> Parser t s a -> Parser t s' a Source # mapMaybeParserInput :: (InputParsing (Parser t s), s ~ ParserInput (Parser t s), Monoid s, Monoid s') => (s -> Maybe s') -> (s' -> Maybe s) -> Parser t s a -> Parser t s' a Source # |
class Monad m => FixTraversable m where Source #
A subclass of MonadFix
for monads that can fix a function that handles higher-kinded data
Nothing
fixSequence :: (Traversable g, Applicative n) => g m -> m (g n) Source #
This specialized form of traverse
can be used inside mfix
.
Instances
FixTraversable Parser Source # | |
Defined in Construct.Classes fixSequence :: (Traversable g, Applicative n) => g Parser -> Parser (g n) Source # | |
Monoid s => FixTraversable (Parser t s) Source # | |
Defined in Construct.Classes fixSequence :: (Traversable g, Applicative n) => g (Parser t s) -> Parser t s (g n) Source # |
errorString :: Error -> String Source #