2010-10-10 19:16:47 -04:00
|
|
|
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables, TypeSynonymInstances #-}
|
2007-05-01 01:49:58 -04:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Module: System.FilePath.Manip
|
|
|
|
-- Copyright: Bryan O'Sullivan
|
2008-02-03 12:52:21 -05:00
|
|
|
-- License: BSD3
|
2007-05-01 01:49:58 -04:00
|
|
|
-- Maintainer: Bryan O'Sullivan <bos@serpentine.com>
|
|
|
|
-- Stability: unstable
|
|
|
|
-- Portability: Unix-like systems (requires flexible instances)
|
2007-04-30 16:11:13 -04:00
|
|
|
|
2007-04-30 15:46:06 -04:00
|
|
|
module System.FilePath.Manip (
|
2007-05-01 01:49:58 -04:00
|
|
|
Streamable(..)
|
2007-04-30 16:11:13 -04:00
|
|
|
, renameWith
|
2007-04-30 15:46:06 -04:00
|
|
|
, modifyWith
|
|
|
|
, modifyWithBackup
|
|
|
|
, modifyInPlace
|
|
|
|
) where
|
|
|
|
|
2010-10-10 19:16:47 -04:00
|
|
|
import Control.Exception
|
2007-04-30 15:46:06 -04:00
|
|
|
import Control.Monad (liftM)
|
|
|
|
import Data.Bits ((.&.))
|
|
|
|
import System.Directory (removeFile)
|
2007-05-01 01:49:58 -04:00
|
|
|
import System.IO (Handle, IOMode(..), hClose, openFile)
|
2011-11-06 21:16:43 -05:00
|
|
|
import System.PosixCompat.Files (fileMode, getFileStatus, rename, setFileMode)
|
|
|
|
import System.PosixCompat.Temp (mkstemp)
|
2007-04-30 16:11:13 -04:00
|
|
|
import qualified Data.ByteString.Char8 as B
|
2007-04-30 15:46:06 -04:00
|
|
|
import qualified Data.ByteString.Lazy.Char8 as L
|
2007-05-01 01:49:58 -04:00
|
|
|
import qualified System.IO as I
|
2007-04-30 15:46:06 -04:00
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
-- | Use a renaming function to generate a new name for a file, then
|
|
|
|
-- rename it.
|
|
|
|
renameWith :: (FilePath -> FilePath) -- ^ function to rename with
|
|
|
|
-> FilePath -- ^ file to rename
|
|
|
|
-> IO ()
|
2007-04-30 15:46:06 -04:00
|
|
|
|
|
|
|
renameWith f path = rename path (f path)
|
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
-- | Type class for string manipulation over files.
|
|
|
|
class Streamable a where
|
|
|
|
-- | Read the entire contents of a 'Handle'.
|
|
|
|
readAll :: Handle -> IO a
|
|
|
|
-- | Write an entire string to a 'Handle'.
|
|
|
|
writeAll :: Handle -> a -> IO ()
|
2007-04-30 16:11:13 -04:00
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
instance Streamable B.ByteString where
|
|
|
|
readAll = B.hGetContents
|
|
|
|
writeAll = B.hPut
|
2007-04-30 16:11:13 -04:00
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
instance Streamable L.ByteString where
|
|
|
|
readAll = L.hGetContents
|
|
|
|
writeAll = L.hPut
|
2007-04-30 16:11:13 -04:00
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
instance Streamable String where
|
|
|
|
readAll = I.hGetContents
|
|
|
|
writeAll = I.hPutStr
|
2007-04-30 16:11:13 -04:00
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
-- | Modify a file in place using the given function. This is
|
|
|
|
-- performed by writing to a temporary file, then renaming it on top of
|
|
|
|
-- the existing file when done.
|
|
|
|
modifyInPlace :: Streamable a => (a -> a) -- ^ transformation function
|
|
|
|
-> FilePath -- ^ name of file to modify
|
|
|
|
-> IO ()
|
2007-04-30 16:11:13 -04:00
|
|
|
|
|
|
|
modifyInPlace = modifyWith (flip rename)
|
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
-- | Modify a file in place using the given function. The original
|
|
|
|
-- copy of the file is saved under a new name. This is performed by
|
|
|
|
-- writing to a temporary file; renaming the original file to its new
|
|
|
|
-- name; then renaming the temporary file to the original name.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- -- save original file with a \".bak\" extension
|
|
|
|
-- 'modifyWithBackup' (\<.\> \"bak\")
|
|
|
|
-- @
|
|
|
|
modifyWithBackup :: Streamable a =>
|
|
|
|
(FilePath -> FilePath) -- ^ chooses new name for original file
|
|
|
|
-> (a -> a) -- ^ transformation function
|
|
|
|
-> FilePath -- ^ name of file to modify
|
2007-04-30 16:11:13 -04:00
|
|
|
-> IO ()
|
|
|
|
|
|
|
|
modifyWithBackup f = modifyWith backup
|
|
|
|
where backup path tmpPath = renameWith f path >> rename tmpPath path
|
|
|
|
|
2007-05-01 01:49:58 -04:00
|
|
|
-- | Modify a file in place using the given function. The new content
|
|
|
|
-- is written to a temporary file. Once this is complete, the file
|
|
|
|
-- manipulation action is called. Its arguments are the names of the
|
|
|
|
-- original and temporary files.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- 'modifyInPlace' = 'modifyWith' (flip rename)
|
|
|
|
-- @
|
|
|
|
modifyWith :: Streamable a =>
|
|
|
|
(FilePath -> FilePath -> IO ()) -- ^ file manipulation action
|
|
|
|
-> (a -> a) -- ^ transformation function
|
2007-04-30 16:11:13 -04:00
|
|
|
-> FilePath
|
|
|
|
-> IO ()
|
2007-04-30 15:46:06 -04:00
|
|
|
|
|
|
|
modifyWith after transform path =
|
|
|
|
bracket (openFile path ReadMode) hClose $ \ih -> do
|
|
|
|
(tmpPath, oh) <- mkstemp (path ++ "XXXXXX")
|
|
|
|
let ignore = return ()
|
2010-10-10 19:16:47 -04:00
|
|
|
nukeTmp = handle (\(_::IOException) -> ignore) (removeFile tmpPath)
|
|
|
|
handle (\(e::IOException) -> nukeTmp >> throw e) $ do
|
2007-04-30 15:46:06 -04:00
|
|
|
bracket_ ignore (hClose oh) $
|
2007-05-01 01:49:58 -04:00
|
|
|
readAll ih >>= return . transform >>= writeAll oh
|
2010-10-10 19:16:47 -04:00
|
|
|
handle (\(_::IOException) -> nukeTmp) $ do
|
2007-04-30 15:46:06 -04:00
|
|
|
mode <- fileMode `liftM` getFileStatus path
|
|
|
|
setFileMode tmpPath (mode .&. 0777)
|
|
|
|
after path tmpPath
|