License | BSD-3-Clause |
---|---|
Maintainer | Jamie Willis |
Stability | unstable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Since: 0.1.0.0
Synopsis
- class (InputPrep input, Ops input) => Input input
- eval :: forall input a. (Input input, Trace, ?flags :: Flags) => Code input -> (LetBinding input a a, DMap MVar (LetBinding input a)) -> Code (Maybe a)
- data Coins = Coins {
- willConsume :: !Int
- willCache :: !Int
- knownPreds :: !(Maybe CharPred)
- pattern Zero :: Coins
- items :: Int -> Coins
- minCoins :: Coins -> Coins -> Coins
- plus1 :: CharPred -> Coins -> Coins
- minus :: Coins -> Int -> Coins
- module Parsley.Internal.Backend.Machine.Instructions
- user :: Defunc a -> Defunc a
- module Parsley.Internal.Backend.Machine.Identifiers
- data LetBinding o a x
- makeLetBinding :: Binding o a x -> Set SomeΣVar -> Metadata -> LetBinding o a x
- newMeta :: Metadata
Documentation
class (InputPrep input, Ops input) => Input input Source #
This class is exposed to parsley itself and is used to denote which types may be used as input for a parser.
Since: 0.1.0.0
Instances
Input ByteString Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input ByteString Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input CharList Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input Stream Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input Text16 Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input Text Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input String Source # | |
Defined in Parsley.Internal.Backend.Machine | |
Input (UArray Int Char) Source # | |
Defined in Parsley.Internal.Backend.Machine |
eval :: forall input a. (Input input, Trace, ?flags :: Flags) => Code input -> (LetBinding input a a, DMap MVar (LetBinding input a)) -> Code (Maybe a) Source #
This function is exposed to parsley itself and is used to generate the Haskell code for a parser.
Since: 0.1.0.0
Packages together the known input that can be consumed after a length-check with the number of characters that can be rewound on a lookahead backtrack.
Since: 1.5.0.0
Coins | |
|
minCoins :: Coins -> Coins -> Coins Source #
Takes the pairwise min of two Coins
values.
Since: 1.5.0.0
user :: Defunc a -> Defunc a Source #
Promotes a Defunc
value from the Frontend API into a Backend one.
Since: 1.1.0.0
data LetBinding o a x Source #
Packages a binding along with its free registers that are required
for it, which are left existential. This is possible since the Regs
datatype serves as a singleton-style witness of the original registers
and their types. It also requires Metadata
to be provided, sourced
from analysis.
Since: 1.5.0.0
makeLetBinding :: Binding o a x -> Set SomeΣVar -> Metadata -> LetBinding o a x Source #
Given a Binding
, a set of existential ΣVar
s, and some Metadata
, produces a
LetBinding
instance.
Since: 1.5.0.0