input-parsers-0.2.2: Extension of the parsers library with more capability and efficiency
Safe HaskellNone
LanguageHaskell2010

Text.Parser.Input

Description

Parsers that can consume and return a prefix of their input.

Synopsis

Documentation

class LookAheadParsing m => InputParsing m where Source #

Methods for parsing monoidal inputs

Minimal complete definition

getInput, take

Associated Types

type ParserInput m Source #

The type of the input stream that the parser m expects to parse.

type ParserPosition m Source #

Methods

getInput :: m (ParserInput m) Source #

Always sucessful parser that returns the entire remaining input without consuming it.

getSourcePos :: m (ParserPosition m) Source #

Retrieve the Position reached by the parser in the input source.

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.

take n == count n anyToken

satisfy :: (ParserInput m -> Bool) -> m (ParserInput m) Source #

A parser that accepts an input atom only if it satisfies the given predicate.

default satisfy :: Monad m => (ParserInput m -> Bool) -> m (ParserInput m) Source #

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.

default scan :: (Monad m, FactorialMonoid (ParserInput m)) => state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m) Source #

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 concat . many . 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 concat . some . satisfy.

Instances

Instances details
InputParsing ReadP Source # 
Instance details

Defined in Text.Parser.Input

InputParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (Strict Get) Source #

type ParserPosition (Strict Get) Source #

InputParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (Lazy Get) Source #

type ParserPosition (Lazy Get) Source #

(Monad m, InputParsing m) => InputParsing (IdentityT m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (IdentityT m) Source #

type ParserPosition (IdentityT m) Source #

(MonadPlus m, InputParsing m) => InputParsing (ReaderT e m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (ReaderT e m) Source #

type ParserPosition (ReaderT e m) Source #

(MonadPlus m, InputParsing m) => InputParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (StateT s m) Source #

type ParserPosition (StateT s m) Source #

(MonadPlus m, InputParsing m) => InputParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (StateT s m) Source #

type ParserPosition (StateT s m) Source #

(MonadPlus m, InputParsing m, Monoid w) => InputParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (WriterT w m) Source #

type ParserPosition (WriterT w m) Source #

(MonadPlus m, InputParsing m, Monoid w) => InputParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (WriterT w m) Source #

type ParserPosition (WriterT w m) Source #

(FactorialMonoid s, LeftReductive s, Show s, Stream s m t, Show t) => InputParsing (ParsecT s u m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (ParsecT s u m) Source #

type ParserPosition (ParsecT s u m) Source #

Methods

getInput :: ParsecT s u m (ParserInput (ParsecT s u m)) Source #

getSourcePos :: ParsecT s u m (ParserPosition (ParsecT s u m)) Source #

anyToken :: ParsecT s u m (ParserInput (ParsecT s u m)) Source #

take :: Int -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

satisfy :: (ParserInput (ParsecT s u m) -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

notSatisfy :: (ParserInput (ParsecT s u m) -> Bool) -> ParsecT s u m () Source #

scan :: state -> (state -> ParserInput (ParsecT s u m) -> Maybe state) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

string :: ParserInput (ParsecT s u m) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

takeWhile :: (ParserInput (ParsecT s u m) -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

takeWhile1 :: (ParserInput (ParsecT s u m) -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

(MonadPlus m, InputParsing m, Monoid w) => InputParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (RWST r w s m) Source #

type ParserPosition (RWST r w s m) Source #

Methods

getInput :: RWST r w s m (ParserInput (RWST r w s m)) Source #

getSourcePos :: RWST r w s m (ParserPosition (RWST r w s m)) Source #

anyToken :: RWST r w s m (ParserInput (RWST r w s m)) Source #

take :: Int -> RWST r w s m (ParserInput (RWST r w s m)) Source #

satisfy :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

notSatisfy :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m () Source #

scan :: state -> (state -> ParserInput (RWST r w s m) -> Maybe state) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

string :: ParserInput (RWST r w s m) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeWhile :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeWhile1 :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

(MonadPlus m, InputParsing m, Monoid w) => InputParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (RWST r w s m) Source #

type ParserPosition (RWST r w s m) Source #

Methods

getInput :: RWST r w s m (ParserInput (RWST r w s m)) Source #

getSourcePos :: RWST r w s m (ParserPosition (RWST r w s m)) Source #

anyToken :: RWST r w s m (ParserInput (RWST r w s m)) Source #

take :: Int -> RWST r w s m (ParserInput (RWST r w s m)) Source #

satisfy :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

notSatisfy :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m () Source #

scan :: state -> (state -> ParserInput (RWST r w s m) -> Maybe state) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

string :: ParserInput (RWST r w s m) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeWhile :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeWhile1 :: (ParserInput (RWST r w s m) -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

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

Methods for parsing textual monoid inputs

Minimal complete definition

satisfyCharInput

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.

default scanChars :: (Monad m, TextualMonoid (ParserInput m)) => state -> (state -> Char -> Maybe state) -> m (ParserInput m) Source #

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.

Instances

Instances details
InputCharParsing ReadP Source # 
Instance details

Defined in Text.Parser.Input

(MonadPlus m, InputCharParsing m) => InputCharParsing (IdentityT m) Source # 
Instance details

Defined in Text.Parser.Input

(MonadPlus m, InputCharParsing m) => InputCharParsing (ReaderT e m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> ReaderT e m (ParserInput (ReaderT e m)) Source #

notSatisfyChar :: (Char -> Bool) -> ReaderT e m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> ReaderT e m (ParserInput (ReaderT e m)) Source #

takeCharsWhile :: (Char -> Bool) -> ReaderT e m (ParserInput (ReaderT e m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> ReaderT e m (ParserInput (ReaderT e m)) Source #

(MonadPlus m, InputCharParsing m) => InputCharParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

notSatisfyChar :: (Char -> Bool) -> StateT s m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> StateT s m (ParserInput (StateT s m)) Source #

takeCharsWhile :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

(MonadPlus m, InputCharParsing m) => InputCharParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

notSatisfyChar :: (Char -> Bool) -> StateT s m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> StateT s m (ParserInput (StateT s m)) Source #

takeCharsWhile :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> StateT s m (ParserInput (StateT s m)) Source #

(MonadPlus m, InputCharParsing m, Monoid w) => InputCharParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

notSatisfyChar :: (Char -> Bool) -> WriterT w m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> WriterT w m (ParserInput (WriterT w m)) Source #

takeCharsWhile :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

(MonadPlus m, InputCharParsing m, Monoid w) => InputCharParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

notSatisfyChar :: (Char -> Bool) -> WriterT w m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> WriterT w m (ParserInput (WriterT w m)) Source #

takeCharsWhile :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> WriterT w m (ParserInput (WriterT w m)) Source #

(TextualMonoid s, Show s, Stream s m Char) => InputCharParsing (ParsecT s u m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

notSatisfyChar :: (Char -> Bool) -> ParsecT s u m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

takeCharsWhile :: (Char -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> ParsecT s u m (ParserInput (ParsecT s u m)) Source #

(MonadPlus m, InputCharParsing m, Monoid w) => InputCharParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

notSatisfyChar :: (Char -> Bool) -> RWST r w s m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeCharsWhile :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

(MonadPlus m, InputCharParsing m, Monoid w) => InputCharParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

satisfyCharInput :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

notSatisfyChar :: (Char -> Bool) -> RWST r w s m () Source #

scanChars :: state -> (state -> Char -> Maybe state) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeCharsWhile :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

takeCharsWhile1 :: (Char -> Bool) -> RWST r w s m (ParserInput (RWST r w s m)) Source #

class InputParsing m => ConsumedInputParsing m where Source #

Parsers that keep track of the consumed input.

Methods

match :: m a -> m (ParserInput m, a) Source #

Return both the result of a parse and the portion of the input that the argument parser consumed.

Instances

Instances details
ConsumedInputParsing ReadP Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: ReadP a -> ReadP (ParserInput ReadP, a) Source #

ConsumedInputParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input

ConsumedInputParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: Lazy Get a -> Lazy Get (ParserInput (Lazy Get), a) Source #

(Monad m, ConsumedInputParsing m) => ConsumedInputParsing (IdentityT m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: IdentityT m a -> IdentityT m (ParserInput (IdentityT m), a) Source #

(MonadPlus m, ConsumedInputParsing m) => ConsumedInputParsing (ReaderT e m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: ReaderT e m a -> ReaderT e m (ParserInput (ReaderT e m), a) Source #

(MonadPlus m, ConsumedInputParsing m) => ConsumedInputParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: StateT s m a -> StateT s m (ParserInput (StateT s m), a) Source #

(MonadPlus m, ConsumedInputParsing m) => ConsumedInputParsing (StateT s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: StateT s m a -> StateT s m (ParserInput (StateT s m), a) Source #

(MonadPlus m, ConsumedInputParsing m, Monoid w) => ConsumedInputParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: WriterT w m a -> WriterT w m (ParserInput (WriterT w m), a) Source #

(MonadPlus m, ConsumedInputParsing m, Monoid w) => ConsumedInputParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: WriterT w m a -> WriterT w m (ParserInput (WriterT w m), a) Source #

(MonadPlus m, ConsumedInputParsing m, Monoid w) => ConsumedInputParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: RWST r w s m a -> RWST r w s m (ParserInput (RWST r w s m), a) Source #

(MonadPlus m, ConsumedInputParsing m, Monoid w) => ConsumedInputParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: RWST r w s m a -> RWST r w s m (ParserInput (RWST r w s m), a) Source #

newtype Lazy f a Source #

Wrapper that signifies lazy ByteString inputs

Constructors

Lazy 

Fields

Instances

Instances details
Monad f => Monad (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

(>>=) :: Lazy f a -> (a -> Lazy f b) -> Lazy f b #

(>>) :: Lazy f a -> Lazy f b -> Lazy f b #

return :: a -> Lazy f a #

Functor f => Functor (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

fmap :: (a -> b) -> Lazy f a -> Lazy f b #

(<$) :: a -> Lazy f b -> Lazy f a #

Applicative f => Applicative (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

pure :: a -> Lazy f a #

(<*>) :: Lazy f (a -> b) -> Lazy f a -> Lazy f b #

liftA2 :: (a -> b -> c) -> Lazy f a -> Lazy f b -> Lazy f c #

(*>) :: Lazy f a -> Lazy f b -> Lazy f b #

(<*) :: Lazy f a -> Lazy f b -> Lazy f a #

Alternative f => Alternative (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

empty :: Lazy f a #

(<|>) :: Lazy f a -> Lazy f a -> Lazy f a #

some :: Lazy f a -> Lazy f [a] #

many :: Lazy f a -> Lazy f [a] #

MonadPlus f => MonadPlus (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

mzero :: Lazy f a #

mplus :: Lazy f a -> Lazy f a -> Lazy f a #

TokenParsing f => TokenParsing (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

someSpace :: Lazy f () #

nesting :: Lazy f a -> Lazy f a #

semi :: Lazy f Char #

highlight :: Highlight -> Lazy f a -> Lazy f a #

token :: Lazy f a -> Lazy f a #

LookAheadParsing f => LookAheadParsing (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

lookAhead :: Lazy f a -> Lazy f a #

CharParsing f => CharParsing (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

satisfy :: (Char -> Bool) -> Lazy f Char #

char :: Char -> Lazy f Char #

notChar :: Char -> Lazy f Char #

anyChar :: Lazy f Char #

string :: String -> Lazy f String #

text :: Text -> Lazy f Text #

Parsing f => Parsing (Lazy f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

try :: Lazy f a -> Lazy f a #

(<?>) :: Lazy f a -> String -> Lazy f a #

skipMany :: Lazy f a -> Lazy f () #

skipSome :: Lazy f a -> Lazy f () #

unexpected :: String -> Lazy f a #

eof :: Lazy f () #

notFollowedBy :: Show a => Lazy f a -> Lazy f () #

ConsumedInputParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

Methods

match :: Lazy Get a -> Lazy Get (ParserInput (Lazy Get), a) Source #

InputParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (Lazy Get) Source #

type ParserPosition (Lazy Get) Source #

DeterministicParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Deterministic

Eq (f a) => Eq (Lazy f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

(==) :: Lazy f a -> Lazy f a -> Bool #

(/=) :: Lazy f a -> Lazy f a -> Bool #

Ord (f a) => Ord (Lazy f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

compare :: Lazy f a -> Lazy f a -> Ordering #

(<) :: Lazy f a -> Lazy f a -> Bool #

(<=) :: Lazy f a -> Lazy f a -> Bool #

(>) :: Lazy f a -> Lazy f a -> Bool #

(>=) :: Lazy f a -> Lazy f a -> Bool #

max :: Lazy f a -> Lazy f a -> Lazy f a #

min :: Lazy f a -> Lazy f a -> Lazy f a #

Read (f a) => Read (Lazy f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

readsPrec :: Int -> ReadS (Lazy f a) #

readList :: ReadS [Lazy f a] #

readPrec :: ReadPrec (Lazy f a) #

readListPrec :: ReadPrec [Lazy f a] #

Show (f a) => Show (Lazy f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

showsPrec :: Int -> Lazy f a -> ShowS #

show :: Lazy f a -> String #

showList :: [Lazy f a] -> ShowS #

type ParserInput (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

type ParserPosition (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Input

newtype Strict f a Source #

Wrapper that signifies strict ByteString inputs

Constructors

Strict 

Fields

Instances

Instances details
Monad f => Monad (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

(>>=) :: Strict f a -> (a -> Strict f b) -> Strict f b #

(>>) :: Strict f a -> Strict f b -> Strict f b #

return :: a -> Strict f a #

Functor f => Functor (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

fmap :: (a -> b) -> Strict f a -> Strict f b #

(<$) :: a -> Strict f b -> Strict f a #

Applicative f => Applicative (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

pure :: a -> Strict f a #

(<*>) :: Strict f (a -> b) -> Strict f a -> Strict f b #

liftA2 :: (a -> b -> c) -> Strict f a -> Strict f b -> Strict f c #

(*>) :: Strict f a -> Strict f b -> Strict f b #

(<*) :: Strict f a -> Strict f b -> Strict f a #

Alternative f => Alternative (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

empty :: Strict f a #

(<|>) :: Strict f a -> Strict f a -> Strict f a #

some :: Strict f a -> Strict f [a] #

many :: Strict f a -> Strict f [a] #

MonadPlus f => MonadPlus (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

mzero :: Strict f a #

mplus :: Strict f a -> Strict f a -> Strict f a #

TokenParsing f => TokenParsing (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

someSpace :: Strict f () #

nesting :: Strict f a -> Strict f a #

semi :: Strict f Char #

highlight :: Highlight -> Strict f a -> Strict f a #

token :: Strict f a -> Strict f a #

LookAheadParsing f => LookAheadParsing (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

lookAhead :: Strict f a -> Strict f a #

CharParsing f => CharParsing (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Parsing f => Parsing (Strict f) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

try :: Strict f a -> Strict f a #

(<?>) :: Strict f a -> String -> Strict f a #

skipMany :: Strict f a -> Strict f () #

skipSome :: Strict f a -> Strict f () #

unexpected :: String -> Strict f a #

eof :: Strict f () #

notFollowedBy :: Show a => Strict f a -> Strict f () #

ConsumedInputParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input

InputParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input

Associated Types

type ParserInput (Strict Get) Source #

type ParserPosition (Strict Get) Source #

DeterministicParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Deterministic

Eq (f a) => Eq (Strict f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

(==) :: Strict f a -> Strict f a -> Bool #

(/=) :: Strict f a -> Strict f a -> Bool #

Ord (f a) => Ord (Strict f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

compare :: Strict f a -> Strict f a -> Ordering #

(<) :: Strict f a -> Strict f a -> Bool #

(<=) :: Strict f a -> Strict f a -> Bool #

(>) :: Strict f a -> Strict f a -> Bool #

(>=) :: Strict f a -> Strict f a -> Bool #

max :: Strict f a -> Strict f a -> Strict f a #

min :: Strict f a -> Strict f a -> Strict f a #

Read (f a) => Read (Strict f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Show (f a) => Show (Strict f a) Source # 
Instance details

Defined in Text.Parser.Wrapper

Methods

showsPrec :: Int -> Strict f a -> ShowS #

show :: Strict f a -> String #

showList :: [Strict f a] -> ShowS #

type ParserInput (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input

type ParserPosition (Strict Get) Source # 
Instance details

Defined in Text.Parser.Input