libzfs-0.2.0.0: Bindings to libzfs, for dealing with the Z File System and Zpools.

Safe HaskellSafe
LanguageHaskell2010

System.Zfs.Types

Synopsis

Documentation

newtype ZfsContext #

Libzfs context (hidden)

newtype Zpool #

A Zpool handle

Constructors

Zpool (ForeignPtr ZpoolHandle) 

newtype Zdataset #

A Zfs handle

Constructors

Zdataset (ForeignPtr ZfsHandle) 

newtype ZfsT m a #

A monad transformer encapsulating all ZFS actions. Calls libzfs_init and libzfs_fini.

Constructors

Zfs 

Fields

Instances

MonadTrans ZfsT # 

Methods

lift :: Monad m => m a -> ZfsT m a #

Monad m => MonadError ZError (ZfsT m) # 

Methods

throwError :: ZError -> ZfsT m a

catchError :: ZfsT m a -> (ZError -> ZfsT m a) -> ZfsT m a

Monad m => Monad (ZfsT m) # 

Methods

(>>=) :: ZfsT m a -> (a -> ZfsT m b) -> ZfsT m b #

(>>) :: ZfsT m a -> ZfsT m b -> ZfsT m b #

return :: a -> ZfsT m a #

fail :: String -> ZfsT m a #

Monad m => Functor (ZfsT m) # 

Methods

fmap :: (a -> b) -> ZfsT m a -> ZfsT m b #

(<$) :: a -> ZfsT m b -> ZfsT m a #

Monad m => Applicative (ZfsT m) # 

Methods

pure :: a -> ZfsT m a #

(<*>) :: ZfsT m (a -> b) -> ZfsT m a -> ZfsT m b #

(*>) :: ZfsT m a -> ZfsT m b -> ZfsT m b #

(<*) :: ZfsT m a -> ZfsT m b -> ZfsT m a #

MonadIO m => MonadIO (ZfsT m) # 

Methods

liftIO :: IO a -> ZfsT m a #

type Zfs a = forall m. MonadIO m => ZfsT m a #

Some Zfs function that works for all underlying MonadIO instances

data Vdev #

A Zpool device

Constructors

VdFile String 
VdMirror [Vdev] 

Instances

Eq Vdev # 

Methods

(==) :: Vdev -> Vdev -> Bool #

(/=) :: Vdev -> Vdev -> Bool #

Show Vdev # 

Methods

showsPrec :: Int -> Vdev -> ShowS #

show :: Vdev -> String #

showList :: [Vdev] -> ShowS #

withZfs :: MonadIO m => (Ptr LibzfsHandle -> IO (Either ZError a)) -> ZfsT m a #