Safe Haskell | None |
---|---|
Language | Haskell2010 |
This is an internal module. You probably don't need to import this.
WARNING
Definitions in this module allow violating invariants that would otherwise be guaranteed by non-internal modules. Use at your own risk!
Synopsis
- data Parser c a where
- PToken :: forall c a. !(c -> Maybe a) -> Parser c a
- PFmap :: forall a1 a c. !Strictness -> !(a1 -> a) -> !(Parser c a1) -> Parser c a
- PFmap_ :: forall c a. !(Node c a) -> Parser c a
- PPure :: forall a c. a -> Parser c a
- PLiftA2 :: forall a1 a2 a c. !Strictness -> !(a1 -> a2 -> a) -> !(Parser c a1) -> !(Parser c a2) -> Parser c a
- PEmpty :: forall c a. Parser c a
- PAlt :: forall c a. !Unique -> !(Parser c a) -> !(Parser c a) -> !(SmallArray (Parser c a)) -> Parser c a
- PFoldGr :: forall a a1 c. !Unique -> !Strictness -> !(a -> a1 -> a) -> a -> !(Parser c a1) -> Parser c a
- PFoldMn :: forall a a1 c. !Unique -> !Strictness -> !(a -> a1 -> a) -> a -> !(Parser c a1) -> Parser c a
- PMany :: forall a1 a a2 c. !Unique -> !(a1 -> a) -> !(a2 -> a) -> !(a2 -> a1 -> a2) -> !a2 -> !(Parser c a1) -> Parser c a
- data Node c a where
- compile :: RE c a -> Parser c a
- compileBounded :: Int -> RE c a -> Maybe (Parser c a)
- data ParserState c a
- prepareParser :: Parser c a -> Maybe (ParserState c a)
- stepParser :: ParserState c a -> c -> Maybe (ParserState c a)
- finishParser :: ParserState c a -> Maybe a
- type Foldr f a = forall b. (a -> b -> b) -> b -> f -> b
- parseFoldr :: Foldr f c -> Parser c a -> f -> Maybe a
- parseNext :: Monad m => Parser c a -> m (Maybe c) -> m (Maybe a)
Documentation
data Parser c a where Source #
A parser compiled from a
.RE
c a
PToken :: forall c a. !(c -> Maybe a) -> Parser c a | |
PFmap :: forall a1 a c. !Strictness -> !(a1 -> a) -> !(Parser c a1) -> Parser c a | |
PFmap_ :: forall c a. !(Node c a) -> Parser c a | |
PPure :: forall a c. a -> Parser c a | |
PLiftA2 :: forall a1 a2 a c. !Strictness -> !(a1 -> a2 -> a) -> !(Parser c a1) -> !(Parser c a2) -> Parser c a | |
PEmpty :: forall c a. Parser c a | |
PAlt :: forall c a. !Unique -> !(Parser c a) -> !(Parser c a) -> !(SmallArray (Parser c a)) -> Parser c a | |
PFoldGr :: forall a a1 c. !Unique -> !Strictness -> !(a -> a1 -> a) -> a -> !(Parser c a1) -> Parser c a | |
PFoldMn :: forall a a1 c. !Unique -> !Strictness -> !(a -> a1 -> a) -> a -> !(Parser c a1) -> Parser c a | |
PMany :: forall a1 a a2 c. !Unique -> !(a1 -> a) -> !(a2 -> a) -> !(a2 -> a1 -> a2) -> !a2 -> !(Parser c a1) -> Parser c a |
A node in the NFA. Used for recognition.
compile :: RE c a -> Parser c a Source #
\(O(m)\). Compile a RE c a
to a Parser c a
.
Note: compile
does not limit the size of the RE
. See compileBounded
if you would like to limit the size.
RE
s with size greater than (maxBound::Int) `div` 2
are not supported
and the behavior of such a RE
is undefined.
compileBounded :: Int -> RE c a -> Maybe (Parser c a) Source #
\(O(\min(l,m))\). Compile a RE c a
to a Parser c a
.
Returns Nothing
if the size of the RE
is greater than the provided limit
\(l\). You may want to use this if you suspect that the RE
may be too
large, for instance if the regex is constructed from an untrusted source.
While the exact size of a RE
depends on an internal representation, it can
be assumed to be in the same order as the length of a
regex pattern
corresponding to the RE
.
data ParserState c a Source #
The state maintained for parsing.
prepareParser :: Parser c a -> Maybe (ParserState c a) Source #
\(O(m \log m)\). Prepare a parser for input.
Returns Nothing
if parsing has failed regardless of further input.
Otherwise, returns the initial ParserState
.
stepParser :: ParserState c a -> c -> Maybe (ParserState c a) Source #
\(O(m \log m)\). Step a parser by feeding a single element c
.
Returns Nothing
if parsing has failed regardless of further input.
Otherwise, returns an updated ParserState
.
finishParser :: ParserState c a -> Maybe a Source #
\(O(1)\). Get the parse result for the input fed into the parser so far.
parseFoldr :: Foldr f c -> Parser c a -> f -> Maybe a Source #
\(O(mn \log m)\). Run a parser given a sequence f
and a fold function.
Parses the entire sequence, not just a prefix or an substring. Returns early on parse failure, if the fold can short circuit.
Examples
import qualified Data.Vector.Generic as VG -- from vector
import Regex.Base (Parser)
import qualified Regex.Base as R
parseVector :: VG.Vector v c => Parser c a -> v c -> Maybe a
parseVector p v = R.parseFoldr
VG.foldr p v
>>>
import Control.Applicative (many)
>>>
import qualified Data.Vector as V
>>>
import Regex.Base (Parser)
>>>
import qualified Regex.Base as R
>>>
>>>
let p = R.compile $ many ((,) <$> R.satisfy even <*> R.satisfy odd) :: Parser Int [(Int, Int)]
>>>
parseVector p (V.fromList [0..5])
Just [(0,1),(2,3),(4,5)]>>>
parseVector p (V.fromList [0,2..6])
Nothing
parseNext :: Monad m => Parser c a -> m (Maybe c) -> m (Maybe a) Source #
\(O(mn \log m)\). Run a parser given a "next
" action.
Calls next
repeatedly to yield elements. A Nothing
is interpreted as
end-of-sequence.
Parses the entire sequence, not just a prefix or an substring. Returns without exhausting the input on parse failure.
Examples
import Conduit (ConduitT, await, sinkNull) -- from conduit
import Regex.Base (Parser)
import qualified Regex.Base as R
parseConduit :: Monad m => Parser c a -> ConduitT c x m (Maybe a)
parseConduit p = R.parseNext
p await <* sinkNull
>>>
import Control.Applicative (many)
>>>
import Conduit ((.|), iterMC, runConduit, yieldMany)
>>>
import Regex.Base (Parser)
>>>
import qualified Regex.Base as R
>>>
>>>
let p = R.compile $ many ((,) <$> R.satisfy even <*> R.satisfy odd) :: Parser Int [(Int, Int)]
>>>
let printYieldMany xs = yieldMany xs .| iterMC print
>>>
runConduit $ printYieldMany [0..5] .| parseConduit p
0 1 2 3 4 5 Just [(0,1),(2,3),(4,5)]>>>
runConduit $ printYieldMany [0,2..6] .| parseConduit p
0 2 4 6 Nothing
Since: 0.2.0.0