module GLL.Flags where

-- | Flags to influence the behaviour of the parser.
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
                        }

-- | The default flags:
-- * Do not add symbol nodes to the 'SPPF'.
-- * Do not add intermediate nodes to the 'SPPF'.
-- * Do not add edges to the 'SPPF'.
-- * Flexible binarisation.
-- * The three furthest discoveries of a token mismatch are reported. 
-- * Select tests are performed.
defaultFlags :: Flags
defaultFlags = Bool -> Bool -> Bool -> Bool -> Int -> Bool -> Flags
Flags Bool
False Bool
False Bool
False Bool
True Int
3 Bool
True

-- | Execute the given 'Options' in left-to-right order on 'defaultFlags'.
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

-- | An option updates the current set of 'Flags'.
type ParseOption = Flags -> Flags

-- | A list of 'ParserOption's
type ParseOptions = [ParseOption]

-- | 
-- Create the 'SPPF' with all nodes and edges, not necessarily strictly binarised.
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}

-- |
-- Create all nodes, but no edges between nodes.
allNodes :: ParseOption
allNodes :: ParseOption
allNodes Flags
flags = Flags
flags{symbol_nodes :: Bool
symbol_nodes = Bool
True, intermediate_nodes :: Bool
intermediate_nodes = Bool
True}

-- | 
-- Create packed-nodes only.
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}

-- | 
-- Fully binarise the SPPF, resulting in a larger 'SPPF' and possibly slower runtimes.
-- When this flag is on, packed nodes can only have a single symbol node child 
-- or one intermediate node child and one symbol node child.
-- With the flag disabled a packed node can have two symbol node children.
strictBinarisation :: ParseOption
strictBinarisation :: ParseOption
strictBinarisation Flags
flags = Flags
flags{flexible_binarisation :: Bool
flexible_binarisation = Bool
False}

-- | 
-- Set the maximum number of errors shown in case of an unsuccessful parse.
maximumErrors :: Int -> ParseOption
maximumErrors :: Int -> ParseOption
maximumErrors Int
n Flags
flags = Flags
flags {max_errors :: Int
max_errors = Int
n}

-- |
-- Turn of select tests. Disables lookahead.
noSelectTest :: ParseOption
noSelectTest :: ParseOption
noSelectTest Flags
flags = Flags
flags{do_select_test :: Bool
do_select_test = Bool
False}