| Copyright | (c) 2021 Composewell Technologies | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | streamly@composewell.com | 
| Stability | released | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streamly.Unicode.Parser
Description
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 :: forall (m :: Type -> Type). Monad m => Char -> Parser Char m Char
- charIgnoreCase :: forall (m :: Type -> Type). Monad m => Char -> Parser Char m Char
- alpha :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- alphaNum :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- letter :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- ascii :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- asciiLower :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- asciiUpper :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- latin1 :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- lower :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- upper :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- mark :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- printable :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- punctuation :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- separator :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- space :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- symbol :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- digit :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- octDigit :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- hexDigit :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- numeric :: forall (m :: Type -> Type). Monad m => Parser Char m Char
- string :: forall (m :: Type -> Type). Monad m => String -> Parser Char m String
- stringIgnoreCase :: forall (m :: Type -> Type). Monad m => String -> Parser Char m String
- dropSpace :: forall (m :: Type -> Type). Monad m => Parser Char m ()
- dropSpace1 :: forall (m :: Type -> Type). Monad m => Parser Char m ()
- decimal :: forall (m :: Type -> Type) a. (Monad m, Integral a) => Parser Char m a
- hexadecimal :: forall (m :: Type -> Type) a. (Monad m, Integral a, Bits a) => Parser Char m a
- double :: forall (m :: Type -> Type). Monad m => Parser Char m Double
- signed :: forall a (m :: Type -> Type). (Num a, Monad m) => Parser Char m a -> Parser Char m a
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.Data.Stream as Stream (parsePos)>>>import qualified Streamly.Internal.Unicode.Parser as Unicode (number, mkDouble)
Single Chars
char :: forall (m :: Type -> Type). Monad m => Char -> Parser Char m Char Source #
Match a specific character.
charIgnoreCase :: forall (m :: Type -> Type). Monad m => Char -> Parser Char m Char Source #
Match a specific character ignoring case.
alpha :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isAlpha
alphaNum :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isAlphaNum
letter :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isLetter
ascii :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isAscii
asciiLower :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isAsciiLower
asciiUpper :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isAsciiUpper
latin1 :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isLatin1
lower :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isLower
upper :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isUpper
mark :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isMark
printable :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isPrint
punctuation :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isPunctuation
separator :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isSeparator
space :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isSpace
symbol :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isSymbol
digit :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isDigit
octDigit :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isOctDigit
hexDigit :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isHexDigit
numeric :: forall (m :: Type -> Type). Monad m => Parser Char m Char Source #
Match any character that satisfies isNumber
Char Sequences
string :: forall (m :: Type -> Type). Monad m => String -> Parser Char m String Source #
Match the input with the supplied string and return it if successful.
stringIgnoreCase :: forall (m :: Type -> Type). Monad m => String -> Parser Char m String Source #
Match the input with the supplied string and return it if successful.
dropSpace :: forall (m :: Type -> Type). Monad m => Parser Char m () Source #
Drop zero or more white space characters.
dropSpace1 :: forall (m :: Type -> Type). Monad m => Parser Char m () Source #
Drop one or more white space characters.
Digit Sequences (Numbers)
decimal :: forall (m :: Type -> Type) a. (Monad m, Integral a) => Parser Char m a Source #
Parse and decode an unsigned integral decimal number.
hexadecimal :: forall (m :: Type -> Type) a. (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.
double :: forall (m :: Type -> Type). 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.parsePos 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 (ParseErrorPos 0 "number: expecting sign or decimal digit, got end of input")
>>>p ".1"Left (ParseErrorPos 1 "number: expecting sign or decimal digit, got '.'")
>>>p "+"Left (ParseErrorPos 1 "number: expecting decimal digit, got end of input")