module System.MountPoints (
Mntent(..),
getMounts,
getProcMounts,
) where
import Control.Monad
import Control.Exception
import Data.Maybe
import Control.Applicative
import Foreign
import Foreign.C
import Prelude
data Mntent = Mntent
{ mnt_fsname :: String
, mnt_dir :: FilePath
, mnt_type :: String
} deriving (Show, Eq, Ord)
getMounts :: IO [Mntent]
getMounts = do
h <- c_mounts_start
when (h == nullPtr) $
throwErrno "getMounts"
mntent <- getmntent h []
_ <- c_mounts_end h
return mntent
where
getmntent h c = do
ptr <- c_mounts_next h
if ptr == nullPtr
then return (reverse c)
else do
mnt_fsname_str <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr >>= peekCString
mnt_dir_str <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr >>= peekCString
mnt_type_str <- (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr >>= peekCString
let ent = Mntent
{ mnt_fsname = mnt_fsname_str
, mnt_dir = mnt_dir_str
, mnt_type = mnt_type_str
}
getmntent h (ent:c)
foreign import ccall unsafe "libmounts.h mounts_start" c_mounts_start
:: IO (Ptr ())
foreign import ccall unsafe "libmounts.h mounts_next" c_mounts_next
:: Ptr () -> IO (Ptr ())
foreign import ccall unsafe "libmounts.h mounts_end" c_mounts_end
:: Ptr () -> IO CInt
getProcMounts :: IO [Mntent]
getProcMounts = do
v <- try go :: IO (Either SomeException [Mntent])
return (either (const []) id v)
where
go = mapMaybe (parse . words) . lines <$> readFile "/proc/mounts"
parse (device:mountpoint:fstype:_rest) = Just $ Mntent
{ mnt_fsname = device
, mnt_dir = mountpoint
, mnt_type = fstype
}
parse _ = Nothing