Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Parser s a
- class KnownBase (s :: Type)
- parse :: (forall s. KnownBase s => Parser s a) -> ByteString -> Either Location a
- try :: Parser s a -> Parser s a
- atEnd :: Parser s Bool
- endOfInput :: Parser s ()
- tillSubstring :: KnownBase s => ByteString -> Parser s ByteString
- skipTillSubstring :: ByteString -> Parser s ()
- skip :: forall s. KnownBase s => Int -> Parser s ()
- skip0 :: Int -> Parser s ()
- take :: forall s. KnownBase s => Int -> Parser s ByteString
- data Mark s
- mark :: Parser s (Mark s)
- release :: Mark s -> Parser s ()
- snip :: forall s. KnownBase s => Mark s -> Mark s -> ByteString
- snipping :: forall s a. KnownBase s => Parser s a -> Parser s ByteString
- input :: KnownBase s => Parser s ByteString
- pos :: forall s. KnownBase s => Parser s Int
- betwixt :: forall s. KnownBase s => Int -> Int -> ByteString
- rest :: KnownBase s => Parser s ByteString
- loc :: KnownBase s => Parser s Location
Documentation
Instances
Monad (Parser s) Source # | |
Functor (Parser s) Source # | |
Applicative (Parser s) Source # | |
Alternative (Parser s) Source # | |
MonadPlus (Parser s) Source # | |
PrimMonad (Parser s) Source # | |
a ~ ByteString => IsString (Parser s a) Source # | |
Defined in Text.Parsnip.Internal.Parser fromString :: String -> Parser s a # | |
type PrimState (Parser s) Source # | |
Defined in Text.Parsnip.Internal.Parser type PrimState (Parser s) = s |
endOfInput :: Parser s () Source #
tillSubstring :: KnownBase s => ByteString -> Parser s ByteString Source #
skipTillSubstring :: ByteString -> Parser s () Source #
skip :: forall s. KnownBase s => Int -> Parser s () Source #
We can do this two ways, this way is O(1) but needs KnownBase.
snip :: forall s. KnownBase s => Mark s -> Mark s -> ByteString Source #
To grab all the text covered by a given parser, consider using snipping
and applying it to a combinator simply recognizes the content rather than returns
it. snipping
a ByteString
is significantly cheaper than assembling one from
smaller fragments.
betwixt :: forall s. KnownBase s => Int -> Int -> ByteString Source #
snip
is a smidge faster, easier to type, if less fun to say, and
doesn't need you to fiddle with explicit type application to actually
apply.
The benefit of this combinator is that it is easy to come up with numbers
of bytes into a file, and this combinator will automatically trim the
result to the actual range of bytes available, whereas constructing an
illegal Mark
will error in toEnum
fromEnum
succ
or whatever other
combinator tries to produce one out of range to maintain the invariant
that a mark is always a well formed location in the content.