[commit: packages/directory] master: Make `-Wall` clean and use `{-# LANGUAGE #-}` (ad35787)
git at git.haskell.org
git at git.haskell.org
Sun Oct 13 16:05:33 UTC 2013
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://git.haskell.org/packages/directory.git/commitdiff/ad35787ab729b8415d48b953d2573a50d791223e
>---------------------------------------------------------------
commit ad35787ab729b8415d48b953d2573a50d791223e
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sun Oct 13 12:48:13 2013 +0200
Make `-Wall` clean and use `{-# LANGUAGE #-}`
This commit adds a `{-# LANGUAGE #-}` declaration for non-Haskell2010
language extensions and refactors the code to become `-Wall` warning
free for GHC 7.4/7.6/HEAD.
As I can't test Windows compilation myself right now, I've left
`{-# OPTIONS_GHC -w #-}` guarded by an `#ifdef mingw32_HOST_OS`
for now.
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
ad35787ab729b8415d48b953d2573a50d791223e
System/Directory.hs | 18 +++++++++++-------
1 file changed, 11 insertions(+), 7 deletions(-)
diff --git a/System/Directory.hs b/System/Directory.hs
index 3aef66f..0444d0e 100644
--- a/System/Directory.hs
+++ b/System/Directory.hs
@@ -1,9 +1,13 @@
-{-# OPTIONS_GHC -w #-}
--- XXX We get some warnings on Windows
+{-# LANGUAGE CPP, NondecreasingIndentation #-}
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE Trustworthy #-}
#endif
+#ifdef mingw32_HOST_OS
+{-# OPTIONS_GHC -w #-}
+-- XXX We get some warnings on Windows
+#endif
+
-----------------------------------------------------------------------------
-- |
-- Module : System.Directory
@@ -77,7 +81,6 @@ module System.Directory
, getModificationTime
) where
-import Control.Monad (guard)
import System.Environment ( getEnv )
import System.FilePath
import System.IO
@@ -99,7 +102,7 @@ import Data.Time.Clock.POSIX
#ifdef __GLASGOW_HASKELL__
-import GHC.IO.Exception ( IOException(..), IOErrorType(..), ioException )
+import GHC.IO.Exception ( IOErrorType(InappropriateType) )
import GHC.IO.Encoding
import GHC.Foreign as GHC
@@ -578,7 +581,7 @@ renameDirectory opath npath = do
let is_dir = Posix.fileMode stat .&. Posix.directoryMode /= 0
#endif
if (not is_dir)
- then ioException (ioeSetErrorString
+ then ioError (ioeSetErrorString
(mkIOError InappropriateType "renameDirectory" Nothing (Just opath))
"not a directory")
else do
@@ -644,7 +647,7 @@ renameFile opath npath = do
let is_dir = Posix.isDirectory stat
#endif
if is_dir
- then ioException (ioeSetErrorString
+ then ioError (ioeSetErrorString
(mkIOError InappropriateType "renameFile" Nothing (Just opath))
"is a directory")
else do
@@ -708,7 +711,8 @@ canonicalizePath fpath =
do enc <- getFileSystemEncoding
GHC.withCString enc fpath $ \pInPath ->
allocaBytes long_path_size $ \pOutPath ->
- do throwErrnoPathIfNull "canonicalizePath" fpath $ c_realpath pInPath pOutPath
+ do _ <- throwErrnoPathIfNull "canonicalizePath" fpath $ c_realpath pInPath pOutPath
+ -- NB: pOutPath will be passed thru as result pointer by c_realpath
path <- GHC.peekCString enc pOutPath
#endif
return (normalise path)
More information about the ghc-commits
mailing list