#include "StatVFSConfig.h"
module System.Posix.StatVFS where
import Control.Applicative
import Foreign
import Foreign.C.Error (throwErrnoIfMinus1_)
import Foreign.C.Types (CInt(..), CULong(..))
import Foreign.C.String (CString, withCString)
import System.Posix.Types
import Unsafe.Coerce (unsafeCoerce)
newtype CFSBlkCnt = CFSBlkCnt HTYPE_FSBLKCNT_T deriving (Bounded, Enum, Eq, Integral, Num, Ord, Real, Storable)
newtype CFSFilCnt = CFSFilCnt HTYPE_FSFILCNT_T deriving (Bounded, Enum, Eq, Integral, Num, Ord, Real, Storable)
instance Read CFSBlkCnt where
readsPrec = unsafeCoerce (readsPrec :: Int -> ReadS HTYPE_FSBLKCNT_T)
readList = unsafeCoerce (readList :: ReadS [HTYPE_FSBLKCNT_T])
instance Show CFSBlkCnt where
showsPrec = unsafeCoerce (showsPrec :: Int -> HTYPE_FSBLKCNT_T -> ShowS)
show = unsafeCoerce (show :: HTYPE_FSBLKCNT_T -> String)
showList = unsafeCoerce (showList :: [HTYPE_FSBLKCNT_T] -> ShowS)
instance Read CFSFilCnt where
readsPrec = unsafeCoerce (readsPrec :: Int -> ReadS HTYPE_FSFILCNT_T)
readList = unsafeCoerce (readList :: ReadS [HTYPE_FSFILCNT_T])
instance Show CFSFilCnt where
showsPrec = unsafeCoerce (showsPrec :: Int -> HTYPE_FSFILCNT_T -> ShowS)
show = unsafeCoerce (show :: HTYPE_FSFILCNT_T -> String)
showList = unsafeCoerce (showList :: [HTYPE_FSFILCNT_T] -> ShowS)
type CStatVFS = ()
foreign import capi unsafe "sys/statvfs.h fstatvfs"
c_fstatvfs :: CInt -> Ptr CStatVFS -> IO CInt
foreign import capi unsafe "sys/statvfs.h statvfs"
c_statvfs :: CString -> Ptr CStatVFS -> IO CInt
data StatVFS = StatVFS {
statVFS_bsize :: CULong
, statVFS_frsize :: CULong
, statVFS_blocks :: CFSBlkCnt
, statVFS_bfree :: CFSBlkCnt
, statVFS_bavail :: CFSBlkCnt
, statVFS_files :: CFSFilCnt
, statVFS_ffree :: CFSFilCnt
, statVFS_favail :: CFSFilCnt
, statVFS_fsid :: CULong
, statVFS_flag :: CULong
, statVFS_namemax :: CULong
} deriving Show
statVFS_st_rdonly :: CULong
statVFS_st_rdonly = (1)
statVFS_st_nosuid :: CULong
statVFS_st_nosuid = (2)
toStatVFS :: Ptr CStatVFS -> IO StatVFS
toStatVFS p = StatVFS
<$> ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 32)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 40)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 48)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 56)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 64)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 72)) p
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 80)) p
fStatVFS :: Fd -> IO StatVFS
fStatVFS (Fd fd) = do
fp <- mallocForeignPtrBytes (112)
withForeignPtr fp $ \p -> do
throwErrnoIfMinus1_ "fStatVFS" $ c_fstatvfs fd p
toStatVFS p
statVFS :: FilePath -> IO StatVFS
statVFS path = do
withCString path $ \c_path -> do
fp <- mallocForeignPtrBytes (112)
withForeignPtr fp $ \p -> do
throwErrnoIfMinus1_ "statVFS" $ c_statvfs c_path p
toStatVFS p