module B9.B9Config.Podman ( podmanConfigToCPDocument, defaultPodmanConfig, parsePodmanConfig, PodmanConfig (..), podmanNetworkId, podmanCapabilities, ) where import B9.B9Config.Container import Control.Lens (makeLenses) import Data.ConfigFile.B9Extras data PodmanConfig = PodmanConfig { PodmanConfig -> Maybe String _podmanNetworkId :: Maybe String, PodmanConfig -> [ContainerCapability] _podmanCapabilities :: [ContainerCapability] } deriving (ReadPrec [PodmanConfig] ReadPrec PodmanConfig Int -> ReadS PodmanConfig ReadS [PodmanConfig] (Int -> ReadS PodmanConfig) -> ReadS [PodmanConfig] -> ReadPrec PodmanConfig -> ReadPrec [PodmanConfig] -> Read PodmanConfig forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [PodmanConfig] $creadListPrec :: ReadPrec [PodmanConfig] readPrec :: ReadPrec PodmanConfig $creadPrec :: ReadPrec PodmanConfig readList :: ReadS [PodmanConfig] $creadList :: ReadS [PodmanConfig] readsPrec :: Int -> ReadS PodmanConfig $creadsPrec :: Int -> ReadS PodmanConfig Read, Int -> PodmanConfig -> ShowS [PodmanConfig] -> ShowS PodmanConfig -> String (Int -> PodmanConfig -> ShowS) -> (PodmanConfig -> String) -> ([PodmanConfig] -> ShowS) -> Show PodmanConfig forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [PodmanConfig] -> ShowS $cshowList :: [PodmanConfig] -> ShowS show :: PodmanConfig -> String $cshow :: PodmanConfig -> String showsPrec :: Int -> PodmanConfig -> ShowS $cshowsPrec :: Int -> PodmanConfig -> ShowS Show, PodmanConfig -> PodmanConfig -> Bool (PodmanConfig -> PodmanConfig -> Bool) -> (PodmanConfig -> PodmanConfig -> Bool) -> Eq PodmanConfig forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: PodmanConfig -> PodmanConfig -> Bool $c/= :: PodmanConfig -> PodmanConfig -> Bool == :: PodmanConfig -> PodmanConfig -> Bool $c== :: PodmanConfig -> PodmanConfig -> Bool Eq) makeLenses ''PodmanConfig defaultPodmanConfig :: PodmanConfig defaultPodmanConfig :: PodmanConfig defaultPodmanConfig = Maybe String -> [ContainerCapability] -> PodmanConfig PodmanConfig Maybe String forall a. Maybe a Nothing [ ContainerCapability CAP_MKNOD, ContainerCapability CAP_SYS_ADMIN, ContainerCapability CAP_SYS_CHROOT, ContainerCapability CAP_SETGID, ContainerCapability CAP_SETUID, ContainerCapability CAP_NET_BIND_SERVICE, ContainerCapability CAP_SETPCAP, ContainerCapability CAP_SYS_PTRACE, ContainerCapability CAP_SYS_MODULE ] cfgFileSection :: String cfgFileSection :: String cfgFileSection = String "podman" networkIdK :: String networkIdK :: String networkIdK = String "network" podmanConfigToCPDocument :: PodmanConfig -> CPDocument -> Either CPError CPDocument podmanConfigToCPDocument :: PodmanConfig -> CPDocument -> Either CPError CPDocument podmanConfigToCPDocument PodmanConfig c CPDocument cp = do CPDocument cp1 <- CPDocument -> String -> Either CPError CPDocument forall (m :: * -> *). MonadError CPError m => CPDocument -> String -> m CPDocument addSectionCP CPDocument cp String cfgFileSection CPDocument cp2 <- CPDocument -> String -> String -> Maybe String -> Either CPError CPDocument forall a (m :: * -> *). (Show a, MonadError CPError m) => CPDocument -> String -> String -> a -> m CPDocument setShowCP CPDocument cp1 String cfgFileSection String networkIdK (Maybe String -> Either CPError CPDocument) -> Maybe String -> Either CPError CPDocument forall a b. (a -> b) -> a -> b $ PodmanConfig -> Maybe String _podmanNetworkId PodmanConfig c CPDocument -> String -> [ContainerCapability] -> Either CPError CPDocument containerCapsToCPDocument CPDocument cp2 String cfgFileSection ([ContainerCapability] -> Either CPError CPDocument) -> [ContainerCapability] -> Either CPError CPDocument forall a b. (a -> b) -> a -> b $ PodmanConfig -> [ContainerCapability] _podmanCapabilities PodmanConfig c parsePodmanConfig :: CPDocument -> Either CPError PodmanConfig parsePodmanConfig :: CPDocument -> Either CPError PodmanConfig parsePodmanConfig CPDocument cp = let getr :: (CPGet a) => CPOptionSpec -> Either CPError a getr :: String -> Either CPError a getr = CPDocument -> String -> String -> Either CPError a forall a (m :: * -> *). (CPGet a, MonadError CPError m) => CPDocument -> String -> String -> m a readCP CPDocument cp String cfgFileSection in Maybe String -> [ContainerCapability] -> PodmanConfig PodmanConfig (Maybe String -> [ContainerCapability] -> PodmanConfig) -> Either CPError (Maybe String) -> Either CPError ([ContainerCapability] -> PodmanConfig) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> Either CPError (Maybe String) forall a. CPGet a => String -> Either CPError a getr String networkIdK Either CPError ([ContainerCapability] -> PodmanConfig) -> Either CPError [ContainerCapability] -> Either CPError PodmanConfig forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> CPDocument -> String -> Either CPError [ContainerCapability] parseContainerCapabilities CPDocument cp String cfgFileSection