boomerang-1.4.7: Library for invertible parsing and printing
Safe HaskellNone
LanguageHaskell2010

Text.Boomerang.Texts

Description

a Boomerang library for working with '[Text]'

Synopsis

Types

Combinators

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

equivalent to f . eos . g

alpha :: Boomerang TextsError [Text] 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)

anyChar :: Boomerang TextsError [Text] r (Char :- r) Source #

any character

anyText :: Boomerang TextsError [Text] r (Text :- r) Source #

matches any Text

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

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

For example, if we have:

unparseTexts (rPair . anyText . anyText)  ("foo","bar")

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

parseTexts (rPair . anyText . anyText)  ["foobar"]

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

char :: Char -> Boomerang TextsError [Text] r (Char :- r) Source #

matches the specified character

digit :: Boomerang TextsError [Text] r (Char :- r) Source #

ascii digits '0'..'9'

digits :: Boomerang TextsError [Text] r (Text :- r) Source #

a sequence of one or more digits

signed :: Boomerang TextsError [Text] a (Text :- r) -> Boomerang TextsError [Text] a (Text :- r) Source #

an optional - character

Typically used with digits to support signed numbers

signed digits

eos :: Boomerang TextsError [Text] r r Source #

end of string

integral :: (Integral a, Show a) => Boomerang TextsError [Text] r (a :- r) Source #

matches an Integral value

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

int :: Boomerang TextsError [Text] r (Int :- r) Source #

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

integer :: Boomerang TextsError [Text] 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 :: Text -> Boomerang TextsError [Text] r r Source #

a constant string

readshow :: (Read a, Show a) => Boomerang TextsError [Text] 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 TextsError [Text] r (Char :- r) Source #

statisfy a Char predicate

satisfyStr :: (Text -> Bool) -> Boomerang TextsError [Text] r (Text :- r) Source #

satisfy a Text predicate.

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

space :: Boomerang TextsError [Text] r (Char :- r) Source #

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

rTextCons :: Boomerang e tok (Char :- (Text :- r)) (Text :- r) Source #

the first character of a Text

rEmpty :: Boomerang e [Text] r (Text :- r) Source #

the empty string

rText :: Boomerang e [Text] r (Char :- r) -> Boomerang e [Text] r (Text :- r) Source #

construct/parse some Text by repeatedly apply a Char 0 or more times parser

rText1 :: Boomerang e [Text] r (Char :- r) -> Boomerang e [Text] r (Text :- r) Source #

construct/parse some Text by repeatedly apply a Char 1 or more times parser

Running the Boomerang

isComplete :: [Text] -> Bool Source #

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

see also: parseTexts

parseTexts :: Boomerang TextsError [Text] () (r :- ()) -> [Text] -> Either TextsError r Source #

run the parser

Returns the first complete parse or a parse error.

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

unparseTexts :: Boomerang e [Text] () (r :- ()) -> r -> Maybe [Text] Source #

run the printer

unparseTexts (rUnit . lit "foo") ()

Orphan instances

InitialPosition TextsError Source # 
Instance details

a ~ b => IsString (Boomerang TextsError [Text] a b) Source # 
Instance details