[commit: packages/primitive] ghc-head: Make `-Wall` clean (eaeec02)
git at git.haskell.org
git at git.haskell.org
Thu Sep 26 11:45:16 CEST 2013
Repository : ssh://git@git.haskell.org/primitive
On branch : ghc-head
Link : http://git.haskell.org/packages/primitive.git/commitdiff/eaeec02c913c566f7178d5a81055753576060f35
>---------------------------------------------------------------
commit eaeec02c913c566f7178d5a81055753576060f35
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Thu Sep 26 10:44:56 2013 +0200
Make `-Wall` clean
This makes compilation `-Wall` warning-free with GHC 7.0/7.2/7.4/7.6/7.7
>---------------------------------------------------------------
eaeec02c913c566f7178d5a81055753576060f35
Data/Primitive/ByteArray.hs | 12 ++++++------
Data/Primitive/Types.hs | 1 -
primitive.cabal | 2 +-
3 files changed, 7 insertions(+), 8 deletions(-)
diff --git a/Data/Primitive/ByteArray.hs b/Data/Primitive/ByteArray.hs
index b8a6a89..6b1a609 100644
--- a/Data/Primitive/ByteArray.hs
+++ b/Data/Primitive/ByteArray.hs
@@ -151,8 +151,8 @@ writeByteArray (MutableByteArray arr#) (I# i#) x
= primitive_ (writeByteArray# arr# i# x)
#if __GLASGOW_HASKELL__ >= 702
-i# :: Int -> Int#
-i# (I# n#) = n#
+unI# :: Int -> Int#
+unI# (I# n#) = n#
#endif
-- | Copy a slice of an immutable byte array to a mutable byte array.
@@ -167,7 +167,7 @@ copyByteArray
{-# INLINE copyByteArray #-}
copyByteArray (MutableByteArray dst#) doff (ByteArray src#) soff sz
#if __GLASGOW_HASKELL__ >= 702
- = primitive_ (copyByteArray# src# (i# soff) dst# (i# doff) (i# sz))
+ = primitive_ (copyByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz))
#else
= unsafePrimToPrim
$ memcpy_ba dst# (fromIntegral doff) src# (fromIntegral soff)
@@ -189,7 +189,7 @@ copyMutableByteArray
copyMutableByteArray (MutableByteArray dst#) doff
(MutableByteArray src#) soff sz
#if __GLASGOW_HASKELL__ >= 702
- = primitive_ (copyMutableByteArray# src# (i# soff) dst# (i# doff) (i# sz))
+ = primitive_ (copyMutableByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz))
#else
= unsafePrimToPrim
$ memcpy_mba dst# (fromIntegral doff) src# (fromIntegral soff)
@@ -237,8 +237,7 @@ fillByteArray
{-# INLINE fillByteArray #-}
fillByteArray = setByteArray
-
-
+#if __GLASGOW_HASKELL__ < 702
foreign import ccall unsafe "primitive-memops.h hsprimitive_memcpy"
memcpy_mba :: MutableByteArray# s -> CInt
-> MutableByteArray# s -> CInt
@@ -248,6 +247,7 @@ foreign import ccall unsafe "primitive-memops.h hsprimitive_memcpy"
memcpy_ba :: MutableByteArray# s -> CInt
-> ByteArray# -> CInt
-> CSize -> IO ()
+#endif
foreign import ccall unsafe "primitive-memops.h hsprimitive_memmove"
memmove_mba :: MutableByteArray# s -> CInt
diff --git a/Data/Primitive/Types.hs b/Data/Primitive/Types.hs
index 68f2d52..35603a5 100644
--- a/Data/Primitive/Types.hs
+++ b/Data/Primitive/Types.hs
@@ -22,7 +22,6 @@ import Data.Primitive.MachDeps
import Data.Primitive.Internal.Operations
import GHC.Base (
- unsafeCoerce#,
Int(..), Char(..),
)
import GHC.Float (
diff --git a/primitive.cabal b/primitive.cabal
index b4aa289..55444b8 100644
--- a/primitive.cabal
+++ b/primitive.cabal
@@ -38,7 +38,7 @@ Library
Build-Depends: base >= 4 && < 5, ghc-prim
- Ghc-Options: -O2
+ Ghc-Options: -O2 -Wall
Include-Dirs: cbits
Install-Includes: primitive-memops.h
More information about the ghc-commits
mailing list