eed20fe3b7
Also audited for other calls to openTempFile, and all are ok, except for viaTmp which will need further work. Remote.Directory fixed to set umask mode when writing to an export, although it has another one using viaTmp that's not fixed. Will make exports that are published via a http server running as another user work, for example. Remote.BitTorrent fixed to set umask mode when downloading the torrent file. Normally this does not matter as that file does not hang around after the download, but if a bittorrent download were started by one user, got interrupted and then another user ran it, this will let them access the torrent file created by the first user.
90 lines
2.7 KiB
Haskell
90 lines
2.7 KiB
Haskell
{- Temporary files.
|
|
-
|
|
- Copyright 2010-2013 Joey Hess <id@joeyh.name>
|
|
-
|
|
- License: BSD-2-clause
|
|
-}
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
|
|
|
module Utility.Tmp (
|
|
Template,
|
|
viaTmp,
|
|
withTmpFile,
|
|
withTmpFileIn,
|
|
relatedTemplate,
|
|
) where
|
|
|
|
import System.IO
|
|
import System.FilePath
|
|
import System.Directory
|
|
import Control.Monad.IO.Class
|
|
import System.PosixCompat.Files
|
|
|
|
import Utility.Exception
|
|
import Utility.FileSystemEncoding
|
|
|
|
type Template = String
|
|
|
|
{- Runs an action like writeFile, writing to a temp file first and
|
|
- then moving it into place. The temp file is stored in the same
|
|
- directory as the final file to avoid cross-device renames.
|
|
-
|
|
- Note that the tmp file will have a file mode that only allows the
|
|
- current user to access it. The write action can change the mode
|
|
- to whatever is desired.
|
|
-}
|
|
viaTmp :: (MonadMask m, MonadIO m) => (FilePath -> v -> m ()) -> FilePath -> v -> m ()
|
|
viaTmp a file content = bracketIO setup cleanup use
|
|
where
|
|
(dir, base) = splitFileName file
|
|
template = relatedTemplate (base ++ ".tmp")
|
|
setup = do
|
|
createDirectoryIfMissing True dir
|
|
openTempFile dir template
|
|
cleanup (tmpfile, h) = do
|
|
_ <- tryIO $ hClose h
|
|
tryIO $ removeFile tmpfile
|
|
use (tmpfile, h) = do
|
|
liftIO $ hClose h
|
|
a tmpfile content
|
|
liftIO $ rename tmpfile file
|
|
|
|
{- Runs an action with a tmp file located in the system's tmp directory
|
|
- (or in "." if there is none) then removes the file. -}
|
|
withTmpFile :: (MonadIO m, MonadMask m) => Template -> (FilePath -> Handle -> m a) -> m a
|
|
withTmpFile template a = do
|
|
tmpdir <- liftIO $ catchDefaultIO "." getTemporaryDirectory
|
|
withTmpFileIn tmpdir template a
|
|
|
|
{- Runs an action with a tmp file located in the specified directory,
|
|
- then removes the file.
|
|
-
|
|
- Note that the tmp file will have a file mode that only allows the
|
|
- current user to access it.
|
|
-}
|
|
withTmpFileIn :: (MonadIO m, MonadMask m) => FilePath -> Template -> (FilePath -> Handle -> m a) -> m a
|
|
withTmpFileIn tmpdir template a = bracket create remove use
|
|
where
|
|
create = liftIO $ openTempFile tmpdir template
|
|
remove (name, h) = liftIO $ do
|
|
hClose h
|
|
catchBoolIO (removeFile name >> return True)
|
|
use (name, h) = a name h
|
|
|
|
{- It's not safe to use a FilePath of an existing file as the template
|
|
- for openTempFile, because if the FilePath is really long, the tmpfile
|
|
- will be longer, and may exceed the maximum filename length.
|
|
-
|
|
- This generates a template that is never too long.
|
|
- (Well, it allocates 20 characters for use in making a unique temp file,
|
|
- anyway, which is enough for the current implementation and any
|
|
- likely implementation.)
|
|
-}
|
|
relatedTemplate :: FilePath -> FilePath
|
|
relatedTemplate f
|
|
| len > 20 = truncateFilePath (len - 20) f
|
|
| otherwise = f
|
|
where
|
|
len = length f
|