{-# LANGUAGE RankNTypes #-} module System.Zfs.Dataset where import Control.Monad import Control.Monad.IO.Class import qualified System.Zfs.Lowlevel as L import System.Zfs.Types import System.Zfs.Errors import Foreign.C.String import Foreign.Ptr import Foreign.ForeignPtr import Foreign.Marshal.Alloc import Foreign.Storable -- | Create a filesystem createFilesystem :: String -> Zfs () createFilesystem path = withZfs $ \z -> do cpath <- newCString path props <- alloca $ \nvptr -> do L.nvlist_alloc nvptr 1 1 peek nvptr r <- L.zfs_create z cpath 1 {- ZFS_TYPE_FILESYSTEM -} props if r /= 0 then yieldZError z else return $ Right () -- | Create a block volume (path, block size, vol size) createVolume :: String -> Integer -> Integer -> Zfs () createVolume path blocksize volsize = withZfs $ \z -> do cpath <- newCString path props <- alloca $ \nvptr -> do L.nvlist_alloc nvptr 1 1 peek nvptr str_volsize <- newCString "volsize" str_volblocksize <- newCString "volblocksize" L.nvlist_add_uint64 props str_volsize $ fromIntegral volsize L.nvlist_add_uint64 props str_volblocksize $ fromIntegral blocksize r <- L.zfs_create z cpath 4 {- ZFS_TYPE_VOLUME -} props if r /= 0 then yieldZError z else return $ Right () -- | Destroy a dataset. destroyDataset :: Zdataset -> Zfs () destroyDataset (Zdataset fptr) = withZfs $ \z -> withForeignPtr fptr $ \ptr -> do r <- L.zfs_destroy ptr False if r /= 0 then yieldZError z else return $ Right () -- | Gets the name of some Zfs getDatasetName :: Zdataset -> Zfs String getDatasetName (Zdataset fptr) = withZfs $ \z -> do cstr <- withForeignPtr fptr L.zfs_get_name str <- peekCString cstr return $ Right str