[commit: packages/directory] master: Make `mingw32_HOST_OS` `-Wall`-clean as well (79691fe)
git at git.haskell.org
git at git.haskell.org
Sun Oct 13 16:05:39 UTC 2013
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://git.haskell.org/packages/directory.git/commitdiff/79691feddca44e9bd2c9879a584507357f1e772a
>---------------------------------------------------------------
commit 79691feddca44e9bd2c9879a584507357f1e772a
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sun Oct 13 17:26:35 2013 +0200
Make `mingw32_HOST_OS` `-Wall`-clean as well
This is a follow-up to ad35787a which cleans up compilation for
`mingw32_HOST_OS` builds.
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
79691feddca44e9bd2c9879a584507357f1e772a
System/Directory.hs | 14 +++++---------
1 file changed, 5 insertions(+), 9 deletions(-)
diff --git a/System/Directory.hs b/System/Directory.hs
index bf768db..89e03f4 100644
--- a/System/Directory.hs
+++ b/System/Directory.hs
@@ -3,11 +3,6 @@
{-# LANGUAGE Trustworthy #-}
#endif
-#ifdef mingw32_HOST_OS
-{-# OPTIONS_GHC -w #-}
--- XXX We get some warnings on Windows
-#endif
-
-----------------------------------------------------------------------------
-- |
-- Module : System.Directory
@@ -81,7 +76,6 @@ module System.Directory
, getModificationTime
) where
-import System.Environment ( getEnv )
import System.FilePath
import System.IO
import System.IO.Error
@@ -103,14 +97,15 @@ import Data.Time.Clock.POSIX
#ifdef __GLASGOW_HASKELL__
import GHC.IO.Exception ( IOErrorType(InappropriateType) )
-import GHC.IO.Encoding
-import GHC.Foreign as GHC
#ifdef mingw32_HOST_OS
import System.Posix.Types
import System.Posix.Internals
import qualified System.Win32 as Win32
#else
+import GHC.IO.Encoding
+import GHC.Foreign as GHC
+import System.Environment ( getEnv )
import qualified System.Posix as Posix
#endif
@@ -1030,7 +1025,7 @@ foreign import ccall unsafe "HsDirectory.h __hscore_S_IXUSR" s_IXUSR :: CMode
foreign import ccall unsafe "__hscore_S_IFDIR" s_IFDIR :: CMode
#endif
-
+#ifndef mingw32_HOST_OS
#ifdef __GLASGOW_HASKELL__
foreign import ccall unsafe "__hscore_long_path_size"
long_path_size :: Int
@@ -1038,6 +1033,7 @@ foreign import ccall unsafe "__hscore_long_path_size"
long_path_size :: Int
long_path_size = 2048 -- // guess?
#endif /* __GLASGOW_HASKELL__ */
+#endif /* !mingw32_HOST_OS */
{- | Returns the current user's home directory.
More information about the ghc-commits
mailing list