parsley-core-2.0.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ImplicitParams
  • ScopedTypeVariables
  • UnboxedTuples
  • BangPatterns
  • GADTs
  • GADTSyntax
  • PolyKinds
  • DataKinds
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • 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 where 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

Methods

prepare :: rep ~ Rep input => Code input -> Code (InputDependant rep) Source #

Given the user's input to the parser, in its original form, this function distils it first into Rep input, which is parsley's internal representation, and then produces an InputDependant containing the core operations.

Since: 1.0.0.0

Instances

Instances details
InputPrep ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind ByteString)). rep ~ Rep ByteString => Code ByteString -> Code (InputDependant rep) Source #

InputPrep ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind ByteString)). rep ~ Rep ByteString => Code ByteString -> Code (InputDependant rep) Source #

InputPrep Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind Text)). rep ~ Rep Text => Code Text -> Code (InputDependant rep) Source #

InputPrep Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind Stream)). rep ~ Rep Stream => Code Stream -> Code (InputDependant rep) Source #

InputPrep CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind CharList)). rep ~ Rep CharList => Code CharList -> Code (InputDependant rep) Source #

InputPrep Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind Text16)). rep ~ Rep Text16 => Code Text16 -> Code (InputDependant rep) Source #

InputPrep [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind [Char])). rep ~ Rep [Char] => Code [Char] -> Code (InputDependant rep) Source #

InputPrep (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind (UArray Int Char))). rep ~ Rep (UArray Int Char) => Code (UArray Int Char) -> Code (InputDependant rep) Source #

class PositionOps (rep :: TYPE r) 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 :: Code rep -> Code 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

shiftRight :: Code rep -> Code Int# -> Code rep 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: 1.0.0.0

class LogOps (rep :: TYPE r) where Source #

Defines operation used for debugging operations.

Since: 1.0.0.0

Methods

shiftLeft :: Code rep -> Code Int# -> Code rep 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

offToInt :: Code rep -> Code Int Source #

Converts the represention of the input into an Int.

Since: 1.0.0.0

data InputOps (rep :: TYPE r) Source #

This is a psuedo-typeclass, which depends directly on the values obtained from InputDependant. Because this instance must depend on local information, it is synthesised and passed around using ImplicitParams.

Since: 1.0.0.0

Constructors

InputOps 

Fields

  • _more :: Code (rep -> Bool)

    Does the input have any more characters?

  • _next :: Code (rep -> (# Char, rep #))

    Read the next character (without checking existence)

more :: forall r (rep :: TYPE r). (?ops :: InputOps rep) => Code rep -> Code Bool Source #

Wraps around InputOps and _more.

Queries the input to see if another character may be consumed.

Since: 1.4.0.0

next :: forall r (rep :: TYPE r) a. (?ops :: InputOps rep) => Code rep -> (Code Char -> Code 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

type InputDependant (rep :: TYPE r) = (# rep -> (# Char, rep #), rep -> Bool, rep #) Source #

Given some associated representation type, defines the operations that work with a closed over instance of that type. These are:

  • next: extract the next character from the input (existence not included)
  • more: query whether another character can be read
  • init: the initial state of the input.

Since: 1.0.0.0