Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Stack.Types.ConfigureOpts
Synopsis
- data ConfigureOpts = ConfigureOpts {
- pathRelated :: ![String]
- nonPathRelated :: ![String]
- data BaseConfigOpts = BaseConfigOpts {}
- data PackageConfigureOpts = PackageConfigureOpts {}
- configureOpts :: EnvConfig -> BaseConfigOpts -> Map PackageIdentifier GhcPkgId -> Bool -> IsMutable -> PackageConfigureOpts -> ConfigureOpts
- configureOptsFromDb :: (HasField "configCacheDirOptionValue" b1 String, HasField "configCacheNoDirOptionValue" b2 String) => [Entity b1] -> [Entity b2] -> ConfigureOpts
- renderConfigureOpts :: ConfigureOpts -> [String]
- packageConfigureOptsFromPackage :: Package -> PackageConfigureOpts
Documentation
data ConfigureOpts Source #
Configure options to be sent to Setup.hs configure.
Constructors
ConfigureOpts | |
Fields
|
Instances
Data ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigureOpts # toConstr :: ConfigureOpts -> Constr # dataTypeOf :: ConfigureOpts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigureOpts) # gmapT :: (forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts # gmapQl :: (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 # gmapQ :: (forall d. Data d => d -> u) -> ConfigureOpts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # | |
Generic ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Associated Types type Rep ConfigureOpts :: Type -> Type # | |
Show ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods showsPrec :: Int -> ConfigureOpts -> ShowS # show :: ConfigureOpts -> String # showList :: [ConfigureOpts] -> ShowS # | |
NFData ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods rnf :: ConfigureOpts -> () # | |
Eq ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods (==) :: ConfigureOpts -> ConfigureOpts -> Bool # (/=) :: ConfigureOpts -> ConfigureOpts -> Bool # | |
type Rep ConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts type Rep ConfigureOpts = D1 ('MetaData "ConfigureOpts" "Stack.Types.ConfigureOpts" "stack-3.1.1-I5OI2i8TUoz1thruFO0H72" 'False) (C1 ('MetaCons "ConfigureOpts" 'PrefixI 'True) (S1 ('MetaSel ('Just "pathRelated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String]) :*: S1 ('MetaSel ('Just "nonPathRelated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String]))) |
data BaseConfigOpts Source #
Basic information used to calculate what the configure options are
Constructors
BaseConfigOpts | |
Instances
Show BaseConfigOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods showsPrec :: Int -> BaseConfigOpts -> ShowS # show :: BaseConfigOpts -> String # showList :: [BaseConfigOpts] -> ShowS # |
data PackageConfigureOpts Source #
All these fields come from the Package
data type but bringing the whole
Package is way too much, hence this datatype.
Constructors
PackageConfigureOpts | |
Fields
|
Instances
Show PackageConfigureOpts Source # | |
Defined in Stack.Types.ConfigureOpts Methods showsPrec :: Int -> PackageConfigureOpts -> ShowS # show :: PackageConfigureOpts -> String # showList :: [PackageConfigureOpts] -> ShowS # |
Arguments
:: EnvConfig | |
-> BaseConfigOpts | |
-> Map PackageIdentifier GhcPkgId | dependencies |
-> Bool | local non-extra-dep? |
-> IsMutable | |
-> PackageConfigureOpts | |
-> ConfigureOpts |
Render a BaseConfigOpts
to an actual list of options
configureOptsFromDb :: (HasField "configCacheDirOptionValue" b1 String, HasField "configCacheNoDirOptionValue" b2 String) => [Entity b1] -> [Entity b2] -> ConfigureOpts Source #
renderConfigureOpts :: ConfigureOpts -> [String] Source #
Render configure options as a single list of options.