Safe Haskell | None |
---|---|
Language | Haskell2010 |
a Boomerang
library for working with '[String]'
Synopsis
- type StringsError = ParserError MajorMinorPos
- (</>) :: Boomerang StringsError [String] b c -> Boomerang StringsError [String] a b -> Boomerang StringsError [String] a c
- alpha :: Boomerang StringsError [String] r (Char :- r)
- anyChar :: Boomerang StringsError [String] r (Char :- r)
- anyString :: Boomerang StringsError [String] r (String :- r)
- char :: Char -> Boomerang StringsError [String] r (Char :- r)
- digit :: Boomerang StringsError [String] r (Char :- r)
- eos :: Boomerang StringsError [String] r r
- int :: Boomerang StringsError [String] r (Int :- r)
- integer :: Boomerang StringsError [String] r (Integer :- r)
- lit :: String -> Boomerang StringsError [String] r r
- readshow :: (Read a, Show a) => Boomerang StringsError [String] r (a :- r)
- satisfy :: (Char -> Bool) -> Boomerang StringsError [String] r (Char :- r)
- satisfyStr :: (String -> Bool) -> Boomerang StringsError [String] r (String :- r)
- space :: Boomerang StringsError [String] r (Char :- r)
- isComplete :: [String] -> Bool
- parseStrings :: Boomerang StringsError [String] () (r :- ()) -> [String] -> Either StringsError r
- unparseStrings :: Boomerang e [String] () (r :- ()) -> r -> Maybe [String]
Types
type StringsError = ParserError MajorMinorPos Source #
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
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.
readshow :: (Read a, Show a) => Boomerang StringsError [String] r (a :- r) Source #
There are a few restrictions here:
satisfy :: (Char -> Bool) -> Boomerang StringsError [String] r (Char :- r) Source #
statisfy a Char
predicate
satisfyStr :: (String -> Bool) -> Boomerang StringsError [String] r (String :- r) Source #
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
InitialPosition StringsError Source # | |
a ~ b => IsString (Boomerang StringsError [String] a b) Source # | |
fromString :: String -> Boomerang StringsError [String] a b # |