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