aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-05-12 19:19:28 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-05-12 19:19:28 -0400
commit1dd4574909b40ffdb77ae1338b353156d73983af (patch)
tree21a2d65e054964e91ba7376fcbca95b33f7f4472
parentb8558b724b302a9db16e9b75ac2cba425ecdc5c1 (diff)
rename module
-rw-r--r--Annex/Content/Direct.hs2
-rw-r--r--Assistant/DaemonStatus.hs2
-rw-r--r--Assistant/Install.hs2
-rw-r--r--Assistant/Ssh.hs4
-rw-r--r--Assistant/Threads/WebApp.hs4
-rw-r--r--Config/Files.hs2
-rw-r--r--Init.hs2
-rw-r--r--Logs/Unused.hs2
-rw-r--r--Remote/Git.hs4
-rw-r--r--Upgrade/V1.hs2
-rw-r--r--Upgrade/V2.hs2
-rw-r--r--Utility/Directory.hs2
-rw-r--r--Utility/Tmp.hs (renamed from Utility/TempFile.hs)24
-rw-r--r--Utility/WebApp.hs2
14 files changed, 28 insertions, 28 deletions
diff --git a/Annex/Content/Direct.hs b/Annex/Content/Direct.hs
index 54befdf73..3560c8b6c 100644
--- a/Annex/Content/Direct.hs
+++ b/Annex/Content/Direct.hs
@@ -29,7 +29,7 @@ import Common.Annex
import qualified Annex
import Annex.Perms
import qualified Git
-import Utility.TempFile
+import Utility.Tmp
import Logs.Location
import Utility.InodeCache
diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs
index f94521117..af072d8ae 100644
--- a/Assistant/DaemonStatus.hs
+++ b/Assistant/DaemonStatus.hs
@@ -9,7 +9,7 @@ module Assistant.DaemonStatus where
import Assistant.Common
import Assistant.Alert.Utility
-import Utility.TempFile
+import Utility.Tmp
import Assistant.Types.NetMessager
import Utility.NotificationBroadcaster
import Logs.Transfer
diff --git a/Assistant/Install.hs b/Assistant/Install.hs
index 227d1bc03..3c7d09698 100644
--- a/Assistant/Install.hs
+++ b/Assistant/Install.hs
@@ -16,7 +16,7 @@ import Assistant.Ssh
import Config.Files
import Utility.FileMode
import Utility.Shell
-import Utility.TempFile
+import Utility.Tmp
import Utility.Env
#ifdef darwin_HOST_OS
diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs
index 0c718d019..7875c4c4c 100644
--- a/Assistant/Ssh.hs
+++ b/Assistant/Ssh.hs
@@ -8,7 +8,7 @@
module Assistant.Ssh where
import Common.Annex
-import Utility.TempFile
+import Utility.Tmp
import Utility.UserInfo
import Utility.Shell
import Git.Remote
@@ -146,7 +146,7 @@ authorizedKeysLine rsynconly dir pubkey
{- Generates a ssh key pair. -}
genSshKeyPair :: IO SshKeyPair
-genSshKeyPair = withTempDir "git-annex-keygen" $ \dir -> do
+genSshKeyPair = withTmpDir "git-annex-keygen" $ \dir -> do
ok <- boolSystem "ssh-keygen"
[ Param "-P", Param "" -- no password
, Param "-f", File $ dir </> "key"
diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs
index 19300cf3c..3c1e6178a 100644
--- a/Assistant/Threads/WebApp.hs
+++ b/Assistant/Threads/WebApp.hs
@@ -33,7 +33,7 @@ import Assistant.WebApp.Control
import Assistant.WebApp.OtherRepos
import Assistant.Types.ThreadedMonad
import Utility.WebApp
-import Utility.TempFile
+import Utility.Tmp
import Utility.FileMode
import Git
@@ -74,7 +74,7 @@ webAppThread assistantdata urlrenderer noannex listenhost postfirstrun onstartup
, return app
)
runWebApp listenhost app' $ \addr -> if noannex
- then withTempFile "webapp.html" $ \tmpfile _ ->
+ then withTmpFile "webapp.html" $ \tmpfile _ ->
go addr webapp tmpfile Nothing
else do
let st = threadState assistantdata
diff --git a/Config/Files.hs b/Config/Files.hs
index 45f478eeb..6504d1f6d 100644
--- a/Config/Files.hs
+++ b/Config/Files.hs
@@ -8,7 +8,7 @@
module Config.Files where
import Common
-import Utility.TempFile
+import Utility.Tmp
import Utility.FreeDesktop
{- ~/.config/git-annex/file -}
diff --git a/Init.hs b/Init.hs
index c2ddf6905..d1a57d51e 100644
--- a/Init.hs
+++ b/Init.hs
@@ -16,7 +16,7 @@ module Init (
) where
import Common.Annex
-import Utility.TempFile
+import Utility.Tmp
import Utility.Network
import qualified Git
import qualified Git.LsFiles
diff --git a/Logs/Unused.hs b/Logs/Unused.hs
index 437b01f71..342d88aa6 100644
--- a/Logs/Unused.hs
+++ b/Logs/Unused.hs
@@ -19,7 +19,7 @@ import qualified Data.Map as M
import Common.Annex
import Command
import Types.Key
-import Utility.TempFile
+import Utility.Tmp
writeUnusedLog :: FilePath -> [(Int, Key)] -> Annex ()
writeUnusedLog prefix l = do
diff --git a/Remote/Git.hs b/Remote/Git.hs
index 0cc4da40c..3f88a0334 100644
--- a/Remote/Git.hs
+++ b/Remote/Git.hs
@@ -35,7 +35,7 @@ import qualified Annex.Content
import qualified Annex.BranchState
import qualified Annex.Branch
import qualified Utility.Url as Url
-import Utility.TempFile
+import Utility.Tmp
import Config
import Config.Cost
import Init
@@ -179,7 +179,7 @@ tryGitConfigRead r
geturlconfig headers = do
s <- Url.get (Git.repoLocation r ++ "/config") headers
- withTempFile "git-annex.tmp" $ \tmpfile h -> do
+ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
hPutStr h s
hClose h
safely $ pipedconfig "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile]
diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs
index e048b3db8..9793f04e8 100644
--- a/Upgrade/V1.hs
+++ b/Upgrade/V1.hs
@@ -20,7 +20,7 @@ import qualified Git.LsFiles as LsFiles
import Backend
import Annex.Version
import Utility.FileMode
-import Utility.TempFile
+import Utility.Tmp
import qualified Upgrade.V2
-- v2 adds hashing of filenames of content and location log files.
diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs
index 935fc4825..b5de6c8c0 100644
--- a/Upgrade/V2.hs
+++ b/Upgrade/V2.hs
@@ -14,7 +14,7 @@ import qualified Git.Ref
import qualified Annex.Branch
import Logs.Location
import Annex.Content
-import Utility.TempFile
+import Utility.Tmp
olddir :: Git.Repo -> FilePath
olddir g
diff --git a/Utility/Directory.hs b/Utility/Directory.hs
index 599d41a03..9477ad5b9 100644
--- a/Utility/Directory.hs
+++ b/Utility/Directory.hs
@@ -18,7 +18,7 @@ import Control.Applicative
import System.IO.Unsafe (unsafeInterleaveIO)
import Utility.SafeCommand
-import Utility.TempFile
+import Utility.Tmp
import Utility.Exception
import Utility.Monad
diff --git a/Utility/TempFile.hs b/Utility/Tmp.hs
index 58d07c3a2..f03e4c0dc 100644
--- a/Utility/TempFile.hs
+++ b/Utility/Tmp.hs
@@ -1,11 +1,11 @@
-{- temp file functions
+{- Temporary files and directories.
-
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
-module Utility.TempFile where
+module Utility.Tmp where
import Control.Exception (bracket)
import System.IO
@@ -31,15 +31,15 @@ viaTmp a file content = do
{- Runs an action with a tmp file located in the system's tmp directory
- (or in "." if there is none) then removes the file. -}
-withTempFile :: Template -> (FilePath -> Handle -> IO a) -> IO a
-withTempFile template a = do
+withTmpFile :: Template -> (FilePath -> Handle -> IO a) -> IO a
+withTmpFile template a = do
tmpdir <- catchDefaultIO "." getTemporaryDirectory
- withTempFileIn tmpdir template a
+ withTmpFileIn tmpdir template a
{- Runs an action with a tmp file located in the specified directory,
- then removes the file. -}
-withTempFileIn :: FilePath -> Template -> (FilePath -> Handle -> IO a) -> IO a
-withTempFileIn tmpdir template a = bracket create remove use
+withTmpFileIn :: FilePath -> Template -> (FilePath -> Handle -> IO a) -> IO a
+withTmpFileIn tmpdir template a = bracket create remove use
where
create = openTempFile tmpdir template
remove (name, handle) = do
@@ -50,15 +50,15 @@ withTempFileIn tmpdir template a = bracket create remove use
{- Runs an action with a tmp directory located within the system's tmp
- directory (or within "." if there is none), then removes the tmp
- directory and all its contents. -}
-withTempDir :: Template -> (FilePath -> IO a) -> IO a
-withTempDir template a = do
+withTmpDir :: Template -> (FilePath -> IO a) -> IO a
+withTmpDir template a = do
tmpdir <- catchDefaultIO "." getTemporaryDirectory
- withTempDirIn tmpdir template a
+ withTmpDirIn tmpdir template a
{- Runs an action with a tmp directory located within a specified directory,
- then removes the tmp directory and all its contents. -}
-withTempDirIn :: FilePath -> Template -> (FilePath -> IO a) -> IO a
-withTempDirIn tmpdir template = bracket create remove
+withTmpDirIn :: FilePath -> Template -> (FilePath -> IO a) -> IO a
+withTmpDirIn tmpdir template = bracket create remove
where
remove d = whenM (doesDirectoryExist d) $
removeDirectoryRecursive d
diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs
index 0614384a1..762819b2f 100644
--- a/Utility/WebApp.hs
+++ b/Utility/WebApp.hs
@@ -10,7 +10,7 @@
module Utility.WebApp where
import Common
-import Utility.TempFile
+import Utility.Tmp
import Utility.FileMode
import qualified Yesod