module System.FilePath.Manip (
Streamable(..)
, renameWith
, modifyWith
, modifyWithBackup
, modifyInPlace
) where
import Control.Exception
import Control.Monad (liftM)
import Data.Bits ((.&.))
import System.Directory (removeFile)
import System.IO (Handle, IOMode(..), hClose, openFile)
import System.PosixCompat.Files (fileMode, getFileStatus, rename, setFileMode)
import System.PosixCompat.Temp (mkstemp)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as L
import qualified System.IO as I
renameWith :: (FilePath -> FilePath)
-> FilePath
-> IO ()
renameWith f path = rename path (f path)
class Streamable a where
readAll :: Handle -> IO a
writeAll :: Handle -> a -> IO ()
instance Streamable B.ByteString where
readAll = B.hGetContents
writeAll = B.hPut
instance Streamable L.ByteString where
readAll = L.hGetContents
writeAll = L.hPut
instance Streamable String where
readAll = I.hGetContents
writeAll = I.hPutStr
modifyInPlace :: Streamable a => (a -> a)
-> FilePath
-> IO ()
modifyInPlace = modifyWith (flip rename)
modifyWithBackup :: Streamable a =>
(FilePath -> FilePath)
-> (a -> a)
-> FilePath
-> IO ()
modifyWithBackup f = modifyWith backup
where backup path tmpPath = renameWith f path >> rename tmpPath path
modifyWith :: Streamable a =>
(FilePath -> FilePath -> IO ())
-> (a -> a)
-> FilePath
-> IO ()
modifyWith after transform path =
bracket (openFile path ReadMode) hClose $ \ih -> do
(tmpPath, oh) <- mkstemp (path ++ "XXXXXX")
let ignore = return ()
nukeTmp = handle (\(_::IOException) -> ignore) (removeFile tmpPath)
handle (\(e::IOException) -> nukeTmp >> throw e) $ do
bracket_ ignore (hClose oh) $
readAll ih >>= return . transform >>= writeAll oh
handle (\(_::IOException) -> nukeTmp) $ do
mode <- fileMode `liftM` getFileStatus path
setFileMode tmpPath (mode .&. 0777)
after path tmpPath