b9-0.5.67: 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

runB9ConfigReader :: B9Config -> Eff (B9ConfigReader ': e) a -> Eff e a Source #

Run a B9ConfigReader.

Since: 0.5.65

type B9ConfigReader = Reader B9Config Source #

Reader for B9Config. See getB9Config and localB9Config.

Since: 0.5.65

getB9Config :: Member B9ConfigReader e => Eff e 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.

Since: 0.5.65

getConfig :: Member B9ConfigReader e => Eff e B9Config Source #

An alias for getB9Config.

@deprecated

Since: 0.5.65

getLogVerbosity :: Member B9ConfigReader e => Eff e (Maybe LogLevel) Source #

Ask for the LogLevel.

Since: 0.5.65

getProjectRoot :: Member B9ConfigReader e => Eff e FilePath Source #

Ask for the project root directory.

Since: 0.5.65

getRemoteRepos :: Member B9ConfigReader e => Eff e [RemoteRepo] Source #

Ask for the RemoteRepos.

Since: 0.5.65

isInteractive :: Member B9ConfigReader e => Eff e Bool Source #

Ask whether stdin of the B9 process should be redirected to the external commands executed during the build.

Since: 0.5.65

type B9ConfigWriter = Writer (Endo B9Config) Source #

Accumulate B9Config changes that go back to the config file. See B9ConfigAction and modifyPermanentConfig.

Since: 0.5.65

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.

type B9ConfigAction a = Eff '[B9ConfigWriter, B9ConfigReader, EnvironmentReader, Lift IO] a Source #

A monad that gives access to the (transient) B9Config to be used at _runtime_ with getB9Config or localB9Config, and that allows to write permanent B9Config changes back to the configuration file using modifyPermanentConfig. This is the amalgamation of B9ConfigWriter B9ConfigReader and IO.

Since: 0.5.65

runB9ConfigActionWithOverrides :: B9ConfigAction a -> B9ConfigOverride -> IO 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 runB9ConfigAction, which does not need the B9ConfigOverride parameter.

Since: 0.5.65

localB9Config :: Member B9ConfigReader e => (B9Config -> B9Config) -> Eff e a -> Eff e a Source #

Run an action with an updated runtime configuration.

Since: 0.5.65

modifyPermanentConfig :: Member B9ConfigWriter e => Endo B9Config -> Eff e () 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.

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 -> () #

type Rep Environment Source # 
Instance details

Defined in B9.Environment

type Rep Environment = D1 (MetaData "Environment" "B9.Environment" "b9-0.5.67-4MXIVPGi3xJKScGz4mdQYc" 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))))