b9-0.5.63: A tool and library for building virtual machine images.

Safe HaskellNone
LanguageHaskell2010

B9.B9Config

Description

Static B9 configuration. Read, write and merge configurable properties. The properties are independent of specific build targets.

Synopsis

Documentation

data B9ConfigOverride Source #

Override b9 configuration items and/or the path of the b9 configuration file. This is useful, i.e. when dealing with command line parameters.

noB9ConfigOverride :: B9ConfigOverride Source #

An empty default B9ConfigOverride value, that will neither apply any additional B9Config nor change the path of the configuration file.

data B9ConfigAction m a Source #

A monad that gives access to the (transient) B9Config to be used at _runtime_ with askRuntimeConfig or localRuntimeConfig, and that allows to write permanent B9Config changes back to the configuration file using modifyPermanentConfig. Execute a B9ConfigAction by invoking either invokeB9 (which is simple) or execB9ConfigAction.

Instances
Monad m => Monad (B9ConfigAction m) Source # 
Instance details

Defined in B9.B9Config

Functor m => Functor (B9ConfigAction m) Source # 
Instance details

Defined in B9.B9Config

Methods

fmap :: (a -> b) -> B9ConfigAction m a -> B9ConfigAction m b #

(<$) :: a -> B9ConfigAction m b -> B9ConfigAction m a #

Applicative m => Applicative (B9ConfigAction m) Source # 
Instance details

Defined in B9.B9Config

Methods

pure :: a -> B9ConfigAction m a #

(<*>) :: B9ConfigAction m (a -> b) -> B9ConfigAction m a -> B9ConfigAction m b #

liftA2 :: (a -> b -> c) -> B9ConfigAction m a -> B9ConfigAction m b -> B9ConfigAction m c #

(*>) :: B9ConfigAction m a -> B9ConfigAction m b -> B9ConfigAction m b #

(<*) :: B9ConfigAction m a -> B9ConfigAction m b -> B9ConfigAction m a #

MonadIO m => MonadIO (B9ConfigAction m) Source # 
Instance details

Defined in B9.B9Config

Methods

liftIO :: IO a -> B9ConfigAction m a #

execB9ConfigAction :: MonadIO m => B9ConfigAction m a -> B9ConfigOverride -> m a Source #

Execute a B9ConfigAction. It will take a B9ConfigOverride as input. The B9Config in that value is treated as the _runtime_ configuration, and the _customConfigPath is used as the alternative location of the configuration file. The configuration file is read from either the path in _customB9ConfigPath or from defaultB9ConfigFile. Every modification done via modifyPermanentConfig is applied to the **contents** of the configuration file and written back to that file, note that these changes are ONLY reflected in the configuration file and **not** in the _runtime configuration_.

See also invokeB9, which does not need the B9ConfigOverride parameter.

invokeB9 :: MonadIO m => B9ConfigAction m a -> m a Source #

Run a B9ConfigAction using noB9ConfigOverride. See execB9ConfigAction for more details.

askRuntimeConfig :: Monad m => B9ConfigAction m B9Config Source #

Return the runtime configuration, that should be the configuration merged from all configuration sources. This is the configuration to be used during a VM image build.

localRuntimeConfig :: Monad m => (B9Config -> B9Config) -> B9ConfigAction m a -> B9ConfigAction m a Source #

Run an action with an updated runtime configuration.

modifyPermanentConfig :: Monad m => Endo B9Config -> B9ConfigAction m () Source #

Add a modification to the permanent configuration file.

overrideB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride Source #

Convenience utility to override the B9 configuration file path.

overrideB9Config :: (B9Config -> B9Config) -> B9ConfigOverride -> B9ConfigOverride Source #

Modify the runtime configuration.

overrideWorkingDirectory :: FilePath -> B9ConfigOverride -> B9ConfigOverride Source #

Define the current working directory to be used when building.

overrideVerbosity :: LogLevel -> B9ConfigOverride -> B9ConfigOverride Source #

Overwrite the verbosity settings in the configuration with those given.

overrideKeepBuildDirs :: Bool -> B9ConfigOverride -> B9ConfigOverride Source #

Overwrite the keepTempDirs flag in the configuration with those given.

openOrCreateB9Config :: MonadIO m => Maybe SystemPath -> m CPDocument Source #

Open the configuration file that contains the B9Config. If the configuration does not exist, write a default configuration file, and create a all missing directories.

writeB9CPDocument :: MonadIO m => Maybe SystemPath -> CPDocument -> m () Source #

Write the configuration in the CPDocument to either the user supplied configuration file path or to defaultB9ConfigFile. Create all missing (parent) directories.

appendPositionalArguments :: [String] -> B9Config -> B9Config Source #

If environment variables arg_1 .. arg_n are bound and a list of k additional values are passed to this function, store them with keys arg_(n+1) .. arg_(n+k).

modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument Source #

Parse a B9Config, modify it, and merge it back to the given CPDocument.

b9ConfigToCPDocument :: B9Config -> Either CPError CPDocument Source #

Append a config file section for the B9Config to an empty CPDocument.

data Environment Source #

A map of textual keys to textual values.

Since: 0.5.62

Instances
Eq Environment Source # 
Instance details

Defined in B9.Environment

Data Environment Source # 
Instance details

Defined in B9.Environment

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Environment -> c Environment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Environment #

toConstr :: Environment -> Constr #

dataTypeOf :: Environment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Environment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Environment) #

gmapT :: (forall b. Data b => b -> b) -> Environment -> Environment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Environment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Environment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

Show Environment Source # 
Instance details

Defined in B9.Environment

Generic Environment Source # 
Instance details

Defined in B9.Environment

Associated Types

type Rep Environment :: Type -> Type #

Semigroup Environment Source # 
Instance details

Defined in B9.Environment

Monoid Environment Source # 
Instance details

Defined in B9.Environment

NFData Environment Source # 
Instance details

Defined in B9.Environment

Methods

rnf :: Environment -> () #

Monad m => MonadReader Environment (ContentGeneratorT m) Source # 
Instance details

Defined in B9.Artifact.Content

type Rep Environment Source # 
Instance details

Defined in B9.Environment

type Rep Environment = D1 (MetaData "Environment" "B9.Environment" "b9-0.5.63-7s6MhXL8SGnDZDbvlqlj2V" False) (C1 (MetaCons "MkEnvironment" PrefixI True) (S1 (MetaSel (Just "nextPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "fromEnvironment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))