Skip to content
GitLab
Menu
Projects
Groups
Snippets
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
2ebfd255
Commit
2ebfd255
authored
Jun 14, 2008
by
Ian Lynagh
Browse files
Whitespace only in DynFlags
parent
6b4ab02f
Changes
1
Hide whitespace changes
Inline
Side-by-side
compiler/main/DynFlags.hs
View file @
2ebfd255
...
...
@@ -20,42 +20,42 @@
-----------------------------------------------------------------------------
module
DynFlags
(
-- Dynamic flags
DynFlag
(
..
),
DynFlags
(
..
),
HscTarget
(
..
),
isObjectTarget
,
defaultObjectTarget
,
GhcMode
(
..
),
isOneShot
,
GhcLink
(
..
),
isNoLink
,
PackageFlag
(
..
),
Option
(
..
),
DynLibLoader
(
..
),
-- Dynamic flags
DynFlag
(
..
),
DynFlags
(
..
),
HscTarget
(
..
),
isObjectTarget
,
defaultObjectTarget
,
GhcMode
(
..
),
isOneShot
,
GhcLink
(
..
),
isNoLink
,
PackageFlag
(
..
),
Option
(
..
),
DynLibLoader
(
..
),
fFlags
,
xFlags
,
-- Configuration of the core-to-core and stg-to-stg phases
CoreToDo
(
..
),
StgToDo
(
..
),
SimplifierSwitch
(
..
),
SimplifierMode
(
..
),
FloatOutSwitches
(
..
),
getCoreToDo
,
getStgToDo
,
-- Manipulating DynFlags
defaultDynFlags
,
-- DynFlags
initDynFlags
,
-- DynFlags -> IO DynFlags
dopt
,
-- DynFlag -> DynFlags -> Bool
dopt_set
,
dopt_unset
,
-- DynFlags -> DynFlag -> DynFlags
getOpts
,
-- (DynFlags -> [a]) -> IO [a]
getVerbFlag
,
updOptLevel
,
setTmpDir
,
setPackageName
,
-- parsing DynFlags
parseDynamicFlags
,
-- Configuration of the core-to-core and stg-to-stg phases
CoreToDo
(
..
),
StgToDo
(
..
),
SimplifierSwitch
(
..
),
SimplifierMode
(
..
),
FloatOutSwitches
(
..
),
getCoreToDo
,
getStgToDo
,
-- Manipulating DynFlags
defaultDynFlags
,
-- DynFlags
initDynFlags
,
-- DynFlags -> IO DynFlags
dopt
,
-- DynFlag -> DynFlags -> Bool
dopt_set
,
dopt_unset
,
-- DynFlags -> DynFlag -> DynFlags
getOpts
,
-- (DynFlags -> [a]) -> IO [a]
getVerbFlag
,
updOptLevel
,
setTmpDir
,
setPackageName
,
-- parsing DynFlags
parseDynamicFlags
,
allFlags
,
-- misc stuff
machdepCCOpts
,
picCCOpts
,
-- misc stuff
machdepCCOpts
,
picCCOpts
,
supportedLanguages
,
compilerInfo
,
)
where
...
...
@@ -64,28 +64,28 @@ module DynFlags (
import
Module
import
PackageConfig
import
PrelNames
(
mAIN
)
import
PrelNames
(
mAIN
)
#
ifdef
i386_TARGET_ARCH
import
StaticFlags
(
opt_Static
)
import
StaticFlags
(
opt_Static
)
#
endif
import
StaticFlags
(
opt_PIC
,
WayName
(
..
),
v_Ways
,
v_Build_tag
,
v_RTS_Build_tag
)
import
StaticFlags
(
opt_PIC
,
WayName
(
..
),
v_Ways
,
v_Build_tag
,
v_RTS_Build_tag
)
import
{-#
SOURCE
#-
}
Packages
(
PackageState
)
import
DriverPhases
(
Phase
(
..
),
phaseInputExt
)
import
DriverPhases
(
Phase
(
..
),
phaseInputExt
)
import
Config
import
CmdLineParser
import
Constants
(
mAX_CONTEXT_REDUCTION_DEPTH
)
import
Panic
(
panic
,
GhcException
(
..
)
)
import
Constants
(
mAX_CONTEXT_REDUCTION_DEPTH
)
import
Panic
(
panic
,
GhcException
(
..
)
)
import
UniqFM
(
UniqFM
)
import
Util
import
Maybes
(
orElse
,
fromJust
)
import
Maybes
(
orElse
,
fromJust
)
import
SrcLoc
(
SrcSpan
)
import
Outputable
import
{-#
SOURCE
#-
}
ErrUtils
(
Severity
(
..
),
Message
,
mkLocMessage
)
import
Data.IORef
(
readIORef
)
import
Data.IORef
(
readIORef
)
import
Control.Exception
(
throwDyn
)
import
Control.Monad
(
when
)
import
Control.Monad
(
when
)
import
Data.Char
import
System.FilePath
...
...
@@ -151,14 +151,14 @@ data DynFlag
|
Opt_D_dump_mod_cycles
|
Opt_D_dump_view_pattern_commoning
|
Opt_D_faststring_stats
|
Opt_DumpToFile
-- ^ Append dump output to files instead of stdout.
|
Opt_DumpToFile
-- ^ Append dump output to files instead of stdout.
|
Opt_D_no_debug_output
|
Opt_DoCoreLinting
|
Opt_DoStgLinting
|
Opt_DoCmmLinting
|
Opt_DoAsmLinting
|
Opt_WarnIsError
-- -Werror; makes warnings fatal
|
Opt_WarnIsError
-- -Werror; makes warnings fatal
|
Opt_WarnDuplicateExports
|
Opt_WarnHiShadows
|
Opt_WarnImplicitPrelude
...
...
@@ -186,16 +186,16 @@ data DynFlag
|
Opt_IncoherentInstances
|
Opt_MonomorphismRestriction
|
Opt_MonoPatBinds
|
Opt_ExtendedDefaultRules
-- Use GHC's extended rules for defaulting
|
Opt_ExtendedDefaultRules
-- Use GHC's extended rules for defaulting
|
Opt_ForeignFunctionInterface
|
Opt_UnliftedFFITypes
|
Opt_PArr
-- Syntactic support for parallel arrays
|
Opt_Arrows
-- Arrow-notation syntax
|
Opt_PArr
-- Syntactic support for parallel arrays
|
Opt_Arrows
-- Arrow-notation syntax
|
Opt_TemplateHaskell
|
Opt_QuasiQuotes
|
Opt_ImplicitParams
|
Opt_Generics
|
Opt_ImplicitPrelude
|
Opt_ImplicitPrelude
|
Opt_ScopedTypeVariables
|
Opt_UnboxedTuples
|
Opt_BangPatterns
...
...
@@ -253,8 +253,8 @@ data DynFlag
|
Opt_DictsCheap
|
Opt_RewriteRules
|
Opt_Vectorise
|
Opt_RegsGraph
-- do graph coloring register allocation
|
Opt_RegsIterative
-- do iterative coalescing graph coloring register allocation
|
Opt_RegsGraph
-- do graph coloring register allocation
|
Opt_RegsIterative
-- do iterative coalescing graph coloring register allocation
-- misc opts
|
Opt_Cpp
...
...
@@ -289,116 +289,116 @@ data DynFlag
|
Opt_KeepTmpFiles
deriving
(
Eq
,
Show
)
data
DynFlags
=
DynFlags
{
ghcMode
::
GhcMode
,
ghcLink
::
GhcLink
,
coreToDo
::
Maybe
[
CoreToDo
],
-- reserved for -Ofile
stgToDo
::
Maybe
[
StgToDo
],
-- similarly
hscTarget
::
HscTarget
,
hscOutName
::
String
,
-- name of the output file
extCoreName
::
String
,
-- name of the .core output file
verbosity
::
Int
,
-- verbosity level
optLevel
::
Int
,
-- optimisation level
ghcMode
::
GhcMode
,
ghcLink
::
GhcLink
,
coreToDo
::
Maybe
[
CoreToDo
],
-- reserved for -Ofile
stgToDo
::
Maybe
[
StgToDo
],
-- similarly
hscTarget
::
HscTarget
,
hscOutName
::
String
,
-- name of the output file
extCoreName
::
String
,
-- name of the .core output file
verbosity
::
Int
,
-- verbosity level
optLevel
::
Int
,
-- optimisation level
simplPhases
::
Int
,
-- number of simplifier phases
maxSimplIterations
::
Int
,
-- max simplifier iterations
maxSimplIterations
::
Int
,
-- max simplifier iterations
shouldDumpSimplPhase
::
SimplifierMode
->
Bool
,
ruleCheck
::
Maybe
String
,
ruleCheck
::
Maybe
String
,
specConstrThreshold
::
Maybe
Int
,
-- Threshold for SpecConstr
specConstrCount
::
Maybe
Int
,
-- Max number of specialisations for any one function
liberateCaseThreshold
::
Maybe
Int
,
-- Threshold for LiberateCase
specConstrThreshold
::
Maybe
Int
,
-- Threshold for SpecConstr
specConstrCount
::
Maybe
Int
,
-- Max number of specialisations for any one function
liberateCaseThreshold
::
Maybe
Int
,
-- Threshold for LiberateCase
stolen_x86_regs
::
Int
,
cmdlineHcIncludes
::
[
String
],
-- -#includes
importPaths
::
[
FilePath
],
mainModIs
::
Module
,
mainFunIs
::
Maybe
String
,
ctxtStkDepth
::
Int
,
-- Typechecker context stack depth
stolen_x86_regs
::
Int
,
cmdlineHcIncludes
::
[
String
],
-- -#includes
importPaths
::
[
FilePath
],
mainModIs
::
Module
,
mainFunIs
::
Maybe
String
,
ctxtStkDepth
::
Int
,
-- Typechecker context stack depth
thisPackage
::
PackageId
,
thisPackage
::
PackageId
,
-- ways
wayNames
::
[
WayName
],
-- way flags from the cmd line
buildTag
::
String
,
-- the global "way" (eg. "p" for prof)
rtsBuildTag
::
String
,
-- the RTS "way"
wayNames
::
[
WayName
],
-- way flags from the cmd line
buildTag
::
String
,
-- the global "way" (eg. "p" for prof)
rtsBuildTag
::
String
,
-- the RTS "way"
-- paths etc.
objectDir
::
Maybe
String
,
hiDir
::
Maybe
String
,
stubDir
::
Maybe
String
,
objectDir
::
Maybe
String
,
hiDir
::
Maybe
String
,
stubDir
::
Maybe
String
,
objectSuf
::
String
,
hcSuf
::
String
,
hiSuf
::
String
,
objectSuf
::
String
,
hcSuf
::
String
,
hiSuf
::
String
,
outputFile
::
Maybe
String
,
outputHi
::
Maybe
String
,
dynLibLoader
::
DynLibLoader
,
outputFile
::
Maybe
String
,
outputHi
::
Maybe
String
,
dynLibLoader
::
DynLibLoader
,
-- | This is set by DriverPipeline.runPipeline based on where
--
its output is going.
dumpPrefix
::
Maybe
FilePath
,
--
its output is going.
dumpPrefix
::
Maybe
FilePath
,
-- | Override the dumpPrefix set by runPipeline.
--
Set by -ddump-file-prefix
dumpPrefixForce
::
Maybe
FilePath
,
includePaths
::
[
String
],
libraryPaths
::
[
String
],
frameworkPaths
::
[
String
],
-- used on darwin only
cmdlineFrameworks
::
[
String
],
-- ditto
tmpDir
::
String
,
-- no trailing '/'
--
Set by -ddump-file-prefix
dumpPrefixForce
::
Maybe
FilePath
,
includePaths
::
[
String
],
libraryPaths
::
[
String
],
frameworkPaths
::
[
String
],
-- used on darwin only
cmdlineFrameworks
::
[
String
],
-- ditto
tmpDir
::
String
,
-- no trailing '/'
ghcUsagePath
::
FilePath
,
-- Filled in by SysTools
ghciUsagePath
::
FilePath
,
-- ditto
hpcDir
::
String
,
-- ^ path to store the .mix files
hpcDir
::
String
,
-- ^ path to store the .mix files
-- options for particular phases
opt_L
::
[
String
],
opt_P
::
[
String
],
opt_F
::
[
String
],
opt_c
::
[
String
],
opt_m
::
[
String
],
opt_a
::
[
String
],
opt_l
::
[
String
],
opt_dep
::
[
String
],
opt_windres
::
[
String
],
opt_L
::
[
String
],
opt_P
::
[
String
],
opt_F
::
[
String
],
opt_c
::
[
String
],
opt_m
::
[
String
],
opt_a
::
[
String
],
opt_l
::
[
String
],
opt_dep
::
[
String
],
opt_windres
::
[
String
],
-- commands for particular phases
pgm_L
::
String
,
pgm_P
::
(
String
,[
Option
]),
pgm_F
::
String
,
pgm_c
::
(
String
,[
Option
]),
pgm_m
::
(
String
,[
Option
]),
pgm_s
::
(
String
,[
Option
]),
pgm_a
::
(
String
,[
Option
]),
pgm_l
::
(
String
,[
Option
]),
pgm_dll
::
(
String
,[
Option
]),
pgm_L
::
String
,
pgm_P
::
(
String
,[
Option
]),
pgm_F
::
String
,
pgm_c
::
(
String
,[
Option
]),
pgm_m
::
(
String
,[
Option
]),
pgm_s
::
(
String
,[
Option
]),
pgm_a
::
(
String
,[
Option
]),
pgm_l
::
(
String
,[
Option
]),
pgm_dll
::
(
String
,[
Option
]),
pgm_T
::
String
,
pgm_sysman
::
String
,
pgm_windres
::
String
,
-- Package flags
extraPkgConfs
::
[
FilePath
],
extraPkgConfs
::
[
FilePath
],
topDir
::
FilePath
,
-- filled in by SysTools
systemPackageConfig
::
FilePath
,
-- ditto
-- The -package-conf flags given on the command line, in the order
-- they appeared.
-- The -package-conf flags given on the command line, in the order
-- they appeared.
packageFlags
::
[
PackageFlag
],
-- The -package and -hide-package flags from the command-line
packageFlags
::
[
PackageFlag
],
-- The -package and -hide-package flags from the command-line
-- Package state
-- NB. do not modify this field, it is calculated by
-- NB. do not modify this field, it is calculated by
-- Packages.initPackages and Packages.updatePackages.
pkgDatabase
::
Maybe
(
UniqFM
PackageConfig
),
pkgState
::
PackageState
,
pkgState
::
PackageState
,
-- hsc dynamic flags
flags
::
[
DynFlag
],
flags
::
[
DynFlag
],
-- message output
log_action
::
Severity
->
SrcSpan
->
PprStyle
->
Message
->
IO
()
,
...
...
@@ -427,7 +427,7 @@ isObjectTarget _ = False
-- in order to check whether they need to be recompiled.
data
GhcMode
=
CompManager
-- ^ --make, GHCi, etc.
|
OneShot
-- ^ ghc -c Foo.hs
|
OneShot
-- ^ ghc -c Foo.hs
|
MkDepend
-- ^ ghc -M, see Finder for why we need this
deriving
Eq
...
...
@@ -436,11 +436,11 @@ isOneShot OneShot = True
isOneShot
_other
=
False
-- | What kind of linking to do.
data
GhcLink
-- What to do in the link step, if there is one
=
NoLink
-- Don't link at all
|
LinkBinary
-- Link object code into a binary
data
GhcLink
-- What to do in the link step, if there is one
=
NoLink
-- Don't link at all
|
LinkBinary
-- Link object code into a binary
|
LinkInMemory
-- Use the in-memory dynamic linker
|
LinkDynLib
-- Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
|
LinkDynLib
-- Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
deriving
(
Eq
,
Show
)
isNoLink
::
GhcLink
->
Bool
...
...
@@ -460,8 +460,8 @@ defaultHscTarget = defaultObjectTarget
-- object files on the current platform.
defaultObjectTarget
::
HscTarget
defaultObjectTarget
|
cGhcWithNativeCodeGen
==
"YES"
=
HscAsm
|
otherwise
=
HscC
|
cGhcWithNativeCodeGen
==
"YES"
=
HscAsm
|
otherwise
=
HscC
data
DynLibLoader
=
Deployable
...
...
@@ -476,74 +476,74 @@ initDynFlags dflags = do
build_tag
<-
readIORef
v_Build_tag
rts_build_tag
<-
readIORef
v_RTS_Build_tag
return
dflags
{
wayNames
=
ways
,
buildTag
=
build_tag
,
rtsBuildTag
=
rts_build_tag
}
wayNames
=
ways
,
buildTag
=
build_tag
,
rtsBuildTag
=
rts_build_tag
}
defaultDynFlags
::
DynFlags
defaultDynFlags
=
DynFlags
{
ghcMode
=
CompManager
,
ghcLink
=
LinkBinary
,
coreToDo
=
Nothing
,
stgToDo
=
Nothing
,
hscTarget
=
defaultHscTarget
,
hscOutName
=
""
,
extCoreName
=
""
,
verbosity
=
0
,
optLevel
=
0
,
ghcMode
=
CompManager
,
ghcLink
=
LinkBinary
,
coreToDo
=
Nothing
,
stgToDo
=
Nothing
,
hscTarget
=
defaultHscTarget
,
hscOutName
=
""
,
extCoreName
=
""
,
verbosity
=
0
,
optLevel
=
0
,
simplPhases
=
2
,
maxSimplIterations
=
4
,
maxSimplIterations
=
4
,
shouldDumpSimplPhase
=
const
False
,
ruleCheck
=
Nothing
,
specConstrThreshold
=
Just
200
,
specConstrCount
=
Just
3
,
ruleCheck
=
Nothing
,
specConstrThreshold
=
Just
200
,
specConstrCount
=
Just
3
,
liberateCaseThreshold
=
Just
200
,
stolen_x86_regs
=
4
,
cmdlineHcIncludes
=
[]
,
importPaths
=
[
"."
],
mainModIs
=
mAIN
,
mainFunIs
=
Nothing
,
ctxtStkDepth
=
mAX_CONTEXT_REDUCTION_DEPTH
,
thisPackage
=
mainPackageId
,
objectDir
=
Nothing
,
hiDir
=
Nothing
,
stubDir
=
Nothing
,
objectSuf
=
phaseInputExt
StopLn
,
hcSuf
=
phaseInputExt
HCc
,
hiSuf
=
"hi"
,
outputFile
=
Nothing
,
outputHi
=
Nothing
,
dynLibLoader
=
Deployable
,
dumpPrefix
=
Nothing
,
dumpPrefixForce
=
Nothing
,
includePaths
=
[]
,
libraryPaths
=
[]
,
frameworkPaths
=
[]
,
cmdlineFrameworks
=
[]
,
tmpDir
=
cDEFAULT_TMPDIR
,
hpcDir
=
".hpc"
,
opt_L
=
[]
,
opt_P
=
(
if
opt_PIC
then
[
"-D__PIC__"
]
else
[]
),
opt_F
=
[]
,
opt_c
=
[]
,
opt_a
=
[]
,
opt_m
=
[]
,
opt_l
=
[]
,
opt_dep
=
[]
,
stolen_x86_regs
=
4
,
cmdlineHcIncludes
=
[]
,
importPaths
=
[
"."
],
mainModIs
=
mAIN
,
mainFunIs
=
Nothing
,
ctxtStkDepth
=
mAX_CONTEXT_REDUCTION_DEPTH
,
thisPackage
=
mainPackageId
,
objectDir
=
Nothing
,
hiDir
=
Nothing
,
stubDir
=
Nothing
,
objectSuf
=
phaseInputExt
StopLn
,
hcSuf
=
phaseInputExt
HCc
,
hiSuf
=
"hi"
,
outputFile
=
Nothing
,
outputHi
=
Nothing
,
dynLibLoader
=
Deployable
,
dumpPrefix
=
Nothing
,
dumpPrefixForce
=
Nothing
,
includePaths
=
[]
,
libraryPaths
=
[]
,
frameworkPaths
=
[]
,
cmdlineFrameworks
=
[]
,
tmpDir
=
cDEFAULT_TMPDIR
,
hpcDir
=
".hpc"
,
opt_L
=
[]
,
opt_P
=
(
if
opt_PIC
then
[
"-D__PIC__"
]
else
[]
),
opt_F
=
[]
,
opt_c
=
[]
,
opt_a
=
[]
,
opt_m
=
[]
,
opt_l
=
[]
,
opt_dep
=
[]
,
opt_windres
=
[]
,
extraPkgConfs
=
[]
,
packageFlags
=
[]
,
extraPkgConfs
=
[]
,
packageFlags
=
[]
,
pkgDatabase
=
Nothing
,
pkgState
=
panic
"no package state yet: call GHC.setSessionDynFlags"
,
haddockOptions
=
Nothing
,
...
...
@@ -569,17 +569,17 @@ defaultDynFlags =
-- The default -O0 options
++
standardWarnings
,
log_action
=
\
severity
srcSpan
style
msg
->
log_action
=
\
severity
srcSpan
style
msg
->
case
severity
of
SevInfo
->
hPutStrLn
stderr
(
show
(
msg
style
))
SevFatal
->
hPutStrLn
stderr
(
show
(
msg
style
))
_
->
hPutStrLn
stderr
(
'
\n
'
:
show
((
mkLocMessage
srcSpan
msg
)
style
))
}
{-
{-
Verbosity levels:
0
| print errors & warnings only
0
| print errors & warnings only
1 | minimal verbosity: print "compiling M ... done." for each module.
2 | equivalent to -dshow-passes
3 | equivalent to existing "ghc -v"
...
...
@@ -598,11 +598,11 @@ dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
getOpts
::
DynFlags
->
(
DynFlags
->
[
a
])
->
[
a
]
getOpts
dflags
opts
=
reverse
(
opts
dflags
)
-- We add to the options from the front, so we need to reverse the list
-- We add to the options from the front, so we need to reverse the list
getVerbFlag
::
DynFlags
->
String
getVerbFlag
dflags
|
verbosity
dflags
>=
3
=
"-v"
getVerbFlag
dflags
|
verbosity
dflags
>=
3
=
"-v"
|
otherwise
=
""
setObjectDir
,
setHiDir
,
setStubDir
,
setObjectSuf
,
setHiSuf
,
setHcSuf
,
parseDynLibLoaderMode
,
...
...
@@ -677,11 +677,11 @@ addHaddockOpts f d = d{ haddockOptions = Just f}
data
Option
=
FileOption
-- an entry that _contains_ filename(s) / filepaths.
String
-- a non-filepath prefix that shouldn't be
-- transformed (e.g., "/out=")
String
-- the filepath/filename portion
String
-- a non-filepath prefix that shouldn't be
-- transformed (e.g., "/out=")
String
-- the filepath/filename portion
|
Option
String
-----------------------------------------------------------------------------
-- Setting the optimisation level
...
...
@@ -690,36 +690,36 @@ updOptLevel :: Int -> DynFlags -> DynFlags
updOptLevel
n
dfs
=
dfs2
{
optLevel
=
final_n
}
where
final_n
=
max
0
(
min
2
n
)
-- Clamp to 0 <= n <= 2
final_n
=
max
0
(
min
2
n
)
-- Clamp to 0 <= n <= 2
dfs1
=
foldr
(
flip
dopt_unset
)
dfs
remove_dopts
dfs2
=
foldr
(
flip
dopt_set
)
dfs1
extra_dopts
extra_dopts
=
[
f
|
(
ns
,
f
)
<-
optLevelFlags
,
final_n
`
elem
`
ns
]
remove_dopts
=
[
f
|
(
ns
,
f
)
<-
optLevelFlags
,
final_n
`
notElem
`
ns
]
optLevelFlags
::
[([
Int
],
DynFlag
)]
optLevelFlags
=
[
([
0
],
Opt_IgnoreInterfacePragmas
)
=
[
([
0
],
Opt_IgnoreInterfacePragmas
)
,
([
0
],
Opt_OmitInterfacePragmas
)
,
([
1
,
2
],
Opt_IgnoreAsserts
)
,
([
1
,
2
],
Opt_RewriteRules
)
-- Off for -O0; see Note [Scoping for Builtin rules]
--
in PrelRules
,
([
1
,
2
],
Opt_DoEtaReduction
)
,
([
1
,
2
],
Opt_CaseMerge
)
,
([
1
,
2
],
Opt_Strictness
)
,
([
1
,
2
],
Opt_CSE
)
,
([
1
,
2
],
Opt_FullLaziness
)
,
([
1
,
2
],
Opt_IgnoreAsserts
)
,
([
1
,
2
],
Opt_RewriteRules
)
-- Off for -O0; see Note [Scoping for Builtin rules]
--
in PrelRules
,
([
1
,
2
],
Opt_DoEtaReduction
)
,
([
1
,
2
],
Opt_CaseMerge
)
,
([
1
,
2
],
Opt_Strictness
)
,
([
1
,
2
],
Opt_CSE
)
,
([
1
,
2
],
Opt_FullLaziness
)
,
([
2
],
Opt_LiberateCase
)