avoid more build warnings on Windows

This commit is contained in:
Joey Hess 2013-08-04 13:54:09 -04:00
parent fc96861084
commit a3224ce35b
12 changed files with 29 additions and 20 deletions

View file

@ -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

View file

@ -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.

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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.

View file

@ -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

View file

@ -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

View file

@ -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. -}

View file

@ -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