| License | CC0-1.0 |
|---|---|
| Maintainer | mordae@anilinux.org |
| Stability | unstable |
| Portability | non-portable (ghc) |
| Safe Haskell | Safe-Inferred |
| Language | GHC2021 |
Data.Text.Parser
Description
This module provides a parser for Unicode Text.
Synopsis
- newtype Parser a = Parser {}
- parseOnly :: Parser a -> Text -> Maybe a
- char :: Char -> Parser Char
- notChar :: Char -> Parser Char
- anyChar :: Parser Char
- satisfy :: (Char -> Bool) -> Parser Char
- space :: Parser Char
- isSpace :: Char -> Bool
- skipSpace :: Parser ()
- peekChar :: Parser Char
- string :: Text -> Parser Text
- stringCI :: Text -> Parser Text
- take :: Int -> Parser Text
- scan :: s -> (s -> Char -> Maybe s) -> Parser Text
- runScanner :: s -> (s -> Char -> Maybe s) -> Parser (Text, s)
- inRange :: Char -> Char -> Char -> Bool
- notInRange :: Char -> Char -> Char -> Bool
- takeWhile :: (Char -> Bool) -> Parser Text
- takeWhile1 :: (Char -> Bool) -> Parser Text
- takeTill :: (Char -> Bool) -> Parser Text
- takeTill1 :: (Char -> Bool) -> Parser Text
- signed :: Num a => Parser a -> Parser a
- decimal :: Integral a => Parser a
- hexadecimal :: Integral a => Parser a
- octal :: Integral a => Parser a
- fractional :: Fractional a => Parser a
- provided :: (Alternative m, Monad m) => (a -> Bool) -> m a -> m a
- choice :: Alternative f => [f a] -> f a
- count :: Monad m => Int -> m a -> m [a]
- optional :: Alternative f => f a -> f (Maybe a)
- eitherP :: Alternative f => f a -> f b -> f (Either a b)
- option :: Alternative f => a -> f a -> f a
- many :: Alternative f => f a -> f [a]
- many1 :: Alternative f => f a -> f [a]
- manyTill :: Alternative f => f a -> f a -> f [a]
- sepBy :: Alternative f => f a -> f b -> f [a]
- sepBy1 :: Alternative f => f a -> f b -> f [a]
- wrap :: Applicative f => f a -> f b -> f a
- match :: Parser a -> Parser (Text, a)
- takeText :: Parser Text
- endOfInput :: Parser ()
- atEnd :: Parser Bool
- empty :: Alternative f => f a
- pure :: Applicative f => a -> f a
- guard :: Alternative f => Bool -> f ()
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- void :: Functor f => f a -> f ()
Documentation
Characters
Returns True for any Unicode space character, and the control
characters \t, \n, \r, \f, \v.
Strings
runScanner :: s -> (s -> Char -> Maybe s) -> Parser (Text, s) Source #
Like scan, but also returns the final scanner state.
inRange :: Char -> Char -> Char -> Bool Source #
Tests whether the character lies within given range.
Definition:
inRange lo hi = c -> (lo <= c && c <= hi)
Numbers
hexadecimal :: Integral a => Parser a Source #
fractional :: Fractional a => Parser a Source #
Combinators
choice :: Alternative f => [f a] -> f a Source #
Tries various parsers, one by one. Alias for asum.
Example:
pExpression = choice [ pConstant
, pVariable
, pBinaryOperation
, pFunctionApplication
]
count :: Monad m => Int -> m a -> m [a] Source #
Replicates the parser given number of times, collecting the results in a list. Fails if any instance of the parser fails.
Example:
pFourWords = (:) <$> word <*> count 3 (blank *> word)
where word = takeWhile1 isLetter
blank = takeWhile1 isSpace
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative instance of Control.Monad.Except, the following functions:
>>>import Control.Monad.Except
>>>canFail = throwError "it failed" :: Except String Int>>>final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>>runExcept $ canFail *> finalLeft "it failed">>>runExcept $ optional canFail *> finalRight 42
eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #
Captures first parser as Left or the second as Right.
option :: Alternative f => a -> f a -> f a Source #
Shortcut for optional with a default value.
Example:
data Contact =
Contact
{ contactName :: Text
, contactEmail :: Maybe Text
}
pContact = Contact <$> pFullName <*> option pEmail
many :: Alternative f => f a -> f [a] #
Zero or more.
many1 :: Alternative f => f a -> f [a] Source #
Like many1, but requires at least one match.
manyTill :: Alternative f => f a -> f a -> f [a] Source #
sepBy :: Alternative f => f a -> f b -> f [a] Source #
sepBy1 :: Alternative f => f a -> f b -> f [a] Source #
Like sepBy, but requires at least one match.
wrap :: Applicative f => f a -> f b -> f a Source #
Wraps the parser from both sides.
Example:
pToken = takeWhile1 (inClass "A-Za-z0-9_") wrap takeWhile isSpace
End Of Input
endOfInput :: Parser () Source #
Miscelaneous
These are all generic methods, but since I sometimes forget about them, it is nice to have them listed here for reference what writing parsers.
empty :: Alternative f => f a #
The identity of <|>
pure :: Applicative f => a -> f a #
Lift a value.
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative computations. Defined by
guard True =pure() guard False =empty
Examples
Common uses of guard include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative-based parser.
As an example of signaling an error in the error monad Maybe,
consider a safe division function safeDiv x y that returns
Nothing when the denominator y is zero and otherwise. For example:Just (x `div`
y)
>>>safeDiv 4 0Nothing
>>>safeDiv 4 2Just 2
A definition of safeDiv using guards, but not guard:
safeDiv :: Int -> Int -> Maybe Int
safeDiv x y | y /= 0 = Just (x `div` y)
| otherwise = Nothing
A definition of safeDiv using guard and Monad do-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging if the Boolean value debug
is True, and otherwise do nothing.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when.
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void valueIO action.
Examples
Replace the contents of a with unit:Maybe Int
>>>void NothingNothing>>>void (Just 3)Just ()
Replace the contents of an
with unit, resulting in an Either Int Int:Either Int ()
>>>void (Left 8675309)Left 8675309>>>void (Right 8675309)Right ()
Replace every element of a list with unit:
>>>void [1,2,3][(),(),()]
Replace the second element of a pair with unit:
>>>void (1,2)(1,())
Discard the result of an IO action:
>>>mapM print [1,2]1 2 [(),()]>>>void $ mapM print [1,2]1 2