[commit: packages/primitive] master: Follow changes in comparison primops (see #6135) (27b18d5)
git at git.haskell.org
git at git.haskell.org
Wed Sep 18 17:12:23 CEST 2013
Repository : ssh://git@git.haskell.org/primitive
On branch : master
Link : http://git.haskell.org/packages/primitive.git/commitdiff/27b18d5bb12827e279f5cca541ae15508da6b6f7
>---------------------------------------------------------------
commit 27b18d5bb12827e279f5cca541ae15508da6b6f7
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date: Mon Sep 16 15:17:04 2013 +0100
Follow changes in comparison primops (see #6135)
>---------------------------------------------------------------
27b18d5bb12827e279f5cca541ae15508da6b6f7
Data/Primitive/Array.hs | 4 ++--
Data/Primitive/ByteArray.hs | 4 ++--
Data/Primitive/Types.hs | 15 +++++++--------
3 files changed, 11 insertions(+), 12 deletions(-)
diff --git a/Data/Primitive/Array.hs b/Data/Primitive/Array.hs
index aa2dc86..0551b90 100644
--- a/Data/Primitive/Array.hs
+++ b/Data/Primitive/Array.hs
@@ -21,7 +21,7 @@ module Data.Primitive.Array (
import Control.Monad.Primitive
-import GHC.Base ( Int(..) )
+import GHC.Base ( Int(..), isTrue# )
import GHC.Prim
import Data.Typeable ( Typeable )
@@ -106,7 +106,7 @@ unsafeThawArray (Array arr#)
sameMutableArray :: MutableArray s a -> MutableArray s a -> Bool
{-# INLINE sameMutableArray #-}
sameMutableArray (MutableArray arr#) (MutableArray brr#)
- = tagToEnum# (sameMutableArray# arr# brr#)
+ = isTrue# (sameMutableArray# arr# brr#)
-- | Copy a slice of an immutable array to a mutable array.
copyArray :: PrimMonad m
diff --git a/Data/Primitive/ByteArray.hs b/Data/Primitive/ByteArray.hs
index ae1ae3f..b32b070 100644
--- a/Data/Primitive/ByteArray.hs
+++ b/Data/Primitive/ByteArray.hs
@@ -31,7 +31,7 @@ import Data.Primitive.Types
import Foreign.C.Types
import Data.Word ( Word8 )
-import GHC.Base ( Int(..) )
+import GHC.Base ( Int(..), isTrue# )
import GHC.Prim
import Data.Typeable ( Typeable )
@@ -88,7 +88,7 @@ mutableByteArrayContents (MutableByteArray arr#)
sameMutableByteArray :: MutableByteArray s -> MutableByteArray s -> Bool
{-# INLINE sameMutableByteArray #-}
sameMutableByteArray (MutableByteArray arr#) (MutableByteArray brr#)
- = tagToEnum# (sameMutableByteArray# arr# brr#)
+ = isTrue# (sameMutableByteArray# arr# brr#)
-- | Convert a mutable byte array to an immutable one without copying. The
-- array should not be modified after the conversion.
diff --git a/Data/Primitive/Types.hs b/Data/Primitive/Types.hs
index 8513059..6560644 100644
--- a/Data/Primitive/Types.hs
+++ b/Data/Primitive/Types.hs
@@ -21,7 +21,7 @@ import Control.Monad.Primitive
import Data.Primitive.MachDeps
import GHC.Base (
- Int(..), Char(..),
+ Int(..), Char(..), isTrue#
)
import GHC.Float (
Float(..), Double(..)
@@ -34,7 +34,6 @@ import GHC.Int (
)
import GHC.Prim
-import GHC.PrimWrappers
import Data.Typeable ( Typeable )
import Data.Data ( Data(..) )
@@ -44,14 +43,14 @@ import Data.Primitive.Internal.Compat ( mkNoRepType )
data Addr = Addr Addr# deriving ( Typeable )
instance Eq Addr where
- Addr a# == Addr b# = eqAddr# a# b#
- Addr a# /= Addr b# = neAddr# a# b#
+ Addr a# == Addr b# = isTrue# (eqAddr# a# b#)
+ Addr a# /= Addr b# = isTrue# (neAddr# a# b#)
instance Ord Addr where
- Addr a# > Addr b# = gtAddr# a# b#
- Addr a# >= Addr b# = geAddr# a# b#
- Addr a# < Addr b# = ltAddr# a# b#
- Addr a# <= Addr b# = leAddr# a# b#
+ Addr a# > Addr b# = isTrue# (gtAddr# a# b#)
+ Addr a# >= Addr b# = isTrue# (geAddr# a# b#)
+ Addr a# < Addr b# = isTrue# (ltAddr# a# b#)
+ Addr a# <= Addr b# = isTrue# (leAddr# a# b#)
instance Data Addr where
toConstr _ = error "toConstr"
More information about the ghc-commits
mailing list