squash build warnings on windows

This commit is contained in:
Joey Hess 2020-11-23 14:00:17 -04:00
parent 06a80dc790
commit 804808d569
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
9 changed files with 10 additions and 10 deletions

View file

@ -10,10 +10,10 @@
module Annex.PidLock where
import Annex.Common
import Annex.GitOverlay
import Git
import Git.Env
#ifndef mingw32_HOST_OS
import Git.Env
import Annex.GitOverlay
import qualified Utility.LockFile.PidLock as PidF
import qualified Utility.LockPool.PidLock as PidP
import Utility.LockPool (dropLock)

View file

@ -207,11 +207,13 @@ runAction repo action@(CommandAction {}) = liftIO $ do
where
gitparams = gitCommandLine
(Param (getSubcommand action):getParams action) repo
#ifndef mingw32_HOST_OS
go p (Just h) _ _ pid = do
hPutStr h $ intercalate "\0" $ toCommand $ getFiles action
hClose h
forceSuccessProcess p pid
go _ _ _ _ _ = error "internal"
#endif
runAction repo action@(InternalAction {}) =
let InternalActionRunner _ runner = getRunner action
in runner repo (getInternalFiles action)

View file

@ -41,13 +41,11 @@ batch a = wait =<< batchthread
batchthread = asyncBound $ do
setProcessPriority 0 maxNice
a
maxNice = 19
#else
batch a = a
#endif
maxNice :: Int
maxNice = 19
{- Makes a command be run by whichever of nice, ionice, and nocache
- are available in the path. -}
type BatchCommandMaker = (String, [CommandParam]) -> (String, [CommandParam])

View file

@ -178,6 +178,7 @@ fromRawFilePath = decodeFilePath
toRawFilePath :: FilePath -> RawFilePath
toRawFilePath = encodeFilePath
#ifndef mingw32_HOST_OS
{- Converts a [Word8] to a FilePath, encoding using the filesystem encoding.
-
- w82s produces a String, which may contain Chars that are invalid
@ -206,6 +207,7 @@ decodeW8NUL :: FilePath -> [Word8]
decodeW8NUL = intercalate [c2w8 nul] . map decodeW8 . splitc nul
where
nul = '\NUL'
#endif
c2w8 :: Char -> Word8
c2w8 = fromIntegral . fromEnum

View file

@ -332,6 +332,7 @@ genRandom cmd highQuality size = checksize <$> readStrict cmd params
testKeyId :: String
testKeyId = "129D6E0AC537B9C7"
#ifndef mingw32_HOST_OS
testKey :: String
testKey = keyBlock True
[ "mI0ETvFAZgEEAKnqwWgZqznMhi1RQExem2H8t3OyKDxaNN3rBN8T6LWGGqAYV4wT"
@ -400,7 +401,6 @@ keyBlock public ls = unlines
| public = "PUBLIC"
| otherwise = "PRIVATE"
#ifndef mingw32_HOST_OS
{- Runs an action using gpg in a test harness, in which gpg does
- not use ~/.gpg/, but sets up the test key in a subdirectory of
- the passed directory and uses it.

View file

@ -16,7 +16,6 @@ module Utility.LockFile.Windows (
import System.Win32.Types
import System.Win32.File
import Control.Concurrent
import System.FilePath.ByteString (RawFilePath)
import Utility.FileSystemEncoding

View file

@ -16,11 +16,11 @@ module Utility.MoveFile (
import Control.Monad
import System.FilePath
import System.PosixCompat.Files
import Control.Monad.IfElse
import System.IO.Error
import Prelude
#ifndef mingw32_HOST_OS
import Control.Monad.IfElse
import Utility.SafeCommand
#endif

View file

@ -20,8 +20,8 @@ import System.IO
import System.Exit
import Control.Concurrent.Async
import Control.Monad
import Control.Exception
#ifndef mingw32_HOST_OS
import Control.Exception
import qualified System.Posix.IO
#else
import Control.Applicative

View file

@ -46,7 +46,6 @@ createDirectory :: RawFilePath -> IO ()
createDirectory p = D.createDirectory p 0o777
#else
import qualified Data.ByteString as B
import System.PosixCompat (FileStatus, FileMode)
import qualified System.PosixCompat as P
import qualified System.PosixCompat.Files as F