Safe Haskell | None |
---|---|
Language | Haskell2010 |
Haskus.Utils.Parser
Description
Tools to write parsers using Flows
Synopsis
- data ParseError
- data Choice a = Choice
- choice :: forall m fs zs. (Monad m, HFoldl (Choice ParseError) (Flow m '[ParseError]) fs (Flow m zs)) => HList fs -> Flow m zs
- choice' :: forall a m fs zs. (Monad m, HFoldl (Choice a) (Flow m '[a]) fs (Flow m zs)) => HList fs -> Flow m zs
- manyBounded :: forall zs xs m. (zs ~ Remove ParseError xs, Monad m, ParseError :<? xs) => Maybe Word -> Maybe Word -> Flow m xs -> Flow m '[[V zs], ParseError]
- manyAtMost :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> Flow m '[[V zs]]
- manyAtMost' :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> m [V zs]
- manyAtMost'' :: ('[x] ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> m [x]
- many :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Flow m xs -> Flow m '[[V zs]]
- manyAtLeast :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> Flow m '[[V zs], ParseError]
- manyTill :: (zs ~ Remove ParseError xs, zs' ~ Remove ParseError ys, Monad m, ParseError :<? xs, ParseError :< ys) => Flow m xs -> Flow m ys -> Flow m '[([V zs], V zs'), ParseError]
- manyTill' :: (zs ~ Remove ParseError xs, Monad m, ParseError :<? xs, ParseError :< ys) => Flow m xs -> Flow m ys -> Flow m '[[V zs], ParseError]
Documentation
data ParseError Source #
Parser error
Constructors
SyntaxError | |
EndOfInput |
Instances
Eq ParseError Source # | |
Defined in Haskus.Utils.Parser | |
Show ParseError Source # | |
Defined in Haskus.Utils.Parser Methods showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # |
Constructors
Choice |
choice :: forall m fs zs. (Monad m, HFoldl (Choice ParseError) (Flow m '[ParseError]) fs (Flow m zs)) => HList fs -> Flow m zs Source #
Try to apply the actions in the list in order, until one of them succeeds. Returns the value of the succeeding action, or the value of the last one. Failures are detected with values of type ParseError.
choice' :: forall a m fs zs. (Monad m, HFoldl (Choice a) (Flow m '[a]) fs (Flow m zs)) => HList fs -> Flow m zs Source #
Try to apply the actions in the list in order, until one of them succeeds. Returns the value of the succeeding action, or the value of the last one. Failures are detected with values of type "a".
manyBounded :: forall zs xs m. (zs ~ Remove ParseError xs, Monad m, ParseError :<? xs) => Maybe Word -> Maybe Word -> Flow m xs -> Flow m '[[V zs], ParseError] Source #
Apply the given action at least min
times and at most max
time
On failure, fails.
manyAtMost :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> Flow m '[[V zs]] Source #
Apply the action zero or more times (up to max) until a ParseError result is returned
manyAtMost' :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> m [V zs] Source #
Apply the action zero or more times (up to max) until a ParseError result is returned
manyAtMost'' :: ('[x] ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> m [x] Source #
Apply the action zero or more times (up to max) until a ParseError result is returned
many :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Flow m xs -> Flow m '[[V zs]] Source #
Apply the action zero or more times (until a ParseError result is returned)
manyAtLeast :: (zs ~ Remove ParseError xs, Monad m, ParseError :< xs) => Word -> Flow m xs -> Flow m '[[V zs], ParseError] Source #
Apply the action at least n times or more times (until a ParseError result is returned)
manyTill :: (zs ~ Remove ParseError xs, zs' ~ Remove ParseError ys, Monad m, ParseError :<? xs, ParseError :< ys) => Flow m xs -> Flow m ys -> Flow m '[([V zs], V zs'), ParseError] Source #
Apply the first action zero or more times until the second succeeds. If the first action fails, the whole operation fails.
Return both the list of first values and the ending value
manyTill' :: (zs ~ Remove ParseError xs, Monad m, ParseError :<? xs, ParseError :< ys) => Flow m xs -> Flow m ys -> Flow m '[[V zs], ParseError] Source #
Apply the first action zero or more times until the second succeeds. If the first action fails, the whole operation fails.
Return only the list of first values