Merge branch 'windows' of git://git-annex.branchable.com into windows

This commit is contained in:
Joey Hess 2013-05-13 20:11:30 -05:00
commit 43f2de8522
31 changed files with 31 additions and 28 deletions

0
Annex/CatFile.hs Executable file → Normal file
View file

View file

@ -29,7 +29,7 @@ import Common.Annex
import qualified Annex import qualified Annex
import Annex.Perms import Annex.Perms
import qualified Git import qualified Git
import Utility.TempFile import Utility.Tmp
import Logs.Location import Logs.Location
import Utility.InodeCache import Utility.InodeCache

0
Annex/Journal.hs Executable file → Normal file
View file

0
Annex/Link.hs Executable file → Normal file
View file

View file

@ -9,7 +9,7 @@ module Assistant.DaemonStatus where
import Assistant.Common import Assistant.Common
import Assistant.Alert.Utility import Assistant.Alert.Utility
import Utility.TempFile import Utility.Tmp
import Assistant.Types.NetMessager import Assistant.Types.NetMessager
import Utility.NotificationBroadcaster import Utility.NotificationBroadcaster
import Logs.Transfer import Logs.Transfer

View file

@ -16,7 +16,7 @@ import Assistant.Ssh
import Config.Files import Config.Files
import Utility.FileMode import Utility.FileMode
import Utility.Shell import Utility.Shell
import Utility.TempFile import Utility.Tmp
import Utility.Env import Utility.Env
#ifdef darwin_HOST_OS #ifdef darwin_HOST_OS

View file

@ -8,7 +8,7 @@
module Assistant.Ssh where module Assistant.Ssh where
import Common.Annex import Common.Annex
import Utility.TempFile import Utility.Tmp
import Utility.UserInfo import Utility.UserInfo
import Utility.Shell import Utility.Shell
import Git.Remote import Git.Remote
@ -146,7 +146,7 @@ authorizedKeysLine rsynconly dir pubkey
{- Generates a ssh key pair. -} {- Generates a ssh key pair. -}
genSshKeyPair :: IO SshKeyPair genSshKeyPair :: IO SshKeyPair
genSshKeyPair = withTempDir "git-annex-keygen" $ \dir -> do genSshKeyPair = withTmpDir "git-annex-keygen" $ \dir -> do
ok <- boolSystem "ssh-keygen" ok <- boolSystem "ssh-keygen"
[ Param "-P", Param "" -- no password [ Param "-P", Param "" -- no password
, Param "-f", File $ dir </> "key" , Param "-f", File $ dir </> "key"

View file

@ -33,7 +33,7 @@ import Assistant.WebApp.Control
import Assistant.WebApp.OtherRepos import Assistant.WebApp.OtherRepos
import Assistant.Types.ThreadedMonad import Assistant.Types.ThreadedMonad
import Utility.WebApp import Utility.WebApp
import Utility.TempFile import Utility.Tmp
import Utility.FileMode import Utility.FileMode
import Git import Git
@ -74,7 +74,7 @@ webAppThread assistantdata urlrenderer noannex listenhost postfirstrun onstartup
, return app , return app
) )
runWebApp listenhost app' $ \addr -> if noannex runWebApp listenhost app' $ \addr -> if noannex
then withTempFile "webapp.html" $ \tmpfile _ -> then withTmpFile "webapp.html" $ \tmpfile _ ->
go addr webapp tmpfile Nothing go addr webapp tmpfile Nothing
else do else do
let st = threadState assistantdata let st = threadState assistantdata

View file

@ -26,6 +26,7 @@ import Types.StandardGroups
import System.IO.HVFS (SystemFS(..)) import System.IO.HVFS (SystemFS(..))
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Map as M import qualified Data.Map as M
import System.Path
notCurrentRepo :: UUID -> Handler RepHtml -> Handler RepHtml notCurrentRepo :: UUID -> Handler RepHtml -> Handler RepHtml
notCurrentRepo uuid a = go =<< liftAnnex (Remote.remoteFromUUID uuid) notCurrentRepo uuid a = go =<< liftAnnex (Remote.remoteFromUUID uuid)

0
Common.hs Executable file → Normal file
View file

View file

@ -8,7 +8,7 @@
module Config.Files where module Config.Files where
import Common import Common
import Utility.TempFile import Utility.Tmp
import Utility.FreeDesktop import Utility.FreeDesktop
{- ~/.config/git-annex/file -} {- ~/.config/git-annex/file -}

0
Git/CatFile.hs Executable file → Normal file
View file

0
Git/CheckAttr.hs Executable file → Normal file
View file

0
Git/FilePath.hs Executable file → Normal file
View file

0
Git/LsFiles.hs Executable file → Normal file
View file

0
Git/UpdateIndex.hs Executable file → Normal file
View file

View file

@ -16,7 +16,7 @@ module Init (
) where ) where
import Common.Annex import Common.Annex
import Utility.TempFile import Utility.Tmp
import Utility.Network import Utility.Network
import qualified Annex import qualified Annex
import qualified Git import qualified Git

0
Locations.hs Executable file → Normal file
View file

0
Logs/Presence.hs Executable file → Normal file
View file

View file

@ -19,7 +19,7 @@ import qualified Data.Map as M
import Common.Annex import Common.Annex
import Command import Command
import Types.Key import Types.Key
import Utility.TempFile import Utility.Tmp
writeUnusedLog :: FilePath -> [(Int, Key)] -> Annex () writeUnusedLog :: FilePath -> [(Int, Key)] -> Annex ()
writeUnusedLog prefix l = do writeUnusedLog prefix l = do

View file

@ -35,7 +35,7 @@ import qualified Annex.Content
import qualified Annex.BranchState import qualified Annex.BranchState
import qualified Annex.Branch import qualified Annex.Branch
import qualified Utility.Url as Url import qualified Utility.Url as Url
import Utility.TempFile import Utility.Tmp
import Config import Config
import Config.Cost import Config.Cost
import Init import Init
@ -179,7 +179,7 @@ tryGitConfigRead r
geturlconfig headers = do geturlconfig headers = do
s <- Url.get (Git.repoLocation r ++ "/config") headers 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 hPutStr h s
hClose h hClose h
safely $ pipedconfig "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile] safely $ pipedconfig "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile]

View file

@ -16,6 +16,7 @@ import Control.Exception.Extensible
import qualified Data.Map as M import qualified Data.Map as M
import System.IO.HVFS (SystemFS(..)) import System.IO.HVFS (SystemFS(..))
import qualified Text.JSON import qualified Text.JSON
import System.Path
import Common import Common

View file

@ -20,7 +20,7 @@ import qualified Git.LsFiles as LsFiles
import Backend import Backend
import Annex.Version import Annex.Version
import Utility.FileMode import Utility.FileMode
import Utility.TempFile import Utility.Tmp
import qualified Upgrade.V2 import qualified Upgrade.V2
-- v2 adds hashing of filenames of content and location log files. -- v2 adds hashing of filenames of content and location log files.

View file

@ -14,7 +14,7 @@ import qualified Git.Ref
import qualified Annex.Branch import qualified Annex.Branch
import Logs.Location import Logs.Location
import Annex.Content import Annex.Content
import Utility.TempFile import Utility.Tmp
olddir :: Git.Repo -> FilePath olddir :: Git.Repo -> FilePath
olddir g olddir g

View file

@ -18,7 +18,7 @@ import Control.Applicative
import System.IO.Unsafe (unsafeInterleaveIO) import System.IO.Unsafe (unsafeInterleaveIO)
import Utility.SafeCommand import Utility.SafeCommand
import Utility.TempFile import Utility.Tmp
import Utility.Exception import Utility.Exception
import Utility.Monad import Utility.Monad

0
Utility/Env.hs Executable file → Normal file
View file

View file

@ -13,6 +13,7 @@ import System.Posix.Types
import Control.Applicative import Control.Applicative
import Control.Concurrent import Control.Concurrent
import Control.Exception (bracket) import Control.Exception (bracket)
import System.Path
import Common import Common
import Utility.Env import Utility.Env

0
Utility/Path.hs Executable file → Normal file
View file

24
Utility/TempFile.hs → Utility/Tmp.hs Executable file → Normal file
View file

@ -1,11 +1,11 @@
{- temp file functions {- Temporary files and directories.
- -
- Copyright 2010-2013 Joey Hess <joey@kitenet.net> - Copyright 2010-2013 Joey Hess <joey@kitenet.net>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Utility.TempFile where module Utility.Tmp where
import Control.Exception (bracket) import Control.Exception (bracket)
import System.IO 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 {- Runs an action with a tmp file located in the system's tmp directory
- (or in "." if there is none) then removes the file. -} - (or in "." if there is none) then removes the file. -}
withTempFile :: Template -> (FilePath -> Handle -> IO a) -> IO a withTmpFile :: Template -> (FilePath -> Handle -> IO a) -> IO a
withTempFile template a = do withTmpFile template a = do
tmpdir <- catchDefaultIO "." getTemporaryDirectory tmpdir <- catchDefaultIO "." getTemporaryDirectory
withTempFileIn tmpdir template a withTmpFileIn tmpdir template a
{- Runs an action with a tmp file located in the specified directory, {- Runs an action with a tmp file located in the specified directory,
- then removes the file. -} - then removes the file. -}
withTempFileIn :: FilePath -> Template -> (FilePath -> Handle -> IO a) -> IO a withTmpFileIn :: FilePath -> Template -> (FilePath -> Handle -> IO a) -> IO a
withTempFileIn tmpdir template a = bracket create remove use withTmpFileIn tmpdir template a = bracket create remove use
where where
create = openTempFile tmpdir template create = openTempFile tmpdir template
remove (name, handle) = do 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 {- 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 (or within "." if there is none), then removes the tmp
- directory and all its contents. -} - directory and all its contents. -}
withTempDir :: Template -> (FilePath -> IO a) -> IO a withTmpDir :: Template -> (FilePath -> IO a) -> IO a
withTempDir template a = do withTmpDir template a = do
tmpdir <- catchDefaultIO "." getTemporaryDirectory tmpdir <- catchDefaultIO "." getTemporaryDirectory
withTempDirIn tmpdir template a withTmpDirIn tmpdir template a
{- Runs an action with a tmp directory located within a specified directory, {- Runs an action with a tmp directory located within a specified directory,
- then removes the tmp directory and all its contents. -} - then removes the tmp directory and all its contents. -}
withTempDirIn :: FilePath -> Template -> (FilePath -> IO a) -> IO a withTmpDirIn :: FilePath -> Template -> (FilePath -> IO a) -> IO a
withTempDirIn tmpdir template = bracket create remove withTmpDirIn tmpdir template = bracket create remove
where where
remove d = whenM (doesDirectoryExist d) $ remove d = whenM (doesDirectoryExist d) $
removeDirectoryRecursive d removeDirectoryRecursive d

0
Utility/UserInfo.hs Executable file → Normal file
View file

View file

@ -10,7 +10,7 @@
module Utility.WebApp where module Utility.WebApp where
import Common import Common
import Utility.TempFile import Utility.Tmp
import Utility.FileMode import Utility.FileMode
import qualified Yesod import qualified Yesod