module System.AtomicWrite (atomicWriteFile) where
import System.Directory (renameFile, doesFileExist)
import System.FilePath.Posix (takeDirectory)
import System.IO
  (Handle, openTempFile, openTempFileWithDefaultPermissions, hPutStr, hClose)
import System.Posix.Files (setFileMode, getFileStatus, fileMode)
atomicWriteFile ::
  FilePath   
  -> String  
  -> IO ()
atomicWriteFile f txt = do
  (temppath, h) <- tempFileFor f
  hPutStr h txt
  hClose h
  renameFile temppath f
tempFileFor :: FilePath -> IO (FilePath, Handle)
tempFileFor originalFilePath = do
  let targetDirectory = takeDirectory originalFilePath
  doesFileExist originalFilePath >>=
    tmpFile originalFilePath targetDirectory "atomic.write"
  where
    tmpFile :: FilePath -> FilePath -> String -> Bool -> IO (FilePath, Handle)
    tmpFile originalPath workingDirectory template previousExisted =
      if previousExisted then do
        (temppath, handle) <- openTempFile workingDirectory template
        oldStat <- getFileStatus originalPath
        setFileMode temppath $ fileMode oldStat
        return (temppath, handle)
      else
        openTempFileWithDefaultPermissions workingDirectory template