{-# LANGUAGE NumericUnderscores #-}
module B9.B9Config
( B9Config (..),
Timeout (..),
runB9ConfigReader,
B9ConfigReader,
getB9Config,
getConfig,
getLogVerbosity,
getProjectRoot,
getRemoteRepos,
B9ConfigWriter,
verbosity,
logFile,
projectRoot,
keepTempDirs,
uniqueBuildDirs,
repositoryCache,
repository,
defaultTimeout,
libVirtLXCConfigs,
dockerConfigs,
podmanConfigs,
systemdNspawnConfigs,
remoteRepos,
timeoutFactor,
maxLocalSharedImageRevisionsK,
maxLocalSharedImageRevisions,
B9ConfigOverride (..),
noB9ConfigOverride,
B9ConfigAction (),
runB9ConfigActionWithOverrides,
runB9ConfigAction,
localB9Config,
modifyPermanentConfig,
customB9Config,
customB9ConfigPath,
customEnvironment,
customDefaulB9ConfigPath,
overrideB9ConfigPath,
overrideDefaultB9ConfigPath,
overrideB9Config,
overrideWorkingDirectory,
overrideDefaultTimeout,
overrideTimeoutFactor,
overrideVerbosity,
overrideKeepBuildDirs,
defaultB9ConfigFile,
defaultRepositoryCache,
defaultB9Config,
openOrCreateB9Config,
writeB9CPDocument,
readB9Config,
parseB9Config,
modifyCPDocument,
b9ConfigToCPDocument,
LogLevel (..),
Environment,
module X,
)
where
import B9.B9Config.Container as X
import B9.B9Config.Docker as X
import B9.B9Config.LibVirtLXC as X
import B9.B9Config.Podman as X
import B9.B9Config.Repository as X
import B9.B9Config.SystemdNspawn as X
import B9.Environment
import B9.QCUtil (smaller)
import Control.Eff
import Control.Eff.Reader.Lazy
import Control.Eff.Writer.Lazy
import Control.Exception
import Control.Lens as Lens ((<>~), (?~), (^.), makeLenses, set)
import Control.Monad ((>=>), filterM)
import Control.Monad.IO.Class
import Data.ConfigFile.B9Extras
( CPDocument,
CPError,
CPGet,
CPOptionSpec,
CPReadException (..),
addSectionCP,
emptyCP,
mergeCP,
readCP,
readCPDocument,
setShowCP,
toStringCP,
)
import Data.Function (on)
import Data.List (inits)
import Data.Maybe (fromMaybe)
import Data.Monoid
import Data.Semigroup as Semigroup hiding (Last (..))
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Version
import GHC.Stack
import qualified Paths_b9 as My
import System.Directory
import System.FilePath ((<.>))
import System.IO.B9Extras (SystemPath (..), ensureDir, resolve)
import Text.Printf (printf)
import Test.QuickCheck (Arbitrary(arbitrary))
import qualified Test.QuickCheck as QuickCheck
newtype Timeout = TimeoutMicros Int
deriving (Show, Eq, Ord, Read)
instance Arbitrary Timeout where
arbitrary = do
QuickCheck.Positive t <- arbitrary
pure (TimeoutMicros (t * 1_000_000))
data LogLevel
= LogTrace
| LogDebug
| LogInfo
| LogError
| LogNothing
deriving (Eq, Show, Ord, Read)
instance Arbitrary LogLevel where
arbitrary = QuickCheck.elements [LogTrace, LogDebug, LogInfo, LogError, LogNothing]
data B9Config
= B9Config
{ _verbosity :: Maybe LogLevel,
_logFile :: Maybe FilePath,
_projectRoot :: Maybe FilePath,
_keepTempDirs :: Bool,
_uniqueBuildDirs :: Bool,
_repositoryCache :: Maybe SystemPath,
_repository :: Maybe String,
_maxLocalSharedImageRevisions :: Maybe Int,
_systemdNspawnConfigs :: Maybe SystemdNspawnConfig,
_podmanConfigs :: Maybe PodmanConfig,
_dockerConfigs :: Maybe DockerConfig,
_libVirtLXCConfigs :: Maybe LibVirtLXCConfig,
_remoteRepos :: Set RemoteRepo,
_defaultTimeout :: Maybe Timeout,
_timeoutFactor :: Maybe Int
}
deriving (Show, Eq)
instance Arbitrary B9Config where
arbitrary =
B9Config
<$> smaller arbitrary
<*> smaller arbitrary
<*> smaller arbitrary
<*> smaller arbitrary
<*> smaller arbitrary
<*> (QuickCheck.elements [Nothing, Just (InTempDir "xxx")])
<*> smaller arbitrary
<*> smaller (fmap QuickCheck.getPositive <$> arbitrary)
<*> smaller arbitrary
<*> pure Nothing
<*> pure Nothing
<*> smaller arbitrary
<*> smaller arbitrary
<*> smaller arbitrary
<*> (fmap QuickCheck.getPositive <$> smaller arbitrary)
instance Semigroup B9Config where
c <> c' =
B9Config
{ _verbosity = getLast $ on mappend (Last . _verbosity) c c',
_logFile = getLast $ on mappend (Last . _logFile) c c',
_projectRoot = getLast $ on mappend (Last . _projectRoot) c c',
_keepTempDirs = getAny $ on mappend (Any . _keepTempDirs) c c',
_uniqueBuildDirs = getAll ((mappend `on` (All . _uniqueBuildDirs)) c c'),
_repositoryCache = getLast $ on mappend (Last . _repositoryCache) c c',
_repository = getLast ((mappend `on` (Last . _repository)) c c'),
_maxLocalSharedImageRevisions = getLast ((mappend `on` (Last . _maxLocalSharedImageRevisions)) c c'),
_systemdNspawnConfigs = getLast ((mappend `on` (Last . _systemdNspawnConfigs)) c c'),
_podmanConfigs = getLast ((mappend `on` (Last . _podmanConfigs)) c c'),
_dockerConfigs = getLast ((mappend `on` (Last . _dockerConfigs)) c c'),
_libVirtLXCConfigs = getLast ((mappend `on` (Last . _libVirtLXCConfigs)) c c'),
_remoteRepos = (mappend `on` _remoteRepos) c c',
_defaultTimeout = getLast $ on mappend (Last . _defaultTimeout) c c',
_timeoutFactor = getLast $ on mappend (Last . _timeoutFactor) c c'
}
instance Monoid B9Config where
mappend = (<>)
mempty = B9Config Nothing Nothing Nothing False True Nothing Nothing Nothing Nothing Nothing Nothing Nothing mempty (Just (TimeoutMicros (60 * 60 * 1_000_000))) Nothing
type B9ConfigReader = Reader B9Config
runB9ConfigReader :: HasCallStack => B9Config -> Eff (B9ConfigReader ': e) a -> Eff e a
runB9ConfigReader = runReader
getB9Config :: Member B9ConfigReader e => Eff e B9Config
getB9Config = ask
localB9Config :: Member B9ConfigReader e => (B9Config -> B9Config) -> Eff e a -> Eff e a
localB9Config = local
getConfig :: Member B9ConfigReader e => Eff e B9Config
getConfig = getB9Config
getRemoteRepos :: Member B9ConfigReader e => Eff e (Set RemoteRepo)
getRemoteRepos = _remoteRepos <$> getB9Config
getLogVerbosity :: Member B9ConfigReader e => Eff e (Maybe LogLevel)
getLogVerbosity = _verbosity <$> getB9Config
getProjectRoot :: Member B9ConfigReader e => Eff e FilePath
getProjectRoot = fromMaybe "." . _projectRoot <$> ask
data B9ConfigOverride
= B9ConfigOverride
{ _customB9ConfigPath :: Maybe SystemPath,
_customB9Config :: Endo B9Config,
_customEnvironment :: Environment,
_customDefaulB9ConfigPath :: Maybe SystemPath
}
instance Show B9ConfigOverride where
show x =
unlines
[ "config file path: " ++ show (_customB9ConfigPath x),
"config modification: " ++ show (appEndo (_customB9Config x) mempty),
"environment: " ++ show (_customEnvironment x),
"default config file: " ++ show (_customDefaulB9ConfigPath x)
]
noB9ConfigOverride :: B9ConfigOverride
noB9ConfigOverride = B9ConfigOverride Nothing mempty mempty Nothing
makeLenses ''B9Config
makeLenses ''B9ConfigOverride
overrideB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
overrideB9ConfigPath p = customB9ConfigPath ?~ p
overrideB9Config :: (B9Config -> B9Config) -> B9ConfigOverride -> B9ConfigOverride
overrideB9Config e = customB9Config <>~ Endo e
overrideDefaultB9ConfigPath :: SystemPath -> B9ConfigOverride -> B9ConfigOverride
overrideDefaultB9ConfigPath p = customDefaulB9ConfigPath ?~ p
overrideWorkingDirectory :: FilePath -> B9ConfigOverride -> B9ConfigOverride
overrideWorkingDirectory p = overrideB9Config (projectRoot ?~ p)
overrideDefaultTimeout :: Maybe Timeout -> B9ConfigOverride -> B9ConfigOverride
overrideDefaultTimeout = overrideB9Config . Lens.set defaultTimeout
overrideTimeoutFactor :: Maybe Int -> B9ConfigOverride -> B9ConfigOverride
overrideTimeoutFactor = overrideB9Config . Lens.set timeoutFactor
overrideVerbosity :: LogLevel -> B9ConfigOverride -> B9ConfigOverride
overrideVerbosity = overrideB9Config . Lens.set verbosity . Just
overrideKeepBuildDirs :: Bool -> B9ConfigOverride -> B9ConfigOverride
overrideKeepBuildDirs = overrideB9Config . Lens.set keepTempDirs
type B9ConfigAction a = Eff '[B9ConfigWriter, B9ConfigReader, EnvironmentReader, Lift IO] a
type B9ConfigWriter = Writer (Semigroup.Endo B9Config)
modifyPermanentConfig :: (HasCallStack, Member B9ConfigWriter e) => Endo B9Config -> Eff e ()
modifyPermanentConfig = tell
runB9ConfigActionWithOverrides :: HasCallStack => B9ConfigAction a -> B9ConfigOverride -> IO a
runB9ConfigActionWithOverrides act cfg = do
configuredCfgPaths <- traverse resolve (cfg ^. customB9ConfigPath)
defCfgPath <- resolve (fromMaybe defaultB9ConfigFile (cfg ^. customDefaulB9ConfigPath))
let (Version myVer _) = My.version
appendVersionVariations name =
(\v' -> name <.> showVersion (makeVersion v')) <$> reverse (inits myVer)
(pathsToTry, pathsToCreate) =
case configuredCfgPaths of
Just configuredCfgPath ->
(appendVersionVariations configuredCfgPath, Nothing)
Nothing ->
(appendVersionVariations defCfgPath, Just defCfgPath)
existingCfgPaths <- filterM doesFileExist pathsToTry
cfgPath <-
case existingCfgPaths of
(cfgPath : _) ->
return cfgPath
[] -> do
putStrLn ("B9 config file resolver: None of these files exists " ++ show pathsToTry)
case pathsToCreate of
Just c -> do
putStrLn ("creating a new config file with defaults at: " ++ c)
return c
Nothing ->
error "Please provide a valid config file path."
cp <- openOrCreateB9Config cfgPath
case parseB9Config cp of
Left e -> error (printf "Internal configuration load error, please report this: %s\n" (show e))
Right permanentConfigIn -> do
let runtimeCfg = appEndo (cfg ^. customB9Config) permanentConfigIn
(res, permanentB9ConfigUpdates) <-
runLift (runEnvironmentReader (cfg ^. customEnvironment) (runReader runtimeCfg (runMonoidWriter act)))
let cpExtErr = modifyCPDocument cp <$> permanentB9ConfigUpdateMaybe
permanentB9ConfigUpdateMaybe =
if appEndo permanentB9ConfigUpdates permanentConfigIn == permanentConfigIn
then Nothing
else Just permanentB9ConfigUpdates
cpExt <-
maybe
(return Nothing)
(either (error . printf "Internal configuration update error! Please report this: %s\n" . show) (return . Just))
cpExtErr
mapM_ (writeB9CPDocument (cfg ^. customB9ConfigPath)) cpExt
return res
runB9ConfigAction :: HasCallStack => B9ConfigAction a -> IO a
runB9ConfigAction = flip runB9ConfigActionWithOverrides noB9ConfigOverride
openOrCreateB9Config :: (HasCallStack, MonadIO m) => FilePath -> m CPDocument
openOrCreateB9Config cfgFile = do
ensureDir cfgFile
liftIO $ do
exists <- doesFileExist cfgFile
if exists
then readCPDocument (Path cfgFile)
else
let res = b9ConfigToCPDocument defaultB9Config
in case res of
Left e -> throwIO (CPReadException cfgFile e)
Right cp -> writeFile cfgFile (toStringCP cp) >> return cp
writeB9CPDocument :: (HasCallStack, MonadIO m) => Maybe SystemPath -> CPDocument -> m ()
writeB9CPDocument cfgFileIn cp = do
cfgFile <- resolve (fromMaybe defaultB9ConfigFile cfgFileIn)
ensureDir cfgFile
liftIO (writeFile cfgFile (toStringCP cp))
defaultB9Config :: B9Config
defaultB9Config =
B9Config
{ _verbosity = Just LogInfo,
_logFile = Nothing,
_projectRoot = Nothing,
_keepTempDirs = False,
_uniqueBuildDirs = True,
_repository = Nothing,
_repositoryCache = Just defaultRepositoryCache,
_maxLocalSharedImageRevisions = Just 2,
_systemdNspawnConfigs = Just defaultSystemdNspawnConfig,
_podmanConfigs = Just defaultPodmanConfig,
_libVirtLXCConfigs = Just defaultLibVirtLXCConfig,
_dockerConfigs = Just defaultDockerConfig,
_remoteRepos = mempty,
_defaultTimeout = Just (TimeoutMicros (3_600_000_000)),
_timeoutFactor = Nothing
}
defaultRepositoryCache :: SystemPath
defaultRepositoryCache = InB9UserDir "repo-cache"
defaultB9ConfigFile :: SystemPath
defaultB9ConfigFile = InB9UserDir "b9.conf"
verbosityK :: String
verbosityK = "verbosity"
logFileK :: String
logFileK = "log_file"
projectRootK :: String
projectRootK = "build_dir_root"
keepTempDirsK :: String
keepTempDirsK = "keep_temp_dirs"
uniqueBuildDirsK :: String
uniqueBuildDirsK = "unique_build_dirs"
repositoryCacheK :: String
repositoryCacheK = "repository_cache"
maxLocalSharedImageRevisionsK :: String
maxLocalSharedImageRevisionsK = "max_cached_shared_images"
repositoryK :: String
repositoryK = "repository"
defaultTimeoutK :: String
defaultTimeoutK = "default_timeout_seconds"
timeoutFactorK :: String
timeoutFactorK = "timeout_factor"
cfgFileSection :: String
cfgFileSection = "global"
modifyCPDocument :: CPDocument -> Endo B9Config -> Either CPError CPDocument
modifyCPDocument cp f = do
cfg <- parseB9Config cp
cp2 <- b9ConfigToCPDocument (appEndo f cfg)
return (mergeCP cp cp2)
b9ConfigToCPDocument :: HasCallStack => B9Config -> Either CPError CPDocument
b9ConfigToCPDocument c = do
cp1 <- addSectionCP emptyCP cfgFileSection
cp2 <- setShowCP cp1 cfgFileSection verbosityK (_verbosity c)
cp3 <- setShowCP cp2 cfgFileSection logFileK (_logFile c)
cp4 <- setShowCP cp3 cfgFileSection projectRootK (_projectRoot c)
cp5 <- setShowCP cp4 cfgFileSection keepTempDirsK (_keepTempDirs c)
cp7 <- setShowCP cp5 cfgFileSection uniqueBuildDirsK (_uniqueBuildDirs c)
cp8 <- setShowCP cp7 cfgFileSection maxLocalSharedImageRevisionsK (_maxLocalSharedImageRevisions c)
cp9 <- setShowCP cp8 cfgFileSection repositoryCacheK (_repositoryCache c)
cpA <- foldr (>=>) return (systemdNspawnConfigToCPDocument <$> _systemdNspawnConfigs c) cp9
cpB <- foldr (>=>) return (podmanConfigToCPDocument <$> _podmanConfigs c) cpA
cpC <- foldr (>=>) return (dockerConfigToCPDocument <$> _dockerConfigs c) cpB
cpD <- foldr (>=>) return (libVirtLXCConfigToCPDocument <$> _libVirtLXCConfigs c) cpC
cpE <- foldr (>=>) return ( remoteRepoToCPDocument <$> Set.toList (_remoteRepos c)) cpD
cpF <- setShowCP cpE cfgFileSection repositoryK (_repository c)
cpFinal <- maybe (pure cpF) (setShowCP cpF cfgFileSection defaultTimeoutK)
( case _defaultTimeout c of
Just (TimeoutMicros t) ->
Just (t `div` 1_000_000)
Nothing -> Nothing
)
maybe (pure cpFinal) (setShowCP cpFinal cfgFileSection timeoutFactorK) (_timeoutFactor c)
readB9Config :: (HasCallStack, MonadIO m) => Maybe SystemPath -> m CPDocument
readB9Config cfgFile = readCPDocument (fromMaybe defaultB9ConfigFile cfgFile)
parseB9Config :: HasCallStack => CPDocument -> Either CPError B9Config
parseB9Config cp =
let getr :: (CPGet a) => CPOptionSpec -> Either CPError a
getr = readCP cp cfgFileSection
in B9Config
<$> getr verbosityK
<*> getr logFileK
<*> getr projectRootK
<*> getr keepTempDirsK
<*> getr uniqueBuildDirsK
<*> getr repositoryCacheK
<*> getr repositoryK
<*> pure (either (const Nothing) id (getr maxLocalSharedImageRevisionsK))
<*> pure (either (const Nothing) Just (parseSystemdNspawnConfig cp))
<*> pure (either (const Nothing) Just (parsePodmanConfig cp))
<*> pure (either (const Nothing) Just (parseDockerConfig cp))
<*> pure (either (const Nothing) Just (parseLibVirtLXCConfig cp))
<*> (Set.fromList <$> parseRemoteRepos cp)
<*> pure (either (const Nothing) Just (parseDefaultTimeoutConfig cp))
<*> pure (either (const Nothing) Just (getr timeoutFactorK))
parseDefaultTimeoutConfig :: CPDocument -> Either CPError Timeout
parseDefaultTimeoutConfig cp = do
seconds <- readCP cp cfgFileSection defaultTimeoutK
let mu = seconds * 1_000_000
return (TimeoutMicros mu)