{-# LANGUAGE RankNTypes #-}

module System.Zfs.Mount where

import Control.Monad
import Control.Monad.IO.Class
import System.Zfs.Types
import System.Zfs.Errors
import qualified System.Zfs.Lowlevel as L
import Foreign.C.String
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.Storable

-- | Mount all datasets in the given pool. Second argument contains mount options (TODO: this shouldn't be a string...)
enableDatasets :: Zpool z -> String -> Zfs z ()
enableDatasets (Zpool fptr) mntopts = Zfs $ \(ZfsContext z) ->
  liftIO $ withCString mntopts $ \cstr ->
  withForeignPtr fptr $ \ptr -> do
    r <- L.zpool_enable_datasets ptr cstr 0
    if r /= 0
      then yieldZError z
      else return $ Right ()

-- | Unmount all datasets in the given pool. Second argument specifies whether to force unmounting.
disableDatasets :: Zpool z -> Bool -> Zfs z ()
disableDatasets (Zpool fptr) force = Zfs $ \(ZfsContext z) ->
  liftIO $ withForeignPtr fptr $ \ptr -> do
    r <- L.zpool_disable_datasets ptr force
    if r /= 0
      then yieldZError z
      else return $ Right ()
           
-- | Unmount this filesystem and any children inheriting the mountpoint property.
unmountAll :: Zdataset z -> Zfs z ()
unmountAll (Zdataset fptr) = Zfs $ \(ZfsContext z) ->
  liftIO $ withForeignPtr fptr $ \ptr -> do
    r <- L.zfs_unmountall ptr 0
    if r /= 0
      then yieldZError z
      else return $ Right ()

-- | Mount the given filesystem with custom mount options
mount' :: Zdataset z -> Maybe String -> Zfs z ()
mount' (Zdataset fptr) mstr = Zfs $ \(ZfsContext z) ->
  liftIO $ withForeignPtr fptr $ \ptr -> do
    r <- case mstr of
      Nothing -> L.zfs_mount ptr nullPtr 0
      Just str -> withCString str $ \cstr -> L.zfs_mount ptr cstr 0
    if r /= 0
      then yieldZError z
      else return $ Right ()

-- | Mount the given filesystem with default options
mount :: Zdataset z -> Zfs z ()
mount znode = mount' znode Nothing

-- | Remount the given filesystem
remount :: Zdataset z -> Zfs z ()
remount znode = mount' znode $ Just "remount"

-- | Unmount the given filesystem
unmount :: Zdataset z -> Zfs z ()
unmount (Zdataset fptr) = Zfs $ \(ZfsContext z) ->
  liftIO $ withForeignPtr fptr $ \ptr -> do
    r <- L.zfs_unmount ptr nullPtr 0
    if r /= 0
      then yieldZError z
      else return $ Right ()

-- | Check if a file system is mounted and return the mountpoint if available
tryGetMountpoint :: Zdataset z -> Zfs z (Maybe String)
tryGetMountpoint (Zdataset fptr) = Zfs $ \(ZfsContext z) ->
  liftIO $ withForeignPtr fptr $ \ptr ->
  alloca $ \cstrptr -> do
    r <- L.zfs_is_mounted ptr cstrptr
    if not r
      then return $ Right Nothing
      else do
      cstr <- peek cstrptr
      str <- peekCString cstr
      return $ Right $ Just str