Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data PCOptions = PCOptions {
- left_biased_choice :: Bool
- pivot_select :: Maybe (Int -> Int -> Ordering)
- pivot_select_nt :: Bool
- throw_errors :: Bool
- do_memo :: Bool
- max_errors :: Int
- nt_select_test :: Bool
- alt_select_test :: Bool
- seq_select_test :: Bool
- type CombinatorOptions = [CombinatorOption]
- type CombinatorOption = PCOptions -> PCOptions
- runOptions :: CombinatorOptions -> PCOptions
- runOptionsOn :: PCOptions -> CombinatorOptions -> PCOptions
- defaultOptions :: PCOptions
- maximumPivot :: CombinatorOption
- minimumPivot :: CombinatorOption
- anyPivot :: CombinatorOption
- maximumPivotAtNt :: CombinatorOption
- maximumErrors :: Int -> CombinatorOption
- throwErrors :: CombinatorOption
- leftBiased :: CombinatorOption
- useMemoisation :: CombinatorOption
- maximumsWith :: (a -> a -> Ordering) -> [a] -> [a]
- maintainWith :: Eq k => (k -> k -> Ordering) -> [[(k, a)]] -> [[(k, a)]]
- doSelectTest :: CombinatorOption
- noSelectTest :: CombinatorOption
- doAltSelectTest :: CombinatorOption
- noAltSelectTest :: CombinatorOption
- doNtSelectTest :: CombinatorOption
- noNtSelectTest :: CombinatorOption
- doSlotSelectTest :: CombinatorOption
- noSlotSelectTest :: CombinatorOption
Documentation
CombinatorOptions datatype
* left_biased_choice: see function leftBiased
* pivot_select: provide a filtering function on pivots
PCOptions | |
|
type CombinatorOptions = [CombinatorOption] Source #
A list of CombinatorOption
s for evaluating combinator expressions.
type CombinatorOption = PCOptions -> PCOptions Source #
A single option.
runOptionsOn :: PCOptions -> CombinatorOptions -> PCOptions Source #
defaultOptions :: PCOptions Source #
The default options: no disambiguation.
maximumPivot :: CombinatorOption Source #
Enables a 'longest-match' at production level.
minimumPivot :: CombinatorOption Source #
Enables a 'shortest-match' at production level.
anyPivot :: CombinatorOption Source #
Discards a pivot select option (internal use only)
maximumPivotAtNt :: CombinatorOption Source #
Enables 'longest-match' at non-terminal level.
maximumErrors :: Int -> CombinatorOption Source #
Set the maximum number of errors shown in case of an unsuccessful parse.
throwErrors :: CombinatorOption Source #
If there are no parse results, the default behaviour is to return an empty list. If this option is used, a runtime error will be reported, with debugging information.
leftBiased :: CombinatorOption Source #
Turns all occurrences of <||>
into a 'left biased' variant:
only return results of the second alternate if the first alternate
does not have any results.
useMemoisation :: CombinatorOption Source #
Whether to use unsafe memoisation to speed up the enumeration of parse results.
maximumsWith :: (a -> a -> Ordering) -> [a] -> [a] Source #
Filter a list such that the only remaining elements are equal to the maximum element, given an ordering operator.
maintainWith :: Eq k => (k -> k -> Ordering) -> [[(k, a)]] -> [[(k, a)]] Source #
doSelectTest :: CombinatorOption Source #
Enables select tests at all levels: nonterminal, alternative and slot.
noSelectTest :: CombinatorOption Source #
Disables select tests at all levels: nonterminal, alternative and slot.
doAltSelectTest :: CombinatorOption Source #
Enables select tests at the level of alternatives
noAltSelectTest :: CombinatorOption Source #
Disables select tests at the level of alternatives
doNtSelectTest :: CombinatorOption Source #
Enables select tests at the level of nonterminals
noNtSelectTest :: CombinatorOption Source #
Disables select tests at the level of nonterminals
doSlotSelectTest :: CombinatorOption Source #
Enables select tests at the level of grammar slots
noSlotSelectTest :: CombinatorOption Source #
Disables select tests at the level of grammar slots