Safe Haskell | None |
---|---|
Language | Haskell2010 |
Static B9 configuration. Read, write and merge configurable properties. The properties are independent of specific build targets.
Synopsis
- data B9Config = B9Config {
- _verbosity :: Maybe LogLevel
- _logFile :: Maybe FilePath
- _projectRoot :: Maybe FilePath
- _keepTempDirs :: Bool
- _uniqueBuildDirs :: Bool
- _repositoryCache :: Maybe SystemPath
- _repository :: Maybe String
- _interactive :: Bool
- _maxLocalSharedImageRevisions :: Maybe Int
- _systemdNspawnConfigs :: Maybe SystemdNspawnConfig
- _podmanConfigs :: Maybe PodmanConfig
- _dockerConfigs :: Maybe DockerConfig
- _libVirtLXCConfigs :: Maybe LibVirtLXCConfig
- _remoteRepos :: [RemoteRepo]
- _defaultTimeout :: Maybe Timeout
- _timeoutFactor :: Maybe Int
- newtype Timeout = TimeoutMicros Int
- runB9ConfigReader :: HasCallStack => B9Config -> Eff (B9ConfigReader ': e) a -> Eff e a
- type B9ConfigReader = Reader B9Config
- getB9Config :: Member B9ConfigReader e => Eff e B9Config
- getConfig :: Member B9ConfigReader e => Eff e B9Config
- getLogVerbosity :: Member B9ConfigReader e => Eff e (Maybe LogLevel)
- getProjectRoot :: Member B9ConfigReader e => Eff e FilePath
- getRemoteRepos :: Member B9ConfigReader e => Eff e [RemoteRepo]
- isInteractive :: Member B9ConfigReader e => Eff e Bool
- type B9ConfigWriter = Writer (Endo B9Config)
- verbosity :: Lens' B9Config (Maybe LogLevel)
- logFile :: Lens' B9Config (Maybe FilePath)
- projectRoot :: Lens' B9Config (Maybe FilePath)
- keepTempDirs :: Lens' B9Config Bool
- uniqueBuildDirs :: Lens' B9Config Bool
- repositoryCache :: Lens' B9Config (Maybe SystemPath)
- repository :: Lens' B9Config (Maybe String)
- interactive :: Lens' B9Config Bool
- defaultTimeout :: Lens' B9Config (Maybe Timeout)
- libVirtLXCConfigs :: Lens' B9Config (Maybe LibVirtLXCConfig)
- dockerConfigs :: Lens' B9Config (Maybe DockerConfig)
- podmanConfigs :: Lens' B9Config (Maybe PodmanConfig)
- systemdNspawnConfigs :: Lens' B9Config (Maybe SystemdNspawnConfig)
- remoteRepos :: Lens' B9Config [RemoteRepo]
- timeoutFactor :: Lens' B9Config (Maybe Int)
- maxLocalSharedImageRevisionsK :: String
- maxLocalSharedImageRevisions :: Lens' B9Config (Maybe Int)
- data B9ConfigOverride = B9ConfigOverride {}
- noB9ConfigOverride :: B9ConfigOverride
- type B9ConfigAction a = Eff '[B9ConfigWriter, B9ConfigReader, EnvironmentReader, Lift IO] a
- runB9ConfigActionWithOverrides :: HasCallStack => B9ConfigAction a -> B9ConfigOverride -> IO a
- runB9ConfigAction :: HasCallStack => B9ConfigAction a -> IO a
- localB9Config :: Member B9ConfigReader e => (B9Config -> B9Config) -> Eff e a -> Eff e a
- modifyPermanentConfig :: (HasCallStack, Member B9ConfigWriter e) => Endo B9Config -> Eff e ()
- customB9Config :: Lens' B9ConfigOverride (Endo B9Config)
- customB9ConfigPath :: Lens' B9ConfigOverride (Maybe SystemPath)
- customEnvironment :: Lens' B9ConfigOverride Environment
- customDefaulB9ConfigPath :: Lens' B9ConfigOverride (Maybe SystemPath)
- overrideB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
- overrideDefaultB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
- overrideB9Config :: (B9Config -> B9Config) -> B9ConfigOverride -> B9ConfigOverride
- overrideWorkingDirectory :: FilePath -> B9ConfigOverride -> B9ConfigOverride
- overrideDefaultTimeout :: Maybe Timeout -> B9ConfigOverride -> B9ConfigOverride
- overrideTimeoutFactor :: Maybe Int -> B9ConfigOverride -> B9ConfigOverride
- overrideVerbosity :: LogLevel -> B9ConfigOverride -> B9ConfigOverride
- overrideKeepBuildDirs :: Bool -> B9ConfigOverride -> B9ConfigOverride
- defaultB9ConfigFile :: SystemPath
- defaultRepositoryCache :: SystemPath
- defaultB9Config :: B9Config
- openOrCreateB9Config :: (HasCallStack, MonadIO m) => FilePath -> m CPDocument
- writeB9CPDocument :: (HasCallStack, MonadIO m) => Maybe SystemPath -> CPDocument -> m ()
- readB9Config :: (HasCallStack, MonadIO m) => Maybe SystemPath -> m CPDocument
- parseB9Config :: HasCallStack => CPDocument -> Either CPError B9Config
- modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument
- b9ConfigToCPDocument :: HasCallStack => B9Config -> Either CPError CPDocument
- data LogLevel
- data Environment
- module B9.B9Config.SystemdNspawn
- module B9.B9Config.Repository
- module B9.B9Config.Podman
- module B9.B9Config.LibVirtLXC
- module B9.B9Config.Docker
- module B9.B9Config.Container
Documentation
A way to specify a time intervall for example for the timeouts of system commands.
Since: 1.1.0
runB9ConfigReader :: HasCallStack => 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
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 RemoteRepo
s.
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.
Instances
Show B9ConfigOverride Source # | |
Defined in B9.B9Config showsPrec :: Int -> B9ConfigOverride -> ShowS # show :: B9ConfigOverride -> String # showList :: [B9ConfigOverride] -> ShowS # |
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 :: HasCallStack => 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
runB9ConfigAction :: HasCallStack => B9ConfigAction a -> IO a Source #
Run a B9ConfigAction
using noB9ConfigOverride
.
See runB9ConfigActionWithOverrides
for more details.
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 :: (HasCallStack, 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.
overrideDefaultB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride Source #
Convenience utility to override the *default* B9 configuration file path.
Since: 1.1.0
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.
overrideDefaultTimeout :: Maybe Timeout -> B9ConfigOverride -> B9ConfigOverride Source #
Define the default timeout for external commands.
Since: 1.1.0
overrideTimeoutFactor :: Maybe Int -> B9ConfigOverride -> B9ConfigOverride Source #
Define the timeout factor for external commands.
Since: 1.1.0
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 :: (HasCallStack, MonadIO m) => FilePath -> 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 :: (HasCallStack, 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.
readB9Config :: (HasCallStack, MonadIO m) => Maybe SystemPath -> m CPDocument Source #
parseB9Config :: HasCallStack => CPDocument -> Either CPError B9Config Source #
modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument Source #
Parse a B9Config
, modify it, and merge it back to the given CPDocument
.
b9ConfigToCPDocument :: HasCallStack => 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
module B9.B9Config.SystemdNspawn
module B9.B9Config.Repository
module B9.B9Config.Podman
module B9.B9Config.LibVirtLXC
module B9.B9Config.Docker
module B9.B9Config.Container