module GHC.Iface.Flags (
IfaceDynFlags(..)
, IfaceGeneralFlag(..)
, IfaceProfAuto(..)
, IfaceExtension(..)
, IfaceLanguage(..)
, IfaceCppOptions(..)
, IfaceCodeGen(..)
, IfaceDistinctConstructorConfig(..)
, pprIfaceDynFlags
, missingExtraFlagInfo
) where
import GHC.Prelude
import qualified Data.Set as Set
import GHC.Utils.Outputable
import Control.DeepSeq
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
import GHC.Driver.DynFlags
import GHC.Types.SafeHaskell
import GHC.Core.Opt.CallerCC.Types
import qualified GHC.LanguageExtensions as LangExt
import GHC.Stg.Debug.Types
data IfaceDynFlags = IfaceDynFlags
{ IfaceDynFlags -> Maybe (Maybe String)
ifaceMainIs :: Maybe (Maybe String)
, IfaceDynFlags -> IfaceTrustInfo
ifaceSafeMode :: IfaceTrustInfo
, IfaceDynFlags -> Maybe IfaceLanguage
ifaceLang :: Maybe IfaceLanguage
, IfaceDynFlags -> [IfaceExtension]
ifaceExts :: [IfaceExtension]
, IfaceDynFlags -> IfaceCppOptions
ifaceCppOptions :: IfaceCppOptions
, IfaceDynFlags -> IfaceCppOptions
ifaceJsOptions :: IfaceCppOptions
, IfaceDynFlags -> IfaceCppOptions
ifaceCmmOptions :: IfaceCppOptions
, IfaceDynFlags -> [String]
ifacePaths :: [String]
, IfaceDynFlags -> Maybe IfaceProfAuto
ifaceProf :: Maybe IfaceProfAuto
, IfaceDynFlags -> [IfaceGeneralFlag]
ifaceTicky :: [IfaceGeneralFlag]
, IfaceDynFlags -> IfaceCodeGen
ifaceCodeGen :: IfaceCodeGen
, IfaceDynFlags -> Bool
ifaceFatIface :: Bool
, IfaceDynFlags -> Int
ifaceDebugLevel :: Int
, IfaceDynFlags -> [CallerCcFilter]
ifaceCallerCCFilters :: [CallerCcFilter]
}
pprIfaceDynFlags :: IfaceDynFlags -> SDoc
pprIfaceDynFlags :: IfaceDynFlags -> SDoc
pprIfaceDynFlags (IfaceDynFlags Maybe (Maybe String)
a1 IfaceTrustInfo
a2 Maybe IfaceLanguage
a3 [IfaceExtension]
a4 IfaceCppOptions
a5 IfaceCppOptions
a6 IfaceCppOptions
a7 [String]
a8 Maybe IfaceProfAuto
a9 [IfaceGeneralFlag]
a10 IfaceCodeGen
a11 Bool
a12 Int
a13 [CallerCcFilter]
a14) =
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"main-is:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Maybe (Maybe SDoc) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Maybe (Maybe SDoc) -> SDoc) -> Maybe (Maybe SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ (Maybe String -> Maybe SDoc)
-> Maybe (Maybe String) -> Maybe (Maybe SDoc)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String -> SDoc) -> Maybe String -> Maybe SDoc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall doc. IsLine doc => String -> doc
text @SDoc)) Maybe (Maybe String)
a1)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"safe-mode:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceTrustInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceTrustInfo
a2
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"lang:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Maybe IfaceLanguage -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe IfaceLanguage
a3
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"exts:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [IfaceExtension] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceExtension]
a4
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"cpp-options:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceCppOptions -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceCppOptions
a5
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"js-options:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceCppOptions -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceCppOptions
a6
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"cmm-options:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceCppOptions -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceCppOptions
a7
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"paths:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
forall doc. IsLine doc => String -> doc
text [String]
a8)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"prof:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Maybe IfaceProfAuto -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe IfaceProfAuto
a9
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ticky:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((IfaceGeneralFlag -> SDoc) -> [IfaceGeneralFlag] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceGeneralFlag -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceGeneralFlag]
a10)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"codegen:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceCodeGen -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceCodeGen
a11
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"fat-iface:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
a12
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"debug-level:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
a13
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"caller-cc-filters:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [CallerCcFilter] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [CallerCcFilter]
a14
]
missingExtraFlagInfo :: SDoc
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"flags: no detailed info, recompile with -fwrite-if-self-recomp-flags"
where
_placeholder :: GeneralFlag
_placeholder = GeneralFlag
Opt_WriteSelfRecompFlags
instance Binary IfaceDynFlags where
put_ :: WriteBinHandle -> IfaceDynFlags -> IO ()
put_ WriteBinHandle
bh (IfaceDynFlags Maybe (Maybe String)
a1 IfaceTrustInfo
a2 Maybe IfaceLanguage
a3 [IfaceExtension]
a4 IfaceCppOptions
a5 IfaceCppOptions
a6 IfaceCppOptions
a7 [String]
a8 Maybe IfaceProfAuto
a9 [IfaceGeneralFlag]
a10 IfaceCodeGen
a11 Bool
a12 Int
a13 [CallerCcFilter]
a14) = do
WriteBinHandle -> Maybe (Maybe String) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe (Maybe String)
a1
WriteBinHandle -> IfaceTrustInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTrustInfo
a2
WriteBinHandle -> Maybe IfaceLanguage -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfaceLanguage
a3
WriteBinHandle -> [IfaceExtension] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceExtension]
a4
WriteBinHandle -> IfaceCppOptions -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCppOptions
a5
WriteBinHandle -> IfaceCppOptions -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCppOptions
a6
WriteBinHandle -> IfaceCppOptions -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCppOptions
a7
WriteBinHandle -> [String] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [String]
a8
WriteBinHandle -> Maybe IfaceProfAuto -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfaceProfAuto
a9
WriteBinHandle -> [IfaceGeneralFlag] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceGeneralFlag]
a10
WriteBinHandle -> IfaceCodeGen -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCodeGen
a11
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a12
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
a13
WriteBinHandle -> [CallerCcFilter] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [CallerCcFilter]
a14
get :: ReadBinHandle -> IO IfaceDynFlags
get ReadBinHandle
bh = Maybe (Maybe String)
-> IfaceTrustInfo
-> Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags
IfaceDynFlags (Maybe (Maybe String)
-> IfaceTrustInfo
-> Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO (Maybe (Maybe String))
-> IO
(IfaceTrustInfo
-> Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO (Maybe (Maybe String))
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(IfaceTrustInfo
-> Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO IfaceTrustInfo
-> IO
(Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceTrustInfo
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(Maybe IfaceLanguage
-> [IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO (Maybe IfaceLanguage)
-> IO
([IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO (Maybe IfaceLanguage)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
([IfaceExtension]
-> IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO [IfaceExtension]
-> IO
(IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [IfaceExtension]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(IfaceCppOptions
-> IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO IfaceCppOptions
-> IO
(IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceCppOptions
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(IfaceCppOptions
-> IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO IfaceCppOptions
-> IO
(IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceCppOptions
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(IfaceCppOptions
-> [String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO IfaceCppOptions
-> IO
([String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceCppOptions
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
([String]
-> Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO [String]
-> IO
(Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [String]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(Maybe IfaceProfAuto
-> [IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO (Maybe IfaceProfAuto)
-> IO
([IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO (Maybe IfaceProfAuto)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
([IfaceGeneralFlag]
-> IfaceCodeGen
-> Bool
-> Int
-> [CallerCcFilter]
-> IfaceDynFlags)
-> IO [IfaceGeneralFlag]
-> IO
(IfaceCodeGen -> Bool -> Int -> [CallerCcFilter] -> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [IfaceGeneralFlag]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO
(IfaceCodeGen -> Bool -> Int -> [CallerCcFilter] -> IfaceDynFlags)
-> IO IfaceCodeGen
-> IO (Bool -> Int -> [CallerCcFilter] -> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceCodeGen
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO (Bool -> Int -> [CallerCcFilter] -> IfaceDynFlags)
-> IO Bool -> IO (Int -> [CallerCcFilter] -> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO Bool
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO (Int -> [CallerCcFilter] -> IfaceDynFlags)
-> IO Int -> IO ([CallerCcFilter] -> IfaceDynFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
IO ([CallerCcFilter] -> IfaceDynFlags)
-> IO [CallerCcFilter] -> IO IfaceDynFlags
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [CallerCcFilter]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance NFData IfaceDynFlags where
rnf :: IfaceDynFlags -> ()
rnf (IfaceDynFlags Maybe (Maybe String)
a1 IfaceTrustInfo
a2 Maybe IfaceLanguage
a3 [IfaceExtension]
a4 IfaceCppOptions
a5 IfaceCppOptions
a6 IfaceCppOptions
a7 [String]
a8 Maybe IfaceProfAuto
a9 [IfaceGeneralFlag]
a10 IfaceCodeGen
a11 Bool
a12 Int
a13 [CallerCcFilter]
a14) =
Maybe (Maybe String) -> ()
forall a. NFData a => a -> ()
rnf Maybe (Maybe String)
a1
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceTrustInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceTrustInfo
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceLanguage -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceLanguage
a3
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceExtension] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExtension]
a4
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCppOptions -> ()
forall a. NFData a => a -> ()
rnf IfaceCppOptions
a5
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCppOptions -> ()
forall a. NFData a => a -> ()
rnf IfaceCppOptions
a6
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCppOptions -> ()
forall a. NFData a => a -> ()
rnf IfaceCppOptions
a7
() -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
a8
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceProfAuto -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceProfAuto
a9
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceGeneralFlag] -> ()
forall a. NFData a => a -> ()
rnf [IfaceGeneralFlag]
a10
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCodeGen -> ()
forall a. NFData a => a -> ()
rnf IfaceCodeGen
a11
() -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
a12
() -> () -> ()
forall a b. a -> b -> b
`seq` Int -> ()
forall a. NFData a => a -> ()
rnf Int
a13
() -> () -> ()
forall a b. a -> b -> b
`seq` [CallerCcFilter] -> ()
forall a. NFData a => a -> ()
rnf [CallerCcFilter]
a14
newtype IfaceGeneralFlag = IfaceGeneralFlag GeneralFlag
instance NFData IfaceGeneralFlag where
rnf :: IfaceGeneralFlag -> ()
rnf (IfaceGeneralFlag !GeneralFlag
_) = ()
instance Binary IfaceGeneralFlag where
put_ :: WriteBinHandle -> IfaceGeneralFlag -> IO ()
put_ WriteBinHandle
bh (IfaceGeneralFlag GeneralFlag
f) = WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (GeneralFlag -> Int
forall a. Enum a => a -> Int
fromEnum GeneralFlag
f)
get :: ReadBinHandle -> IO IfaceGeneralFlag
get ReadBinHandle
bh = GeneralFlag -> IfaceGeneralFlag
IfaceGeneralFlag (GeneralFlag -> IfaceGeneralFlag)
-> (Int -> GeneralFlag) -> Int -> IfaceGeneralFlag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> GeneralFlag
forall a. Enum a => Int -> a
toEnum (Int -> IfaceGeneralFlag) -> IO Int -> IO IfaceGeneralFlag
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceGeneralFlag where
ppr :: IfaceGeneralFlag -> SDoc
ppr (IfaceGeneralFlag GeneralFlag
f) = String -> SDoc
forall doc. IsLine doc => String -> doc
text (GeneralFlag -> String
forall a. Show a => a -> String
show GeneralFlag
f)
newtype IfaceProfAuto = IfaceProfAuto ProfAuto
instance NFData IfaceProfAuto where
rnf :: IfaceProfAuto -> ()
rnf (IfaceProfAuto !ProfAuto
_) = ()
instance Binary IfaceProfAuto where
put_ :: WriteBinHandle -> IfaceProfAuto -> IO ()
put_ WriteBinHandle
bh (IfaceProfAuto ProfAuto
f) = WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (ProfAuto -> Int
forall a. Enum a => a -> Int
fromEnum ProfAuto
f)
get :: ReadBinHandle -> IO IfaceProfAuto
get ReadBinHandle
bh = ProfAuto -> IfaceProfAuto
IfaceProfAuto (ProfAuto -> IfaceProfAuto)
-> (Int -> ProfAuto) -> Int -> IfaceProfAuto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ProfAuto
forall a. Enum a => Int -> a
toEnum (Int -> IfaceProfAuto) -> IO Int -> IO IfaceProfAuto
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceProfAuto where
ppr :: IfaceProfAuto -> SDoc
ppr (IfaceProfAuto ProfAuto
f) = String -> SDoc
forall doc. IsLine doc => String -> doc
text (ProfAuto -> String
forall a. Show a => a -> String
show ProfAuto
f)
newtype IfaceExtension = IfaceExtension LangExt.Extension
instance NFData IfaceExtension where
rnf :: IfaceExtension -> ()
rnf (IfaceExtension !Extension
_) = ()
instance Binary IfaceExtension where
put_ :: WriteBinHandle -> IfaceExtension -> IO ()
put_ WriteBinHandle
bh (IfaceExtension Extension
f) = WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Extension -> Int
forall a. Enum a => a -> Int
fromEnum Extension
f)
get :: ReadBinHandle -> IO IfaceExtension
get ReadBinHandle
bh = Extension -> IfaceExtension
IfaceExtension (Extension -> IfaceExtension)
-> (Int -> Extension) -> Int -> IfaceExtension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Extension
forall a. Enum a => Int -> a
toEnum (Int -> IfaceExtension) -> IO Int -> IO IfaceExtension
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceExtension where
ppr :: IfaceExtension -> SDoc
ppr (IfaceExtension Extension
f) = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Extension -> String
forall a. Show a => a -> String
show Extension
f)
newtype IfaceLanguage = IfaceLanguage Language
instance NFData IfaceLanguage where
rnf :: IfaceLanguage -> ()
rnf (IfaceLanguage !Language
_) = ()
instance Binary IfaceLanguage where
put_ :: WriteBinHandle -> IfaceLanguage -> IO ()
put_ WriteBinHandle
bh (IfaceLanguage Language
f) = WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Language -> Int
forall a. Enum a => a -> Int
fromEnum Language
f)
get :: ReadBinHandle -> IO IfaceLanguage
get ReadBinHandle
bh = Language -> IfaceLanguage
IfaceLanguage (Language -> IfaceLanguage)
-> (Int -> Language) -> Int -> IfaceLanguage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Language
forall a. Enum a => Int -> a
toEnum (Int -> IfaceLanguage) -> IO Int -> IO IfaceLanguage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceLanguage where
ppr :: IfaceLanguage -> SDoc
ppr (IfaceLanguage Language
f) = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Language -> String
forall a. Show a => a -> String
show Language
f)
data IfaceCppOptions = IfaceCppOptions { IfaceCppOptions -> [String]
ifaceCppIncludes :: [FilePath]
, IfaceCppOptions -> [String]
ifaceCppOpts :: [String]
, IfaceCppOptions -> ([String], Fingerprint)
ifaceCppSig :: ([String], Fingerprint)
}
instance NFData IfaceCppOptions where
rnf :: IfaceCppOptions -> ()
rnf (IfaceCppOptions [String]
is [String]
os ([String], Fingerprint)
s) = [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
is () -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
os () -> () -> ()
forall a b. a -> b -> b
`seq` ([String], Fingerprint) -> ()
forall a. NFData a => a -> ()
rnf ([String], Fingerprint)
s
instance Binary IfaceCppOptions where
put_ :: WriteBinHandle -> IfaceCppOptions -> IO ()
put_ WriteBinHandle
bh (IfaceCppOptions [String]
is [String]
os ([String], Fingerprint)
s) = do
WriteBinHandle -> [String] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [String]
is
WriteBinHandle -> [String] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [String]
os
WriteBinHandle -> ([String], Fingerprint) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh ([String], Fingerprint)
s
get :: ReadBinHandle -> IO IfaceCppOptions
get ReadBinHandle
bh = [String] -> [String] -> ([String], Fingerprint) -> IfaceCppOptions
IfaceCppOptions ([String]
-> [String] -> ([String], Fingerprint) -> IfaceCppOptions)
-> IO [String]
-> IO ([String] -> ([String], Fingerprint) -> IfaceCppOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [String]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO ([String] -> ([String], Fingerprint) -> IfaceCppOptions)
-> IO [String] -> IO (([String], Fingerprint) -> IfaceCppOptions)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [String]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (([String], Fingerprint) -> IfaceCppOptions)
-> IO ([String], Fingerprint) -> IO IfaceCppOptions
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO ([String], Fingerprint)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceCppOptions where
ppr :: IfaceCppOptions -> SDoc
ppr (IfaceCppOptions [String]
is [String]
os ([String]
wos, Fingerprint
fp)) =
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"includes:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
forall doc. IsLine doc => String -> doc
text [String]
is)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"opts:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
forall doc. IsLine doc => String -> doc
text [String]
os)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"signature:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
fp) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => String -> doc
text @SDoc) [String]
wos)
]
data IfaceCodeGen = IfaceCodeGen
{ IfaceCodeGen -> [IfaceGeneralFlag]
ifaceCodeGenFlags :: [IfaceGeneralFlag]
, IfaceCodeGen -> IfaceDistinctConstructorConfig
ifaceCodeGenDistinctConstructorTables :: IfaceDistinctConstructorConfig
}
instance NFData IfaceCodeGen where
rnf :: IfaceCodeGen -> ()
rnf (IfaceCodeGen [IfaceGeneralFlag]
flags IfaceDistinctConstructorConfig
distinctCnstrTables) =
[IfaceGeneralFlag] -> ()
forall a. NFData a => a -> ()
rnf [IfaceGeneralFlag]
flags () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceDistinctConstructorConfig -> ()
forall a. NFData a => a -> ()
rnf IfaceDistinctConstructorConfig
distinctCnstrTables
instance Binary IfaceCodeGen where
put_ :: WriteBinHandle -> IfaceCodeGen -> IO ()
put_ WriteBinHandle
bh (IfaceCodeGen [IfaceGeneralFlag]
flags IfaceDistinctConstructorConfig
distinctCnstrTables) = do
WriteBinHandle -> [IfaceGeneralFlag] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceGeneralFlag]
flags
WriteBinHandle -> IfaceDistinctConstructorConfig -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceDistinctConstructorConfig
distinctCnstrTables
get :: ReadBinHandle -> IO IfaceCodeGen
get ReadBinHandle
bh =
[IfaceGeneralFlag]
-> IfaceDistinctConstructorConfig -> IfaceCodeGen
IfaceCodeGen ([IfaceGeneralFlag]
-> IfaceDistinctConstructorConfig -> IfaceCodeGen)
-> IO [IfaceGeneralFlag]
-> IO (IfaceDistinctConstructorConfig -> IfaceCodeGen)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [IfaceGeneralFlag]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (IfaceDistinctConstructorConfig -> IfaceCodeGen)
-> IO IfaceDistinctConstructorConfig -> IO IfaceCodeGen
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceDistinctConstructorConfig
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Outputable IfaceCodeGen where
ppr :: IfaceCodeGen -> SDoc
ppr (IfaceCodeGen [IfaceGeneralFlag]
flags IfaceDistinctConstructorConfig
distinctCnstrTables) =
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat
[ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"flags:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [IfaceGeneralFlag] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceGeneralFlag]
flags
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"distinct constructor tables:"
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceDistinctConstructorConfig -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceDistinctConstructorConfig
distinctCnstrTables
]
newtype IfaceDistinctConstructorConfig = IfaceDistinctConstructorConfig StgDebugDctConfig
instance NFData IfaceDistinctConstructorConfig where
rnf :: IfaceDistinctConstructorConfig -> ()
rnf (IfaceDistinctConstructorConfig StgDebugDctConfig
cnf) = case StgDebugDctConfig
cnf of
StgDebugDctConfig
All -> ()
(Only Set String
v) -> Set String -> ()
forall a. NFData a => a -> ()
rnf Set String
v
StgDebugDctConfig
None -> ()
instance Outputable IfaceDistinctConstructorConfig where
ppr :: IfaceDistinctConstructorConfig -> SDoc
ppr (IfaceDistinctConstructorConfig StgDebugDctConfig
cnf) = case StgDebugDctConfig
cnf of
StgDebugDctConfig
All -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"all"
(Only Set String
v) -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"only" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ (String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> SDoc
forall doc. IsLine doc => String -> doc
text ([String] -> [SDoc]) -> [String] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ Set String -> [String]
forall a. Set a -> [a]
Set.toList Set String
v)
StgDebugDctConfig
None -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"none"
instance Binary IfaceDistinctConstructorConfig where
put_ :: WriteBinHandle -> IfaceDistinctConstructorConfig -> IO ()
put_ WriteBinHandle
bh (IfaceDistinctConstructorConfig StgDebugDctConfig
cnf) = case StgDebugDctConfig
cnf of
StgDebugDctConfig
All -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
(Only Set String
cs) -> do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> Set String -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Set String
cs
StgDebugDctConfig
None -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
get :: ReadBinHandle -> IO IfaceDistinctConstructorConfig
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
IfaceDistinctConstructorConfig <$>
case h of
Word8
0 -> StgDebugDctConfig -> IO StgDebugDctConfig
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StgDebugDctConfig
All
Word8
1 -> Set String -> StgDebugDctConfig
Only (Set String -> StgDebugDctConfig)
-> IO (Set String) -> IO StgDebugDctConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO (Set String)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> StgDebugDctConfig -> IO StgDebugDctConfig
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StgDebugDctConfig
None