cassette-0.2.0: A combinator library for simultaneously defining parsers and pretty printers.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Cassette.Prim

Description

The primitive parser combinators.

Synopsis

Data types

data K7 (p :: Type -> Type -> Type) a b Source #

A cassette consists of two tracks, represented by profunctors. The second track has its polarities flipped relative to the first.

Constructors

K7 

Fields

  • sideA :: p a b
     
  • sideB :: forall t. p (a -> t) (b -> t)
     

Instances

Instances details
Category p => Category (K7 p :: Type -> Type -> Type) Source # 
Instance details

Defined in Text.Cassette.Prim

Methods

id :: K7 p a a #

(.) :: K7 p b c -> K7 p a b -> K7 p a c #

(forall r1 r'1. Monoid (p r1 r'1)) => Monoid (K7 p r r') Source # 
Instance details

Defined in Text.Cassette.Prim

Methods

mempty :: K7 p r r' #

mappend :: K7 p r r' -> K7 p r r' -> K7 p r r' #

mconcat :: [K7 p r r'] -> K7 p r r' #

(forall r1 r'1. Semigroup (p r1 r'1)) => Semigroup (K7 p r r') Source # 
Instance details

Defined in Text.Cassette.Prim

Methods

(<>) :: K7 p r r' -> K7 p r r' -> K7 p r r' #

sconcat :: NonEmpty (K7 p r r') -> K7 p r r' #

stimes :: Integral b => b -> K7 p r r' -> K7 p r r' #

data Tr r r' Source #

Tr r r' is the type of string transformers with answer type modification from r to r' through control effects.

Instances

Instances details
Category Tr Source # 
Instance details

Defined in Text.Cassette.Internal.Tr

Methods

id :: Tr a a #

(.) :: Tr b c -> Tr a b -> Tr a c #

Monoid (Tr r r') Source #

mempty is the string transformer that always fails.

Instance details

Defined in Text.Cassette.Internal.Tr

Methods

mempty :: Tr r r' #

mappend :: Tr r r' -> Tr r r' -> Tr r r' #

mconcat :: [Tr r r'] -> Tr r r' #

Semigroup (Tr r r') Source #

(<>) is the choice operator. Note that this is an unrestricted backtracking operator: it never commits to any particular choice.

Instance details

Defined in Text.Cassette.Internal.Tr

Methods

(<>) :: Tr r r' -> Tr r r' -> Tr r r' #

sconcat :: NonEmpty (Tr r r') -> Tr r r' #

stimes :: Integral b => b -> Tr r r' -> Tr r r' #

type PP a = forall r. K7 Tr r (a -> r) Source #

The type of cassettes with a string transformer on each side. The A-side produces a value in addition to transforming the string, i.e. it is a parser. The B-side consumes a value to transform the string, i.e. it is a printer.

type PP0 = forall r. K7 Tr r r Source #

The type of cassettes only useful for their effect on the input or output strings, but do not produce/consume any value.

Composition

(-->) :: forall (p :: Type -> Type -> Type) b c a. Category p => K7 p b c -> K7 p a b -> K7 p a c infixr 9 Source #

A synonym to (.)

Extraction

parse :: PP a -> String -> Maybe a Source #

Extract the parser from a cassette.

pretty :: PP a -> a -> Maybe String Source #

Flip the cassette around to extract the pretty printer.

sscanf :: HasCallStack => K7 Tr r r' -> String -> r' -> r Source #

An equivalent to sscanf() in C: sscanf fmt k s extracts data from string s according to format descriptor fmt and hands the data to continuation k.

>>> spec = satisfy (=='A') . satisfy (=='B') . satisfy (=='C')
>>> sscanf spec "ABC" (,,)
('A','B','C')

sprintf :: HasCallStack => K7 Tr String r -> r Source #

An equivalent to sprintf() in C: sprintf fmt returns a function that returns a string and whose number of arguments depends on format descriptor fmt.

>>> spec = satisfy (=='A') . satisfy (=='B') . satisfy (=='C')
>>> sprintf spec 'A' 'B' 'C'
"ABC"

Primitive combinators

nothing :: PP0 Source #

Do nothing.

>>> pretty (set () nothing) ()
Just ""

set :: a -> PP0 -> PP a Source #

Turn the given pure transformer into a parsing/printing pair. That is, return a cassette that provides an output on the one side, and consumes an input on the other, in addition to the string transformations of the given pure transformer. set x p provides x as the output of p on the parsing side, and on the printing side accepts an input that is ignored.

unset :: a -> PP a -> PP0 Source #

Turn the given parsing/printing pair into a pure string transformer. That is, return a cassette that does not produce an output or consume an input. unset x p throws away the output of p on the parsing side, and on the printing side sets the input to x.

string :: String -> PP0 Source #

Strip/add the given string from/to the output string.

satisfy :: (Char -> Bool) -> PP Char Source #

Successful only if predicate holds.

lookAhead :: PP a -> PP a Source #

Parse/print without consuming/producing any input.

>>> let spec = lookAhead (satisfy (=='A')) . string "A"
>>> parse spec "ABCD"
Just 'A'

eof :: PP0 Source #

Succeeds if input string is empty.

>>> parse (set () eof) ""
Just ()
>>> parse (set () eof) "ABCD"
Nothing