[commit: packages/array] master: Follow changes in comparison primops (see #6135) (6d8d15c)
git at git.haskell.org
git at git.haskell.org
Wed Sep 18 17:11:49 CEST 2013
Repository : ssh://git@git.haskell.org/array
On branch : master
Link : http://git.haskell.org/packages/array.git/commitdiff/6d8d15c4fb4b184cc2e4907e8c0aacf50a899ea0
>---------------------------------------------------------------
commit 6d8d15c4fb4b184cc2e4907e8c0aacf50a899ea0
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date: Mon Sep 16 15:16:27 2013 +0100
Follow changes in comparison primops (see #6135)
>---------------------------------------------------------------
6d8d15c4fb4b184cc2e4907e8c0aacf50a899ea0
Data/Array/Base.hs | 25 +++++++++++++++++++------
1 file changed, 19 insertions(+), 6 deletions(-)
diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs
index 2b997b0..3298ac4 100644
--- a/Data/Array/Base.hs
+++ b/Data/Array/Base.hs
@@ -503,9 +503,14 @@ instance IArray UArray Bool where
{-# INLINE unsafeArray #-}
unsafeArray lu ies = runST (unsafeArrayUArray lu ies False)
{-# INLINE unsafeAt #-}
+#if __GLASGOW_HASKELL__ > 706
+ unsafeAt (UArray _ _ _ arr#) (I# i#) = isTrue#
+#else
unsafeAt (UArray _ _ _ arr#) (I# i#) =
- (indexWordArray# arr# (bOOL_INDEX i#) `and#` bOOL_BIT i#)
- `neWord#` int2Word# 0#
+#endif
+ ((indexWordArray# arr# (bOOL_INDEX i#) `and#` bOOL_BIT i#)
+ `neWord#` int2Word# 0#)
+
{-# INLINE unsafeReplace #-}
unsafeReplace arr ies = runST (unsafeReplaceUArray arr ies)
{-# INLINE unsafeAccum #-}
@@ -988,7 +993,11 @@ data STUArray s i e = STUArray !i !i !Int (MutableByteArray# s)
instance Eq (STUArray s i e) where
STUArray _ _ _ arr1# == STUArray _ _ _ arr2# =
- tagToEnum# (sameMutableByteArray# arr1# arr2#)
+#if __GLASGOW_HASKELL__ > 706
+ isTrue# (sameMutableByteArray# arr1# arr2#)
+#else
+ sameMutableByteArray# arr1# arr2#
+#endif
{-# INLINE unsafeNewArraySTUArray_ #-}
unsafeNewArraySTUArray_ :: Ix i
@@ -1011,8 +1020,12 @@ instance MArray (STUArray s) Bool (ST s) where
case safeRangeSize (l,u) of { n@(I# n#) ->
case newByteArray# (bOOL_SCALE n#) s1# of { (# s2#, marr# #) ->
case bOOL_WORD_SCALE n# of { n'# ->
- let loop i# s3# | i# ==# n'# = s3#
- | otherwise =
+#if __GLASGOW_HASKELL__ > 706
+ let loop i# s3# | isTrue# (i# ==# n'#) = s3#
+#else
+ let loop i# s3# | i# ==# n'# = s3#
+#endif
+ | otherwise =
case writeWordArray# marr# i# e# s3# of { s4# ->
loop (i# +# 1#) s4# } in
case loop 0# s2# of { s3# ->
@@ -1026,7 +1039,7 @@ 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# #) ->
- (# s2#, (e# `and#` bOOL_BIT i#) `neWord#` int2Word# 0# #) }
+ (# s2#, isTrue# ((e# `and#` bOOL_BIT i#) `neWord#` int2Word# 0#) :: Bool #) }
{-# INLINE unsafeWrite #-}
unsafeWrite (STUArray _ _ _ marr#) (I# i#) e = ST $ \s1# ->
case bOOL_INDEX i# of { j# ->
More information about the ghc-commits
mailing list