Copyright | (c) 2021 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
To parse a text input, use the decode routines from Streamly.Unicode.Stream module to convert an input byte stream to a Unicode Char stream and then use these parsers on the Char stream.
Synopsis
- char :: Monad m => Char -> Parser Char m Char
- charIgnoreCase :: Monad m => Char -> Parser Char m Char
- string :: Monad m => String -> Parser Char m String
- stringIgnoreCase :: Monad m => String -> Parser Char m String
- dropSpace :: Monad m => Parser Char m ()
- dropSpace1 :: Monad m => Parser Char m ()
- alpha :: Monad m => Parser Char m Char
- alphaNum :: Monad m => Parser Char m Char
- letter :: Monad m => Parser Char m Char
- ascii :: Monad m => Parser Char m Char
- asciiLower :: Monad m => Parser Char m Char
- asciiUpper :: Monad m => Parser Char m Char
- latin1 :: Monad m => Parser Char m Char
- lower :: Monad m => Parser Char m Char
- upper :: Monad m => Parser Char m Char
- mark :: Monad m => Parser Char m Char
- printable :: Monad m => Parser Char m Char
- punctuation :: Monad m => Parser Char m Char
- separator :: Monad m => Parser Char m Char
- space :: Monad m => Parser Char m Char
- symbol :: Monad m => Parser Char m Char
- digit :: Monad m => Parser Char m Char
- octDigit :: Monad m => Parser Char m Char
- hexDigit :: Monad m => Parser Char m Char
- numeric :: Monad m => Parser Char m Char
- signed :: (Num a, Monad m) => Parser Char m a -> Parser Char m a
- number :: Monad m => Parser Char m (Integer, Int)
- doubleParser :: Monad m => Parser Char m (Int, Int)
- double :: Monad m => Parser Char m Double
- decimal :: (Monad m, Integral a) => Parser Char m a
- hexadecimal :: (Monad m, Integral a, Bits a) => Parser Char m a
- mkDouble :: Integer -> Int -> Double
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>
:m
>>>
import qualified Streamly.Data.Stream as Stream
>>>
import qualified Streamly.Unicode.Parser as Unicode
For APIs that have not been released yet.
>>>
import qualified Streamly.Internal.Unicode.Parser as Unicode (number, mkDouble)
Generic
charIgnoreCase :: Monad m => Char -> Parser Char m Char Source #
Match a specific character ignoring case.
Sequences
string :: Monad m => String -> Parser Char m String Source #
Match the input with the supplied string and return it if successful.
stringIgnoreCase :: Monad m => String -> Parser Char m String Source #
Match the input with the supplied string and return it if successful.
Classes
asciiLower :: Monad m => Parser Char m Char Source #
Match any character that satisfies isAsciiLower
asciiUpper :: Monad m => Parser Char m Char Source #
Match any character that satisfies isAsciiUpper
punctuation :: Monad m => Parser Char m Char Source #
Match any character that satisfies isPunctuation
Numeric
signed :: (Num a, Monad m) => Parser Char m a -> Parser Char m a Source #
Allow an optional leading '+'
or '-'
sign character before any
parser.
doubleParser :: Monad m => Parser Char m (Int, Int) Source #
A fast, custom parser for double precision flaoting point numbers. Returns
(mantissa, exponent) tuple. This is much faster than number
because it
assumes the number will fit in a Double
type and uses Int
representation
to store mantissa.
Number larger than Double
may overflow. Int overflow is not checked in the
exponent.
double :: Monad m => Parser Char m Double Source #
Parse a decimal Double
value. This parser accepts an optional sign (+ or
-) followed by at least one decimal digit. Decimal digits are optionally
followed by a decimal point and at least one decimal digit after the point.
This parser accepts the maximal valid input as long as it gives a valid
number. Specifcally a trailing decimal point is allowed but not consumed.
This function does not accept "NaN" or "Infinity" string representations
of double values.
Definition:
>>>
double = uncurry Unicode.mkDouble <$> Unicode.number
Examples:
>>>
p = Stream.parse Unicode.double . Stream.fromList
>>>
p "-1.23e-123"
Right (-1.23e-123)
Trailing input examples:
>>>
p "1."
Right 1.0
>>>
p "1.2.3"
Right 1.2
>>>
p "1e"
Right 1.0
>>>
p "1e2.3"
Right 100.0
>>>
p "1+2"
Right 1.0
Error cases:
>>>
p ""
Left (ParseError "number: expecting sign or decimal digit, got end of input")
>>>
p ".1"
Left (ParseError "number: expecting sign or decimal digit, got '.'")
>>>
p "+"
Left (ParseError "number: expecting decimal digit, got end of input")
decimal :: (Monad m, Integral a) => Parser Char m a Source #
Parse and decode an unsigned integral decimal number.
hexadecimal :: (Monad m, Integral a, Bits a) => Parser Char m a Source #
Parse and decode an unsigned integral hexadecimal number. The hex digits
'a'
through 'f'
may be upper or lower case.
Note: This parser does not accept a leading "0x"
string.