OsPath transition Windows build fixes
authorJoey Hess <id@joeyh.name>
Wed, 12 Feb 2025 03:23:02 +0000 (19:23 -0800)
committerJoey Hess <joeyh@joeyh.name>
Tue, 11 Feb 2025 19:40:53 +0000 (15:40 -0400)
This gets it building on Windows again, with 1 test suite failure
(addurl).

Sponsored-by: Kevin Mueller
23 files changed:
Annex/Link.hs
Annex/Proxy.hs
Assistant.hs
Build/NullSoftInstaller.hs
Git/Remote.hs
Remote/Directory.hs
Test.hs
Utility/Daemon.hs
Utility/DirWatcher.hs
Utility/DirWatcher/Win32Notify.hs
Utility/Directory/Stream.hs
Utility/FileIO.hs
Utility/FileSize.hs
Utility/Gpg.hs
Utility/LockFile/Windows.hs
Utility/MoveFile.hs
Utility/Path.hs
Utility/RawFilePath.hs
Utility/Rsync.hs
Utility/Shell.hs
Utility/StatelessOpenPGP.hs
Utility/Tmp.hs
Utility/Tmp/Dir.hs

index 2f22143dd8bb06d63cecf2a0188785e945daef0e..5ed296007b497e5ddf7b9cd68bac721ac58f738b 100644 (file)
@@ -468,12 +468,13 @@ isPointerFile f = catchDefaultIO Nothing $
  - than .git to be used.
  -}
 isLinkToAnnex :: S.ByteString -> Bool
-isLinkToAnnex s = p `OS.isInfixOf` (toOsPath s)
+isLinkToAnnex s = p `OS.isInfixOf` s'
 #ifdef mingw32_HOST_OS
        -- '/' is used inside pointer files on Windows, not the native '\'
-       || p' `OS.isInfixOf` s
+       || p' `OS.isInfixOf` s'
 #endif
   where
+       s' = toOsPath s
        p = pathSeparator `OS.cons` objectDir
 #ifdef mingw32_HOST_OS
        p' = toInternalGitPath p
index d6c3fe8f12e346646f514e731a374cd9fd2bcbad..d34c5ef600821a84f6a6bc29302a5aafa94fd945 100644 (file)
@@ -36,7 +36,9 @@ import qualified Utility.FileIO as F
 import Utility.OpenFile
 #endif
 
+#ifndef mingw32_HOST_OS
 import Control.Concurrent
+#endif
 import Control.Concurrent.STM
 import Control.Concurrent.Async
 import qualified Data.ByteString as B
index 41553c6949a00326c74a25e4022b747a225467df..3ad89269601da10627ee5a6cdf4ed7520d7dda9a 100644 (file)
@@ -105,7 +105,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost listenport star
                        ( liftIO $ withNullHandle $ \nullh -> do
                                loghandle <- openLog (fromOsPath logfile)
                                e <- getEnvironment
-                               cmd <- programPath
+                               cmd <- fromOsPath <$> programPath
                                ps <- getArgs
                                let p = (proc cmd ps)
                                        { env = Just (addEntry flag "1" e)
@@ -116,7 +116,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost listenport star
                                exitcode <- withCreateProcess p $ \_ _ _ pid ->
                                        waitForProcess pid
                                exitWith exitcode
-                       , start (Utility.Daemon.foreground (Just (fromOsPath pidfile))) $
+                       , start (Utility.Daemon.foreground (Just pidfile)) $
                                case startbrowser of
                                        Nothing -> Nothing
                                        Just a -> Just $ a Nothing Nothing
index ca209076d39a319c60ab6b4ce92076aa567d9180..8241ff8dd861f596675565560a852449224d5d5c 100644 (file)
@@ -16,7 +16,7 @@
  - A build of libmagic will also be included in the installer, if its files\r
  - are found in the current directory: \r
  -   ./magic.mgc ./libmagic-1.dll ./libgnurx-0.dll\r
- - To build git-annex to usse libmagic, it has to be built with the\r
+ - To build git-annex to use libmagic, it has to be built with the\r
  - magicmime build flag turned on.\r
  -\r
  - Copyright 2013-2020 Joey Hess <id@joeyh.name>\r
@@ -27,7 +27,6 @@
 {-# LANGUAGE OverloadedStrings, FlexibleContexts #-}\r
 \r
 import Development.NSIS\r
-import System.FilePath\r
 import Control.Monad\r
 import Control.Applicative\r
 import Data.String\r
@@ -42,27 +41,29 @@ import Utility.SafeCommand
 import Utility.Process\r
 import Utility.Exception\r
 import Utility.Directory\r
+import Utility.SystemDirectory\r
+import Utility.OsPath\r
 import Build.BundledPrograms\r
 \r
 main = do\r
        withTmpDir "nsis-build" $ \tmpdir -> do\r
-               let gitannex = tmpdir </> gitannexprogram\r
+               let gitannex = fromOsPath $ tmpdir </> toOsPath gitannexprogram\r
                mustSucceed "ln" [File "git-annex.exe", File gitannex]\r
                magicDLLs' <- installwhenpresent magicDLLs tmpdir\r
                magicShare' <- installwhenpresent magicShare tmpdir\r
-               let license = tmpdir </> licensefile\r
+               let license = fromOsPath $ tmpdir </> toOsPath licensefile\r
                mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"]\r
                webappscript <- vbsLauncher tmpdir "git-annex-webapp" "git annex webapp"\r
                autostartscript <- vbsLauncher tmpdir "git-annex-autostart" "git annex assistant --autostart"\r
-               let htmlhelp = tmpdir </> "git-annex.html"\r
+               let htmlhelp = fromOsPath $ tmpdir </> literalOsPath "git-annex.html"\r
                writeFile htmlhelp htmlHelpText\r
-               let gitannexcmd = tmpdir </> "git-annex.cmd"\r
+               let gitannexcmd = fromOsPath $ tmpdir </> literalOsPath "git-annex.cmd"\r
                writeFile gitannexcmd "git annex %*"\r
                writeFile nsifile $ makeInstaller\r
                        gitannex gitannexcmd license htmlhelp (winPrograms ++ magicDLLs') magicShare'\r
                        [ webappscript, autostartscript ]\r
                mustSucceed "makensis" [File nsifile]\r
-       removeFile nsifile -- left behind if makensis fails\r
+       removeFile (toOsPath nsifile) -- left behind if makensis fails\r
   where\r
        nsifile = "git-annex.nsi"\r
        mustSucceed cmd params = do\r
@@ -72,19 +73,19 @@ main = do
                        False -> error $ cmd ++ " failed"\r
        installwhenpresent fs tmpdir = do\r
                fs' <- forM fs $ \f -> do\r
-                       present <- doesFileExist f\r
+                       present <- doesFileExist (toOsPath f)\r
                        if present\r
                                then do\r
-                                       mustSucceed "ln" [File f, File (tmpdir </> f)]\r
+                                       mustSucceed "ln" [File f, File (fromOsPath (tmpdir </> toOsPath f))]\r
                                        return (Just f)\r
                                else return Nothing\r
                return (catMaybes fs')\r
 \r
 {- Generates a .vbs launcher which runs a command without any visible DOS\r
  - box. It expects to be passed the directory where git-annex is installed. -}\r
-vbsLauncher :: FilePath -> String -> String -> IO String\r
+vbsLauncher :: OsPath -> String -> String -> IO String\r
 vbsLauncher tmpdir basename cmd = do\r
-       let f = tmpdir </> basename ++ ".vbs"\r
+       let f = fromOsPath $ tmpdir </> toOsPath (basename ++ ".vbs")\r
        writeFile f $ unlines\r
                [ "Set objshell=CreateObject(\"Wscript.Shell\")"\r
                , "objShell.CurrentDirectory = Wscript.Arguments.item(0)"\r
@@ -207,7 +208,7 @@ makeInstaller gitannex gitannexcmd license htmlhelp extrabins sharefiles launche
                removefilesFrom "$INSTDIR" [license, uninstaller]\r
   where\r
        addfile f = file [] (str f)\r
-       removefilesFrom d = mapM_ (\f -> delete [RebootOK] $ fromString $ d ++ "/" ++ takeFileName f)\r
+       removefilesFrom d = mapM_ (\f -> delete [RebootOK] $ fromString $ d ++ "/" ++ fromOsPath (takeFileName (toOsPath f)))\r
 \r
 winPrograms :: [FilePath]\r
 winPrograms = map (\p -> p ++ ".exe") bundledPrograms\r
index b09aee66436cfc2ecab76f9d50dd93e2cfb3e6bf..eb4d78e88ded88387f57fd6f5e4079c9563b89d7 100644 (file)
@@ -122,8 +122,8 @@ parseRemoteLocation s knownurl repo = go
 #ifdef mingw32_HOST_OS
        -- git on Windows will write a path to .git/config with "drive:",
        -- which is not to be confused with a "host:"
-       dosstyle = hasDrive
-       dospath = fromRawFilePath . fromInternalGitPath . toRawFilePath
+       dosstyle = hasDrive . toOsPath
+       dospath = fromOsPath . fromInternalGitPath . toOsPath
 #endif
 
 insteadOfUrl :: String -> S.ByteString -> RepoFullConfig -> Maybe String
index 6acaf251f6a71dfa0d8f8c942aab630470b4a24e..75e003d5a1612963ae3187b7518dc38325788e81 100644 (file)
@@ -480,7 +480,7 @@ retrieveExportWithContentIdentifierM ii dir cow loc cids dest gk p =
                        closeFd dupfd
                bracketIO open close $ \(h, dupfd) -> do
 #else
-               let open = openBinaryFile f' ReadMode
+               let open = F.openBinaryFile f ReadMode
                let close = hClose
                bracketIO open close $ \h -> do
 #endif
diff --git a/Test.hs b/Test.hs
index b66dd9b78e02713569201855469de806829be997..0032e855e03f951c624380ab1bfd110994584789 100644 (file)
--- a/Test.hs
+++ b/Test.hs
@@ -88,9 +88,9 @@ import qualified Utility.Aeson
 import qualified Utility.CopyFile
 import qualified Utility.MoveFile
 import qualified Utility.StatelessOpenPGP
-import qualified Utility.OsString as OS
 import qualified Types.Remote
 #ifndef mingw32_HOST_OS
+import qualified Utility.OsString as OS
 import qualified Remote.Helper.Encryptable
 import qualified Types.Crypto
 import qualified Utility.Gpg
index 8fd142da363fb76762ca76b48a0a777059fb81f6..6d5ea6c0bf9484155d7981b74c15ec2dc7af3f65 100644 (file)
@@ -158,7 +158,7 @@ checkDaemon pidfile = maybe (return Nothing) (check . readish)
   where
        check Nothing = return Nothing
        check (Just pid) = do
-               v <- lockShared =<< winLockFile pid (fromOsPath pidfile)
+               v <- lockShared =<< winLockFile pid pidfile
                case v of
                        Just h -> do
                                dropLock h
index f0805aa2c0a1479a85358566b4ceceb59dcca185..d7573d747591250fa5b0d9bcb1635b002dfb1e03 100644 (file)
@@ -134,7 +134,7 @@ watchDir dir prune scanevents hooks runstartup =
 #else
 #if WITH_WIN32NOTIFY
 type DirWatcherHandle = Win32Notify.WatchManager
-watchDir :: FilePath -> Pruner -> Bool -> WatchHooks -> (IO Win32Notify.WatchManager -> IO Win32Notify.WatchManager) -> IO DirWatcherHandle
+watchDir :: OsPath -> Pruner -> Bool -> WatchHooks -> (IO Win32Notify.WatchManager -> IO Win32Notify.WatchManager) -> IO DirWatcherHandle
 watchDir dir prune scanevents hooks runstartup =
        runstartup $ Win32Notify.watchDir dir prune scanevents hooks
 #else
index 5f53c13bf5b6fbd3a7006da8906d9aa60b8694d9..3291f4a77ae8099405ace2808dbcf4c26dafd81a 100644 (file)
@@ -14,15 +14,15 @@ import qualified Utility.RawFilePath as R
 import System.Win32.Notify
 import System.PosixCompat.Files (isRegularFile)
 
-watchDir :: FilePath -> (FilePath -> Bool) -> Bool -> WatchHooks -> IO WatchManager
+watchDir :: OsPath -> (OsPath -> Bool) -> Bool -> WatchHooks -> IO WatchManager
 watchDir dir ignored scanevents hooks = do
        scan dir
        wm <- initWatchManager
-       void $ watchDirectory wm dir True [Create, Delete, Modify, Move] dispatch
+       void $ watchDirectory wm (fromOsPath dir) True [Create, Delete, Modify, Move] dispatch
        return wm
   where
        dispatch evt
-               | ignoredPath ignored (filePath evt) = noop
+               | ignoredPath ignored (toOsPath (filePath evt)) = noop
                | otherwise = case evt of
                        (Deleted _ _)
                                | isDirectory evt -> runhook delDirHook Nothing
@@ -40,11 +40,11 @@ watchDir dir ignored scanevents hooks = do
                                        runhook addHook Nothing
                                        runhook modifyHook Nothing
          where
-               runhook h s = maybe noop (\a -> a (filePath evt) s) (h hooks)
+               runhook h s = maybe noop (\a -> a (toOsPath (filePath evt)) s) (h hooks)
 
        scan d = unless (ignoredPath ignored d) $
-               mapM_ (go . fromRawFilePath) =<< emptyWhenDoesNotExist
-                       (dirContentsRecursiveSkipping (const False) False (toRawFilePath d))
+               mapM_ go =<< emptyWhenDoesNotExist
+                       (dirContentsRecursiveSkipping (const False) False d)
          where         
                go f
                        | ignoredPath ignored f = noop
@@ -61,8 +61,8 @@ watchDir dir ignored scanevents hooks = do
                  where
                        runhook h s = maybe noop (\a -> a f s) (h hooks)
                
-       getstatus = catchMaybeIO . R.getFileStatus . toRawFilePath
+       getstatus = catchMaybeIO . R.getFileStatus . fromOsPath
 
 {- Check each component of the path to see if it's ignored. -}
-ignoredPath :: (FilePath -> Bool) -> FilePath -> Bool
+ignoredPath :: (OsPath -> Bool) -> OsPath -> Bool
 ignoredPath ignored = any ignored . map dropTrailingPathSeparator . splitPath
index 2dd975955c052c654629dca0cff199565c6d52cb..8ae6b32e4062995ef18e75f6d2ea0078c85d58fc 100644 (file)
@@ -7,6 +7,7 @@
 
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
 {-# OPTIONS_GHC -fno-warn-tabs #-}
 
 module Utility.Directory.Stream (
@@ -24,7 +25,6 @@ import Prelude
 
 #ifdef mingw32_HOST_OS
 import qualified System.Win32 as Win32
-import System.FilePath
 #else
 import qualified Data.ByteString as B
 import qualified System.Posix.Directory.ByteString as Posix
@@ -50,7 +50,7 @@ openDirectory path = do
        isopen <- newMVar ()
        return (DirectoryHandle isopen dirp)
 #else
-       (h, fdat) <- Win32.findFirstFile (fromRawFilePath path </> "*")
+       (h, fdat) <- Win32.findFirstFile (fromOsPath (toOsPath path </> literalOsPath "*"))
        -- Indicate that the fdat contains a filename that readDirectory
        -- has not yet returned, by making the MVar be full.
        -- (There's always at least a "." entry.)
index e0cd546a286309f7cf60151d5e22a023aa86baf3..f10cb20ffcb56f44849ac1c64105862b833e66ac 100644 (file)
@@ -37,7 +37,6 @@ import System.File.OsPath
 -- https://github.com/haskell/file-io/issues/39
 import Utility.Path.Windows
 import Utility.OsPath
-import System.OsPath
 import System.IO (IO, Handle, IOMode)
 import Prelude (return)
 import qualified System.File.OsPath as O
index e275771d052b15c659afdbe3bc656b91d10e1dd0..36f37889a62dbd58d0bd23d6f7f5b407807947b7 100644 (file)
@@ -18,12 +18,11 @@ module Utility.FileSize (
 import Control.Exception (bracket)
 import System.IO
 import qualified Utility.FileIO as F
-import Utility.OsPath
 #else
 import System.PosixCompat.Files (fileSize)
+import qualified Utility.RawFilePath as R
 #endif
 import System.PosixCompat.Files (FileStatus)
-import qualified Utility.RawFilePath as R
 import Utility.OsPath
 
 type FileSize = Integer
index 781b9a4a586090eee6a83404096864d84a164930..6c13392032aa3143829d4e1f69ff30be14c6534a 100644 (file)
@@ -179,7 +179,7 @@ feedRead cmd params passphrase feeder reader = do
                go (passphrasefd ++ params)
 #else
        -- store the passphrase in a temp file for gpg
-       withTmpFile (toOsPath "gpg") $ \tmpfile h -> do
+       withTmpFile (literalOsPath "gpg") $ \tmpfile h -> do
                liftIO $ B.hPutStr h passphrase
                liftIO $ hClose h
                let passphrasefile = [Param "--passphrase-file", File (fromOsPath tmpfile)]
index 8e6c6d290522cb9ac342e8f1c0131d225c944f60..9b2248c0a8d424e5116ff937a02e5cbff9bac876 100644 (file)
@@ -21,11 +21,12 @@ import Control.Concurrent
 
 import Utility.Path.Windows
 import Utility.FileSystemEncoding
+import Utility.OsPath
 #if MIN_VERSION_Win32(2,13,4)
 import Common (tryNonAsync)
 #endif
 
-type LockFile = RawFilePath
+type LockFile = OsPath
 
 type LockHandle = HANDLE
 
@@ -60,7 +61,7 @@ lockExclusive = openLock fILE_SHARE_NONE
  -}
 openLock :: ShareMode -> LockFile -> IO (Maybe LockHandle)
 openLock sharemode f = do
-       f' <- convertToWindowsNativeNamespace f
+       f' <- convertToWindowsNativeNamespace (fromOsPath f)
 #if MIN_VERSION_Win32(2,13,4)
        r <- tryNonAsync $ createFile_NoRetry (fromRawFilePath f') gENERIC_READ sharemode 
                Nothing oPEN_ALWAYS fILE_ATTRIBUTE_NORMAL
index 7bc029753213eff51fa40f11410784c68793e620..54e156920bb94bf55c2c1e5a84f667a76ec70d1e 100644 (file)
@@ -21,6 +21,7 @@ import Prelude
 import System.PosixCompat.Files (isDirectory)
 import Control.Monad.IfElse
 import Utility.SafeCommand
+import qualified Utility.RawFilePath as R
 #endif
 
 import Utility.SystemDirectory
@@ -28,7 +29,6 @@ import Utility.Tmp
 import Utility.Exception
 import Utility.Monad
 import Utility.OsPath
-import qualified Utility.RawFilePath as R
 import Author
 
 {- Moves one filename to another.
index da30b2f9173acfc1140a775782237be0ccf98d67..18abcb250d29d3442e506d0be179f54ce5528ea8 100644 (file)
@@ -43,7 +43,6 @@ import qualified Utility.OsString as OS
 
 #ifdef mingw32_HOST_OS
 import Data.Char
-import Utility.FileSystemEncoding
 #endif
 
 copyright :: Authored t => t
@@ -230,11 +229,11 @@ relPathDirToFileAbs from to
        numcommon = length common
 #ifdef mingw32_HOST_OS
        normdrive = map toLower
+               . fromOsPath
                -- Get just the drive letter, removing any leading
                -- path separator, which takeDrive leaves on the drive
                -- letter.
-               . dropWhileEnd (isPathSeparator . fromIntegral . ord)
-               . fromOsPath 
+               . OS.dropWhileEnd isPathSeparator
                . takeDrive
 #endif
 
@@ -261,7 +260,7 @@ searchPath command
        indir d = check (d </> command')
        check f = firstM doesFileExist
 #ifdef mingw32_HOST_OS
-               [f, f <> ".exe"]
+               [f, f <> literalOsPath ".exe"]
 #else
                [f]
 #endif
index e10f05d703b6bb304435c98b645fdcb5b20f4f37..33d69230ac29f9ccab6d30842c00cf880c4b670e 100644 (file)
@@ -60,11 +60,6 @@ createLink a b = do
        b' <- fromRawFilePath <$> convertToWindowsNativeNamespace b
        P.createLink a' b'
 
-{- On windows, removeLink is not available, so only remove files,
- - not symbolic links. -}
-removeLink :: RawFilePath -> IO ()
-removeLink = D.removeFile . fromRawFilePath
-
 getFileStatus :: RawFilePath -> IO FileStatus
 getFileStatus p = P.getFileStatus . fromRawFilePath
        =<< convertToWindowsNativeNamespace p
index e377eb965dc999d490af6a204295c4ff5599f35a..1a35aca09c1b09029c580d9d092f2675a83c946c 100644 (file)
@@ -25,6 +25,7 @@ import Utility.Tuple
 
 #ifdef mingw32_HOST_OS
 import qualified System.FilePath.Posix as Posix
+import qualified Utility.OsString as OS
 #endif
 
 import Data.Char
@@ -102,7 +103,7 @@ rsyncUrlIsShell s
 rsyncUrlIsPath :: String -> Bool
 rsyncUrlIsPath s
 #ifdef mingw32_HOST_OS
-       | not (null (takeDrive s)) = True
+       | not (OS.null (takeDrive (toOsPath s))) = True
 #endif
        | rsyncUrlIsShell s = False
        | otherwise = ':' `notElem` s
@@ -174,15 +175,15 @@ filterRsyncSafeOptions = fst3 . getOpt Permute
 #ifdef mingw32_HOST_OS
 toMSYS2Path :: FilePath -> FilePath
 toMSYS2Path p
-       | null drive = recombine parts
-       | otherwise = recombine $ "/" : driveletter drive : parts
+       | OS.null drive = recombine parts
+       | otherwise = recombine $ "/" : driveletter (fromOsPath drive) : parts
   where
-       (drive, p') = splitDrive p
-       parts = splitDirectories p'
+       (drive, p') = splitDrive (toOsPath p)
+       parts = map fromOsPath $ splitDirectories p'
        driveletter = map toLower . takeWhile (/= ':')
        recombine = fixtrailing . Posix.joinPath
        fixtrailing s
-               | hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s
+               | hasTrailingPathSeparator (toOsPath p) = Posix.addTrailingPathSeparator s
                | otherwise = s
 #endif
 
index 5d45df434b404511649f0e605df335b1e622ef71..0d43994f98e7fd6c466168d06e3f12afa65dc519 100644 (file)
@@ -21,10 +21,6 @@ import Utility.Exception
 import Utility.PartialPrelude
 #endif
 
-#ifdef mingw32_HOST_OS
-import System.FilePath
-#endif
-
 shellPath :: FilePath
 shellPath = "/bin/sh"
 
@@ -46,13 +42,13 @@ findShellCommand f = do
                Just ('#':'!':rest) -> case words rest of
                        [] -> defcmd
                        (c:ps) -> do
-                               let ps' = map Param ps ++ [File f]
+                               let ps' = map Param ps ++ [File (fromOsPath f)]
                                -- If the command is not inSearchPath,
                                -- take the base of it, and run eg "sh"
                                -- which in some cases on windows will work
                                -- despite it not being inSearchPath.
                                ok <- inSearchPath c
-                               return (if ok then c else takeFileName c, ps')
+                               return (if ok then c else fromOsPath (takeFileName (toOsPath c)), ps')
                _ -> defcmd
 #endif
   where
index 290984c4cc1b82dcf2b3c84c36f3ec4b8e33b0f2..8740c6b3d4f05fbad334887f4a60aa9b3310392f 100644 (file)
@@ -159,7 +159,7 @@ feedRead cmd subcmd params password emptydirectory feeder reader = do
                go (Just emptydirectory) (passwordfd ++ params)
 #else
        -- store the password in a temp file
-       withTmpFile (toOsPath "sop") $ \tmpfile h -> do
+       withTmpFile (literalOsPath "sop") $ \tmpfile h -> do
                liftIO $ B.hPutStr h password
                liftIO $ hClose h
                let passwordfile = [Param $ "--with-password=" ++ fromOsPath tmpfile]
index 11ee051c9693e44c7b7e9466ee441a89afec1776..d442d8740d6640f439a659f2d4f8e6a8b74d0db1 100644 (file)
@@ -136,5 +136,7 @@ relatedTemplate' _ = "t"
  - of openTempFile, and some extra has been added to make it longer
  - than any likely implementation.
  -}
+#ifndef mingw32_HOST_OS
 templateAddedLength :: Int
 templateAddedLength = 20
+#endif
index d6448ef749b808eda468f86c3753d0c7ef4fc92c..4064e9bfae24bc853f7e87d082b04dad38577a54 100644 (file)
@@ -32,8 +32,8 @@ withTmpDir :: (MonadMask m, MonadIO m) => Template -> (OsPath -> m a) -> m a
 withTmpDir template a = do
        topleveltmpdir <- liftIO $
                catchDefaultIO (literalOsPath ".") getTemporaryDirectory
-       let p = fromOsPath $ topleveltmpdir </> template
 #ifndef mingw32_HOST_OS
+       let p = fromOsPath $ topleveltmpdir </> template
        -- Use mkdtemp to create a temp directory securely in /tmp.
        bracket
                (liftIO $ toOsPath <$> mkdtemp p)