Safe Haskell | None |
---|---|
Language | Haskell2010 |
a Boomerang
library for working with '[Text]'
Synopsis
- type TextsError = ParserError MajorMinorPos
- (</>) :: Boomerang TextsError [Text] b c -> Boomerang TextsError [Text] a b -> Boomerang TextsError [Text] a c
- alpha :: Boomerang TextsError [Text] r (Char :- r)
- anyChar :: Boomerang TextsError [Text] r (Char :- r)
- anyText :: Boomerang TextsError [Text] r (Text :- r)
- char :: Char -> Boomerang TextsError [Text] r (Char :- r)
- digit :: Boomerang TextsError [Text] r (Char :- r)
- digits :: Boomerang TextsError [Text] r (Text :- r)
- signed :: Boomerang TextsError [Text] a (Text :- r) -> Boomerang TextsError [Text] a (Text :- r)
- eos :: Boomerang TextsError [Text] r r
- integral :: (Integral a, Show a) => Boomerang TextsError [Text] r (a :- r)
- int :: Boomerang TextsError [Text] r (Int :- r)
- integer :: Boomerang TextsError [Text] r (Integer :- r)
- lit :: Text -> Boomerang TextsError [Text] r r
- readshow :: (Read a, Show a) => Boomerang TextsError [Text] r (a :- r)
- satisfy :: (Char -> Bool) -> Boomerang TextsError [Text] r (Char :- r)
- satisfyStr :: (Text -> Bool) -> Boomerang TextsError [Text] r (Text :- r)
- space :: Boomerang TextsError [Text] r (Char :- r)
- rTextCons :: Boomerang e tok (Char :- (Text :- r)) (Text :- r)
- rEmpty :: Boomerang e [Text] r (Text :- r)
- rText :: Boomerang e [Text] r (Char :- r) -> Boomerang e [Text] r (Text :- r)
- rText1 :: Boomerang e [Text] r (Char :- r) -> Boomerang e [Text] r (Text :- r)
- isComplete :: [Text] -> Bool
- parseTexts :: Boomerang TextsError [Text] () (r :- ()) -> [Text] -> Either TextsError r
- unparseTexts :: Boomerang e [Text] () (r :- ()) -> r -> Maybe [Text]
Types
type TextsError = ParserError MajorMinorPos Source #
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
)
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")
signed :: Boomerang TextsError [Text] a (Text :- r) -> Boomerang TextsError [Text] a (Text :- r) Source #
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.
readshow :: (Read a, Show a) => Boomerang TextsError [Text] r (a :- r) Source #
There are a few restrictions here:
satisfy :: (Char -> Bool) -> Boomerang TextsError [Text] r (Char :- r) Source #
statisfy a Char
predicate
satisfyStr :: (Text -> Bool) -> Boomerang TextsError [Text] r (Text :- r) Source #
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
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 # | |
initialPos :: Maybe TextsError -> Pos TextsError Source # | |
a ~ b => IsString (Boomerang TextsError [Text] a b) Source # | |
fromString :: String -> Boomerang TextsError [Text] a b # |