module GLL.Flags where
data Flags = Flags { Flags -> Bool
symbol_nodes :: Bool
, Flags -> Bool
intermediate_nodes :: Bool
, Flags -> Bool
edges :: Bool
, Flags -> Bool
flexible_binarisation :: Bool
, Flags -> Int
max_errors :: Int
, Flags -> Bool
do_select_test :: Bool
}
defaultFlags :: Flags
defaultFlags = Bool -> Bool -> Bool -> Bool -> Int -> Bool -> Flags
Flags Bool
False Bool
False Bool
False Bool
True Int
3 Bool
True
runOptions :: ParseOptions -> Flags
runOptions :: ParseOptions -> Flags
runOptions = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a b. (a -> b) -> a -> b
($) Flags
defaultFlags
type ParseOption = Flags -> Flags
type ParseOptions = [ParseOption]
fullSPPF :: ParseOption
fullSPPF :: ParseOption
fullSPPF Flags
flags = Flags
flags{symbol_nodes :: Bool
symbol_nodes = Bool
True, intermediate_nodes :: Bool
intermediate_nodes = Bool
True, edges :: Bool
edges = Bool
True}
allNodes :: ParseOption
allNodes :: ParseOption
allNodes Flags
flags = Flags
flags{symbol_nodes :: Bool
symbol_nodes = Bool
True, intermediate_nodes :: Bool
intermediate_nodes = Bool
True}
packedNodesOnly :: ParseOption
packedNodesOnly :: ParseOption
packedNodesOnly Flags
flags = Flags
flags{symbol_nodes :: Bool
symbol_nodes = Bool
False, intermediate_nodes :: Bool
intermediate_nodes = Bool
False, edges :: Bool
edges = Bool
False}
strictBinarisation :: ParseOption
strictBinarisation :: ParseOption
strictBinarisation Flags
flags = Flags
flags{flexible_binarisation :: Bool
flexible_binarisation = Bool
False}
maximumErrors :: Int -> ParseOption
maximumErrors :: Int -> ParseOption
maximumErrors Int
n Flags
flags = Flags
flags {max_errors :: Int
max_errors = Int
n}
noSelectTest :: ParseOption
noSelectTest :: ParseOption
noSelectTest Flags
flags = Flags
flags{do_select_test :: Bool
do_select_test = Bool
False}