{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}

module Distribution.Types.LocalBuildConfig
  ( -- * The types
    PackageBuildDescr (..)
  , ComponentBuildDescr (..)
  , LocalBuildDescr (..)
  , LocalBuildConfig (..)
  , BuildOptions (..)

    -- * Conversion functions
  , buildOptionsConfigFlags
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Types.ComponentId
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.PackageDescription
import Distribution.Types.UnitId

import Distribution.PackageDescription
import Distribution.Simple.Compiler
import Distribution.Simple.Flag
import Distribution.Simple.InstallDirs hiding
  ( absoluteInstallDirs
  , prefixRelativeInstallDirs
  , substPathTemplate
  )
import Distribution.Simple.PackageIndex
import Distribution.Simple.Program
import Distribution.Simple.Setup.Config
import Distribution.System

import Distribution.Compat.Graph (Graph)

-- | 'PackageBuildDescr' contains the information Cabal determines after
-- performing package-wide configuration of a package, before doing any
-- per-component configuration.
data PackageBuildDescr = PackageBuildDescr
  { PackageBuildDescr -> ConfigFlags
configFlags :: ConfigFlags
  -- ^ Options passed to the configuration step.
  -- Needed to re-run configuration when .cabal is out of date
  , PackageBuildDescr -> FlagAssignment
flagAssignment :: FlagAssignment
  -- ^ The final set of flags which were picked for this package
  , PackageBuildDescr -> ComponentRequestedSpec
componentEnabledSpec :: ComponentRequestedSpec
  -- ^ What components were enabled during configuration, and why.
  , PackageBuildDescr -> Compiler
compiler :: Compiler
  -- ^ The compiler we're building with
  , PackageBuildDescr -> Platform
hostPlatform :: Platform
  -- ^ The platform we're building for
  , PackageBuildDescr -> Maybe FilePath
pkgDescrFile :: Maybe FilePath
  -- ^ the filename containing the .cabal file, if available
  , PackageBuildDescr -> PackageDescription
localPkgDescr :: PackageDescription
  -- ^ WARNING WARNING WARNING Be VERY careful about using
  -- this function; we haven't deprecated it but using it
  -- could introduce subtle bugs related to
  -- 'HookedBuildInfo'.
  --
  -- In principle, this is supposed to contain the
  -- resolved package description, that does not contain
  -- any conditionals.  However, it MAY NOT contain
  -- the description with a 'HookedBuildInfo' applied
  -- to it; see 'HookedBuildInfo' for the whole sordid saga.
  -- As much as possible, Cabal library should avoid using
  -- this parameter.
  , PackageBuildDescr -> InstallDirTemplates
installDirTemplates :: InstallDirTemplates
  -- ^ The installation directories for the various different
  -- kinds of files
  -- TODO: inplaceDirTemplates :: InstallDirs FilePath
  , PackageBuildDescr -> PackageDBStack
withPackageDB :: PackageDBStack
  -- ^ What package database to use, global\/user
  , PackageBuildDescr -> [UnitId]
extraCoverageFor :: [UnitId]
  -- ^ For per-package builds-only: an extra list of libraries to be included in
  -- the hpc coverage report for testsuites run with @--enable-coverage@.
  -- Notably, this list must exclude indefinite libraries and instantiations
  -- because HPC does not support backpack (Nov. 2023).
  }
  deriving ((forall x. PackageBuildDescr -> Rep PackageBuildDescr x)
-> (forall x. Rep PackageBuildDescr x -> PackageBuildDescr)
-> Generic PackageBuildDescr
forall x. Rep PackageBuildDescr x -> PackageBuildDescr
forall x. PackageBuildDescr -> Rep PackageBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PackageBuildDescr -> Rep PackageBuildDescr x
from :: forall x. PackageBuildDescr -> Rep PackageBuildDescr x
$cto :: forall x. Rep PackageBuildDescr x -> PackageBuildDescr
to :: forall x. Rep PackageBuildDescr x -> PackageBuildDescr
Generic, ReadPrec [PackageBuildDescr]
ReadPrec PackageBuildDescr
Int -> ReadS PackageBuildDescr
ReadS [PackageBuildDescr]
(Int -> ReadS PackageBuildDescr)
-> ReadS [PackageBuildDescr]
-> ReadPrec PackageBuildDescr
-> ReadPrec [PackageBuildDescr]
-> Read PackageBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PackageBuildDescr
readsPrec :: Int -> ReadS PackageBuildDescr
$creadList :: ReadS [PackageBuildDescr]
readList :: ReadS [PackageBuildDescr]
$creadPrec :: ReadPrec PackageBuildDescr
readPrec :: ReadPrec PackageBuildDescr
$creadListPrec :: ReadPrec [PackageBuildDescr]
readListPrec :: ReadPrec [PackageBuildDescr]
Read, Int -> PackageBuildDescr -> ShowS
[PackageBuildDescr] -> ShowS
PackageBuildDescr -> FilePath
(Int -> PackageBuildDescr -> ShowS)
-> (PackageBuildDescr -> FilePath)
-> ([PackageBuildDescr] -> ShowS)
-> Show PackageBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackageBuildDescr -> ShowS
showsPrec :: Int -> PackageBuildDescr -> ShowS
$cshow :: PackageBuildDescr -> FilePath
show :: PackageBuildDescr -> FilePath
$cshowList :: [PackageBuildDescr] -> ShowS
showList :: [PackageBuildDescr] -> ShowS
Show)

-- | Information about individual components in a package,
-- determined after the configure step.
data ComponentBuildDescr = ComponentBuildDescr
  { ComponentBuildDescr -> Graph ComponentLocalBuildInfo
componentGraph :: Graph ComponentLocalBuildInfo
  -- ^ All the components to build, ordered by topological
  -- sort, and with their INTERNAL dependencies over the
  -- intrapackage dependency graph.
  -- TODO: this is assumed to be short; otherwise we want
  -- some sort of ordered map.
  , ComponentBuildDescr -> Map ComponentName [ComponentLocalBuildInfo]
componentNameMap :: Map ComponentName [ComponentLocalBuildInfo]
  -- ^ A map from component name to all matching
  -- components.  These coincide with 'componentGraph'
  -- There may be more than one matching component because of backpack instantiations
  , ComponentBuildDescr -> Map (PackageName, ComponentName) ComponentId
promisedPkgs :: Map (PackageName, ComponentName) ComponentId
  -- ^ The packages we were promised, but aren't already installed.
  -- MP: Perhaps this just needs to be a Set UnitId at this stage.
  , ComponentBuildDescr -> InstalledPackageIndex
installedPkgs :: InstalledPackageIndex
  -- ^ All the info about the installed packages that the
  -- current package depends on (directly or indirectly).
  -- The copy saved on disk does NOT include internal
  -- dependencies (because we just don't have enough
  -- information at this point to have an
  -- 'InstalledPackageInfo' for an internal dep), but we
  -- will often update it with the internal dependencies;
  -- see for example 'Distribution.Simple.Build.build'.
  -- (This admonition doesn't apply for per-component builds.)
  }
  deriving ((forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x)
-> (forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr)
-> Generic ComponentBuildDescr
forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
from :: forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
$cto :: forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
to :: forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
Generic, ReadPrec [ComponentBuildDescr]
ReadPrec ComponentBuildDescr
Int -> ReadS ComponentBuildDescr
ReadS [ComponentBuildDescr]
(Int -> ReadS ComponentBuildDescr)
-> ReadS [ComponentBuildDescr]
-> ReadPrec ComponentBuildDescr
-> ReadPrec [ComponentBuildDescr]
-> Read ComponentBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ComponentBuildDescr
readsPrec :: Int -> ReadS ComponentBuildDescr
$creadList :: ReadS [ComponentBuildDescr]
readList :: ReadS [ComponentBuildDescr]
$creadPrec :: ReadPrec ComponentBuildDescr
readPrec :: ReadPrec ComponentBuildDescr
$creadListPrec :: ReadPrec [ComponentBuildDescr]
readListPrec :: ReadPrec [ComponentBuildDescr]
Read, Int -> ComponentBuildDescr -> ShowS
[ComponentBuildDescr] -> ShowS
ComponentBuildDescr -> FilePath
(Int -> ComponentBuildDescr -> ShowS)
-> (ComponentBuildDescr -> FilePath)
-> ([ComponentBuildDescr] -> ShowS)
-> Show ComponentBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentBuildDescr -> ShowS
showsPrec :: Int -> ComponentBuildDescr -> ShowS
$cshow :: ComponentBuildDescr -> FilePath
show :: ComponentBuildDescr -> FilePath
$cshowList :: [ComponentBuildDescr] -> ShowS
showList :: [ComponentBuildDescr] -> ShowS
Show)

-- | 'LocalBuildDescr ' contains the information Cabal determines after
-- performing package-wide and per-component configuration of a package.
--
-- This information can no longer be changed after that point.
data LocalBuildDescr = LocalBuildDescr
  { LocalBuildDescr -> PackageBuildDescr
packageBuildDescr :: PackageBuildDescr
  -- ^ Information that is available after configuring the package itself,
  -- before looking at individual components.
  , LocalBuildDescr -> ComponentBuildDescr
componentBuildDescr :: ComponentBuildDescr
  -- ^ Information about individual components in the package
  -- determined after the configure step.
  }
  deriving ((forall x. LocalBuildDescr -> Rep LocalBuildDescr x)
-> (forall x. Rep LocalBuildDescr x -> LocalBuildDescr)
-> Generic LocalBuildDescr
forall x. Rep LocalBuildDescr x -> LocalBuildDescr
forall x. LocalBuildDescr -> Rep LocalBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalBuildDescr -> Rep LocalBuildDescr x
from :: forall x. LocalBuildDescr -> Rep LocalBuildDescr x
$cto :: forall x. Rep LocalBuildDescr x -> LocalBuildDescr
to :: forall x. Rep LocalBuildDescr x -> LocalBuildDescr
Generic, ReadPrec [LocalBuildDescr]
ReadPrec LocalBuildDescr
Int -> ReadS LocalBuildDescr
ReadS [LocalBuildDescr]
(Int -> ReadS LocalBuildDescr)
-> ReadS [LocalBuildDescr]
-> ReadPrec LocalBuildDescr
-> ReadPrec [LocalBuildDescr]
-> Read LocalBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBuildDescr
readsPrec :: Int -> ReadS LocalBuildDescr
$creadList :: ReadS [LocalBuildDescr]
readList :: ReadS [LocalBuildDescr]
$creadPrec :: ReadPrec LocalBuildDescr
readPrec :: ReadPrec LocalBuildDescr
$creadListPrec :: ReadPrec [LocalBuildDescr]
readListPrec :: ReadPrec [LocalBuildDescr]
Read, Int -> LocalBuildDescr -> ShowS
[LocalBuildDescr] -> ShowS
LocalBuildDescr -> FilePath
(Int -> LocalBuildDescr -> ShowS)
-> (LocalBuildDescr -> FilePath)
-> ([LocalBuildDescr] -> ShowS)
-> Show LocalBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBuildDescr -> ShowS
showsPrec :: Int -> LocalBuildDescr -> ShowS
$cshow :: LocalBuildDescr -> FilePath
show :: LocalBuildDescr -> FilePath
$cshowList :: [LocalBuildDescr] -> ShowS
showList :: [LocalBuildDescr] -> ShowS
Show)

-- | 'LocalBuildConfig' contains options that can be controlled
-- by the user and serve as inputs to the configuration of a package.
data LocalBuildConfig = LocalBuildConfig
  { LocalBuildConfig -> [FilePath]
extraConfigArgs :: [String]
  -- ^ Extra args on the command line for the configuration step.
  -- Needed to re-run configuration when .cabal is out of date
  , LocalBuildConfig -> ProgramDb
withPrograms :: ProgramDb
  -- ^ Location and args for all programs
  , LocalBuildConfig -> BuildOptions
withBuildOptions :: BuildOptions
  -- ^ Options to control the build, e.g. whether to
  -- enable profiling or to enable program coverage.
  }
  deriving ((forall x. LocalBuildConfig -> Rep LocalBuildConfig x)
-> (forall x. Rep LocalBuildConfig x -> LocalBuildConfig)
-> Generic LocalBuildConfig
forall x. Rep LocalBuildConfig x -> LocalBuildConfig
forall x. LocalBuildConfig -> Rep LocalBuildConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalBuildConfig -> Rep LocalBuildConfig x
from :: forall x. LocalBuildConfig -> Rep LocalBuildConfig x
$cto :: forall x. Rep LocalBuildConfig x -> LocalBuildConfig
to :: forall x. Rep LocalBuildConfig x -> LocalBuildConfig
Generic, ReadPrec [LocalBuildConfig]
ReadPrec LocalBuildConfig
Int -> ReadS LocalBuildConfig
ReadS [LocalBuildConfig]
(Int -> ReadS LocalBuildConfig)
-> ReadS [LocalBuildConfig]
-> ReadPrec LocalBuildConfig
-> ReadPrec [LocalBuildConfig]
-> Read LocalBuildConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBuildConfig
readsPrec :: Int -> ReadS LocalBuildConfig
$creadList :: ReadS [LocalBuildConfig]
readList :: ReadS [LocalBuildConfig]
$creadPrec :: ReadPrec LocalBuildConfig
readPrec :: ReadPrec LocalBuildConfig
$creadListPrec :: ReadPrec [LocalBuildConfig]
readListPrec :: ReadPrec [LocalBuildConfig]
Read, Int -> LocalBuildConfig -> ShowS
[LocalBuildConfig] -> ShowS
LocalBuildConfig -> FilePath
(Int -> LocalBuildConfig -> ShowS)
-> (LocalBuildConfig -> FilePath)
-> ([LocalBuildConfig] -> ShowS)
-> Show LocalBuildConfig
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBuildConfig -> ShowS
showsPrec :: Int -> LocalBuildConfig -> ShowS
$cshow :: LocalBuildConfig -> FilePath
show :: LocalBuildConfig -> FilePath
$cshowList :: [LocalBuildConfig] -> ShowS
showList :: [LocalBuildConfig] -> ShowS
Show)

-- | 'BuildOptions' contains configuration options that can be controlled
-- by the user.
data BuildOptions = BuildOptions
  { BuildOptions -> Bool
withVanillaLib :: Bool
  -- ^ Whether to build normal libs.
  , BuildOptions -> Bool
withProfLib :: Bool
  -- ^ Whether to build profiling versions of libs.
  , BuildOptions -> Bool
withSharedLib :: Bool
  -- ^ Whether to build shared versions of libs.
  , BuildOptions -> Bool
withStaticLib :: Bool
  -- ^ Whether to build static versions of libs (with all other libs rolled in)
  , BuildOptions -> Bool
withDynExe :: Bool
  -- ^ Whether to link executables dynamically
  , BuildOptions -> Bool
withFullyStaticExe :: Bool
  -- ^ Whether to link executables fully statically
  , BuildOptions -> Bool
withProfExe :: Bool
  -- ^ Whether to build executables for profiling.
  , BuildOptions -> ProfDetailLevel
withProfLibDetail :: ProfDetailLevel
  -- ^ Level of automatic profile detail.
  , BuildOptions -> ProfDetailLevel
withProfExeDetail :: ProfDetailLevel
  -- ^ Level of automatic profile detail.
  , BuildOptions -> OptimisationLevel
withOptimization :: OptimisationLevel
  -- ^ Whether to build with optimization (if available).
  , BuildOptions -> DebugInfoLevel
withDebugInfo :: DebugInfoLevel
  -- ^ Whether to emit debug info (if available).
  , BuildOptions -> Bool
withGHCiLib :: Bool
  -- ^ Whether to build libs suitable for use with GHCi.
  , BuildOptions -> Bool
splitSections :: Bool
  -- ^ Use -split-sections with GHC, if available
  , BuildOptions -> Bool
splitObjs :: Bool
  -- ^ Use -split-objs with GHC, if available
  , BuildOptions -> Bool
stripExes :: Bool
  -- ^ Whether to strip executables during install
  , BuildOptions -> Bool
stripLibs :: Bool
  -- ^ Whether to strip libraries during install
  , BuildOptions -> Bool
exeCoverage :: Bool
  -- ^ Whether to enable executable program coverage
  , BuildOptions -> Bool
libCoverage :: Bool
  -- ^ Whether to enable library program coverage
  , BuildOptions -> Bool
relocatable :: Bool
  -- ^ Whether to build a relocatable package
  }
  deriving (BuildOptions -> BuildOptions -> Bool
(BuildOptions -> BuildOptions -> Bool)
-> (BuildOptions -> BuildOptions -> Bool) -> Eq BuildOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuildOptions -> BuildOptions -> Bool
== :: BuildOptions -> BuildOptions -> Bool
$c/= :: BuildOptions -> BuildOptions -> Bool
/= :: BuildOptions -> BuildOptions -> Bool
Eq, (forall x. BuildOptions -> Rep BuildOptions x)
-> (forall x. Rep BuildOptions x -> BuildOptions)
-> Generic BuildOptions
forall x. Rep BuildOptions x -> BuildOptions
forall x. BuildOptions -> Rep BuildOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BuildOptions -> Rep BuildOptions x
from :: forall x. BuildOptions -> Rep BuildOptions x
$cto :: forall x. Rep BuildOptions x -> BuildOptions
to :: forall x. Rep BuildOptions x -> BuildOptions
Generic, ReadPrec [BuildOptions]
ReadPrec BuildOptions
Int -> ReadS BuildOptions
ReadS [BuildOptions]
(Int -> ReadS BuildOptions)
-> ReadS [BuildOptions]
-> ReadPrec BuildOptions
-> ReadPrec [BuildOptions]
-> Read BuildOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BuildOptions
readsPrec :: Int -> ReadS BuildOptions
$creadList :: ReadS [BuildOptions]
readList :: ReadS [BuildOptions]
$creadPrec :: ReadPrec BuildOptions
readPrec :: ReadPrec BuildOptions
$creadListPrec :: ReadPrec [BuildOptions]
readListPrec :: ReadPrec [BuildOptions]
Read, Int -> BuildOptions -> ShowS
[BuildOptions] -> ShowS
BuildOptions -> FilePath
(Int -> BuildOptions -> ShowS)
-> (BuildOptions -> FilePath)
-> ([BuildOptions] -> ShowS)
-> Show BuildOptions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BuildOptions -> ShowS
showsPrec :: Int -> BuildOptions -> ShowS
$cshow :: BuildOptions -> FilePath
show :: BuildOptions -> FilePath
$cshowList :: [BuildOptions] -> ShowS
showList :: [BuildOptions] -> ShowS
Show)

instance Binary PackageBuildDescr
instance Structured PackageBuildDescr
instance Binary ComponentBuildDescr
instance Structured ComponentBuildDescr
instance Binary LocalBuildDescr
instance Structured LocalBuildDescr
instance Binary LocalBuildConfig
instance Structured LocalBuildConfig
instance Binary BuildOptions
instance Structured BuildOptions

buildOptionsConfigFlags :: BuildOptions -> ConfigFlags
buildOptionsConfigFlags :: BuildOptions -> ConfigFlags
buildOptionsConfigFlags (BuildOptions{Bool
ProfDetailLevel
DebugInfoLevel
OptimisationLevel
withVanillaLib :: BuildOptions -> Bool
withProfLib :: BuildOptions -> Bool
withSharedLib :: BuildOptions -> Bool
withStaticLib :: BuildOptions -> Bool
withDynExe :: BuildOptions -> Bool
withFullyStaticExe :: BuildOptions -> Bool
withProfExe :: BuildOptions -> Bool
withProfLibDetail :: BuildOptions -> ProfDetailLevel
withProfExeDetail :: BuildOptions -> ProfDetailLevel
withOptimization :: BuildOptions -> OptimisationLevel
withDebugInfo :: BuildOptions -> DebugInfoLevel
withGHCiLib :: BuildOptions -> Bool
splitSections :: BuildOptions -> Bool
splitObjs :: BuildOptions -> Bool
stripExes :: BuildOptions -> Bool
stripLibs :: BuildOptions -> Bool
exeCoverage :: BuildOptions -> Bool
libCoverage :: BuildOptions -> Bool
relocatable :: BuildOptions -> Bool
withVanillaLib :: Bool
withProfLib :: Bool
withSharedLib :: Bool
withStaticLib :: Bool
withDynExe :: Bool
withFullyStaticExe :: Bool
withProfExe :: Bool
withProfLibDetail :: ProfDetailLevel
withProfExeDetail :: ProfDetailLevel
withOptimization :: OptimisationLevel
withDebugInfo :: DebugInfoLevel
withGHCiLib :: Bool
splitSections :: Bool
splitObjs :: Bool
stripExes :: Bool
stripLibs :: Bool
exeCoverage :: Bool
libCoverage :: Bool
relocatable :: Bool
..}) =
  ConfigFlags
forall a. Monoid a => a
mempty
    { configVanillaLib = toFlag $ withVanillaLib
    , configSharedLib = toFlag $ withSharedLib
    , configStaticLib = toFlag $ withStaticLib
    , configDynExe = toFlag $ withDynExe
    , configFullyStaticExe = toFlag $ withFullyStaticExe
    , configGHCiLib = toFlag $ withGHCiLib
    , configProfExe = toFlag $ withProfExe
    , configProfLib = toFlag $ withProfLib
    , configProf = mempty
    , -- configProfDetail is for exe+lib, but overridden by configProfLibDetail
      -- so we specify both so we can specify independently
      configProfDetail = toFlag $ withProfExeDetail
    , configProfLibDetail = toFlag $ withProfLibDetail
    , configCoverage = toFlag $ exeCoverage
    , configLibCoverage = mempty
    , configRelocatable = toFlag $ relocatable
    , configOptimization = toFlag $ withOptimization
    , configSplitSections = toFlag $ splitSections
    , configSplitObjs = toFlag $ splitObjs
    , configStripExes = toFlag $ stripExes
    , configStripLibs = toFlag $ stripLibs
    , configDebugInfo = toFlag $ withDebugInfo
    }