module Options where

import System.Console.GetOpt
import Data.Set(Set)
import UU.Scanner.Position(Pos,noPos)
import Data.List(intercalate)
import qualified Data.Set as Set
import System.IO
import System.Exit

-- From CommonTypes
data Identifier   = Ident { Identifier -> String
getName::String, Identifier -> Pos
getPos::Pos }
type NontermIdent = Identifier
identifier :: String -> Identifier
identifier :: String -> Identifier
identifier String
x      = String -> Pos -> Identifier
Ident String
x Pos
noPos

instance Eq Identifier where
 Ident String
x Pos
_ == :: Identifier -> Identifier -> Bool
== Ident String
y Pos
_ = String
x forall a. Eq a => a -> a -> Bool
== String
y

instance Ord Identifier where
 compare :: Identifier -> Identifier -> Ordering
compare (Ident String
x Pos
_) (Ident String
y Pos
_) = forall a. Ord a => a -> a -> Ordering
compare String
x String
y

instance Show Identifier where
  show :: Identifier -> String
show Identifier
ident = Identifier -> String
getName Identifier
ident
  
-- Make options serializable
data MyOptDescr = MyOpt [Char] [String] (ArgDescr (Options -> Options)) (Options -> String -> [String]) String

fromMyOpt :: MyOptDescr -> OptDescr (Options -> Options)
fromMyOpt :: MyOptDescr -> OptDescr (Options -> Options)
fromMyOpt (MyOpt String
sh [String]
ln ArgDescr (Options -> Options)
desc Options -> String -> [String]
_ String
s) = forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
sh [String]
ln ArgDescr (Options -> Options)
desc String
s

noOpt :: Options -> String -> [String]
noOpt :: Options -> String -> [String]
noOpt Options
_ String
_ = []

boolOpt :: (Options -> Bool) -> Options -> String -> [String]
boolOpt :: (Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
get Options
opt String
strArg = let oldVal :: Bool
oldVal = Options -> Bool
get Options
noOptions
                             newVal :: Bool
newVal = Options -> Bool
get Options
opt
                         in  if   Bool
oldVal forall a. Eq a => a -> a -> Bool
/= Bool
newVal
                             then [String
strArg]
                             else []

stringOpt :: (Options -> String) -> Options -> String -> [String]
stringOpt :: (Options -> String) -> Options -> String -> [String]
stringOpt Options -> String
get Options
opt String
strArg = let oldVal :: String
oldVal = Options -> String
get Options
noOptions
                               newVal :: String
newVal = Options -> String
get Options
opt
                           in  if   String
oldVal forall a. Eq a => a -> a -> Bool
/= String
newVal
                               then [String
strArg, String
newVal]
                               else []

mbStringOpt :: (Options -> Maybe String) -> Options -> String -> [String]
mbStringOpt :: (Options -> Maybe String) -> Options -> String -> [String]
mbStringOpt Options -> Maybe String
get Options
opts String
nm = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\String
s -> [String
nmforall a. [a] -> [a] -> [a]
++String
"="forall a. [a] -> [a] -> [a]
++String
s]) (Options -> Maybe String
get Options
opts)

serializeOption :: Options -> MyOptDescr -> [String]
serializeOption :: Options -> MyOptDescr -> [String]
serializeOption Options
opt (MyOpt String
sh [String]
ln ArgDescr (Options -> Options)
_ Options -> String -> [String]
get String
_) = Options -> String -> [String]
get Options
opt String
strArg
  where
    strArg :: String
strArg = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
sh
             then Char
'-' forall a. a -> [a] -> [a]
: Char
'-' forall a. a -> [a] -> [a]
: forall a. [a] -> a
head [String]
ln
             else Char
'-' forall a. a -> [a] -> [a]
: forall a. [a] -> a
head String
sh forall a. a -> [a] -> [a]
: []

-- All options
allOptions :: [MyOptDescr]
allOptions :: [MyOptDescr]
allOptions =  
  [ String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'm']     []                (forall a. a -> ArgDescr a
NoArg (Maybe String -> Options -> Options
moduleOpt forall a. Maybe a
Nothing)) Options -> String -> [String]
noOpt                 String
"generate default module header"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"module"]        (forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg Maybe String -> Options -> Options
moduleOpt String
"name")   Options -> String -> [String]
moduleOptGet          String
"generate module header, specify module name"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'd']     [String
"data"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
dataOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
dataTypes)   String
"generate data type definition"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"datarecords"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
dataRecOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
dataRecords) String
"generate record data types"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictdata"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
strictDataOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
strictData)  String
"generate strict data fields (when data is generated)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictwrap"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
strictWrapOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
strictWrap)  String
"generate strict wrap fields for WRAPPER generated data"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'c']     [String
"catas"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
cataOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
folds)       String
"generate catamorphisms"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'f']     [String
"semfuns"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
semfunsOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
semfuns)     String
"generate semantic functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
's']     [String
"signatures"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
signaturesOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
typeSigs)    String
"generate signatures for semantic functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"newtypes"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
newtypesOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
newtypes)    String
"use newtypes instead of type synonyms"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'p']     [String
"pretty"]        (forall a. a -> ArgDescr a
NoArg Options -> Options
prettyOpt)           ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
attrInfo)    String
"generate pretty printed list of attributes"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'w']     [String
"wrappers"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
wrappersOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
wrappers)    String
"generate wappers for semantic domains"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'r']     [String
"rename"]        (forall a. a -> ArgDescr a
NoArg Options -> Options
renameOpt)           ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
rename)      String
"rename data constructors"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"modcopy"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
modcopyOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
modcopy)     String
"use modified copy rule"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"nest"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
nestOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
nest)        String
"use nested tuples"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"syntaxmacro"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
smacroOpt)           ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
smacro)      String
"experimental: generate syntax macro code (using knit catas)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'o']     [String
"output"]        (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
outputOpt String
"file")   Options -> String -> [String]
outputOptGet          String
"specify output file"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'v']     [String
"verbose"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
verboseOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
verbose)     String
"verbose error message format"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'h',Char
'?'] [String
"help"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
helpOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
showHelp)    String
"get (this) usage information"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'a']     [String
"all"]           (forall a. a -> ArgDescr a
NoArg Options -> Options
allOpt)              Options -> String -> [String]
noOpt                (String
"do everything (-" forall a. [a] -> [a] -> [a]
++ String
allc forall a. [a] -> [a] -> [a]
++ String
")")
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'P']     [String
""]              (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
searchPathOpt String
"search path") Options -> String -> [String]
searchPathOptGet (String
"specify seach path")
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"prefix"]        (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
prefixOpt String
"prefix") ((Options -> String) -> Options -> String -> [String]
stringOpt Options -> String
prefix)    String
"set prefix for semantic functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"self"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
selfOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
withSelf)    String
"generate self attribute"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"cycle"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
cycleOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
withCycle)   String
"check for cyclic definitions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"version"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
versionOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
showVersion) String
"get version information"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'O']     [String
"optimize"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
optimizeOpt)         Options -> String -> [String]
noOpt                 String
"optimize generated code (--visit --case)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"visit"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
visitOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
visit)       String
"try generating visit functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"loag"]          (forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg Maybe String -> Options -> Options
loagOpt String
"Bool")     ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
loag)        String
"recognises all linear ordered attribute grammars by generting a SAT problem, uses --verbose to print out numbers of clauses and variables"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"aoag"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
aoagOpt)             ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
aoag)        String
"recognises all linear ordered attribute grammars by finding fake dependencies, uses --verbose to print out the selected fake dependencies"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"seq"]           (forall a. a -> ArgDescr a
NoArg Options -> Options
seqOpt)              ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
withSeq)     String
"force evaluation using function seq (visit functions only)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"unbox"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
unboxOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
unbox)       String
"use unboxed tuples"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"bangpats"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
bangpatsOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
bangpats)    String
"use bang patterns (visit functions only)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"case"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
casesOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
cases)       String
"Use nested cases instead of let (visit functions only)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictcase"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
strictCasesOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
strictCases) String
"Force evaluation of the scrutinee of cases (in generated code, visit functions only)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictercase"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
stricterCasesOpt)    ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
stricterCases) String
"Force evaluation of all variables bound by a case statement (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictsem"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
strictSemOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
strictSems)  String
"Force evaluation of sem-function arguments (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"localcps"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
localCpsOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
localCps)    String
"Apply a local CPS transformation (in generated code, visit functions only)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"splitsems"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
splitSemsOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
splitSems)   String
"Split semantic functions into smaller pieces"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"Werrors"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
werrorsOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
werrors)     String
"Turn warnings into fatal errors"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"Wignore"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
wignoreOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
wignore)     String
"Ignore warnings"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"Wmax"]          (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
wmaxErrsOpt String
"<max errs reported>") Options -> String -> [String]
wmaxErrsOptGet String
"Sets the maximum number of errors that are reported"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"dumpgrammar"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
dumpgrammarOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
dumpgrammar) String
"Dump internal grammar representation (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"dumpcgrammar"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
dumpcgrammarOpt)     ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
dumpcgrammar)String
"Dump internal cgrammar representation (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"gentraces"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
genTracesOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genTraces)   String
"Generate trace expressions (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"genusetraces"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
genUseTracesOpt)     ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genUseTraces)String
"Generate trace expressions at attribute use sites (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"gencostcentres"] (forall a. a -> ArgDescr a
NoArg Options -> Options
genCostCentresOpt)  ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genCostCentres) String
"Generate cost centre pragmas (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"genlinepragmas"] (forall a. a -> ArgDescr a
NoArg Options -> Options
genLinePragmasOpt)  ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genLinePragmas) String
"Generate GHC LINE pragmas (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"sepsemmods"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
sepSemModsOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
sepSemMods)  String
"Generate separate modules for semantic functions (in generated code)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'M']     [String
"genfiledeps"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
genFileDepsOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genFileDeps) String
"Generate a list of dependencies on the input AG files"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"genvisage"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
genVisageOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genvisage)   String
"Generate output for the AG visualizer Visage"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"genmirage"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
genMirageOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genmirage)   String
"Generate output for the AG visualizer Mirage"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"aspectag"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
genAspectAGOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genAspectAG) String
"Generate AspectAG file"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"nogroup"]       (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
noGroupOpt String
"attributes") Options -> String -> [String]
noGroupOptGet    String
"specify the attributes that won't be grouped in AspectAG"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"extends"]       (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
extendsOpt String
"module") ((Options -> Maybe String) -> Options -> String -> [String]
mbStringOpt Options -> Maybe String
extends)        String
"specify a module to be extended"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"genattrlist"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
genAttrListOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
genAttributeList) String
"Generate a list of all explicitly defined attributes (outside irrefutable patterns)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"forceirrefutable"] (forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg Maybe String -> Options -> Options
forceIrrefutableOpt String
"file") ((Options -> Maybe String) -> Options -> String -> [String]
mbStringOpt Options -> Maybe String
forceIrrefutables) String
"Force a set of explicitly defined attributes to be irrefutable, specify file containing the attribute set"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"uniquedispenser"] (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
uniqueDispenserOpt String
"name") ((Options -> String) -> Options -> String -> [String]
stringOpt Options -> String
uniqueDispenser) String
"The Haskell function to call in the generated code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"lckeywords"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
lcKeywordsOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
lcKeywords)  String
"Use lowercase keywords (sem, attr) instead of the uppercase ones (SEM, ATTR)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"doublecolons"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
doubleColonsOpt)     ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
doubleColons)String
"Use double colons for type signatures instead of single colons"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt [Char
'H']     [String
"haskellsyntax"] (forall a. a -> ArgDescr a
NoArg Options -> Options
haskellSyntaxOpt)    Options -> String -> [String]
noOpt                 String
"Use Haskell like syntax (equivalent to --lckeywords and --doublecolons --genlinepragmas)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"reference"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
referenceOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
reference)   String
"Use reference attributes"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"monadic"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
monadicOpt)          ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
monadic)     String
"Experimental: generate monadic code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"ocaml"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
ocamlOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
ocaml)       String
"Generate Ocaml code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"cleanlang"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
cleanOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
clean)       String
"Generate Clean code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"breadthfirst"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
breadthfirstOpt)     ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
breadthFirst)String
"Experimental: generate breadth-first code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"breadthfirst-strict"] (forall a. a -> ArgDescr a
NoArg Options -> Options
breadthfirstStrictOpt) ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
breadthFirstStrict) String
"Experimental: outermost breadth-first evaluator is strict instead of lazy"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"visitcode"]     (forall a. a -> ArgDescr a
NoArg Options -> Options
visitorsOutputOpt)   ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
visitorsOutput) String
"Experimental: generate visitors code"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"kennedywarren"] (forall a. a -> ArgDescr a
NoArg Options -> Options
kennedyWarrenOpt)    ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
kennedyWarren) String
"Use Kennedy-Warren's algorithm for ordering"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"statistics"]    (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
statisticsOpt String
"FILE to append to") ((Options -> Maybe String) -> Options -> String -> [String]
mbStringOpt Options -> Maybe String
statsFile) String
"Append statistics to FILE"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"checkParseRhs"]           (forall a. a -> ArgDescr a
NoArg Options -> Options
parseHsRhsOpt)              ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
checkParseRhs)         String
"Parse RHS of rules with Haskell parser"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"checkParseTys"]           (forall a. a -> ArgDescr a
NoArg Options -> Options
parseHsTpOpt)               ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
checkParseTy)          String
"Parse types of attrs with Haskell parser"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"checkParseBlocks"]        (forall a. a -> ArgDescr a
NoArg Options -> Options
parseHsBlockOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
checkParseBlock)       String
"Parse blocks with Haskell parser"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"checkParseHaskell"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
parseHsOpt)                 Options -> String -> [String]
noOpt                           String
"Parse Haskell code (recognizer)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"nocatas"]                 (forall a. (String -> a) -> String -> ArgDescr a
ReqArg String -> Options -> Options
nocatasOpt String
"list of nonterms") Options -> String -> [String]
nocatasOptGet               String
"Nonterminals not to generate catas for"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"nooptimize"]              (forall a. a -> ArgDescr a
NoArg Options -> Options
noOptimizeOpt)              ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noOptimizations)       String
"Disable optimizations"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"parallel"]                (forall a. a -> ArgDescr a
NoArg Options -> Options
parallelOpt)                ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
parallelInvoke)        String
"Generate a parallel evaluator (if possible)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"monadicwrapper"]          (forall a. a -> ArgDescr a
NoArg Options -> Options
monadicWrappersOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
monadicWrappers)       String
"Generate monadic wrappers"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"helpinlining"]            (forall a. a -> ArgDescr a
NoArg Options -> Options
helpInliningOpt)            ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
helpInlining)          String
"Generate inline directives for GHC"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"dummytokenvisit"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
dummyTokenVisitOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
dummyTokenVisit)       String
"Add an additional dummy parameter to visit functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"tupleasdummytoken"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
tupleAsDummyTokenOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
tupleAsDummyToken)     String
"Use conventional tuples as dummy parameter instead of a RealWorld state token"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"stateasdummytoken"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
stateAsDummyTokenOpt)       Options -> String -> [String]
noOpt                           String
"Use RealWorld state token as dummy parameter instead of conventional tuples (default)"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"strictdummytoken"]        (forall a. a -> ArgDescr a
NoArg Options -> Options
strictDummyTokenOpt)        ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
strictDummyToken)      String
"Strictify the dummy token that makes states and rules functions"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noperruletypesigs"]       (forall a. a -> ArgDescr a
NoArg Options -> Options
noPerRuleTypeSigsOpt)       ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noPerRuleTypeSigs)     String
"Do not generate type sigs for attrs passed to rules"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noperstatetypesigs"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
noPerStateTypeSigsOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noPerStateTypeSigs)    String
"Do not generate type sigs for attrs saved in node states"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noeagerblackholing"]      (forall a. a -> ArgDescr a
NoArg Options -> Options
noEagerBlackholingOpt)      ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noEagerBlackholing)    String
"Do not automatically add the eager blackholing feature for parallel programs"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noperrulecostcentres"]    (forall a. a -> ArgDescr a
NoArg Options -> Options
noPerRuleCostCentresOpt)    ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noPerRuleCostCentres)  String
"Do not generate cost centres for rules"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"nopervisitcostcentres"]   (forall a. a -> ArgDescr a
NoArg Options -> Options
noPerVisitCostCentresOpt)   ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noPerVisitCostCentres) String
"Do not generate cost centres for visits"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noinlinepragmas"]         (forall a. a -> ArgDescr a
NoArg Options -> Options
noInlinePragmasOpt)         ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noInlinePragmas)       String
"Definitely not generate inline directives"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"aggressiveinlinepragmas"] (forall a. a -> ArgDescr a
NoArg Options -> Options
aggressiveInlinePragmasOpt) ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
aggressiveInlinePragmas) String
"Generate more aggressive inline directives"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"latehigherorderbinding"]  (forall a. a -> ArgDescr a
NoArg Options -> Options
lateHigherOrderBindingOpt)  ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
lateHigherOrderBinding) String
"Generate an attribute and wrapper for late binding of higher-order attributes"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"noincludes"]              (forall a. a -> ArgDescr a
NoArg Options -> Options
noIncludesOpt)              ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
noIncludes)             String
"Ignore include directives in .ag files"
  , String
-> [String]
-> ArgDescr (Options -> Options)
-> (Options -> String -> [String])
-> String
-> MyOptDescr
MyOpt []        [String
"quiet"]                   (forall a. a -> ArgDescr a
NoArg Options -> Options
beQuietOpt)                 ((Options -> Bool) -> Options -> String -> [String]
boolOpt Options -> Bool
beQuiet)                String
"Dont print some compilation information"
  ]

-- For compatibility
options     :: [OptDescr (Options -> Options)]
options :: [OptDescr (Options -> Options)]
options     = forall a b. (a -> b) -> [a] -> [b]
map MyOptDescr -> OptDescr (Options -> Options)
fromMyOpt [MyOptDescr]
allOptions

allc :: String
allc :: String
allc = String
"dcfsprm"

data ModuleHeader  = NoName
                   | Name String
                   | Default deriving (ModuleHeader -> ModuleHeader -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleHeader -> ModuleHeader -> Bool
$c/= :: ModuleHeader -> ModuleHeader -> Bool
== :: ModuleHeader -> ModuleHeader -> Bool
$c== :: ModuleHeader -> ModuleHeader -> Bool
Eq, Int -> ModuleHeader -> ShowS
[ModuleHeader] -> ShowS
ModuleHeader -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleHeader] -> ShowS
$cshowList :: [ModuleHeader] -> ShowS
show :: ModuleHeader -> String
$cshow :: ModuleHeader -> String
showsPrec :: Int -> ModuleHeader -> ShowS
$cshowsPrec :: Int -> ModuleHeader -> ShowS
Show)

data Options = Options{ Options -> ModuleHeader
moduleName :: ModuleHeader
                      , Options -> Bool
dataTypes :: Bool
                      , Options -> Bool
dataRecords :: Bool
                      , Options -> Bool
strictData :: Bool
                      , Options -> Bool
strictWrap :: Bool
                      , Options -> Bool
folds :: Bool
                      , Options -> Bool
semfuns :: Bool
                      , Options -> Bool
typeSigs :: Bool
                      , Options -> Bool
attrInfo :: Bool
                      , Options -> Bool
rename :: Bool
                      , Options -> Bool
wrappers :: Bool
                      , Options -> Bool
modcopy :: Bool
                      , Options -> Bool
newtypes :: Bool
                      , Options -> Bool
nest :: Bool
                      , Options -> Bool
smacro :: Bool
                      , Options -> [String]
outputFiles :: [String]
                      , Options -> [String]
searchPath :: [String]
                      , Options -> Bool
verbose :: Bool
                      , Options -> String
prefix :: String
                      , Options -> Bool
withSelf :: Bool
                      , Options -> Bool
withCycle :: Bool
                      , Options -> Bool
showHelp :: Bool
                      , Options -> Bool
showVersion :: Bool
                      , Options -> Bool
visit :: Bool
                      , Options -> Bool
loag  :: Bool
                      , Options -> Bool
minvisits  :: Bool
                      , Options -> Bool
aoag  :: Bool
                      , Options -> Bool
withSeq :: Bool
                      , Options -> Bool
unbox :: Bool
                      , Options -> Bool
bangpats :: Bool
                      , Options -> Bool
cases :: Bool
                      , Options -> Bool
strictCases :: Bool
                      , Options -> Bool
stricterCases :: Bool
                      , Options -> Bool
strictSems :: Bool
                      , Options -> Bool
localCps :: Bool
                      , Options -> Bool
splitSems :: Bool
                      , Options -> Bool
werrors :: Bool
                      , Options -> Bool
wignore :: Bool
                      , Options -> Int
wmaxerrs :: Int
                      , Options -> Bool
dumpgrammar :: Bool
                      , Options -> Bool
dumpcgrammar :: Bool
                      , Options -> Bool
sepSemMods :: Bool
                      , Options -> Bool
allowSepSemMods :: Bool
                      , Options -> Bool
genFileDeps :: Bool
                      , Options -> Bool
genLinePragmas :: Bool
                      , Options -> Bool
genvisage :: Bool
                      , Options -> Bool
genmirage :: Bool
                      , Options -> Bool
genAspectAG :: Bool
                      , Options -> [String]
noGroup :: [String]
                      , Options -> Maybe String
extends :: Maybe String
                      , Options -> Bool
genAttributeList :: Bool
                      , Options -> Maybe String
forceIrrefutables :: Maybe String
                      , Options -> String
uniqueDispenser :: String
                      , Options -> Bool
lcKeywords :: Bool
                      , Options -> Bool
doubleColons :: Bool
                      , Options -> Bool
monadic :: Bool
                      , Options -> Bool
ocaml :: Bool
                      , Options -> Bool
clean :: Bool
                      , Options -> Bool
visitorsOutput :: Bool
                      , Options -> Maybe String
statsFile :: Maybe String
                      , Options -> Bool
breadthFirst :: Bool
                      , Options -> Bool
breadthFirstStrict :: Bool
                      , Options -> Bool
checkParseRhs :: Bool
                      , Options -> Bool
checkParseTy :: Bool
                      , Options -> Bool
checkParseBlock :: Bool
                      , Options -> Set Identifier
nocatas :: Set NontermIdent
                      , Options -> Bool
noOptimizations :: Bool
                      , Options -> Bool
reference :: Bool
                      , Options -> Bool
noIncludes :: Bool
                      , Options -> String -> IO ()
outputStr :: String -> IO ()
                      , Options -> Int -> IO ()
failWithCode :: Int -> IO ()
                      , Options -> Maybe String
mainFilename :: Maybe String
                      , Options -> Bool
beQuiet :: Bool

                      -- KW code path
                      , Options -> Bool
kennedyWarren       :: Bool
                      , Options -> Bool
parallelInvoke      :: Bool
                      , Options -> Bool
tupleAsDummyToken   :: Bool  -- use the empty tuple as dummy token instead of State# RealWorld (Lambda State Hack GHC?)
                      , Options -> Bool
dummyTokenVisit     :: Bool  -- add a dummy argument/pass dummy extra token to visits (should not really have an effect ... Lambda State Hack GHC?)
                      , Options -> Bool
strictDummyToken    :: Bool  -- make the dummy token strict (to prevent its removal -- should not really have an effect)
                      , Options -> Bool
noPerRuleTypeSigs   :: Bool  -- do not print type signatures for attributes of rules
                      , Options -> Bool
noPerStateTypeSigs  :: Bool  -- do not print type signatures for attributes contained in the state
                      , Options -> Bool
noEagerBlackholing  :: Bool  -- disable the use of eager black holing in the parallel evaluator code
                      , Options -> Bool
lateHigherOrderBinding :: Bool  -- generate code to allow late binding of higher-order children semantics
                      , Options -> Bool
monadicWrappers        :: Bool

                      -- tracing
                      , Options -> Bool
genTraces :: Bool
                      , Options -> Bool
genUseTraces :: Bool
                      , Options -> Bool
genCostCentres :: Bool
                      , Options -> Bool
noPerRuleCostCentres :: Bool
                      , Options -> Bool
noPerVisitCostCentres :: Bool

                      -- inline pragma generation
                      , Options -> Bool
helpInlining :: Bool
                      , Options -> Bool
noInlinePragmas :: Bool
                      , Options -> Bool
aggressiveInlinePragmas :: Bool
                      } -- deriving (Eq, Show)

noOptions :: Options
noOptions :: Options
noOptions = Options { moduleName :: ModuleHeader
moduleName    = ModuleHeader
NoName
                    , dataTypes :: Bool
dataTypes     = Bool
False
                    , dataRecords :: Bool
dataRecords   = Bool
False
                    , strictData :: Bool
strictData    = Bool
False
                    , strictWrap :: Bool
strictWrap    = Bool
False
                    , folds :: Bool
folds         = Bool
False
                    , semfuns :: Bool
semfuns       = Bool
False
                    , typeSigs :: Bool
typeSigs      = Bool
False
                    , attrInfo :: Bool
attrInfo      = Bool
False
                    , rename :: Bool
rename        = Bool
False
                    , wrappers :: Bool
wrappers      = Bool
False
                    , modcopy :: Bool
modcopy       = Bool
False
                    , newtypes :: Bool
newtypes      = Bool
False
                    , nest :: Bool
nest          = Bool
False
                    , smacro :: Bool
smacro        = Bool
False
                    , outputFiles :: [String]
outputFiles   = []
                    , searchPath :: [String]
searchPath    = []
                    , verbose :: Bool
verbose       = Bool
False
                    , showHelp :: Bool
showHelp      = Bool
False
                    , showVersion :: Bool
showVersion   = Bool
False
                    , prefix :: String
prefix        = String
"sem_"
                    , withSelf :: Bool
withSelf      = Bool
False
                    , withCycle :: Bool
withCycle     = Bool
False
                    , visit :: Bool
visit         = Bool
False
                    , loag :: Bool
loag          = Bool
False
                    , minvisits :: Bool
minvisits     = Bool
False
                    , aoag :: Bool
aoag          = Bool
False
                    , withSeq :: Bool
withSeq       = Bool
False
                    , unbox :: Bool
unbox         = Bool
False
                    , bangpats :: Bool
bangpats      = Bool
False
                    , cases :: Bool
cases         = Bool
False
                    , strictCases :: Bool
strictCases   = Bool
False
                    , stricterCases :: Bool
stricterCases = Bool
False
                    , strictSems :: Bool
strictSems    = Bool
False
                    , localCps :: Bool
localCps      = Bool
False
                    , splitSems :: Bool
splitSems     = Bool
False
                    , werrors :: Bool
werrors       = Bool
False
                    , wignore :: Bool
wignore       = Bool
False
                    , wmaxerrs :: Int
wmaxerrs      = Int
99999
                    , dumpgrammar :: Bool
dumpgrammar   = Bool
False
                    , dumpcgrammar :: Bool
dumpcgrammar  = Bool
False
                    , sepSemMods :: Bool
sepSemMods     = Bool
False
                    , allowSepSemMods :: Bool
allowSepSemMods = Bool
True
                    , genFileDeps :: Bool
genFileDeps    = Bool
False
                    , genLinePragmas :: Bool
genLinePragmas = Bool
False
                    , genvisage :: Bool
genvisage      = Bool
False
                    , genmirage :: Bool
genmirage      = Bool
False
                    , genAspectAG :: Bool
genAspectAG    = Bool
False
                    , noGroup :: [String]
noGroup        = []
                    , extends :: Maybe String
extends        = forall a. Maybe a
Nothing
                    , genAttributeList :: Bool
genAttributeList = Bool
False
                    , forceIrrefutables :: Maybe String
forceIrrefutables = forall a. Maybe a
Nothing
                    , uniqueDispenser :: String
uniqueDispenser = String
"nextUnique"
                    , lcKeywords :: Bool
lcKeywords      = Bool
False
                    , doubleColons :: Bool
doubleColons    = Bool
False
                    , monadic :: Bool
monadic         = Bool
False
                    , ocaml :: Bool
ocaml           = Bool
False
                    , clean :: Bool
clean           = Bool
False
                    , visitorsOutput :: Bool
visitorsOutput  = Bool
False
                    , statsFile :: Maybe String
statsFile       = forall a. Maybe a
Nothing
                    , breadthFirst :: Bool
breadthFirst     = Bool
False
                    , breadthFirstStrict :: Bool
breadthFirstStrict = Bool
False
                    , checkParseRhs :: Bool
checkParseRhs = Bool
False
                    , checkParseTy :: Bool
checkParseTy  = Bool
False
                    , checkParseBlock :: Bool
checkParseBlock = Bool
False
                    , nocatas :: Set Identifier
nocatas         = forall a. Set a
Set.empty
                    , noOptimizations :: Bool
noOptimizations = Bool
False
                    , reference :: Bool
reference       = Bool
False
                    , noIncludes :: Bool
noIncludes      = Bool
False
                    , outputStr :: String -> IO ()
outputStr       = Handle -> String -> IO ()
hPutStr Handle
stderr
                    , failWithCode :: Int -> IO ()
failWithCode    = forall a. ExitCode -> IO a
exitWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ExitCode
ExitFailure
                    , mainFilename :: Maybe String
mainFilename    = forall a. Maybe a
Nothing
                    , beQuiet :: Bool
beQuiet         = Bool
False

                    -- defaults for the KW-code path
                    , kennedyWarren :: Bool
kennedyWarren       = Bool
False
                    , parallelInvoke :: Bool
parallelInvoke      = Bool
False
                    , tupleAsDummyToken :: Bool
tupleAsDummyToken   = Bool
True
                    , dummyTokenVisit :: Bool
dummyTokenVisit     = Bool
False
                    , strictDummyToken :: Bool
strictDummyToken    = Bool
False
                    , noPerRuleTypeSigs :: Bool
noPerRuleTypeSigs   = Bool
False
                    , noPerStateTypeSigs :: Bool
noPerStateTypeSigs  = Bool
False
                    , noEagerBlackholing :: Bool
noEagerBlackholing  = Bool
False
                    , lateHigherOrderBinding :: Bool
lateHigherOrderBinding = Bool
False
                    , monadicWrappers :: Bool
monadicWrappers        = Bool
False

                    -- defaults for tracing
                    , genTraces :: Bool
genTraces     = Bool
False
                    , genUseTraces :: Bool
genUseTraces  = Bool
False
                    , genCostCentres :: Bool
genCostCentres = Bool
False
                    , noPerRuleCostCentres :: Bool
noPerRuleCostCentres  = Bool
False
                    , noPerVisitCostCentres :: Bool
noPerVisitCostCentres = Bool
False

                    -- defaults for inline pragma generation
                    , helpInlining :: Bool
helpInlining    = Bool
False
                    , noInlinePragmas :: Bool
noInlinePragmas = Bool
False
                    , aggressiveInlinePragmas :: Bool
aggressiveInlinePragmas = Bool
False
                    }

loagOpt :: (Maybe String) -> Options -> Options
loagOpt :: Maybe String -> Options -> Options
loagOpt Maybe String
mstr Options
opts = 
    case Maybe String
mstr of
        Maybe String
Nothing     -> Options
opts'
        Just String
"0"    -> Options
opts'
        Just String
_      -> Options
opts' {minvisits :: Bool
minvisits = Bool
True}

 where  opts' :: Options
opts'=Options
opts{loag :: Bool
loag = Bool
True, visit :: Bool
visit = Bool
True}

aoagOpt :: Options -> Options
aoagOpt :: Options -> Options
aoagOpt Options
opts = 
    Options
opts{loag :: Bool
loag = Bool
True, visit :: Bool
visit = Bool
True, aoag :: Bool
aoag = Bool
True}

--Options -> String -> [String]
moduleOpt :: Maybe String -> Options -> Options
moduleOpt :: Maybe String -> Options -> Options
moduleOpt  Maybe String
nm   Options
opts = Options
opts{moduleName :: ModuleHeader
moduleName   = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ModuleHeader
Default String -> ModuleHeader
Name Maybe String
nm}
moduleOptGet :: Options -> String -> [String]
moduleOptGet :: Options -> String -> [String]
moduleOptGet Options
opts String
nm = case Options -> ModuleHeader
moduleName Options
opts of
  ModuleHeader
NoName -> []
  Name String
s -> [String
nmforall a. [a] -> [a] -> [a]
++String
"="forall a. [a] -> [a] -> [a]
++String
s]
  ModuleHeader
Default -> [String
nm]

dataOpt, dataRecOpt, strictDataOpt, strictWrapOpt, cataOpt, semfunsOpt, signaturesOpt, prettyOpt,renameOpt, wrappersOpt, modcopyOpt, newtypesOpt, nestOpt, smacroOpt, verboseOpt, helpOpt, versionOpt, selfOpt, cycleOpt, visitOpt, seqOpt, unboxOpt, bangpatsOpt, casesOpt, strictCasesOpt, stricterCasesOpt, strictSemOpt, localCpsOpt, splitSemsOpt, werrorsOpt, wignoreOpt, dumpgrammarOpt, dumpcgrammarOpt, genTracesOpt, genUseTracesOpt, genCostCentresOpt, sepSemModsOpt, genFileDepsOpt, genLinePragmasOpt, genVisageOpt, genMirageOpt, genAspectAGOpt, dummyTokenVisitOpt, tupleAsDummyTokenOpt, stateAsDummyTokenOpt, strictDummyTokenOpt, noPerRuleTypeSigsOpt, noPerStateTypeSigsOpt, noEagerBlackholingOpt, noPerRuleCostCentresOpt, noPerVisitCostCentresOpt, helpInliningOpt, noInlinePragmasOpt, aggressiveInlinePragmasOpt, lateHigherOrderBindingOpt, monadicWrappersOpt, referenceOpt, genAttrListOpt, lcKeywordsOpt, doubleColonsOpt, haskellSyntaxOpt, monadicOpt, parallelOpt, ocamlOpt, cleanOpt, visitorsOutputOpt, breadthfirstOpt, breadthfirstStrictOpt, parseHsRhsOpt, parseHsTpOpt, parseHsBlockOpt, parseHsOpt, kennedyWarrenOpt, noOptimizeOpt, allOpt, optimizeOpt, noIncludesOpt, beQuietOpt, condDisableOptimizations :: Options -> Options

dataOpt :: Options -> Options
dataOpt         Options
opts = Options
opts{dataTypes :: Bool
dataTypes    = Bool
True}
dataRecOpt :: Options -> Options
dataRecOpt      Options
opts = Options
opts{dataRecords :: Bool
dataRecords  = Bool
True}
strictDataOpt :: Options -> Options
strictDataOpt   Options
opts = Options
opts{strictData :: Bool
strictData   = Bool
True}
strictWrapOpt :: Options -> Options
strictWrapOpt   Options
opts = Options
opts{strictWrap :: Bool
strictWrap   = Bool
True}
cataOpt :: Options -> Options
cataOpt         Options
opts = Options
opts{folds :: Bool
folds        = Bool
True}
semfunsOpt :: Options -> Options
semfunsOpt      Options
opts = Options
opts{semfuns :: Bool
semfuns      = Bool
True}
signaturesOpt :: Options -> Options
signaturesOpt   Options
opts = Options
opts{typeSigs :: Bool
typeSigs     = Bool
True}
prettyOpt :: Options -> Options
prettyOpt       Options
opts = Options
opts{attrInfo :: Bool
attrInfo     = Bool
True}
renameOpt :: Options -> Options
renameOpt       Options
opts = Options
opts{rename :: Bool
rename       = Bool
True}
wrappersOpt :: Options -> Options
wrappersOpt     Options
opts = Options
opts{wrappers :: Bool
wrappers     = Bool
True}
modcopyOpt :: Options -> Options
modcopyOpt      Options
opts = Options
opts{modcopy :: Bool
modcopy      = Bool
True}
newtypesOpt :: Options -> Options
newtypesOpt     Options
opts = Options
opts{newtypes :: Bool
newtypes     = Bool
True}
nestOpt :: Options -> Options
nestOpt         Options
opts = Options
opts{nest :: Bool
nest         = Bool
True}
smacroOpt :: Options -> Options
smacroOpt       Options
opts = Options
opts{smacro :: Bool
smacro       = Bool
True}
verboseOpt :: Options -> Options
verboseOpt      Options
opts = Options
opts{verbose :: Bool
verbose      = Bool
True}
helpOpt :: Options -> Options
helpOpt         Options
opts = Options
opts{showHelp :: Bool
showHelp     = Bool
True}
versionOpt :: Options -> Options
versionOpt      Options
opts = Options
opts{showVersion :: Bool
showVersion  = Bool
True}
prefixOpt :: String -> Options -> Options
prefixOpt :: String -> Options -> Options
prefixOpt String
pre   Options
opts = Options
opts{prefix :: String
prefix       = String
pre }
selfOpt :: Options -> Options
selfOpt         Options
opts = Options
opts{withSelf :: Bool
withSelf     = Bool
True}
cycleOpt :: Options -> Options
cycleOpt        Options
opts = Options
opts{withCycle :: Bool
withCycle    = Bool
True}
visitOpt :: Options -> Options
visitOpt        Options
opts = Options
opts{visit :: Bool
visit        = Bool
True, withCycle :: Bool
withCycle = Bool
True}
seqOpt :: Options -> Options
seqOpt          Options
opts = Options
opts{withSeq :: Bool
withSeq      = Bool
True}
unboxOpt :: Options -> Options
unboxOpt        Options
opts = Options
opts{unbox :: Bool
unbox        = Bool
True}
bangpatsOpt :: Options -> Options
bangpatsOpt     Options
opts = Options
opts{bangpats :: Bool
bangpats     = Bool
True}
casesOpt :: Options -> Options
casesOpt        Options
opts = Options
opts{cases :: Bool
cases        = Bool
True}
strictCasesOpt :: Options -> Options
strictCasesOpt  Options
opts = Options
opts{strictCases :: Bool
strictCases  = Bool
True}
stricterCasesOpt :: Options -> Options
stricterCasesOpt Options
opts = Options
opts{strictCases :: Bool
strictCases = Bool
True, stricterCases :: Bool
stricterCases = Bool
True}
strictSemOpt :: Options -> Options
strictSemOpt    Options
opts = Options
opts{strictSems :: Bool
strictSems   = Bool
True}
localCpsOpt :: Options -> Options
localCpsOpt     Options
opts = Options
opts{localCps :: Bool
localCps     = Bool
True}
splitSemsOpt :: Options -> Options
splitSemsOpt    Options
opts = Options
opts{splitSems :: Bool
splitSems    = Bool
True}
werrorsOpt :: Options -> Options
werrorsOpt      Options
opts = Options
opts{werrors :: Bool
werrors      = Bool
True}
wignoreOpt :: Options -> Options
wignoreOpt      Options
opts = Options
opts{wignore :: Bool
wignore      = Bool
True}
wmaxErrsOpt :: String -> Options -> Options
wmaxErrsOpt :: String -> Options -> Options
wmaxErrsOpt String
n   Options
opts = Options
opts{wmaxerrs :: Int
wmaxerrs     = forall a. Read a => String -> a
read String
n}
wmaxErrsOptGet :: Options -> String -> [String]
wmaxErrsOptGet :: Options -> String -> [String]
wmaxErrsOptGet Options
opts String
nm = if Options -> Int
wmaxerrs Options
opts forall a. Eq a => a -> a -> Bool
/= Options -> Int
wmaxerrs Options
noOptions
                         then [String
nm,forall a. Show a => a -> String
show (Options -> Int
wmaxerrs Options
opts)]
                         else []
dumpgrammarOpt :: Options -> Options
dumpgrammarOpt  Options
opts = Options
opts{dumpgrammar :: Bool
dumpgrammar  = Bool
True}
dumpcgrammarOpt :: Options -> Options
dumpcgrammarOpt Options
opts = Options
opts{dumpcgrammar :: Bool
dumpcgrammar = Bool
True}
genTracesOpt :: Options -> Options
genTracesOpt    Options
opts = Options
opts{genTraces :: Bool
genTraces    = Bool
True}
genUseTracesOpt :: Options -> Options
genUseTracesOpt Options
opts = Options
opts{genUseTraces :: Bool
genUseTraces = Bool
True}
genCostCentresOpt :: Options -> Options
genCostCentresOpt Options
opts = Options
opts{genCostCentres :: Bool
genCostCentres = Bool
True}
sepSemModsOpt :: Options -> Options
sepSemModsOpt Options
opts = Options
opts{sepSemMods :: Bool
sepSemMods = Options -> Bool
allowSepSemMods Options
opts}
genFileDepsOpt :: Options -> Options
genFileDepsOpt Options
opts = Options
opts{genFileDeps :: Bool
genFileDeps = Bool
True}
genLinePragmasOpt :: Options -> Options
genLinePragmasOpt Options
opts = Options
opts{genLinePragmas :: Bool
genLinePragmas = Bool
True}
genVisageOpt :: Options -> Options
genVisageOpt Options
opts = Options
opts{genvisage :: Bool
genvisage = Bool
True }
genMirageOpt :: Options -> Options
genMirageOpt Options
opts = Options
opts{genmirage :: Bool
genmirage = Bool
True }
genAspectAGOpt :: Options -> Options
genAspectAGOpt Options
opts = Options
opts{genAspectAG :: Bool
genAspectAG = Bool
True}

dummyTokenVisitOpt :: Options -> Options
dummyTokenVisitOpt Options
opts         = Options
opts { dummyTokenVisit :: Bool
dummyTokenVisit = Bool
True }
tupleAsDummyTokenOpt :: Options -> Options
tupleAsDummyTokenOpt Options
opts       = Options
opts { tupleAsDummyToken :: Bool
tupleAsDummyToken = Bool
True }
stateAsDummyTokenOpt :: Options -> Options
stateAsDummyTokenOpt Options
opts       = Options
opts { tupleAsDummyToken :: Bool
tupleAsDummyToken = Bool
False }
strictDummyTokenOpt :: Options -> Options
strictDummyTokenOpt Options
opts        = Options
opts { strictDummyToken :: Bool
strictDummyToken = Bool
True }
noPerRuleTypeSigsOpt :: Options -> Options
noPerRuleTypeSigsOpt Options
opts       = Options
opts { noPerRuleTypeSigs :: Bool
noPerRuleTypeSigs = Bool
True }
noPerStateTypeSigsOpt :: Options -> Options
noPerStateTypeSigsOpt Options
opts      = Options
opts { noPerStateTypeSigs :: Bool
noPerStateTypeSigs = Bool
True }
noEagerBlackholingOpt :: Options -> Options
noEagerBlackholingOpt Options
opts      = Options
opts { noEagerBlackholing :: Bool
noEagerBlackholing = Bool
True }
noPerRuleCostCentresOpt :: Options -> Options
noPerRuleCostCentresOpt Options
opts    = Options
opts { noPerRuleCostCentres :: Bool
noPerRuleCostCentres = Bool
True }
noPerVisitCostCentresOpt :: Options -> Options
noPerVisitCostCentresOpt Options
opts   = Options
opts { noPerVisitCostCentres :: Bool
noPerVisitCostCentres = Bool
True }
helpInliningOpt :: Options -> Options
helpInliningOpt Options
opts            = Options
opts { helpInlining :: Bool
helpInlining = Bool
True }
noInlinePragmasOpt :: Options -> Options
noInlinePragmasOpt Options
opts         = Options
opts { noInlinePragmas :: Bool
noInlinePragmas = Bool
True }
aggressiveInlinePragmasOpt :: Options -> Options
aggressiveInlinePragmasOpt Options
opts = Options
opts { aggressiveInlinePragmas :: Bool
aggressiveInlinePragmas = Bool
True }
lateHigherOrderBindingOpt :: Options -> Options
lateHigherOrderBindingOpt Options
opts  = Options
opts { lateHigherOrderBinding :: Bool
lateHigherOrderBinding = Bool
True }
monadicWrappersOpt :: Options -> Options
monadicWrappersOpt Options
opts         = Options
opts { monadicWrappers :: Bool
monadicWrappers = Bool
True }
referenceOpt :: Options -> Options
referenceOpt Options
opts               = Options
opts { reference :: Bool
reference = Bool
True }

noGroupOpt :: String -> Options -> Options
noGroupOpt :: String -> Options -> Options
noGroupOpt  String
att  Options
opts = Options
opts{noGroup :: [String]
noGroup  = (Char -> Bool) -> String -> [String]
wordsBy (forall a. Eq a => a -> a -> Bool
== Char
':') String
att  forall a. [a] -> [a] -> [a]
++ Options -> [String]
noGroup Options
opts}
noGroupOptGet :: Options -> String -> [String]
noGroupOptGet :: Options -> String -> [String]
noGroupOptGet Options
opts String
nm = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Options -> [String]
noGroup Options
opts)
                        then []
                        else [String
nm, forall a. [a] -> [[a]] -> [a]
intercalate String
":" (Options -> [String]
noGroup Options
opts)]
extendsOpt :: String -> Options -> Options
extendsOpt :: String -> Options -> Options
extendsOpt  String
m  Options
opts = Options
opts{extends :: Maybe String
extends  = forall a. a -> Maybe a
Just String
m }

genAttrListOpt :: Options -> Options
genAttrListOpt Options
opts = Options
opts { genAttributeList :: Bool
genAttributeList = Bool
True }
forceIrrefutableOpt :: Maybe String -> Options -> Options
forceIrrefutableOpt :: Maybe String -> Options -> Options
forceIrrefutableOpt Maybe String
mbNm Options
opts = Options
opts { forceIrrefutables :: Maybe String
forceIrrefutables = Maybe String
mbNm }
uniqueDispenserOpt :: String -> Options -> Options
uniqueDispenserOpt :: String -> Options -> Options
uniqueDispenserOpt String
nm Options
opts = Options
opts { uniqueDispenser :: String
uniqueDispenser = String
nm }
lcKeywordsOpt :: Options -> Options
lcKeywordsOpt Options
opts = Options
opts { lcKeywords :: Bool
lcKeywords = Bool
True }
doubleColonsOpt :: Options -> Options
doubleColonsOpt Options
opts = Options
opts { doubleColons :: Bool
doubleColons = Bool
True }
haskellSyntaxOpt :: Options -> Options
haskellSyntaxOpt = Options -> Options
lcKeywordsOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
doubleColonsOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
genLinePragmasOpt
monadicOpt :: Options -> Options
monadicOpt Options
opts = Options
opts { monadic :: Bool
monadic = Bool
True }
parallelOpt :: Options -> Options
parallelOpt Options
opts = Options
opts { parallelInvoke :: Bool
parallelInvoke = Bool
True }
ocamlOpt :: Options -> Options
ocamlOpt Options
opts = Options
opts { ocaml :: Bool
ocaml = Bool
True, kennedyWarren :: Bool
kennedyWarren = Bool
True, withCycle :: Bool
withCycle = Bool
True, visit :: Bool
visit = Bool
True }
cleanOpt :: Options -> Options
cleanOpt Options
opts = Options
opts { clean :: Bool
clean = Bool
True } --TODO: More?
visitorsOutputOpt :: Options -> Options
visitorsOutputOpt Options
opts = Options
opts { visitorsOutput :: Bool
visitorsOutput = Bool
True }
statisticsOpt :: String -> Options -> Options
statisticsOpt :: String -> Options -> Options
statisticsOpt String
nm Options
opts = Options
opts { statsFile :: Maybe String
statsFile = forall a. a -> Maybe a
Just String
nm }
breadthfirstOpt :: Options -> Options
breadthfirstOpt Options
opts = Options
opts { breadthFirst :: Bool
breadthFirst = Bool
True }
breadthfirstStrictOpt :: Options -> Options
breadthfirstStrictOpt Options
opts = Options
opts { breadthFirstStrict :: Bool
breadthFirstStrict = Bool
True }
parseHsRhsOpt :: Options -> Options
parseHsRhsOpt Options
opts = Options
opts { checkParseRhs :: Bool
checkParseRhs = Bool
True }
parseHsTpOpt :: Options -> Options
parseHsTpOpt Options
opts = Options
opts { checkParseTy :: Bool
checkParseTy = Bool
True }
parseHsBlockOpt :: Options -> Options
parseHsBlockOpt Options
opts = Options
opts { checkParseBlock :: Bool
checkParseBlock = Bool
True }
parseHsOpt :: Options -> Options
parseHsOpt = Options -> Options
parseHsRhsOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
parseHsTpOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
parseHsBlockOpt
kennedyWarrenOpt :: Options -> Options
kennedyWarrenOpt Options
opts = Options
opts { kennedyWarren :: Bool
kennedyWarren = Bool
True }
noOptimizeOpt :: Options -> Options
noOptimizeOpt Options
opts = Options
opts { noOptimizations :: Bool
noOptimizations = Bool
True }
nocatasOpt :: String -> Options -> Options
nocatasOpt :: String -> Options -> Options
nocatasOpt String
str Options
opts = Options
opts { nocatas :: Set Identifier
nocatas = Set Identifier
set forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Options -> Set Identifier
nocatas Options
opts } where
  set :: Set Identifier
set = forall a. Ord a => [a] -> Set a
Set.fromList [Identifier]
ids
  ids :: [Identifier]
ids = forall a b. (a -> b) -> [a] -> [b]
map String -> Identifier
identifier [String]
lst
  lst :: [String]
lst = (Char -> Bool) -> String -> [String]
wordsBy (forall a. Eq a => a -> a -> Bool
== Char
',') String
str
nocatasOptGet :: Options -> String -> [String]
nocatasOptGet :: Options -> String -> [String]
nocatasOptGet Options
opts String
nm = if forall a. Set a -> Bool
Set.null (Options -> Set Identifier
nocatas Options
opts)
                        then []
                        else [String
nm,forall a. [a] -> [[a]] -> [a]
intercalate String
"," forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Identifier -> String
getName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> [a]
Set.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Set Identifier
nocatas forall a b. (a -> b) -> a -> b
$ Options
opts]
outputOpt :: String -> Options -> Options
outputOpt :: String -> Options -> Options
outputOpt  String
file  Options
opts = Options
opts{outputFiles :: [String]
outputFiles  = String
file forall a. a -> [a] -> [a]
: Options -> [String]
outputFiles Options
opts}
outputOptGet :: Options -> String -> [String]
outputOptGet :: Options -> String -> [String]
outputOptGet Options
opts String
nm  = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [String
nm, String
file] | String
file <- Options -> [String]
outputFiles Options
opts]
searchPathOpt :: String -> Options -> Options
searchPathOpt :: String -> Options -> Options
searchPathOpt  String
path  Options
opts = Options
opts{searchPath :: [String]
searchPath  = (Char -> Bool) -> String -> [String]
wordsBy (\Char
x -> Char
x forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
x forall a. Eq a => a -> a -> Bool
== Char
':') String
path forall a. [a] -> [a] -> [a]
++ Options -> [String]
searchPath Options
opts}
searchPathOptGet :: Options -> String -> [String]
searchPathOptGet :: Options -> String -> [String]
searchPathOptGet Options
opts String
nm = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Options -> [String]
searchPath Options
opts)
                           then []
                           else [String
nm, forall a. [a] -> [[a]] -> [a]
intercalate String
":" (Options -> [String]
searchPath Options
opts)]
allOpt :: Options -> Options
allOpt = Maybe String -> Options -> Options
moduleOpt forall a. Maybe a
Nothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
dataOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
cataOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
semfunsOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
signaturesOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
prettyOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
renameOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
dataRecOpt
optimizeOpt :: Options -> Options
optimizeOpt   = Options -> Options
visitOpt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Options
casesOpt
noIncludesOpt :: Options -> Options
noIncludesOpt Options
opts = Options
opts { noIncludes :: Bool
noIncludes = Bool
True }
beQuietOpt :: Options -> Options
beQuietOpt Options
opts = Options
opts { beQuiet :: Bool
beQuiet = Bool
True }

condDisableOptimizations :: Options -> Options
condDisableOptimizations Options
opts
  | Options -> Bool
noOptimizations Options
opts =
      Options
opts { strictData :: Bool
strictData         = Bool
False
           , strictWrap :: Bool
strictWrap         = Bool
False
           , withSeq :: Bool
withSeq            = Bool
False
           , unbox :: Bool
unbox              = Bool
False
           , bangpats :: Bool
bangpats           = Bool
False
           , cases :: Bool
cases              = Bool
False
           , strictCases :: Bool
strictCases        = Bool
False
           , stricterCases :: Bool
stricterCases      = Bool
False
           , strictSems :: Bool
strictSems         = Bool
False
           , localCps :: Bool
localCps           = Bool
False
           , splitSems :: Bool
splitSems          = Bool
False
           , breadthFirstStrict :: Bool
breadthFirstStrict = Bool
False
           }
  | Bool
otherwise = Options
opts
                
-- | Inverse of intercalate
wordsBy :: (Char -> Bool) -> String -> [String]
wordsBy :: (Char -> Bool) -> String -> [String]
wordsBy Char -> Bool
p = String -> [String]
f
  where
    f :: String -> [String]
f String
s = let (String
x,String
xs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
p String
s
          in  if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
x then [] else String
x forall a. a -> [a] -> [a]
: String -> [String]
f (forall a. Int -> [a] -> [a]
drop Int
1 String
xs)
                
-- | Use all parsed options to generate real options
constructOptions :: [Options -> Options] -> Options
constructOptions :: [Options -> Options] -> Options
constructOptions = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
($)) Options
noOptions

-- | Create Options type from string arguments
getOptions :: [String] -> (Options,[String],[String])
getOptions :: [String] -> (Options, [String], [String])
getOptions [String]
args = let ([Options -> Options]
flags,[String]
files,[String]
errors) = forall a.
ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
getOpt forall a. ArgOrder a
Permute [OptDescr (Options -> Options)]
options [String]
args
                      appliedOpts :: Options
appliedOpts = [Options -> Options] -> Options
constructOptions [Options -> Options]
flags
                      finOpts :: Options
finOpts = Options -> Options
condDisableOptimizations Options
appliedOpts
                  in (Options
finOpts,[String]
files,[String]
errors)

-- | Convert options back to commandline string
optionsToString :: Options -> [String]
optionsToString :: Options -> [String]
optionsToString Options
opt = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Options -> MyOptDescr -> [String]
serializeOption Options
opt) [MyOptDescr]
allOptions

-- | Combine 2 sets of options
combineOptions :: Options -> Options -> Options
combineOptions :: Options -> Options -> Options
combineOptions Options
o1 Options
o2 = let str1 :: [String]
str1      = Options -> [String]
optionsToString Options
o1
                           str2 :: [String]
str2      = Options -> [String]
optionsToString Options
o2
                           (Options
opt,[String]
_,[String]
_) = [String] -> (Options, [String], [String])
getOptions ([String]
str1 forall a. [a] -> [a] -> [a]
++ [String]
str2)
                       in  Options
opt