boomerang-1.4.8.1: Library for invertible parsing and printing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Boomerang.Strings

Description

a Boomerang library for working with '[String]'

Synopsis

Types

Combinators

(</>) :: Boomerang StringsError [String] b c -> Boomerang StringsError [String] a b -> Boomerang StringsError [String] a c infixr 9 Source #

equivalent to f . eos . g

alpha :: Boomerang StringsError [String] r (Char :- r) Source #

matches alphabetic Unicode characters (lower-case, upper-case and title-case letters, plus letters of caseless scripts and modifiers letters). (Uses isAlpha)

anyString :: Boomerang StringsError [String] r (String :- r) Source #

matches any String

the parser returns the remainder of the current String segment, (but does not consume the 'end of segment'.

Note that the only combinator that should follow anyString is eos or </>. Other combinators will lead to inconsistent inversions.

For example, if we have:

unparseStrings (rPair . anyString . anyString)  ("foo","bar")

That will unparse to Just ["foobar"]. But if we call

parseStrings (rPair . anyString . anyString)  ["foobar"]

We will get Right ("foobar","") instead of the original Right ("foo","bar")

char :: Char -> Boomerang StringsError [String] r (Char :- r) Source #

matches the specified character

digit :: Boomerang StringsError [String] r (Char :- r) Source #

ascii digits '0'..'9'

eos :: Boomerang StringsError [String] r r Source #

end of string

int :: Boomerang StringsError [String] r (Int :- r) Source #

matches an Int

Note that the combinator (rPair . int . int) is ill-defined because the parse can not tell where it is supposed to split the sequence of digits to produced two ints.

integer :: Boomerang StringsError [String] r (Integer :- r) Source #

matches an Integer

Note that the combinator (rPair . integer . integer) is ill-defined because the parse can not tell where it is supposed to split the sequence of digits to produced two ints.

lit :: String -> Boomerang StringsError [String] r r Source #

a constant string

readshow :: (Read a, Show a) => Boomerang StringsError [String] r (a :- r) Source #

lift Read/Show to a Boomerang

There are a few restrictions here:

  1. Error messages are a bit fuzzy. Read does not tell us where or why a parse failed. So all we can do it use the the position that we were at when we called read and say that it failed.
  2. it is (currently) not safe to use readshow on integral values because the Read instance for Int, Integer, etc,

satisfy :: (Char -> Bool) -> Boomerang StringsError [String] r (Char :- r) Source #

statisfy a Char predicate

satisfyStr :: (String -> Bool) -> Boomerang StringsError [String] r (String :- r) Source #

satisfy a String predicate.

Note: must match the entire remainder of the String in this segment

space :: Boomerang StringsError [String] r (Char :- r) Source #

matches white-space characters in the Latin-1 range. (Uses isSpace)

Running the Boomerang

isComplete :: [String] -> Bool Source #

Predicate to test if we have parsed all the strings. Typically used as argument to parse1

see also: parseStrings

parseStrings :: Boomerang StringsError [String] () (r :- ()) -> [String] -> Either StringsError r Source #

run the parser

Returns the first complete parse or a parse error.

parseStrings (rUnit . lit "foo") ["foo"]

unparseStrings :: Boomerang e [String] () (r :- ()) -> r -> Maybe [String] Source #

run the printer

unparseStrings (rUnit . lit "foo") ()

Orphan instances