[commit: packages/array] master: Clean up warnings and restore GHC 7.6 compatibility (616527a)

git at git.haskell.org git at git.haskell.org
Mon Sep 23 11:03:37 CEST 2013


Repository : ssh://git@git.haskell.org/array

On branch  : master
Link       : http://git.haskell.org/packages/array.git/commitdiff/616527a9ca5fd8efa9fb339b316aea6ed9ef4523

>---------------------------------------------------------------

commit 616527a9ca5fd8efa9fb339b316aea6ed9ef4523
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Mon Sep 23 01:13:29 2013 +0200

    Clean up warnings and restore GHC 7.6 compatibility
    
    This commit
    
     - removes redundant imports
     - removes obsolete `{-# OPTIONS_GHC -#include "HsBase.h" #-}`
     - adds a forgotten guard to one `isTrue#` occurence
     - adds a few explicit `_ <-` binds to avoid unused-binds warning
     - relax `base` build-dep version constraint to include GHC 7.6
     - remove warning-disabling `OPTIONS_GHC` from modules
     - adds `ghc-options: -Wall` to `array.cabal` file as the code base
       now warning-free on GHC 7.6 and GHC HEAD
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


>---------------------------------------------------------------

616527a9ca5fd8efa9fb339b316aea6ed9ef4523
 Data/Array/Base.hs    |   17 ++++++-----------
 Data/Array/IO.hs      |   10 +++-------
 Data/Array/IO/Safe.hs |    3 +--
 array.cabal           |    3 ++-
 4 files changed, 12 insertions(+), 21 deletions(-)

diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs
index c1433fd..4dcacd1 100644
--- a/Data/Array/Base.hs
+++ b/Data/Array/Base.hs
@@ -1,12 +1,5 @@
 {-# LANGUAGE BangPatterns, CPP, RankNTypes, MagicHash, UnboxedTuples, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, DeriveDataTypeable, UnliftedFFITypes #-}
-{-# OPTIONS_GHC -fno-warn-unused-imports #-}
 {-# OPTIONS_HADDOCK hide #-}
--- XXX With a GHC 6.9 we get a spurious
--- Data/Array/Base.hs:26:0:
---     Warning: Module `Data.Ix' is imported, but nothing from it is used,
---                except perhaps instances visible in `Data.Ix'
---              To suppress this warning, use: import Data.Ix()
--- The -fno-warn-unused-imports works around that bug
 
 -----------------------------------------------------------------------------
 -- |
@@ -32,18 +25,16 @@ import Foreign.C.Types
 import Foreign.StablePtr
 
 import Data.Char
-import GHC.Arr          ( STArray, unsafeIndex )
+import GHC.Arr          ( STArray )
 import qualified GHC.Arr as Arr
 import qualified GHC.Arr as ArrST
 import GHC.ST           ( ST(..), runST )
 import GHC.Base
-import GHC.Word         ( Word(..) )
 import GHC.Ptr          ( Ptr(..), FunPtr(..), nullPtr, nullFunPtr )
-import GHC.Float        ( Float(..), Double(..) )
 import GHC.Stable       ( StablePtr(..) )
 import GHC.Int          ( Int8(..),  Int16(..),  Int32(..),  Int64(..) )
 import GHC.Word         ( Word8(..), Word16(..), Word32(..), Word64(..) )
-import GHC.IO           ( IO(..), stToIO )
+import GHC.IO           ( stToIO )
 import GHC.IOArray      ( IOArray(..),
                           newIOArray, unsafeReadIOArray, unsafeWriteIOArray )
 import Data.Typeable
@@ -1039,7 +1030,11 @@ instance MArray (STUArray s) Bool (ST s) where
     {-# INLINE unsafeRead #-}
     unsafeRead (STUArray _ _ _ marr#) (I# i#) = ST $ \s1# ->
         case readWordArray# marr# (bOOL_INDEX i#) s1# of { (# s2#, e# #) ->
+#if __GLASGOW_HASKELL__ > 706
         (# s2#, isTrue# ((e# `and#` bOOL_BIT i#) `neWord#` int2Word# 0#) :: Bool #) }
+#else
+        (# s2#, (e# `and#` bOOL_BIT i# `neWord#` int2Word# 0#) :: Bool #) }
+#endif
     {-# INLINE unsafeWrite #-}
     unsafeWrite (STUArray _ _ _ marr#) (I# i#) e = ST $ \s1# ->
         case bOOL_INDEX i#              of { j# ->
diff --git a/Data/Array/IO.hs b/Data/Array/IO.hs
index 4b7bbf0..e4ac3ed 100644
--- a/Data/Array/IO.hs
+++ b/Data/Array/IO.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE MagicHash, UnliftedFFITypes #-}
-{-# OPTIONS_GHC -#include "HsBase.h" #-}
-{-# OPTIONS_GHC -w #-} --tmp
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Array.IO
@@ -41,10 +40,7 @@ import Foreign
 import Foreign.C
 
 import GHC.Exts  (MutableByteArray#, RealWorld)
-import GHC.Arr
-import GHC.IORef
 import GHC.IO.Handle
-import GHC.IO.Buffer
 import GHC.IO.Exception
 
 -- ---------------------------------------------------------------------------
@@ -70,7 +66,7 @@ hGetArray handle (IOUArray (STUArray _l _u n ptr)) count
       -- allocate a separate area of memory and copy.
       allocaBytes count $ \p -> do
         r <- hGetBuf handle p count
-        memcpy_ba_ptr ptr p (fromIntegral r)
+        _ <- memcpy_ba_ptr ptr p (fromIntegral r)
         return r
 
 foreign import ccall unsafe "memcpy"
@@ -93,7 +89,7 @@ hPutArray handle (IOUArray (STUArray _l _u n raw)) count
       -- as in hGetArray, we would like to use the array directly, but
       -- we can't be sure that the MutableByteArray# is pinned.
      allocaBytes count $ \p -> do
-       memcpy_ptr_ba p raw (fromIntegral count)
+       _ <- memcpy_ptr_ba p raw (fromIntegral count)
        hPutBuf handle p count
 
 foreign import ccall unsafe "memcpy"
diff --git a/Data/Array/IO/Safe.hs b/Data/Array/IO/Safe.hs
index fe143ff..1026195 100644
--- a/Data/Array/IO/Safe.hs
+++ b/Data/Array/IO/Safe.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# OPTIONS_GHC -#include "HsBase.h" #-}
-{-# OPTIONS_GHC -w #-} --tmp
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Array.IO.Safe
diff --git a/array.cabal b/array.cabal
index a81aec6..f9b9dac 100644
--- a/array.cabal
+++ b/array.cabal
@@ -32,7 +32,8 @@ library
       Trustworthy,
       UnboxedTuples,
       UnliftedFFITypes
-  build-depends: base >= 4.7 && < 5
+  build-depends: base >= 4.6 && < 5
+  ghc-options: -Wall
   exposed-modules:
       Data.Array
       Data.Array.Base




More information about the ghc-commits mailing list