| License | BSD-3-Clause | 
|---|---|
| Maintainer | Jamie Willis | 
| Stability | experimental | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
| Extensions | 
  | 
Parsley.Internal.Backend.Machine.InputOps
Description
This module contains the primitive operations required by the parsing machinery to work with input.
Since: 1.0.0.0
Synopsis
- class InputPrep input
 - class PositionOps rep where
 - class LogOps rep where
 - type DynOps o = DynOps_ (DynRep o) (StaRep o)
 - asDyn :: forall input. DynOps input => StaRep input -> Code (DynRep input)
 - asSta :: forall input. DynOps input => Code (DynRep input) -> StaRep input
 - data InputOps rep
 - next :: forall rep a. (?ops :: InputOps rep) => rep -> (Code Char -> rep -> Code a) -> Code a
 - check :: forall rep a. (?ops :: InputOps rep) => Int -> Int -> rep -> Maybe (Code Char -> Code a -> Code a) -> (rep -> [(Code Char, rep)] -> Code a) -> Code a -> Code a
 - uncons :: forall rep a. (?ops :: InputOps rep) => rep -> (Code Char -> rep -> Code a) -> Code a -> Code a
 - prepare :: InputPrep input => Code input -> ((?ops :: InputOps (StaRep input)) => StaRep input -> Code r) -> Code r
 
Documentation
class InputPrep input Source #
This class is responsible for converting the user's input into a form that parsley can work with efficiently.
Since: 1.0.0.0
Minimal complete definition
_prepare
Instances
| InputPrep ByteString Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods _prepare :: starep ~ StaRep ByteString => Code ByteString -> (InputOps starep -> starep -> Code r) -> Code r  | |
| InputPrep ByteString Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods _prepare :: starep ~ StaRep ByteString => Code ByteString -> (InputOps starep -> starep -> Code r) -> Code r  | |
| InputPrep CharList Source # | |
| InputPrep Stream Source # | |
| InputPrep Text16 Source # | |
| InputPrep Text Source # | |
| InputPrep String Source # | |
| InputPrep (UArray Int Char) Source # | |
class PositionOps rep where Source #
Defines operations for manipulating offsets for regular use. These are not tied to the original captured input but instead to the representation of its offset.
Since: 1.0.0.0
Methods
same :: rep -> rep -> Code Bool Source #
Compares two "input"s for equality. In reality this usually means an offset
  present in the rep.
Since: 1.0.0.0
Instances
| PositionOps PartialStaOffset Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods same :: PartialStaOffset -> PartialStaOffset -> Code Bool Source #  | |
| PositionOps PartialStaText Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods same :: PartialStaText -> PartialStaText -> Code Bool Source #  | |
| PositionOps (PartialStaOffWith ts) Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods same :: PartialStaOffWith ts -> PartialStaOffWith ts -> Code Bool Source #  | |
| PositionOps (Code UnpackedLazyByteString) Source # | |
Defined in Parsley.Internal.Backend.Machine.InputOps Methods same :: Code UnpackedLazyByteString -> Code UnpackedLazyByteString -> Code Bool Source #  | |
class LogOps rep where Source #
Defines operation used for debugging operations.
Since: 1.0.0.0
Methods
shiftLeft :: rep -> Int -> (rep -> Code a) -> Code a Source #
If possible, shifts the input back several characters. This is used to provide the previous input characters for the debugging combinator.
Since: 1.0.0.0
shiftRight :: rep -> Int -> (rep -> Code a) -> Code a Source #
Advances the input by several characters at a time (existence not included).
  This can be used to check if characters exist at a future point in the input
  in conjunction with more.
Since: 2.3.0.0
offToInt :: rep -> Code Int Source #
Converts the represention of the input into an Int.
Since: 1.0.0.0
Instances
This is a psuedo-typeclass, which depends directly on the values obtained from
prepare. Because this instance may depend on local information, it is
synthesised and passed around using ImplicitParams.
Since: 1.0.0.0
next :: forall rep a. (?ops :: InputOps rep) => rep -> (Code Char -> rep -> Code a) -> Code a Source #
Wraps around InputOps and _next.
Given some input and a continuation that accepts new input and a character, it will read a character off (without checking that it exists!) and feeds it and the remaining input to the continuation.
Since: 1.0.0.0
check :: forall rep a. (?ops :: InputOps rep) => Int -> Int -> rep -> Maybe (Code Char -> Code a -> Code a) -> (rep -> [(Code Char, rep)] -> Code a) -> Code a -> Code a Source #