-- |
-- Module      : Data.ByteString.RawFilePath
-- Copyright   : (c) XT 2016
-- License     : Apache 2.0
--
-- Maintainer  : e@xtendo.org
-- Stability   : stable
-- Portability : POSIX
--
-- A drop-in replacement of @Data.ByteString@ from the @bytestring@ package
-- that provides file I/O functions with 'RawFilePath' instead of 'FilePath'.

module Data.ByteString.RawFilePath
    ( module Data.ByteString
    , RawFilePath
    , readFile
    , writeFile
    , appendFile
    , withFile

    ) where

-- base modules

import Prelude hiding (readFile, writeFile, appendFile)
import Control.Exception (bracket)
import System.IO (IOMode(..), Handle, hClose)

-- extra modules

import System.Posix.ByteString
import Data.ByteString hiding (readFile, writeFile, appendFile)

-- | Read an entire file at the 'RawFilePath' strictly into a 'ByteString'.
readFile :: RawFilePath -> IO ByteString
readFile :: RawFilePath -> IO RawFilePath
readFile RawFilePath
path = forall r. RawFilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile RawFilePath
path IOMode
ReadMode Handle -> IO RawFilePath
hGetContents

-- | Write a 'ByteString' to a file at the 'RawFilePath'.
writeFile :: RawFilePath -> ByteString -> IO ()
writeFile :: RawFilePath -> RawFilePath -> IO ()
writeFile RawFilePath
path RawFilePath
content = forall r. RawFilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile RawFilePath
path IOMode
WriteMode (Handle -> RawFilePath -> IO ()
`hPut` RawFilePath
content)

-- | Append a 'ByteString' to a file at the 'RawFilePath'.
appendFile :: RawFilePath -> ByteString -> IO ()
appendFile :: RawFilePath -> RawFilePath -> IO ()
appendFile RawFilePath
path RawFilePath
content = forall r. RawFilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile RawFilePath
path IOMode
AppendMode (Handle -> RawFilePath -> IO ()
`hPut` RawFilePath
content)

-- | Acquire a file handle and perform an I/O action. The file will be closed
-- on exit or when this I/O action throws an exception.
withFile :: RawFilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile :: forall r. RawFilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile RawFilePath
path IOMode
ioMode = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (IO Fd
open forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Fd -> IO Handle
fdToHandle) Handle -> IO ()
hClose
  where
#if MIN_VERSION_unix(2,8,0)
    open = case ioMode of
        ReadMode -> openFd path ReadOnly $ defaultFlags Nothing
        WriteMode -> createFile path stdFileMode
        AppendMode -> openFd path WriteOnly $ appendFlags $ Just stdFileMode
        ReadWriteMode -> openFd path ReadWrite $ defaultFlags $ Just stdFileMode
    defaultFlags creat = OpenFileFlags
        { System.Posix.ByteString.append = False
        , creat = creat
        , exclusive = False
        , noctty = True
        , nonBlock = False
        , trunc = False
        , nofollow = False
        , cloexec = False
        , directory = False
        , sync = False
        }
    appendFlags creat = (defaultFlags creat) { System.Posix.ByteString.append = True }
#else
    open :: IO Fd
open = case IOMode
ioMode of
        IOMode
ReadMode -> RawFilePath -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd RawFilePath
path OpenMode
ReadOnly forall a. Maybe a
Nothing OpenFileFlags
defaultFlags
        IOMode
WriteMode -> RawFilePath -> FileMode -> IO Fd
createFile RawFilePath
path FileMode
stdFileMode
        IOMode
AppendMode -> RawFilePath -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd RawFilePath
path OpenMode
WriteOnly (forall a. a -> Maybe a
Just FileMode
stdFileMode) OpenFileFlags
appendFlags
        IOMode
ReadWriteMode -> RawFilePath -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd RawFilePath
path OpenMode
ReadWrite (forall a. a -> Maybe a
Just FileMode
stdFileMode) OpenFileFlags
defaultFlags
    defaultFlags :: OpenFileFlags
defaultFlags = OpenFileFlags
        { append :: Bool
System.Posix.ByteString.append = Bool
False
        , exclusive :: Bool
exclusive = Bool
False
        , noctty :: Bool
noctty = Bool
True
        , nonBlock :: Bool
nonBlock = Bool
False
        , trunc :: Bool
trunc = Bool
False
        }
    appendFlags :: OpenFileFlags
appendFlags = OpenFileFlags
defaultFlags { append :: Bool
System.Posix.ByteString.append = Bool
True }
#endif