module GLL.Combinators.Options where
import Data.Function (on)
data PCOptions = PCOptions  { PCOptions -> Bool
left_biased_choice    :: Bool
                            , PCOptions -> Maybe (Int -> Int -> Ordering)
pivot_select          :: Maybe (Int -> Int -> Ordering)
                            , PCOptions -> Bool
pivot_select_nt       :: Bool
                            , PCOptions -> Bool
throw_errors          :: Bool
                            , PCOptions -> Bool
do_memo               :: Bool
                            , PCOptions -> Int
max_errors            :: Int
                            , PCOptions -> Bool
nt_select_test        :: Bool
                            , PCOptions -> Bool
alt_select_test       :: Bool
                            , PCOptions -> Bool
seq_select_test       :: Bool
                            }
type CombinatorOptions    = [CombinatorOption]
type CombinatorOption     = PCOptions -> PCOptions
runOptions :: CombinatorOptions -> PCOptions
runOptions :: CombinatorOptions -> PCOptions
runOptions = PCOptions -> CombinatorOptions -> PCOptions
runOptionsOn PCOptions
defaultOptions
runOptionsOn :: PCOptions -> CombinatorOptions -> PCOptions 
runOptionsOn :: PCOptions -> CombinatorOptions -> PCOptions
runOptionsOn = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a b. (a -> b) -> a -> b
($)
defaultOptions :: PCOptions
defaultOptions :: PCOptions
defaultOptions = Bool
-> Maybe (Int -> Int -> Ordering)
-> Bool
-> Bool
-> Bool
-> Int
-> Bool
-> Bool
-> Bool
-> PCOptions
PCOptions Bool
False forall a. Maybe a
Nothing Bool
False Bool
False Bool
False Int
3 Bool
True Bool
True Bool
True
maximumPivot :: CombinatorOption
maximumPivot :: CombinatorOption
maximumPivot PCOptions
opts = PCOptions
opts {pivot_select :: Maybe (Int -> Int -> Ordering)
pivot_select = forall a. a -> Maybe a
Just forall a. Ord a => a -> a -> Ordering
compare}
minimumPivot :: CombinatorOption
minimumPivot :: CombinatorOption
minimumPivot PCOptions
opts = PCOptions
opts {pivot_select :: Maybe (Int -> Int -> Ordering)
pivot_select = forall a. a -> Maybe a
Just (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> a -> Ordering
compare)}
anyPivot :: CombinatorOption
anyPivot :: CombinatorOption
anyPivot PCOptions
opts = PCOptions
opts {pivot_select :: Maybe (Int -> Int -> Ordering)
pivot_select = forall a. Maybe a
Nothing}
maximumPivotAtNt :: CombinatorOption
maximumPivotAtNt :: CombinatorOption
maximumPivotAtNt PCOptions
opts = PCOptions
opts {pivot_select_nt :: Bool
pivot_select_nt = Bool
True, pivot_select :: Maybe (Int -> Int -> Ordering)
pivot_select = forall a. a -> Maybe a
Just forall a. Ord a => a -> a -> Ordering
compare}
maximumErrors :: Int -> CombinatorOption
maximumErrors :: Int -> CombinatorOption
maximumErrors Int
n PCOptions
opts = PCOptions
opts { max_errors :: Int
max_errors = Int
n }
throwErrors :: CombinatorOption
throwErrors :: CombinatorOption
throwErrors PCOptions
opts = PCOptions
opts{throw_errors :: Bool
throw_errors = Bool
True}
leftBiased :: CombinatorOption
leftBiased :: CombinatorOption
leftBiased PCOptions
opts = PCOptions
opts { left_biased_choice :: Bool
left_biased_choice = Bool
True }
useMemoisation :: CombinatorOption
useMemoisation :: CombinatorOption
useMemoisation PCOptions
opts = PCOptions
opts { do_memo :: Bool
do_memo = Bool
True }
maximumsWith :: (a -> a -> Ordering) -> [a] -> [a]
maximumsWith :: forall a. (a -> a -> Ordering) -> [a] -> [a]
maximumsWith a -> a -> Ordering
compare [a]
xs = 
    case [a]
xs of
    []      -> []
    [a
x]     -> [a
x]
    a
x:[a]
xs    -> [a] -> a -> [a] -> [a]
maxx [a]
xs a
x []
 where  maxx :: [a] -> a -> [a] -> [a]
maxx []     a
x [a]
acc = a
x forall a. a -> [a] -> [a]
: [a]
acc
        maxx (a
y:[a]
ys) a
x [a]
acc = case a
y a -> a -> Ordering
`compare` a
x of
                            Ordering
LT -> [a] -> a -> [a] -> [a]
maxx [a]
ys a
x [a]
acc
                            Ordering
GT -> [a] -> a -> [a] -> [a]
maxx [a]
ys a
y []
                            Ordering
EQ -> [a] -> a -> [a] -> [a]
maxx [a]
ys a
y (a
xforall a. a -> [a] -> [a]
:[a]
acc)
maintainWith :: (Eq k) => (k -> k -> Ordering) -> [[(k,a)]] -> [[(k,a)]]
maintainWith :: forall k a.
Eq k =>
(k -> k -> Ordering) -> [[(k, a)]] -> [[(k, a)]]
maintainWith k -> k -> Ordering
compare = 
    forall {b}. [[(k, b)]] -> [[(k, b)]]
maintain forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null)
 where  maintain :: [[(k, b)]] -> [[(k, b)]]
maintain [[(k, b)]]
xss = 
            let (k
max,b
_):[(k, b)]
_ = forall a. (a -> a -> Ordering) -> [a] -> [a]
maximumsWith (k -> k -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> a
head [[(k, b)]]
xss
             in (forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== k
max) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head) [[(k, b)]]
xss)
doSelectTest :: CombinatorOption
doSelectTest :: CombinatorOption
doSelectTest PCOptions
opts = PCOptions
opts { nt_select_test :: Bool
nt_select_test = Bool
True, alt_select_test :: Bool
alt_select_test = Bool
True
                         , seq_select_test :: Bool
seq_select_test = Bool
True }
noSelectTest :: CombinatorOption
noSelectTest :: CombinatorOption
noSelectTest PCOptions
opts = PCOptions
opts { nt_select_test :: Bool
nt_select_test = Bool
False, alt_select_test :: Bool
alt_select_test = Bool
False
                         , seq_select_test :: Bool
seq_select_test = Bool
False }
doAltSelectTest :: CombinatorOption
doAltSelectTest :: CombinatorOption
doAltSelectTest PCOptions
opts = PCOptions
opts { alt_select_test :: Bool
alt_select_test = Bool
True }
noAltSelectTest :: CombinatorOption
noAltSelectTest :: CombinatorOption
noAltSelectTest PCOptions
opts = PCOptions
opts { alt_select_test :: Bool
alt_select_test = Bool
False }
doNtSelectTest :: CombinatorOption
doNtSelectTest :: CombinatorOption
doNtSelectTest PCOptions
opts = PCOptions
opts { nt_select_test :: Bool
nt_select_test = Bool
True }
noNtSelectTest :: CombinatorOption
noNtSelectTest :: CombinatorOption
noNtSelectTest PCOptions
opts = PCOptions
opts { nt_select_test :: Bool
nt_select_test = Bool
False }
doSlotSelectTest :: CombinatorOption
doSlotSelectTest :: CombinatorOption
doSlotSelectTest PCOptions
opts = PCOptions
opts { seq_select_test :: Bool
seq_select_test = Bool
True }
noSlotSelectTest :: CombinatorOption
noSlotSelectTest :: CombinatorOption
noSlotSelectTest PCOptions
opts = PCOptions
opts { seq_select_test :: Bool
seq_select_test = Bool
False }