module GHC.Driver.Config
( initOptCoercionOpts
, initSimpleOpts
, initParserOpts
)
where
import GHC.Prelude
import GHC.Driver.Session
import GHC.Core.SimpleOpt
import GHC.Core.Coercion.Opt
import GHC.Parser.Lexer
initOptCoercionOpts :: DynFlags -> OptCoercionOpts
initOptCoercionOpts :: DynFlags -> OptCoercionOpts
initOptCoercionOpts DynFlags
dflags = OptCoercionOpts
{ optCoercionEnabled :: Bool
optCoercionEnabled = Bool -> Bool
not (DynFlags -> Bool
hasNoOptCoercion DynFlags
dflags)
}
initSimpleOpts :: DynFlags -> SimpleOpts
initSimpleOpts :: DynFlags -> SimpleOpts
initSimpleOpts DynFlags
dflags = SimpleOpts
{ so_uf_opts :: UnfoldingOpts
so_uf_opts = DynFlags -> UnfoldingOpts
unfoldingOpts DynFlags
dflags
, so_co_opts :: OptCoercionOpts
so_co_opts = DynFlags -> OptCoercionOpts
initOptCoercionOpts DynFlags
dflags
}
initParserOpts :: DynFlags -> ParserOpts
initParserOpts :: DynFlags -> ParserOpts
initParserOpts =
EnumSet WarningFlag
-> EnumSet Extension -> Bool -> Bool -> Bool -> Bool -> ParserOpts
mkParserOpts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DynFlags -> EnumSet WarningFlag
warningFlags
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DynFlags -> EnumSet Extension
extensionFlags
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DynFlags -> Bool
safeImportsOn
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Haddock
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepRawTokenStream
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. a -> b -> a
const Bool
True