aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex/Content.hs2
-rw-r--r--Annex/Environment.hs5
-rw-r--r--Annex/Journal.hs3
-rw-r--r--Git/CatFile.hs4
-rw-r--r--Git/CurrentRepo.hs6
-rw-r--r--Logs/Transfer.hs3
-rw-r--r--Remote/Helper/Hooks.hs4
-rw-r--r--Utility/Daemon.hs3
-rw-r--r--Utility/Gpg.hs12
-rw-r--r--Utility/LogFile.hs2
-rw-r--r--Utility/Misc.hs3
-rw-r--r--Utility/Process.hs2
12 files changed, 29 insertions, 20 deletions
diff --git a/Annex/Content.hs b/Annex/Content.hs
index 0b3e18fab..01ad6f96f 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -120,7 +120,7 @@ inAnnexSafe = inAnnex' (fromMaybe False) (Just False) go
- it. (If the content is not present, no locking is done.) -}
lockContent :: Key -> Annex a -> Annex a
#ifndef mingw32_HOST_OS
-lockContent key a =
+lockContent key a = do
file <- calcRepo $ gitAnnexLocation key
bracketIO (openforlock file >>= lock) unlock (const a)
where
diff --git a/Annex/Environment.hs b/Annex/Environment.hs
index ce9c33ad6..ae5a5646f 100644
--- a/Annex/Environment.hs
+++ b/Annex/Environment.hs
@@ -10,12 +10,15 @@
module Annex.Environment where
import Common.Annex
-import Utility.Env
import Utility.UserInfo
import qualified Git.Config
import Config
import Annex.Exception
+#ifndef mingw32_HOST_OS
+import Utility.Env
+#endif
+
{- Checks that the system's environment allows git to function.
- Git requires a GECOS username, or suitable git configuration, or
- environment variables.
diff --git a/Annex/Journal.hs b/Annex/Journal.hs
index 506cbfcaf..fff20ccc4 100644
--- a/Annex/Journal.hs
+++ b/Annex/Journal.hs
@@ -86,12 +86,13 @@ lockJournal a = do
mode <- annexFileMode
bracketIO (lock lockfile mode) unlock (const a)
where
- lock lockfile mode = do
#ifndef mingw32_HOST_OS
+ lock lockfile mode = do
l <- noUmask mode $ createFile lockfile mode
waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
return l
#else
+ lock lockfile _mode = do
writeFile lockfile ""
return lockfile
#endif
diff --git a/Git/CatFile.hs b/Git/CatFile.hs
index f779e99c6..46b59c631 100644
--- a/Git/CatFile.hs
+++ b/Git/CatFile.hs
@@ -93,10 +93,10 @@ catObjectDetails (CatFileHandle hdl repo) object = CoProcess.query hdl send rece
, Param "-p"
, Param query
] repo
- (_, Just h, _, pid) <- withNullHandle $ \null ->
+ (_, Just h, _, pid) <- withNullHandle $ \h ->
createProcess p
{ std_out = CreatePipe
- , std_err = UseHandle null
+ , std_err = UseHandle h
}
fileEncoding h
content <- L.hGetContents h
diff --git a/Git/CurrentRepo.hs b/Git/CurrentRepo.hs
index 777caa981..ee91a6b81 100644
--- a/Git/CurrentRepo.hs
+++ b/Git/CurrentRepo.hs
@@ -13,7 +13,9 @@ import Common
import Git.Types
import Git.Construct
import qualified Git.Config
+#ifndef mingw32_HOST_OS
import Utility.Env
+#endif
{- Gets the current git repository.
-
@@ -40,8 +42,8 @@ get = do
setCurrentDirectory d
return $ addworktree wt r
where
- pathenv s = do
#ifndef mingw32_HOST_OS
+ pathenv s = do
v <- getEnv s
case v of
Just d -> do
@@ -49,7 +51,7 @@ get = do
Just <$> absPath d
Nothing -> return Nothing
#else
- return Nothing
+ pathenv _ = return Nothing
#endif
configure Nothing (Just r) = Git.Config.read r
diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs
index b9084b78a..13f94ea20 100644
--- a/Logs/Transfer.hs
+++ b/Logs/Transfer.hs
@@ -129,8 +129,8 @@ runTransfer t file shouldretry a = do
unless ok $ recordFailedTransfer t info
return ok
where
- prep tfile mode info = do
#ifndef mingw32_HOST_OS
+ prep tfile mode info = do
mfd <- catchMaybeIO $
openFd (transferLockFile tfile) ReadWrite (Just mode)
defaultFileFlags { trunc = True }
@@ -145,6 +145,7 @@ runTransfer t file shouldretry a = do
void $ tryIO $ writeTransferInfoFile info tfile
return (mfd, False)
#else
+ prep tfile _mode info = do
mfd <- catchMaybeIO $ do
writeFile (transferLockFile tfile) ""
writeTransferInfoFile info tfile
diff --git a/Remote/Helper/Hooks.hs b/Remote/Helper/Hooks.hs
index 96081b024..7c2bf68ca 100644
--- a/Remote/Helper/Hooks.hs
+++ b/Remote/Helper/Hooks.hs
@@ -73,8 +73,8 @@ runHooks r starthook stophook a = do
run starthook
Annex.addCleanup (remoteid ++ "-stop-command") $ runstop lck
- runstop lck = do
#ifndef __WINDOWS__
+ runstop lck = do
-- Drop any shared lock we have, and take an
-- exclusive lock, without blocking. If the lock
-- succeeds, we're the only process using this remote,
@@ -90,5 +90,5 @@ runHooks r starthook stophook a = do
Right _ -> run stophook
liftIO $ closeFd fd
#else
- run stophook
+ runstop _lck = run stophook
#endif
diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs
index 124005795..2f942769a 100644
--- a/Utility/Daemon.hs
+++ b/Utility/Daemon.hs
@@ -10,13 +10,14 @@
module Utility.Daemon where
import Common
+#ifndef mingw32_HOST_OS
import Utility.LogFile
+#endif
#ifndef mingw32_HOST_OS
import System.Posix
#else
import System.PosixCompat
-import System.Posix.Types
#endif
{- Run an action as a daemon, with all output sent to a file descriptor.
diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs
index b06ea2fd1..81180148e 100644
--- a/Utility/Gpg.hs
+++ b/Utility/Gpg.hs
@@ -9,16 +9,18 @@
module Utility.Gpg where
-import System.Posix.Types
import Control.Applicative
import Control.Concurrent
-import Control.Exception (bracket)
-import System.Path
import Common
-import Utility.Env
import qualified Build.SysConfig as SysConfig
-#ifdef mingw32_HOST_OS
+
+#ifndef mingw32_HOST_OS
+import System.Posix.Types
+import Control.Exception (bracket)
+import System.Path
+import Utility.Env
+#else
import Utility.Tmp
#endif
diff --git a/Utility/LogFile.hs b/Utility/LogFile.hs
index 25f2e10fe..090ac60d0 100644
--- a/Utility/LogFile.hs
+++ b/Utility/LogFile.hs
@@ -58,8 +58,8 @@ redirLog logfd = do
redirLog _ = error "redirLog TODO"
#endif
-#ifndef mingw32_HOST_OS
redir :: Fd -> Fd -> IO ()
+#ifndef mingw32_HOST_OS
redir newh h = do
closeFd h
void $ dupTo newh h
diff --git a/Utility/Misc.hs b/Utility/Misc.hs
index 39d0e3de0..804a9e487 100644
--- a/Utility/Misc.hs
+++ b/Utility/Misc.hs
@@ -17,9 +17,8 @@ import Data.List
import Control.Applicative
#ifndef mingw32_HOST_OS
import System.Posix.Process (getAnyProcessStatus)
-#endif
-
import Utility.Exception
+#endif
{- A version of hgetContents that is not lazy. Ensures file is
- all read before it gets closed. -}
diff --git a/Utility/Process.hs b/Utility/Process.hs
index 590124289..8ea632120 100644
--- a/Utility/Process.hs
+++ b/Utility/Process.hs
@@ -42,9 +42,9 @@ import System.Log.Logger
import Control.Concurrent
import qualified Control.Exception as E
import Control.Monad
-import Data.Maybe
#ifndef mingw32_HOST_OS
import System.Posix.IO
+import Data.Maybe
#endif
import Utility.Misc