parsley-core-2.3.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ImplicitParams
  • ScopedTypeVariables
  • AllowAmbiguousTypes
  • UnboxedTuples
  • BangPatterns
  • DisambiguateRecordFields
  • RecordWildCards
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • PolyKinds
  • DataKinds
  • InstanceSigs
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • MagicHash
  • KindSignatures
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • TypeApplications

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

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

Instances details
InputPrep ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep ByteString => Code ByteString -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep ByteString => Code ByteString -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep CharList => Code CharList -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep Stream => Code Stream -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep Text16 => Code Text16 -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep Text => Code Text -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep String Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep String => Code String -> (InputOps starep -> starep -> Code r) -> Code r

InputPrep (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep (UArray Int Char) => Code (UArray Int Char) -> (InputOps starep -> starep -> Code r) -> Code r

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

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

Instances details
LogOps PartialStaOffset Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

LogOps PartialStaText Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

LogOps (PartialStaOffWith Stream) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

LogOps (PartialStaOffWith String) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

LogOps (Code UnpackedLazyByteString) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

type DynOps o = DynOps_ (DynRep o) (StaRep o) Source #

asDyn :: forall input. DynOps input => StaRep input -> Code (DynRep input) Source #

asSta :: forall input. DynOps input => Code (DynRep input) -> StaRep input Source #

data InputOps rep Source #

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 #

uncons :: forall rep a. (?ops :: InputOps rep) => rep -> (Code Char -> rep -> Code a) -> Code a -> Code a Source #

prepare :: InputPrep input => Code input -> ((?ops :: InputOps (StaRep input)) => StaRep input -> Code r) -> Code r Source #