{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Stack.Types.ConfigureOpts
( ConfigureOpts (..)
, BaseConfigOpts (..)
, configureOpts
, configureOptsDirs
, configureOptsNoDir
) where
import qualified Data.Map as Map
import qualified Data.Text as T
import Distribution.Types.MungedPackageName
( decodeCompatPackageName )
import Distribution.Types.PackageName ( unPackageName )
import Distribution.Types.UnqualComponentName
( unUnqualComponentName )
import qualified Distribution.Version as C
import Path ( (</>), parseRelDir )
import Path.Extra ( toFilePathNoTrailingSep )
import Stack.Constants
( bindirSuffix, compilerOptionsCabalFlag, docDirSuffix
, relDirEtc, relDirLib, relDirLibexec, relDirShare
)
import Stack.Prelude
import Stack.Types.BuildOpts ( BuildOpts (..), BuildOptsCLI )
import Stack.Types.Compiler ( getGhcVersion, whichCompiler )
import Stack.Types.Config
( Config (..), HasConfig (..) )
import Stack.Types.EnvConfig ( EnvConfig, actualCompilerVersionL )
import Stack.Types.GhcPkgId ( GhcPkgId, ghcPkgIdString )
import Stack.Types.IsMutable ( IsMutable (..) )
import Stack.Types.Package ( Package (..) )
import System.FilePath ( pathSeparator )
data BaseConfigOpts = BaseConfigOpts
{ BaseConfigOpts -> Path Abs Dir
bcoSnapDB :: !(Path Abs Dir)
, BaseConfigOpts -> Path Abs Dir
bcoLocalDB :: !(Path Abs Dir)
, BaseConfigOpts -> Path Abs Dir
bcoSnapInstallRoot :: !(Path Abs Dir)
, BaseConfigOpts -> Path Abs Dir
bcoLocalInstallRoot :: !(Path Abs Dir)
, BaseConfigOpts -> BuildOpts
bcoBuildOpts :: !BuildOpts
, BaseConfigOpts -> BuildOptsCLI
bcoBuildOptsCLI :: !BuildOptsCLI
, :: ![Path Abs Dir]
}
deriving Int -> BaseConfigOpts -> ShowS
[BaseConfigOpts] -> ShowS
BaseConfigOpts -> String
(Int -> BaseConfigOpts -> ShowS)
-> (BaseConfigOpts -> String)
-> ([BaseConfigOpts] -> ShowS)
-> Show BaseConfigOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BaseConfigOpts -> ShowS
showsPrec :: Int -> BaseConfigOpts -> ShowS
$cshow :: BaseConfigOpts -> String
show :: BaseConfigOpts -> String
$cshowList :: [BaseConfigOpts] -> ShowS
showList :: [BaseConfigOpts] -> ShowS
Show
configureOpts :: EnvConfig
-> BaseConfigOpts
-> Map PackageIdentifier GhcPkgId
-> Bool
-> IsMutable
-> Package
-> ConfigureOpts
configureOpts :: EnvConfig
-> BaseConfigOpts
-> Map PackageIdentifier GhcPkgId
-> Bool
-> IsMutable
-> Package
-> ConfigureOpts
configureOpts EnvConfig
econfig BaseConfigOpts
bco Map PackageIdentifier GhcPkgId
deps Bool
isLocal IsMutable
isMutable Package
package = ConfigureOpts
{ coDirs :: [String]
coDirs = BaseConfigOpts -> IsMutable -> Package -> [String]
configureOptsDirs BaseConfigOpts
bco IsMutable
isMutable Package
package
, coNoDirs :: [String]
coNoDirs = EnvConfig
-> BaseConfigOpts
-> Map PackageIdentifier GhcPkgId
-> Bool
-> Package
-> [String]
configureOptsNoDir EnvConfig
econfig BaseConfigOpts
bco Map PackageIdentifier GhcPkgId
deps Bool
isLocal Package
package
}
configureOptsDirs :: BaseConfigOpts
-> IsMutable
-> Package
-> [String]
configureOptsDirs :: BaseConfigOpts -> IsMutable -> Package -> [String]
configureOptsDirs BaseConfigOpts
bco IsMutable
isMutable Package
package = [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [String
"--user", String
"--package-db=clear", String
"--package-db=global"]
, (Path Abs Dir -> String) -> [Path Abs Dir] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((String
"--package-db=" ++) ShowS -> (Path Abs Dir -> String) -> Path Abs Dir -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep) ([Path Abs Dir] -> [String]) -> [Path Abs Dir] -> [String]
forall a b. (a -> b) -> a -> b
$ case IsMutable
isMutable of
IsMutable
Immutable -> BaseConfigOpts -> [Path Abs Dir]
bcoExtraDBs BaseConfigOpts
bco [Path Abs Dir] -> [Path Abs Dir] -> [Path Abs Dir]
forall a. [a] -> [a] -> [a]
++ [BaseConfigOpts -> Path Abs Dir
bcoSnapDB BaseConfigOpts
bco]
IsMutable
Mutable -> BaseConfigOpts -> [Path Abs Dir]
bcoExtraDBs BaseConfigOpts
bco [Path Abs Dir] -> [Path Abs Dir] -> [Path Abs Dir]
forall a. [a] -> [a] -> [a]
++ [BaseConfigOpts -> Path Abs Dir
bcoSnapDB BaseConfigOpts
bco] [Path Abs Dir] -> [Path Abs Dir] -> [Path Abs Dir]
forall a. [a] -> [a] -> [a]
++ [BaseConfigOpts -> Path Abs Dir
bcoLocalDB BaseConfigOpts
bco]
, [ String
"--libdir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep (Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirLib)
, String
"--bindir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep (Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
bindirSuffix)
, String
"--datadir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep (Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirShare)
, String
"--libexecdir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep (Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirLibexec)
, String
"--sysconfdir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep (Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirEtc)
, String
"--docdir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep Path Abs Dir
docDir
, String
"--htmldir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep Path Abs Dir
docDir
, String
"--haddockdir=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs Dir -> String
forall loc. Path loc Dir -> String
toFilePathNoTrailingSep Path Abs Dir
docDir]
]
where
installRoot :: Path Abs Dir
installRoot =
case IsMutable
isMutable of
IsMutable
Immutable -> BaseConfigOpts -> Path Abs Dir
bcoSnapInstallRoot BaseConfigOpts
bco
IsMutable
Mutable -> BaseConfigOpts -> Path Abs Dir
bcoLocalInstallRoot BaseConfigOpts
bco
docDir :: Path Abs Dir
docDir =
case Maybe (Path Rel Dir)
pkgVerDir of
Maybe (Path Rel Dir)
Nothing -> Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
docDirSuffix
Just Path Rel Dir
dir -> Path Abs Dir
installRoot Path Abs Dir -> Path Rel Dir -> Path Abs Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
docDirSuffix Path Rel Dir -> Path Rel Dir -> Path Rel Dir
forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
dir
pkgVerDir :: Maybe (Path Rel Dir)
pkgVerDir = String -> Maybe (Path Rel Dir)
forall (m :: * -> *). MonadThrow m => String -> m (Path Rel Dir)
parseRelDir
( PackageIdentifier -> String
packageIdentifierString
(PackageName -> Version -> PackageIdentifier
PackageIdentifier (Package -> PackageName
packageName Package
package) (Package -> Version
packageVersion Package
package))
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator]
)
configureOptsNoDir ::
EnvConfig
-> BaseConfigOpts
-> Map PackageIdentifier GhcPkgId
-> Bool
-> Package
-> [String]
configureOptsNoDir :: EnvConfig
-> BaseConfigOpts
-> Map PackageIdentifier GhcPkgId
-> Bool
-> Package
-> [String]
configureOptsNoDir EnvConfig
econfig BaseConfigOpts
bco Map PackageIdentifier GhcPkgId
deps Bool
isLocal Package
package = [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [String]
depOptions
, [ String
"--enable-library-profiling"
| BuildOpts -> Bool
boptsLibProfile BuildOpts
bopts Bool -> Bool -> Bool
|| BuildOpts -> Bool
boptsExeProfile BuildOpts
bopts
]
, [String
"--enable-profiling" | BuildOpts -> Bool
boptsExeProfile BuildOpts
bopts Bool -> Bool -> Bool
&& Bool
isLocal]
, [String
"--enable-split-objs" | BuildOpts -> Bool
boptsSplitObjs BuildOpts
bopts]
, [ String
"--disable-library-stripping"
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ BuildOpts -> Bool
boptsLibStrip BuildOpts
bopts Bool -> Bool -> Bool
|| BuildOpts -> Bool
boptsExeStrip BuildOpts
bopts
]
, [String
"--disable-executable-stripping" | Bool -> Bool
not (BuildOpts -> Bool
boptsExeStrip BuildOpts
bopts) Bool -> Bool -> Bool
&& Bool
isLocal]
, ((FlagName, Bool) -> String) -> [(FlagName, Bool)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\(FlagName
name,Bool
enabled) ->
String
"-f" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
(if Bool
enabled
then String
""
else String
"-") String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
FlagName -> String
flagNameString FlagName
name)
(Map FlagName Bool -> [(FlagName, Bool)]
forall k a. Map k a -> [(k, a)]
Map.toList Map FlagName Bool
flags)
, (Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Text -> String
T.unpack ([Text] -> [String]) -> [Text] -> [String]
forall a b. (a -> b) -> a -> b
$ Package -> [Text]
packageCabalConfigOpts Package
package
, [Text] -> [String]
processGhcOptions (Package -> [Text]
packageGhcOptions Package
package)
, ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"--extra-include-dirs=" ++) (Config -> [String]
configExtraIncludeDirs Config
config)
, ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"--extra-lib-dirs=" ++) (Config -> [String]
configExtraLibDirs Config
config)
, [String]
-> (Path Abs File -> [String]) -> Maybe (Path Abs File) -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
[]
(\Path Abs File
customGcc -> [String
"--with-gcc=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Abs File -> String
forall b t. Path b t -> String
toFilePath Path Abs File
customGcc])
(Config -> Maybe (Path Abs File)
configOverrideGccPath Config
config)
, [String
"--exact-configuration"]
, [String
"--ghc-option=-fhide-source-paths" | Version -> Bool
hideSourcePaths Version
cv]
]
where
processGhcOptions :: [Text] -> [String]
processGhcOptions :: [Text] -> [String]
processGhcOptions [Text]
args =
let ([Text]
preRtsArgs, [Text]
mid) = (Text -> Bool) -> [Text] -> ([Text], [Text])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Text
"+RTS" ==) [Text]
args
([Text]
rtsArgs, [Text]
end) = (Text -> Bool) -> [Text] -> ([Text], [Text])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Text
"-RTS" ==) [Text]
mid
fullRtsArgs :: [Text]
fullRtsArgs =
case [Text]
rtsArgs of
[] ->
[]
[Text]
_ ->
[[Text] -> Text
T.unwords ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
rtsArgs [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"-RTS"]]
postRtsArgs :: [Text]
postRtsArgs = Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop Int
1 [Text]
end
newArgs :: [Text]
newArgs = [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Text]
preRtsArgs, [Text]
fullRtsArgs, [Text]
postRtsArgs]
in (Text -> [String]) -> [Text] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Text
x -> [WhichCompiler -> String
compilerOptionsCabalFlag WhichCompiler
wc, Text -> String
T.unpack Text
x]) [Text]
newArgs
wc :: WhichCompiler
wc = Getting WhichCompiler EnvConfig WhichCompiler
-> EnvConfig -> WhichCompiler
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting WhichCompiler EnvConfig ActualCompiler
forall env. HasSourceMap env => SimpleGetter env ActualCompiler
SimpleGetter EnvConfig ActualCompiler
actualCompilerVersionLGetting WhichCompiler EnvConfig ActualCompiler
-> ((WhichCompiler -> Const WhichCompiler WhichCompiler)
-> ActualCompiler -> Const WhichCompiler ActualCompiler)
-> Getting WhichCompiler EnvConfig WhichCompiler
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ActualCompiler -> WhichCompiler)
-> SimpleGetter ActualCompiler WhichCompiler
forall s a. (s -> a) -> SimpleGetter s a
to ActualCompiler -> WhichCompiler
whichCompiler) EnvConfig
econfig
cv :: Version
cv = Getting Version EnvConfig Version -> EnvConfig -> Version
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting Version EnvConfig ActualCompiler
forall env. HasSourceMap env => SimpleGetter env ActualCompiler
SimpleGetter EnvConfig ActualCompiler
actualCompilerVersionLGetting Version EnvConfig ActualCompiler
-> ((Version -> Const Version Version)
-> ActualCompiler -> Const Version ActualCompiler)
-> Getting Version EnvConfig Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ActualCompiler -> Version) -> SimpleGetter ActualCompiler Version
forall s a. (s -> a) -> SimpleGetter s a
to ActualCompiler -> Version
getGhcVersion) EnvConfig
econfig
hideSourcePaths :: Version -> Bool
hideSourcePaths Version
ghcVersion =
Version
ghcVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
C.mkVersion [Int
8, Int
2] Bool -> Bool -> Bool
&& Config -> Bool
configHideSourcePaths Config
config
config :: Config
config = Getting Config EnvConfig Config -> EnvConfig -> Config
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Config EnvConfig Config
forall env. HasConfig env => Lens' env Config
Lens' EnvConfig Config
configL EnvConfig
econfig
bopts :: BuildOpts
bopts = BaseConfigOpts -> BuildOpts
bcoBuildOpts BaseConfigOpts
bco
flags :: Map FlagName Bool
flags = Package -> Map FlagName Bool
packageFlags Package
package Map FlagName Bool -> Map FlagName Bool -> Map FlagName Bool
forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` Package -> Map FlagName Bool
packageDefaultFlags Package
package
depOptions :: [String]
depOptions = ((PackageIdentifier, GhcPkgId) -> String)
-> [(PackageIdentifier, GhcPkgId)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (PackageIdentifier, GhcPkgId) -> String
toDepOption ([(PackageIdentifier, GhcPkgId)] -> [String])
-> [(PackageIdentifier, GhcPkgId)] -> [String]
forall a b. (a -> b) -> a -> b
$ Map PackageIdentifier GhcPkgId -> [(PackageIdentifier, GhcPkgId)]
forall k a. Map k a -> [(k, a)]
Map.toList Map PackageIdentifier GhcPkgId
deps
toDepOption :: (PackageIdentifier, GhcPkgId) -> String
toDepOption (PackageIdentifier PackageName
name Version
_, GhcPkgId
gid) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"--dependency="
, String
depOptionKey
, String
"="
, GhcPkgId -> String
ghcPkgIdString GhcPkgId
gid
]
where
MungedPackageName PackageName
subPkgName LibraryName
lib = PackageName -> MungedPackageName
decodeCompatPackageName PackageName
name
depOptionKey :: String
depOptionKey = case LibraryName
lib of
LibraryName
LMainLibName -> PackageName -> String
unPackageName PackageName
name
LSubLibName UnqualComponentName
cn ->
PackageName -> String
unPackageName PackageName
subPkgName String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> UnqualComponentName -> String
unUnqualComponentName UnqualComponentName
cn
data ConfigureOpts = ConfigureOpts
{ ConfigureOpts -> [String]
coDirs :: ![String]
, ConfigureOpts -> [String]
coNoDirs :: ![String]
}
deriving (Typeable ConfigureOpts
Typeable ConfigureOpts
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConfigureOpts)
-> (ConfigureOpts -> Constr)
-> (ConfigureOpts -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ConfigureOpts))
-> ((forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r)
-> (forall u. (forall d. Data d => d -> u) -> ConfigureOpts -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts)
-> Data ConfigureOpts
ConfigureOpts -> Constr
ConfigureOpts -> DataType
(forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u
forall u. (forall d. Data d => d -> u) -> ConfigureOpts -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConfigureOpts
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ConfigureOpts)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConfigureOpts
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConfigureOpts
$ctoConstr :: ConfigureOpts -> Constr
toConstr :: ConfigureOpts -> Constr
$cdataTypeOf :: ConfigureOpts -> DataType
dataTypeOf :: ConfigureOpts -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ConfigureOpts)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ConfigureOpts)
$cgmapT :: (forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts
gmapT :: (forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ConfigureOpts -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ConfigureOpts -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts
Data, ConfigureOpts -> ConfigureOpts -> Bool
(ConfigureOpts -> ConfigureOpts -> Bool)
-> (ConfigureOpts -> ConfigureOpts -> Bool) -> Eq ConfigureOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfigureOpts -> ConfigureOpts -> Bool
== :: ConfigureOpts -> ConfigureOpts -> Bool
$c/= :: ConfigureOpts -> ConfigureOpts -> Bool
/= :: ConfigureOpts -> ConfigureOpts -> Bool
Eq, (forall x. ConfigureOpts -> Rep ConfigureOpts x)
-> (forall x. Rep ConfigureOpts x -> ConfigureOpts)
-> Generic ConfigureOpts
forall x. Rep ConfigureOpts x -> ConfigureOpts
forall x. ConfigureOpts -> Rep ConfigureOpts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConfigureOpts -> Rep ConfigureOpts x
from :: forall x. ConfigureOpts -> Rep ConfigureOpts x
$cto :: forall x. Rep ConfigureOpts x -> ConfigureOpts
to :: forall x. Rep ConfigureOpts x -> ConfigureOpts
Generic, Int -> ConfigureOpts -> ShowS
[ConfigureOpts] -> ShowS
ConfigureOpts -> String
(Int -> ConfigureOpts -> ShowS)
-> (ConfigureOpts -> String)
-> ([ConfigureOpts] -> ShowS)
-> Show ConfigureOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigureOpts -> ShowS
showsPrec :: Int -> ConfigureOpts -> ShowS
$cshow :: ConfigureOpts -> String
show :: ConfigureOpts -> String
$cshowList :: [ConfigureOpts] -> ShowS
showList :: [ConfigureOpts] -> ShowS
Show, Typeable)
instance NFData ConfigureOpts