{-# LINE 1 "System/DiskSpace.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LINE 2 "System/DiskSpace.hsc" #-}

{- |
Module      : System.DiskSpace

Stability   : provisional
Portability : portable
-}

module System.DiskSpace
    ( DiskUsage(..)
    , getDiskUsage
    , getAvailSpace
    ) where


{-# LINE 17 "System/DiskSpace.hsc" #-}

import Foreign
import Foreign.C


{-# LINE 22 "System/DiskSpace.hsc" #-}

foreign import ccall safe statvfs :: CString -> Ptr a -> IO CInt

type FsBlkCnt = Word64
{-# LINE 26 "System/DiskSpace.hsc" #-}

getDiskUsage path =
    withCString path $ \cPath ->
        allocaBytes ((112)) $ \stat -> do
{-# LINE 30 "System/DiskSpace.hsc" #-}
            throwErrnoPathIfMinus1_ "getDiskUsage" path $ statvfs cPath stat
            bsize  <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) stat :: IO CULong
{-# LINE 32 "System/DiskSpace.hsc" #-}
            frsize <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) stat :: IO CULong
{-# LINE 33 "System/DiskSpace.hsc" #-}
            blocks <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) stat :: IO FsBlkCnt
{-# LINE 34 "System/DiskSpace.hsc" #-}
            bfree  <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) stat :: IO FsBlkCnt
{-# LINE 35 "System/DiskSpace.hsc" #-}
            bavail <- ((\hsc_ptr -> peekByteOff hsc_ptr 32)) stat :: IO FsBlkCnt
{-# LINE 36 "System/DiskSpace.hsc" #-}
            let frsize' = fromIntegral frsize
            return DiskUsage
                { diskTotal = frsize' * fromIntegral blocks
                , diskFree  = frsize' * fromIntegral bfree
                , diskAvail = frsize' * fromIntegral bavail
                , blockSize = fromIntegral bsize
                }


{-# LINE 61 "System/DiskSpace.hsc" #-}

-- | Disk usage information. All fields are in bytes.
data DiskUsage = DiskUsage
    { diskTotal :: Integer -- ^ The total size of the file system.
    , diskFree  :: Integer -- ^ The amount of free space. You probably want to
                           --   use 'diskAvail' instead.
    , diskAvail :: Integer -- ^ The amount of space available to the user.
                           --   Might be less than 'diskFree'. On Windows,
                           --   this is always equal to 'diskFree'.
                           --   This is what most tools report as free
                           --   space (e.g. the unix @df@ tool).
    , blockSize :: Int     -- ^ The optimal block size for I/O in this volume.
                           --   Some operating systems report incorrect values
                           --   for this field.
    }
  deriving (Show, Eq)

-- | Retrieve disk usage information about a volume. The volume is
-- specified with the @FilePath@ argument. The path can refer to the root
-- directory or any other directory inside the volume.
-- Unix systems also accept arbitrary files, but this
-- does not work under Windows and therefore should be avoided if
-- portability is desired.
getDiskUsage :: FilePath -> IO DiskUsage

-- | A convenience function that directly returns the 'diskAvail' field from
-- the result of 'getDiskUsage'. If a large amount of data is to be written
-- in a directory, calling this function for that directory can be used to
-- determine whether the operation will fail because of insufficient disk
-- space.
getAvailSpace :: FilePath -> IO Integer
getAvailSpace = fmap diskAvail . getDiskUsage