input-parsers-0.1: Extension of the parsers library with more capability and efficiency

Safe HaskellNone
LanguageHaskell2010

Text.Parser.Wrapper

Description

Newtype wrappers for parsers

Synopsis

Documentation

newtype Lazy f a Source #

Wrapper that signifies lazy ByteString inputs

Constructors

Lazy 

Fields

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

fail :: String -> 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) :: Type 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

newtype Strict f a Source #

Wrapper that signifies strict ByteString inputs

Constructors

Strict 

Fields

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

fail :: String -> 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) :: Type 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