module Distribution.Compat.Internal.TempFile (
openTempFile,
openBinaryTempFile,
openNewBinaryFile,
createTempDirectory,
) where
import Distribution.Compat.Exception
import System.FilePath ((</>))
import Foreign.C (CInt, eEXIST, getErrno, errnoToIOError)
import System.IO (Handle, openTempFile, openBinaryTempFile)
import Data.Bits ((.|.))
import System.Posix.Internals (c_open, c_close, o_CREAT, o_EXCL, o_RDWR,
o_BINARY, o_NONBLOCK, o_NOCTTY,
withFilePath, c_getpid)
import System.IO.Error (isAlreadyExistsError)
import GHC.IO.Handle.FD (fdToHandle)
import Control.Exception (onException)
#if defined(mingw32_HOST_OS) || defined(ghcjs_HOST_OS)
import System.Directory ( createDirectory )
#else
import qualified System.Posix
#endif
openNewBinaryFile :: FilePath -> String -> IO (FilePath, Handle)
openNewBinaryFile dir template = do
pid <- c_getpid
findTempName pid
where
(prefix,suffix) =
case break (== '.') $ reverse template of
(rev_suffix, "") -> (reverse rev_suffix, "")
(rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
_ -> error "bug in System.IO.openTempFile"
oflags = rw_flags .|. o_EXCL .|. o_BINARY
findTempName x = do
fd <- withFilePath filepath $ \ f ->
c_open f oflags 0o666
if fd < 0
then do
errno <- getErrno
if errno == eEXIST
then findTempName (x+1)
else ioError (errnoToIOError "openNewBinaryFile" errno Nothing (Just dir))
else do
h <- fdToHandle fd `onException` c_close fd
return (filepath, h)
where
filename = prefix ++ show x ++ suffix
filepath = dir `combine` filename
combine a b
| null b = a
| null a = b
| last a == pathSeparator = a ++ b
| otherwise = a ++ [pathSeparator] ++ b
pathSeparator :: Char
#ifdef mingw32_HOST_OS
pathSeparator = '\\'
#else
pathSeparator = '/'
#endif
std_flags, output_flags, rw_flags :: CInt
std_flags = o_NONBLOCK .|. o_NOCTTY
output_flags = std_flags .|. o_CREAT
rw_flags = output_flags .|. o_RDWR
createTempDirectory :: FilePath -> String -> IO FilePath
createTempDirectory dir template = do
pid <- c_getpid
findTempName pid
where
findTempName x = do
let dirpath = dir </> template ++ "-" ++ show x
r <- tryIO $ mkPrivateDir dirpath
case r of
Right _ -> return dirpath
Left e | isAlreadyExistsError e -> findTempName (x+1)
| otherwise -> ioError e
mkPrivateDir :: String -> IO ()
#if defined(mingw32_HOST_OS) || defined(ghcjs_HOST_OS)
mkPrivateDir s = createDirectory s
#else
mkPrivateDir s = System.Posix.createDirectory s 0o700
#endif