construct-0.1: Haskell version of the Construct library for easy specification of file formats

Safe HaskellNone
LanguageHaskell2010

Construct.Classes

Description

The only good reason to import this module is if you intend to add another instance of the classes it exports.

Synopsis

Documentation

class Alternative m => AlternativeFail m where Source #

Subclass of Alternative that carries an error message in case of failure

Minimal complete definition

Nothing

Methods

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 # 
Instance details

Defined in Construct.Classes

Methods

failure :: String -> [a] Source #

expectedName :: String -> [a] -> [a] Source #

AlternativeFail Maybe Source # 
Instance details

Defined in Construct.Classes

AlternativeFail (Either Error) Source # 
Instance details

Defined in Construct.Classes

class LookAheadParsing m => InputParsing m where Source #

Methods for parsing factorial monoid inputs

Minimal complete definition

getInput, take, satisfy

Associated Types

type ParserInput m Source #

Methods

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
InputParsing Parser Source # 
Instance details

Defined in Construct.Classes

Associated Types

type ParserInput Parser :: Type Source #

InputParsing Parser Source # 
Instance details

Defined in Construct.Classes

Associated Types

type ParserInput Parser :: Type Source #

InputParsing ReadP Source # 
Instance details

Defined in Construct.Classes

Associated Types

type ParserInput ReadP :: Type Source #

(FactorialMonoid s, LeftReductive s, LookAheadParsing (Parser t s)) => InputParsing (Parser t s) Source # 
Instance details

Defined in Construct.Classes

Associated Types

type ParserInput (Parser t s) :: Type Source #

Methods

getInput :: Parser t s (ParserInput (Parser t s)) Source #

anyToken :: Parser t s (ParserInput (Parser t s)) Source #

take :: Int -> Parser t s (ParserInput (Parser t s)) Source #

satisfy :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

notSatisfy :: (ParserInput (Parser t s) -> Bool) -> Parser t s () Source #

scan :: state -> (state -> ParserInput (Parser t s) -> Maybe state) -> Parser t s (ParserInput (Parser t s)) Source #

string :: ParserInput (Parser t s) -> Parser t s (ParserInput (Parser t s)) Source #

takeWhile :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

takeWhile1 :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

concatMany :: Monoid a => Parser t s a -> Parser t s a Source #

class (CharParsing m, InputParsing m) => InputCharParsing m where Source #

Methods for parsing textual monoid inputs

Minimal complete definition

Nothing

Methods

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
InputCharParsing Parser Source # 
Instance details

Defined in Construct.Classes

InputCharParsing Parser Source # 
Instance details

Defined in Construct.Classes

InputCharParsing ReadP Source # 
Instance details

Defined in Construct.Classes

(TextualMonoid s, LeftReductive s, LookAheadParsing (Parser t s)) => InputCharParsing (Parser t s) Source # 
Instance details

Defined in Construct.Classes

Methods

satisfyCharInput :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

notSatisfyChar :: (Char -> Bool) -> Parser t s () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> Parser t s (ParserInput (Parser t s)) Source #

takeCharsWhile :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

takeCharsWhile1 :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) Source #

class InputMappableParsing m where Source #

A subclass of InputParsing for parsers that can switch the input stream type

Methods

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 # 
Instance details

Defined in Construct.Classes

Methods

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

Minimal complete definition

Nothing

Methods

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 # 
Instance details

Defined in Construct.Classes

Methods

fixSequence :: (Traversable g, Applicative n) => g Parser -> Parser (g n) Source #

Monoid s => FixTraversable (Parser t s) Source # 
Instance details

Defined in Construct.Classes

Methods

fixSequence :: (Traversable g, Applicative n) => g (Parser t s) -> Parser t s (g n) Source #

data Error Source #

Constructors

Error [String] (Maybe String) 
Instances
Eq Error Source # 
Instance details

Defined in Construct.Classes

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Show Error Source # 
Instance details

Defined in Construct.Classes

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Semigroup Error Source # 
Instance details

Defined in Construct.Classes

Methods

(<>) :: Error -> Error -> Error #

sconcat :: NonEmpty Error -> Error #

stimes :: Integral b => b -> Error -> Error #

Alternative (Either Error) Source # 
Instance details

Defined in Construct.Classes

AlternativeFail (Either Error) Source # 
Instance details

Defined in Construct.Classes