squash build warnings on windows
This commit is contained in:
parent
06a80dc790
commit
804808d569
9 changed files with 10 additions and 10 deletions
|
@ -10,10 +10,10 @@
|
||||||
module Annex.PidLock where
|
module Annex.PidLock where
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import Annex.GitOverlay
|
|
||||||
import Git
|
import Git
|
||||||
import Git.Env
|
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
|
import Git.Env
|
||||||
|
import Annex.GitOverlay
|
||||||
import qualified Utility.LockFile.PidLock as PidF
|
import qualified Utility.LockFile.PidLock as PidF
|
||||||
import qualified Utility.LockPool.PidLock as PidP
|
import qualified Utility.LockPool.PidLock as PidP
|
||||||
import Utility.LockPool (dropLock)
|
import Utility.LockPool (dropLock)
|
||||||
|
|
|
@ -207,11 +207,13 @@ runAction repo action@(CommandAction {}) = liftIO $ do
|
||||||
where
|
where
|
||||||
gitparams = gitCommandLine
|
gitparams = gitCommandLine
|
||||||
(Param (getSubcommand action):getParams action) repo
|
(Param (getSubcommand action):getParams action) repo
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
go p (Just h) _ _ pid = do
|
go p (Just h) _ _ pid = do
|
||||||
hPutStr h $ intercalate "\0" $ toCommand $ getFiles action
|
hPutStr h $ intercalate "\0" $ toCommand $ getFiles action
|
||||||
hClose h
|
hClose h
|
||||||
forceSuccessProcess p pid
|
forceSuccessProcess p pid
|
||||||
go _ _ _ _ _ = error "internal"
|
go _ _ _ _ _ = error "internal"
|
||||||
|
#endif
|
||||||
runAction repo action@(InternalAction {}) =
|
runAction repo action@(InternalAction {}) =
|
||||||
let InternalActionRunner _ runner = getRunner action
|
let InternalActionRunner _ runner = getRunner action
|
||||||
in runner repo (getInternalFiles action)
|
in runner repo (getInternalFiles action)
|
||||||
|
|
|
@ -41,13 +41,11 @@ batch a = wait =<< batchthread
|
||||||
batchthread = asyncBound $ do
|
batchthread = asyncBound $ do
|
||||||
setProcessPriority 0 maxNice
|
setProcessPriority 0 maxNice
|
||||||
a
|
a
|
||||||
|
maxNice = 19
|
||||||
#else
|
#else
|
||||||
batch a = a
|
batch a = a
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
maxNice :: Int
|
|
||||||
maxNice = 19
|
|
||||||
|
|
||||||
{- Makes a command be run by whichever of nice, ionice, and nocache
|
{- Makes a command be run by whichever of nice, ionice, and nocache
|
||||||
- are available in the path. -}
|
- are available in the path. -}
|
||||||
type BatchCommandMaker = (String, [CommandParam]) -> (String, [CommandParam])
|
type BatchCommandMaker = (String, [CommandParam]) -> (String, [CommandParam])
|
||||||
|
|
|
@ -178,6 +178,7 @@ fromRawFilePath = decodeFilePath
|
||||||
toRawFilePath :: FilePath -> RawFilePath
|
toRawFilePath :: FilePath -> RawFilePath
|
||||||
toRawFilePath = encodeFilePath
|
toRawFilePath = encodeFilePath
|
||||||
|
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
{- Converts a [Word8] to a FilePath, encoding using the filesystem encoding.
|
{- Converts a [Word8] to a FilePath, encoding using the filesystem encoding.
|
||||||
-
|
-
|
||||||
- w82s produces a String, which may contain Chars that are invalid
|
- 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
|
decodeW8NUL = intercalate [c2w8 nul] . map decodeW8 . splitc nul
|
||||||
where
|
where
|
||||||
nul = '\NUL'
|
nul = '\NUL'
|
||||||
|
#endif
|
||||||
|
|
||||||
c2w8 :: Char -> Word8
|
c2w8 :: Char -> Word8
|
||||||
c2w8 = fromIntegral . fromEnum
|
c2w8 = fromIntegral . fromEnum
|
||||||
|
|
|
@ -332,6 +332,7 @@ genRandom cmd highQuality size = checksize <$> readStrict cmd params
|
||||||
testKeyId :: String
|
testKeyId :: String
|
||||||
testKeyId = "129D6E0AC537B9C7"
|
testKeyId = "129D6E0AC537B9C7"
|
||||||
|
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
testKey :: String
|
testKey :: String
|
||||||
testKey = keyBlock True
|
testKey = keyBlock True
|
||||||
[ "mI0ETvFAZgEEAKnqwWgZqznMhi1RQExem2H8t3OyKDxaNN3rBN8T6LWGGqAYV4wT"
|
[ "mI0ETvFAZgEEAKnqwWgZqznMhi1RQExem2H8t3OyKDxaNN3rBN8T6LWGGqAYV4wT"
|
||||||
|
@ -400,7 +401,6 @@ keyBlock public ls = unlines
|
||||||
| public = "PUBLIC"
|
| public = "PUBLIC"
|
||||||
| otherwise = "PRIVATE"
|
| otherwise = "PRIVATE"
|
||||||
|
|
||||||
#ifndef mingw32_HOST_OS
|
|
||||||
{- Runs an action using gpg in a test harness, in which gpg does
|
{- 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
|
- not use ~/.gpg/, but sets up the test key in a subdirectory of
|
||||||
- the passed directory and uses it.
|
- the passed directory and uses it.
|
||||||
|
|
|
@ -16,7 +16,6 @@ module Utility.LockFile.Windows (
|
||||||
import System.Win32.Types
|
import System.Win32.Types
|
||||||
import System.Win32.File
|
import System.Win32.File
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import System.FilePath.ByteString (RawFilePath)
|
|
||||||
|
|
||||||
import Utility.FileSystemEncoding
|
import Utility.FileSystemEncoding
|
||||||
|
|
||||||
|
|
|
@ -16,11 +16,11 @@ module Utility.MoveFile (
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.PosixCompat.Files
|
import System.PosixCompat.Files
|
||||||
import Control.Monad.IfElse
|
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
|
import Control.Monad.IfElse
|
||||||
import Utility.SafeCommand
|
import Utility.SafeCommand
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
|
@ -20,8 +20,8 @@ import System.IO
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import Control.Concurrent.Async
|
import Control.Concurrent.Async
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Exception
|
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
|
import Control.Exception
|
||||||
import qualified System.Posix.IO
|
import qualified System.Posix.IO
|
||||||
#else
|
#else
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
|
|
@ -46,7 +46,6 @@ createDirectory :: RawFilePath -> IO ()
|
||||||
createDirectory p = D.createDirectory p 0o777
|
createDirectory p = D.createDirectory p 0o777
|
||||||
|
|
||||||
#else
|
#else
|
||||||
import qualified Data.ByteString as B
|
|
||||||
import System.PosixCompat (FileStatus, FileMode)
|
import System.PosixCompat (FileStatus, FileMode)
|
||||||
import qualified System.PosixCompat as P
|
import qualified System.PosixCompat as P
|
||||||
import qualified System.PosixCompat.Files as F
|
import qualified System.PosixCompat.Files as F
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue