unparse-attoparsec-0.1.0.0: An attoparsec roundtrip

Safe HaskellNone
LanguageHaskell2010

Data.Attoparsec.Unparse.Profunctor

Contents

Synopsis

Documentation

class Profunctor p => Attoparsec p where Source #

Methods

word8 :: Word8 -> p x Word8 Source #

anyWord8 :: p Word8 Word8 Source #

notWord8 :: Word8 -> p Word8 Word8 Source #

satisfy :: (Word8 -> Bool) -> p Word8 Word8 Source #

skip :: (Word8 -> Bool) -> p Word8 () Source #

peekWord8 :: p (Maybe Word8) (Maybe Word8) Source #

peekWord8' :: p Word8 Word8 Source #

peekWord8Class' :: (Word8 -> Bool) -> p Bool Bool Source #

Get the value of a predicate on the lookahead.

This extra method allows the unparser not to worry about knowing the exact value of a lookahead.

unsafePeekWord8Class' :: p (Class Word8) Word8 Source #

Get a representative of a character class a lookahead belongs to.

Care must be taken not to learn more about the resulting character than the class it belongs to.

string :: ByteString -> p x ByteString Source #

skipWhile :: (Word8 -> Bool) -> p ByteString () Source #

take :: Int -> p ByteString ByteString Source #

scan :: s -> (s -> Word8 -> Maybe s) -> p ByteString ByteString Source #

runScanner :: s -> (s -> Word8 -> Maybe s) -> p ByteString (ByteString, s) Source #

takeWhile :: (Word8 -> Bool) -> p ByteString ByteString Source #

takeWhile1 :: (Word8 -> Bool) -> p ByteString ByteString Source #

takeTill :: (Word8 -> Bool) -> p ByteString ByteString Source #

takeByteString :: p ByteString ByteString Source #

(<?>) :: p b a -> String -> p b a Source #

endOfInput :: p x () Source #

atEnd :: p Bool Bool Source #

assert :: String -> (x -> Bool) -> p x () Source #

As a parser, do nothing (return ()); as a printer, fail if the predicate is not satisfied, with the given error message.

parseOrPrint :: Parser a -> (a -> Printer' ()) -> p a a Source #

Instances
Attoparsec Printer Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Attoparsec Parser Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

defaultSkip :: (Attoparsec p, Functor (p Word8)) => (Word8 -> Bool) -> p Word8 () Source #

data Class a Source #

Constructors

Class (a -> Bool) a 

singleton :: Eq a => a -> Class a Source #

Parser

newtype Parser x a Source #

Constructors

Parser 

Fields

Instances
Profunctor Parser Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Parser b c -> Parser a d #

lmap :: (a -> b) -> Parser b c -> Parser a c #

rmap :: (b -> c) -> Parser a b -> Parser a c #

(#.) :: Coercible c b => q b c -> Parser a b -> Parser a c #

(.#) :: Coercible b a => Parser b c -> q a b -> Parser a c #

Attoparsec Parser Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Monad (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

(>>=) :: Parser x a -> (a -> Parser x b) -> Parser x b #

(>>) :: Parser x a -> Parser x b -> Parser x b #

return :: a -> Parser x a #

fail :: String -> Parser x a #

Functor (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

fmap :: (a -> b) -> Parser x a -> Parser x b #

(<$) :: a -> Parser x b -> Parser x a #

MonadFail (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

fail :: String -> Parser x a #

Applicative (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

pure :: a -> Parser x a #

(<*>) :: Parser x (a -> b) -> Parser x a -> Parser x b #

liftA2 :: (a -> b -> c) -> Parser x a -> Parser x b -> Parser x c #

(*>) :: Parser x a -> Parser x b -> Parser x b #

(<*) :: Parser x a -> Parser x b -> Parser x a #

Alternative (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

empty :: Parser x a #

(<|>) :: Parser x a -> Parser x a -> Parser x a #

some :: Parser x a -> Parser x [a] #

many :: Parser x a -> Parser x [a] #

MonadPlus (Parser x) Source # 
Instance details

Defined in Data.Attoparsec.Unparse.Profunctor

Methods

mzero :: Parser x a #

mplus :: Parser x a -> Parser x a -> Parser x a #

type Parser' a = Parser a a Source #