module Distribution.Compat.TempFile (
  openTempFile,
  openBinaryTempFile,
  openNewBinaryFile,
  createTempDirectory,
  ) where
import System.FilePath        ((</>))
import Foreign.C              (eEXIST)
#if __NHC__ || __HUGS__
import System.IO              (openFile, openBinaryFile,
                               Handle, IOMode(ReadWriteMode))
import System.Directory       (doesFileExist)
import System.FilePath        ((<.>), splitExtension)
import System.IO.Error        (try, isAlreadyExistsError)
#else
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)
import System.IO.Error        (isAlreadyExistsError)
#if __GLASGOW_HASKELL__ >= 706
import Control.Exception      (try)
#else
import System.IO.Error        (try)
#endif
#if __GLASGOW_HASKELL__ >= 611
import System.Posix.Internals (withFilePath)
#else
import Foreign.C              (withCString)
#endif
import Foreign.C              (CInt)
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO.Handle.FD       (fdToHandle)
#else
import GHC.Handle             (fdToHandle)
#endif
import Distribution.Compat.Exception (onException)
#endif
import Foreign.C              (getErrno, errnoToIOError)
#if __NHC__
import System.Posix.Types     (CPid(..))
foreign import ccall unsafe "getpid" c_getpid :: IO CPid
#else
import System.Posix.Internals (c_getpid)
#endif
#ifdef mingw32_HOST_OS
import System.Directory       ( createDirectory )
#else
import qualified System.Posix
#endif
#if __NHC__ || __HUGS__
openTempFile :: FilePath -> String -> IO (FilePath, Handle)
openTempFile tmp_dir template
  = do x <- getProcessID
       findTempName x
  where
    (templateBase, templateExt) = splitExtension template
    findTempName :: Int -> IO (FilePath, Handle)
    findTempName x
      = do let path = tmp_dir </> (templateBase ++ "-" ++ show x) <.> templateExt
           b  <- doesFileExist path
           if b then findTempName (x+1)
                else do hnd <- openFile path ReadWriteMode
                        return (path, hnd)
openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
openBinaryTempFile tmp_dir template
  = do x <- getProcessID
       findTempName x
  where
    (templateBase, templateExt) = splitExtension template
    findTempName :: Int -> IO (FilePath, Handle)
    findTempName x
      = do let path = tmp_dir </> (templateBase ++ show x) <.> templateExt
           b  <- doesFileExist path
           if b then findTempName (x+1)
                else do hnd <- openBinaryFile path ReadWriteMode
                        return (path, hnd)
openNewBinaryFile :: FilePath -> String -> IO (FilePath, Handle)
openNewBinaryFile = openBinaryTempFile
getProcessID :: IO Int
getProcessID = fmap fromIntegral c_getpid
#else
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
#if __GLASGOW_HASKELL__ < 611
    withFilePath = withCString
#endif
    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 <-
#if __GLASGOW_HASKELL__ >= 609
              fdToHandle fd
#elif __GLASGOW_HASKELL__ <= 606 && defined(mingw32_HOST_OS)
              
              openFd (fromIntegral fd) Nothing False filepath
                                       ReadWriteMode True
#else
              fdToHandle (fromIntegral fd)
#endif
              `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
#endif
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 <- try $ mkPrivateDir dirpath
      case r of
        Right _ -> return dirpath
        Left  e | isAlreadyExistsError e -> findTempName (x+1)
                | otherwise              -> ioError e
mkPrivateDir :: String -> IO ()
#ifdef mingw32_HOST_OS
mkPrivateDir s = createDirectory s
#else
mkPrivateDir s = System.Posix.createDirectory s 0o700
#endif