{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Git.Internal.FileUtil where
import Control.Applicative
import Control.DeepSeq
import Control.Exception
import Control.Monad
import Control.Monad.IO.Class
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import System.IO
import System.IO.Error (catchIOError, isAlreadyExistsError, isDoesNotExistError,
isPermissionError, tryIOError)
import System.Posix.ByteString
import System.Posix.FilePath
withHandle :: NFData a => Maybe FileMode -> OpenMode -> RawFilePath -> OpenFileFlags -> (Handle -> IO a) -> IO a
withHandle c m p offs app = bracket (fdToHandle =<< openFd p m c offs) hClose (\h -> app h >>= (\r -> r `deepseq` return r))
withHandleAtomic :: NFData a => RawFilePath -> (Handle -> IO (Maybe RawFilePath, a)) -> IO a
withHandleAtomic p app = bracketOnError (mkstemp p) cleanup go
where cleanup (tmp, h) = hClose h >> removeLink tmp
go (tmp, h) = do
(np, force -> !r) <- app h
hClose h
rename tmp $ maybe p id np
return r
data TempFile = TempFile
{ tempHandle :: Handle
, tempFileName :: RawFilePath
, tempTemplate :: RawFilePath
, closeTempFile :: Maybe RawFilePath -> IO ()
}
tempFile :: RawFilePath -> IO TempFile
tempFile p = do
createRawDirectoryIfMissing True (dropFileName p)
bracketOnError (mkstemp p) cleanup go
where
cleanup (tmp, h) = hClose h >> removeLink tmp
go t@(tmp, h) = return $ TempFile h tmp p (finish t)
finish t Nothing = cleanup t
finish (tmp, h) (Just np) = rename tmp np >> hClose h
readFileFlags :: OpenFileFlags
readFileFlags = defaultFileFlags
readRawFileL :: RawFilePath -> IO BL.ByteString
readRawFileL p = withHandle Nothing ReadOnly p readFileFlags BL.hGetContents
readRawFileS :: RawFilePath -> IO B.ByteString
readRawFileS p = withHandle Nothing ReadOnly p readFileFlags B.hGetContents
writeRawFileL :: RawFilePath -> BL.ByteString -> IO ()
writeRawFileL p bs = withHandleAtomic p (\h -> BL.hPut h bs *> return (Nothing, ()))
writeRawFileS :: RawFilePath -> B.ByteString -> IO ()
writeRawFileS p bs = withHandleAtomic p (\h -> B.hPut h bs *> return (Nothing, ()))
whenFileExists :: MonadIO m =>
RawFilePath
-> a
-> m a
-> m a
whenFileExists p a io = do
exists <- liftIO $ fileExist p
if exists
then io
else return a
mwhenFileExists :: (MonadIO m, Alternative f) => RawFilePath -> m a -> m (f a)
mwhenFileExists p io = whenFileExists p empty (pure <$> io)
getRawDirectoryContents :: RawFilePath -> IO [RawFilePath]
getRawDirectoryContents dir = bracket (openDirStream dir) closeDirStream go
where go ds = do f <- readDirStream ds
if f == ""
then return []
else (f:) <$> go ds
createRawDirectoryIfMissing :: Bool -> RawFilePath -> IO ()
createRawDirectoryIfMissing create_parents path0
| create_parents = createDirs (parents path0)
| otherwise = createDirs (take 1 (parents path0))
where
parents = reverse . scanl1 (</>) . splitDirectories
createDirs [] = return ()
createDirs (dir:[]) = createDir dir ioError
createDirs (dir:dirs) =
createDir dir $ \_ -> do
createDirs dirs
createDir dir ioError
createDir dir notExistHandler = do
r <- tryIOError (createDirectory dir dirmode)
case r of
Right () -> return ()
Left e
| isDoesNotExistError e -> notExistHandler e
| isAlreadyExistsError e
|| isPermissionError e -> do
canIgnore <- isDir `catchIOError` \ _ ->
return (isAlreadyExistsError e)
unless canIgnore (ioError e)
| otherwise -> ioError e
where
isDir = (isDirectory <$> getFileStatus dir)
dirmode = foldr unionFileModes directoryMode dirmodes
dirmodes = [ ownerModes,
groupReadMode, groupExecuteMode
, otherReadMode, otherExecuteMode ]
withRawCurrentDirectory :: RawFilePath -> IO a -> IO a
withRawCurrentDirectory dir action =
bracket getWorkingDirectory changeWorkingDirectory $ \ _ -> do
changeWorkingDirectory dir
action