module System.LXC.Internal.AttachOptions where
import Bindings.LXC.AttachOptions
import Data.Int
import Data.Maybe
import Foreign.C.Types
import Foreign.C.String
import Foreign.Marshal.Alloc
import Foreign.Marshal.Array
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable
import System.LXC.Internal.Utils
import System.Posix.Types
newtype AttachExecFn = AttachExecFn { getAttachExecFn :: C_lxc_attach_exec_t }
data AttachEnvPolicy
= AttachKeepEnv
| AttachClearEnv
deriving (Eq, Show)
fromAttachEnvPolicy :: Num a => AttachEnvPolicy -> a
fromAttachEnvPolicy AttachKeepEnv = c'LXC_ATTACH_KEEP_ENV
fromAttachEnvPolicy AttachClearEnv = c'LXC_ATTACH_CLEAR_ENV
data AttachFlag
= AttachMoveToCGroup
| AttachDropCapabilities
| AttachSetPersonality
| AttachLSMExec
| AttachRemountProcSys
| AttachLSMNow
| AttachDefault
| AttachLSM
deriving (Eq, Show)
fromAttachFlag :: Num a => AttachFlag -> a
fromAttachFlag AttachMoveToCGroup = c'LXC_ATTACH_MOVE_TO_CGROUP
fromAttachFlag AttachDropCapabilities = c'LXC_ATTACH_DROP_CAPABILITIES
fromAttachFlag AttachSetPersonality = c'LXC_ATTACH_SET_PERSONALITY
fromAttachFlag AttachLSMExec = c'LXC_ATTACH_LSM_EXEC
fromAttachFlag AttachRemountProcSys = c'LXC_ATTACH_REMOUNT_PROC_SYS
fromAttachFlag AttachLSMNow = c'LXC_ATTACH_LSM_NOW
fromAttachFlag AttachDefault = c'LXC_ATTACH_DEFAULT
fromAttachFlag AttachLSM = c'LXC_ATTACH_LSM
data AttachOptions = AttachOptions
{ attachFlags :: [AttachFlag]
, attachNamespaces :: Int
, attachPersonality :: Maybe Int64
, attachInitialCWD :: Maybe FilePath
, attachUID :: UserID
, attachGID :: GroupID
, attachEnvPolicy :: AttachEnvPolicy
, attachExtraEnvVars :: [String]
, attachExtraKeepEnv :: [String]
, attachStdinFD :: Fd
, attachStdoutFD :: Fd
, attachStderrFD :: Fd
}
deriving (Show)
defaultAttachOptions :: AttachOptions
defaultAttachOptions = AttachOptions
{ attachFlags = [AttachDefault]
, attachNamespaces = 1
, attachPersonality = Nothing
, attachInitialCWD = Nothing
, attachUID = 1
, attachGID = 1
, attachEnvPolicy = AttachKeepEnv
, attachExtraEnvVars = []
, attachExtraKeepEnv = []
, attachStdinFD = 0
, attachStdoutFD = 1
, attachStderrFD = 2
}
data AttachCommand = AttachCommand
{ attachProgram :: String
, attachArgv :: [String]
}
withC'lxc_attach_options_t :: AttachOptions -> (Ptr C'lxc_attach_options_t -> IO a) -> IO a
withC'lxc_attach_options_t a f = do
alloca $ \ca ->
maybeWith withCString (attachInitialCWD a) $ \cinitialCWD ->
withMany withCString (attachExtraEnvVars a) $ \cextraEnvVars ->
withArray0 nullPtr cextraEnvVars $ \cextraEnvVars' ->
withMany withCString (attachExtraKeepEnv a) $ \cextraKeepEnv ->
withArray0 nullPtr cextraKeepEnv $ \cextraKeepEnv' -> do
poke (p'lxc_attach_options_t'attach_flags ca) (mkFlags fromAttachFlag . attachFlags $ a)
poke (p'lxc_attach_options_t'namespaces ca) (fromIntegral . attachNamespaces $ a)
poke (p'lxc_attach_options_t'personality ca) (fromIntegral . fromMaybe (1) . attachPersonality $ a)
poke (p'lxc_attach_options_t'initial_cwd ca) cinitialCWD
poke (p'lxc_attach_options_t'uid ca) (fromIntegral . attachUID $ a)
poke (p'lxc_attach_options_t'gid ca) (fromIntegral . attachGID $ a)
poke (p'lxc_attach_options_t'env_policy ca) (fromAttachEnvPolicy . attachEnvPolicy $ a)
poke (p'lxc_attach_options_t'extra_env_vars ca) cextraEnvVars'
poke (p'lxc_attach_options_t'extra_keep_env ca) cextraKeepEnv'
poke (p'lxc_attach_options_t'stdin_fd ca) (fromIntegral . attachStdinFD $ a)
poke (p'lxc_attach_options_t'stdout_fd ca) (fromIntegral . attachStdoutFD $ a)
poke (p'lxc_attach_options_t'stderr_fd ca) (fromIntegral . attachStderrFD $ a)
f ca
withC'lxc_attach_command_t :: AttachCommand -> (Ptr C'lxc_attach_command_t -> IO a) -> IO a
withC'lxc_attach_command_t a f = do
alloca $ \ca ->
withCString (attachProgram a) $ \cprogram ->
withMany withCString (attachArgv a) $ \cargv ->
withArray0 nullPtr cargv $ \cargv' -> do
poke (p'lxc_attach_command_t'program ca) cprogram
poke (p'lxc_attach_command_t'argv ca) cargv'
f ca
attachRunCommand :: AttachExecFn
attachRunCommand = AttachExecFn p'lxc_attach_run_command
attachRunShell :: AttachExecFn
attachRunShell = AttachExecFn p'lxc_attach_run_shell