module Bindings.LXC.Container (
c'LXC_CLONE_KEEPNAME,
c'LXC_CLONE_KEEPMACADDR,
c'LXC_CLONE_SNAPSHOT,
c'LXC_CLONE_KEEPBDEVTYPE,
c'LXC_CLONE_MAYBE_SNAPSHOT,
c'LXC_CLONE_MAXFLAGS,
c'LXC_CREATE_QUIET,
c'LXC_CREATE_MAXFLAGS,
C'lxc_container(..),
p'lxc_container'error_string,
p'lxc_container'error_num,
p'lxc_container'daemonize,
p'lxc_container'config_path,
C'lxc_snapshot(..),
p'lxc_snapshot'name,
p'lxc_snapshot'comment_pathname,
p'lxc_snapshot'timestamp,
p'lxc_snapshot'lxcpath,
p'lxc_snapshot'free,
C'bdev_specs(..),
p'bdev_specs'fstype,
p'bdev_specs'fssize,
p'bdev_specs'zfs,
p'bdev_specs'lvm,
p'bdev_specs'dir,
C'zfs_t(..),
p'zfs_t'zfsroot,
C'lvm_t(..),
p'lvm_t'vg,
p'lvm_t'lv,
p'lvm_t'thinpool,
p'lxc_container'is_defined,
p'lxc_container'is_running,
p'lxc_container'state,
p'lxc_container'init_pid,
p'lxc_container'get_interfaces,
p'lxc_container'get_ips,
p'lxc_container'config_file_name,
p'lxc_container'get_config_path,
p'lxc_container'set_config_path,
p'lxc_container'load_config,
p'lxc_container'save_config,
p'lxc_container'get_keys,
p'lxc_container'set_config_item,
p'lxc_container'get_config_item,
p'lxc_container'get_running_config_item,
p'lxc_container'clear_config,
p'lxc_container'clear_config_item,
p'lxc_container'start,
p'lxc_container'stop,
p'lxc_container'reboot,
p'lxc_container'shutdown,
p'lxc_container'freeze,
p'lxc_container'unfreeze,
p'lxc_container'wait,
p'lxc_container'create,
p'lxc_container'clone,
p'lxc_container'rename,
p'lxc_container'destroy,
p'lxc_container'console_getfd,
p'lxc_container'console,
p'lxc_container'attach,
p'lxc_container'attach_run_wait,
p'lxc_container'snapshot,
p'lxc_container'snapshot_list,
p'lxc_container'snapshot_restore,
p'lxc_container'snapshot_destroy,
p'lxc_container'want_daemonize,
p'lxc_container'want_close_all_fds,
p'lxc_container'get_cgroup_item,
p'lxc_container'set_cgroup_item,
p'lxc_container'may_control,
p'lxc_container'add_device_node,
p'lxc_container'remove_device_node,
c'lxc_container_new,
c'lxc_container_get,
c'lxc_container_put,
c'list_defined_containers,
c'list_active_containers,
c'list_all_containers,
c'lxc_get_wait_states,
c'lxc_get_global_config_item,
c'lxc_get_version,
c'lxc_log_close,
) where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word
import Bindings.LXC.Sys.Types
import Bindings.LXC.AttachOptions
c'LXC_CLONE_KEEPNAME = 1
c'LXC_CLONE_KEEPNAME :: (Num a) => a
c'LXC_CLONE_KEEPMACADDR = 2
c'LXC_CLONE_KEEPMACADDR :: (Num a) => a
c'LXC_CLONE_SNAPSHOT = 4
c'LXC_CLONE_SNAPSHOT :: (Num a) => a
c'LXC_CLONE_KEEPBDEVTYPE = 8
c'LXC_CLONE_KEEPBDEVTYPE :: (Num a) => a
c'LXC_CLONE_MAYBE_SNAPSHOT = 16
c'LXC_CLONE_MAYBE_SNAPSHOT :: (Num a) => a
c'LXC_CLONE_MAXFLAGS = 32
c'LXC_CLONE_MAXFLAGS :: (Num a) => a
c'LXC_CREATE_QUIET = 1
c'LXC_CREATE_QUIET :: (Num a) => a
c'LXC_CREATE_MAXFLAGS = 2
c'LXC_CREATE_MAXFLAGS :: (Num a) => a
data C'zfs_t = C'zfs_t{
c'zfs_t'zfsroot :: CString
} deriving (Eq,Show)
p'zfs_t'zfsroot p = plusPtr p 0
p'zfs_t'zfsroot :: Ptr (C'zfs_t) -> Ptr (CString)
instance Storable C'zfs_t where
sizeOf _ = 8
alignment _ = 8
peek p = do
v0 <- peekByteOff p 0
return $ C'zfs_t v0
poke p (C'zfs_t v0) = do
pokeByteOff p 0 v0
return ()
data C'lvm_t = C'lvm_t{
c'lvm_t'vg :: CString,
c'lvm_t'lv :: CString,
c'lvm_t'thinpool :: CString
} deriving (Eq,Show)
p'lvm_t'vg p = plusPtr p 0
p'lvm_t'vg :: Ptr (C'lvm_t) -> Ptr (CString)
p'lvm_t'lv p = plusPtr p 8
p'lvm_t'lv :: Ptr (C'lvm_t) -> Ptr (CString)
p'lvm_t'thinpool p = plusPtr p 16
p'lvm_t'thinpool :: Ptr (C'lvm_t) -> Ptr (CString)
instance Storable C'lvm_t where
sizeOf _ = 24
alignment _ = 8
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 8
v2 <- peekByteOff p 16
return $ C'lvm_t v0 v1 v2
poke p (C'lvm_t v0 v1 v2) = do
pokeByteOff p 0 v0
pokeByteOff p 8 v1
pokeByteOff p 16 v2
return ()
data C'bdev_specs = C'bdev_specs{
c'bdev_specs'fstype :: CString,
c'bdev_specs'fssize :: C'uint64_t,
c'bdev_specs'zfs :: C'zfs_t,
c'bdev_specs'lvm :: C'lvm_t,
c'bdev_specs'dir :: CString
} deriving (Eq,Show)
p'bdev_specs'fstype p = plusPtr p 0
p'bdev_specs'fstype :: Ptr (C'bdev_specs) -> Ptr (CString)
p'bdev_specs'fssize p = plusPtr p 8
p'bdev_specs'fssize :: Ptr (C'bdev_specs) -> Ptr (C'uint64_t)
p'bdev_specs'zfs p = plusPtr p 16
p'bdev_specs'zfs :: Ptr (C'bdev_specs) -> Ptr (C'zfs_t)
p'bdev_specs'lvm p = plusPtr p 24
p'bdev_specs'lvm :: Ptr (C'bdev_specs) -> Ptr (C'lvm_t)
p'bdev_specs'dir p = plusPtr p 48
p'bdev_specs'dir :: Ptr (C'bdev_specs) -> Ptr (CString)
instance Storable C'bdev_specs where
sizeOf _ = 56
alignment _ = 8
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 8
v2 <- peekByteOff p 16
v3 <- peekByteOff p 24
v4 <- peekByteOff p 48
return $ C'bdev_specs v0 v1 v2 v3 v4
poke p (C'bdev_specs v0 v1 v2 v3 v4) = do
pokeByteOff p 0 v0
pokeByteOff p 8 v1
pokeByteOff p 16 v2
pokeByteOff p 24 v3
pokeByteOff p 48 v4
return ()
data C'lxc_snapshot = C'lxc_snapshot{
c'lxc_snapshot'name :: CString,
c'lxc_snapshot'comment_pathname :: CString,
c'lxc_snapshot'timestamp :: CString,
c'lxc_snapshot'lxcpath :: CString,
c'lxc_snapshot'free :: FunPtr (Ptr C'lxc_snapshot -> IO ())
} deriving (Eq,Show)
p'lxc_snapshot'name p = plusPtr p 0
p'lxc_snapshot'name :: Ptr (C'lxc_snapshot) -> Ptr (CString)
p'lxc_snapshot'comment_pathname p = plusPtr p 8
p'lxc_snapshot'comment_pathname :: Ptr (C'lxc_snapshot) -> Ptr (CString)
p'lxc_snapshot'timestamp p = plusPtr p 16
p'lxc_snapshot'timestamp :: Ptr (C'lxc_snapshot) -> Ptr (CString)
p'lxc_snapshot'lxcpath p = plusPtr p 24
p'lxc_snapshot'lxcpath :: Ptr (C'lxc_snapshot) -> Ptr (CString)
p'lxc_snapshot'free p = plusPtr p 32
p'lxc_snapshot'free :: Ptr (C'lxc_snapshot) -> Ptr (FunPtr (Ptr C'lxc_snapshot -> IO ()))
instance Storable C'lxc_snapshot where
sizeOf _ = 40
alignment _ = 8
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 8
v2 <- peekByteOff p 16
v3 <- peekByteOff p 24
v4 <- peekByteOff p 32
return $ C'lxc_snapshot v0 v1 v2 v3 v4
poke p (C'lxc_snapshot v0 v1 v2 v3 v4) = do
pokeByteOff p 0 v0
pokeByteOff p 8 v1
pokeByteOff p 16 v2
pokeByteOff p 24 v3
pokeByteOff p 32 v4
return ()
data C'lxc_container = C'lxc_container{
c'lxc_container'error_string :: CString,
c'lxc_container'error_num :: CInt,
c'lxc_container'daemonize :: CBool,
c'lxc_container'config_path :: CString,
c'lxc_container'is_defined :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'state :: FunPtr (Ptr C'lxc_container -> IO CString),
c'lxc_container'is_running :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'freeze :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'unfreeze :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'init_pid :: FunPtr (Ptr C'lxc_container -> IO C'pid_t),
c'lxc_container'load_config :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'start :: FunPtr (Ptr C'lxc_container -> CInt -> Ptr CString -> IO CBool),
c'lxc_container'stop :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'want_daemonize :: FunPtr (Ptr C'lxc_container -> CBool -> IO CBool),
c'lxc_container'want_close_all_fds :: FunPtr (Ptr C'lxc_container -> CBool -> IO CBool),
c'lxc_container'config_file_name :: FunPtr (Ptr C'lxc_container -> IO CString),
c'lxc_container'wait :: FunPtr (Ptr C'lxc_container -> CString -> CInt -> IO CBool),
c'lxc_container'set_config_item :: FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool),
c'lxc_container'destroy :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'save_config :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'create :: FunPtr (Ptr C'lxc_container -> CString -> CString -> Ptr C'bdev_specs -> CInt -> Ptr CString -> IO CBool),
c'lxc_container'rename :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'reboot :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'shutdown :: FunPtr (Ptr C'lxc_container -> CInt -> IO CBool),
c'lxc_container'clear_config :: FunPtr (Ptr C'lxc_container -> IO ()),
c'lxc_container'clear_config_item :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'get_config_item :: FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt),
c'lxc_container'get_running_config_item :: FunPtr (Ptr C'lxc_container -> CString -> IO CString),
c'lxc_container'get_keys :: FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt),
c'lxc_container'get_interfaces :: FunPtr (Ptr C'lxc_container -> IO (Ptr CString)),
c'lxc_container'get_ips :: FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO (Ptr CString)),
c'lxc_container'get_cgroup_item :: FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt),
c'lxc_container'set_cgroup_item :: FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool),
c'lxc_container'get_config_path :: FunPtr (Ptr C'lxc_container -> IO CString),
c'lxc_container'set_config_path :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'clone :: FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> CString -> CString -> C'uint64_t -> Ptr CString -> IO (Ptr C'lxc_container)),
c'lxc_container'console_getfd :: FunPtr (Ptr C'lxc_container -> Ptr CInt -> Ptr CInt -> IO CInt),
c'lxc_container'console :: FunPtr (Ptr C'lxc_container -> CInt -> CInt -> CInt -> CInt -> CInt -> IO CInt),
c'lxc_container'attach :: FunPtr (Ptr C'lxc_container -> C_lxc_attach_exec_t -> Ptr () -> Ptr C'lxc_attach_options_t -> Ptr C'pid_t -> IO CInt),
c'lxc_container'attach_run_wait :: FunPtr (Ptr C'lxc_container -> Ptr C'lxc_attach_options_t -> CString -> Ptr CString -> IO CInt),
c'lxc_container'snapshot :: FunPtr (Ptr C'lxc_container -> CString -> IO CInt),
c'lxc_container'snapshot_list :: FunPtr (Ptr C'lxc_container -> Ptr (Ptr C'lxc_snapshot) -> IO CInt),
c'lxc_container'snapshot_restore :: FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool),
c'lxc_container'snapshot_destroy :: FunPtr (Ptr C'lxc_container -> CString -> IO CBool),
c'lxc_container'may_control :: FunPtr (Ptr C'lxc_container -> IO CBool),
c'lxc_container'add_device_node :: FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool),
c'lxc_container'remove_device_node :: FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool)
} deriving (Eq,Show)
p'lxc_container'error_string p = plusPtr p 56
p'lxc_container'error_string :: Ptr (C'lxc_container) -> Ptr (CString)
p'lxc_container'error_num p = plusPtr p 64
p'lxc_container'error_num :: Ptr (C'lxc_container) -> Ptr (CInt)
p'lxc_container'daemonize p = plusPtr p 68
p'lxc_container'daemonize :: Ptr (C'lxc_container) -> Ptr (CBool)
p'lxc_container'config_path p = plusPtr p 72
p'lxc_container'config_path :: Ptr (C'lxc_container) -> Ptr (CString)
p'lxc_container'is_defined p = plusPtr p 80
p'lxc_container'is_defined :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'state p = plusPtr p 88
p'lxc_container'state :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CString))
p'lxc_container'is_running p = plusPtr p 96
p'lxc_container'is_running :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'freeze p = plusPtr p 104
p'lxc_container'freeze :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'unfreeze p = plusPtr p 112
p'lxc_container'unfreeze :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'init_pid p = plusPtr p 120
p'lxc_container'init_pid :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO C'pid_t))
p'lxc_container'load_config p = plusPtr p 128
p'lxc_container'load_config :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'start p = plusPtr p 136
p'lxc_container'start :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CInt -> Ptr CString -> IO CBool))
p'lxc_container'stop p = plusPtr p 152
p'lxc_container'stop :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'want_daemonize p = plusPtr p 160
p'lxc_container'want_daemonize :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CBool -> IO CBool))
p'lxc_container'want_close_all_fds p = plusPtr p 168
p'lxc_container'want_close_all_fds :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CBool -> IO CBool))
p'lxc_container'config_file_name p = plusPtr p 176
p'lxc_container'config_file_name :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CString))
p'lxc_container'wait p = plusPtr p 184
p'lxc_container'wait :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CInt -> IO CBool))
p'lxc_container'set_config_item p = plusPtr p 192
p'lxc_container'set_config_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool))
p'lxc_container'destroy p = plusPtr p 200
p'lxc_container'destroy :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'save_config p = plusPtr p 208
p'lxc_container'save_config :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'create p = plusPtr p 216
p'lxc_container'create :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> Ptr C'bdev_specs -> CInt -> Ptr CString -> IO CBool))
p'lxc_container'rename p = plusPtr p 232
p'lxc_container'rename :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'reboot p = plusPtr p 240
p'lxc_container'reboot :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'shutdown p = plusPtr p 248
p'lxc_container'shutdown :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CInt -> IO CBool))
p'lxc_container'clear_config p = plusPtr p 256
p'lxc_container'clear_config :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO ()))
p'lxc_container'clear_config_item p = plusPtr p 264
p'lxc_container'clear_config_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'get_config_item p = plusPtr p 272
p'lxc_container'get_config_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt))
p'lxc_container'get_running_config_item p = plusPtr p 280
p'lxc_container'get_running_config_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CString))
p'lxc_container'get_keys p = plusPtr p 288
p'lxc_container'get_keys :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt))
p'lxc_container'get_interfaces p = plusPtr p 296
p'lxc_container'get_interfaces :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO (Ptr CString)))
p'lxc_container'get_ips p = plusPtr p 304
p'lxc_container'get_ips :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO (Ptr CString)))
p'lxc_container'get_cgroup_item p = plusPtr p 312
p'lxc_container'get_cgroup_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> IO CInt))
p'lxc_container'set_cgroup_item p = plusPtr p 320
p'lxc_container'set_cgroup_item :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool))
p'lxc_container'get_config_path p = plusPtr p 328
p'lxc_container'get_config_path :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CString))
p'lxc_container'set_config_path p = plusPtr p 336
p'lxc_container'set_config_path :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'clone p = plusPtr p 344
p'lxc_container'clone :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> CInt -> CString -> CString -> C'uint64_t -> Ptr CString -> IO (Ptr C'lxc_container)))
p'lxc_container'console_getfd p = plusPtr p 352
p'lxc_container'console_getfd :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> Ptr CInt -> Ptr CInt -> IO CInt))
p'lxc_container'console p = plusPtr p 360
p'lxc_container'console :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CInt -> CInt -> CInt -> CInt -> CInt -> IO CInt))
p'lxc_container'attach p = plusPtr p 368
p'lxc_container'attach :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> C_lxc_attach_exec_t -> Ptr () -> Ptr C'lxc_attach_options_t -> Ptr C'pid_t -> IO CInt))
p'lxc_container'attach_run_wait p = plusPtr p 376
p'lxc_container'attach_run_wait :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> Ptr C'lxc_attach_options_t -> CString -> Ptr CString -> IO CInt))
p'lxc_container'snapshot p = plusPtr p 392
p'lxc_container'snapshot :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CInt))
p'lxc_container'snapshot_list p = plusPtr p 400
p'lxc_container'snapshot_list :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> Ptr (Ptr C'lxc_snapshot) -> IO CInt))
p'lxc_container'snapshot_restore p = plusPtr p 408
p'lxc_container'snapshot_restore :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool))
p'lxc_container'snapshot_destroy p = plusPtr p 416
p'lxc_container'snapshot_destroy :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> IO CBool))
p'lxc_container'may_control p = plusPtr p 424
p'lxc_container'may_control :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> IO CBool))
p'lxc_container'add_device_node p = plusPtr p 432
p'lxc_container'add_device_node :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool))
p'lxc_container'remove_device_node p = plusPtr p 440
p'lxc_container'remove_device_node :: Ptr (C'lxc_container) -> Ptr (FunPtr (Ptr C'lxc_container -> CString -> CString -> IO CBool))
instance Storable C'lxc_container where
sizeOf _ = 448
alignment _ = 8
peek p = do
v0 <- peekByteOff p 56
v1 <- peekByteOff p 64
v2 <- peekByteOff p 68
v3 <- peekByteOff p 72
v4 <- peekByteOff p 80
v5 <- peekByteOff p 88
v6 <- peekByteOff p 96
v7 <- peekByteOff p 104
v8 <- peekByteOff p 112
v9 <- peekByteOff p 120
v10 <- peekByteOff p 128
v11 <- peekByteOff p 136
v12 <- peekByteOff p 152
v13 <- peekByteOff p 160
v14 <- peekByteOff p 168
v15 <- peekByteOff p 176
v16 <- peekByteOff p 184
v17 <- peekByteOff p 192
v18 <- peekByteOff p 200
v19 <- peekByteOff p 208
v20 <- peekByteOff p 216
v21 <- peekByteOff p 232
v22 <- peekByteOff p 240
v23 <- peekByteOff p 248
v24 <- peekByteOff p 256
v25 <- peekByteOff p 264
v26 <- peekByteOff p 272
v27 <- peekByteOff p 280
v28 <- peekByteOff p 288
v29 <- peekByteOff p 296
v30 <- peekByteOff p 304
v31 <- peekByteOff p 312
v32 <- peekByteOff p 320
v33 <- peekByteOff p 328
v34 <- peekByteOff p 336
v35 <- peekByteOff p 344
v36 <- peekByteOff p 352
v37 <- peekByteOff p 360
v38 <- peekByteOff p 368
v39 <- peekByteOff p 376
v40 <- peekByteOff p 392
v41 <- peekByteOff p 400
v42 <- peekByteOff p 408
v43 <- peekByteOff p 416
v44 <- peekByteOff p 424
v45 <- peekByteOff p 432
v46 <- peekByteOff p 440
return $ C'lxc_container v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18 v19 v20 v21 v22 v23 v24 v25 v26 v27 v28 v29 v30 v31 v32 v33 v34 v35 v36 v37 v38 v39 v40 v41 v42 v43 v44 v45 v46
poke p (C'lxc_container v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18 v19 v20 v21 v22 v23 v24 v25 v26 v27 v28 v29 v30 v31 v32 v33 v34 v35 v36 v37 v38 v39 v40 v41 v42 v43 v44 v45 v46) = do
pokeByteOff p 56 v0
pokeByteOff p 64 v1
pokeByteOff p 68 v2
pokeByteOff p 72 v3
pokeByteOff p 80 v4
pokeByteOff p 88 v5
pokeByteOff p 96 v6
pokeByteOff p 104 v7
pokeByteOff p 112 v8
pokeByteOff p 120 v9
pokeByteOff p 128 v10
pokeByteOff p 136 v11
pokeByteOff p 152 v12
pokeByteOff p 160 v13
pokeByteOff p 168 v14
pokeByteOff p 176 v15
pokeByteOff p 184 v16
pokeByteOff p 192 v17
pokeByteOff p 200 v18
pokeByteOff p 208 v19
pokeByteOff p 216 v20
pokeByteOff p 232 v21
pokeByteOff p 240 v22
pokeByteOff p 248 v23
pokeByteOff p 256 v24
pokeByteOff p 264 v25
pokeByteOff p 272 v26
pokeByteOff p 280 v27
pokeByteOff p 288 v28
pokeByteOff p 296 v29
pokeByteOff p 304 v30
pokeByteOff p 312 v31
pokeByteOff p 320 v32
pokeByteOff p 328 v33
pokeByteOff p 336 v34
pokeByteOff p 344 v35
pokeByteOff p 352 v36
pokeByteOff p 360 v37
pokeByteOff p 368 v38
pokeByteOff p 376 v39
pokeByteOff p 392 v40
pokeByteOff p 400 v41
pokeByteOff p 408 v42
pokeByteOff p 416 v43
pokeByteOff p 424 v44
pokeByteOff p 432 v45
pokeByteOff p 440 v46
return ()
foreign import ccall "lxc_container_new" c'lxc_container_new
:: CString -> CString -> IO (Ptr C'lxc_container)
foreign import ccall "&lxc_container_new" p'lxc_container_new
:: FunPtr (CString -> CString -> IO (Ptr C'lxc_container))
foreign import ccall "lxc_container_get" c'lxc_container_get
:: Ptr C'lxc_container -> IO CInt
foreign import ccall "&lxc_container_get" p'lxc_container_get
:: FunPtr (Ptr C'lxc_container -> IO CInt)
foreign import ccall "lxc_container_put" c'lxc_container_put
:: Ptr C'lxc_container -> IO CInt
foreign import ccall "&lxc_container_put" p'lxc_container_put
:: FunPtr (Ptr C'lxc_container -> IO CInt)
foreign import ccall "lxc_get_wait_states" c'lxc_get_wait_states
:: Ptr CString -> IO CInt
foreign import ccall "&lxc_get_wait_states" p'lxc_get_wait_states
:: FunPtr (Ptr CString -> IO CInt)
foreign import ccall "lxc_get_global_config_item" c'lxc_get_global_config_item
:: CString -> IO CString
foreign import ccall "&lxc_get_global_config_item" p'lxc_get_global_config_item
:: FunPtr (CString -> IO CString)
foreign import ccall "lxc_get_version" c'lxc_get_version
:: IO CString
foreign import ccall "&lxc_get_version" p'lxc_get_version
:: FunPtr (IO CString)
foreign import ccall "list_defined_containers" c'list_defined_containers
:: CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt
foreign import ccall "&list_defined_containers" p'list_defined_containers
:: FunPtr (CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt)
foreign import ccall "list_active_containers" c'list_active_containers
:: CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt
foreign import ccall "&list_active_containers" p'list_active_containers
:: FunPtr (CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt)
foreign import ccall "list_all_containers" c'list_all_containers
:: CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt
foreign import ccall "&list_all_containers" p'list_all_containers
:: FunPtr (CString -> Ptr (Ptr CString) -> Ptr (Ptr (Ptr C'lxc_container)) -> IO CInt)
foreign import ccall "lxc_log_close" c'lxc_log_close
:: IO ()
foreign import ccall "&lxc_log_close" p'lxc_log_close
:: FunPtr (IO ())