Skip to content
Snippets Groups Projects
Commit 1b155606 authored by Ryan Scott's avatar Ryan Scott
Browse files

Accommodate recent Int64#/Word64#-related changes

parent 9b21848a
No related branches found
No related tags found
No related merge requests found
......@@ -440,10 +440,25 @@ index ecccba1..e8e9de2 100644
cast = word64ToInt64
instance Cast Word Int where
diff --git a/Basement/From.hs b/Basement/From.hs
index 4f51154..53c0653 100644
index 4f51154..be645d9 100644
--- a/Basement/From.hs
+++ b/Basement/From.hs
@@ -54,6 +54,7 @@ import Basement.These
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -36,6 +37,9 @@ import Basement.Compat.Base
-- basic instances
import GHC.Types
import GHC.Prim
+#if __GLASGOW_HASKELL__ >= 903
+ hiding (word64ToWord#)
+#endif
import GHC.Int
import GHC.Word
import Basement.Numerical.Number
@@ -54,6 +58,7 @@ import Basement.These
import Basement.PrimType (PrimType, PrimSize)
import Basement.Types.OffsetSize
import Basement.Compat.Natural
......@@ -451,7 +466,7 @@ index 4f51154..53c0653 100644
import qualified Prelude (fromIntegral)
-- nat instances
@@ -102,79 +103,79 @@ instance IsIntegral n => From n Integer where
@@ -102,79 +107,79 @@ instance IsIntegral n => From n Integer where
from = toInteger
instance From Int8 Int16 where
......@@ -564,7 +579,7 @@ index 4f51154..53c0653 100644
instance From Word64 Word128 where
from w = Word128 0 w
@@ -270,11 +271,11 @@ instance (NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty)
@@ -270,11 +275,11 @@ instance (NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty)
tryFrom = BlockN.toBlockN . UArray.toBlock . BoxArray.mapToUnboxed id
instance (KnownNat n, NatWithinBound Word8 n) => From (Zn64 n) Word8 where
......@@ -579,7 +594,7 @@ index 4f51154..53c0653 100644
instance From (Zn64 n) Word64 where
from = unZn64
instance From (Zn64 n) Word128 where
@@ -283,11 +284,11 @@ instance From (Zn64 n) Word256 where
@@ -283,11 +288,11 @@ instance From (Zn64 n) Word256 where
from = from . unZn64
instance (KnownNat n, NatWithinBound Word8 n) => From (Zn n) Word8 where
......@@ -720,10 +735,23 @@ index 0000000..62fecde
+narrow32WordCompat# = narrow32Word#
+#endif
diff --git a/Basement/IntegralConv.hs b/Basement/IntegralConv.hs
index aff92b1..ed99b1d 100644
index aff92b1..357bcdf 100644
--- a/Basement/IntegralConv.hs
+++ b/Basement/IntegralConv.hs
@@ -26,6 +26,7 @@ import GHC.Word
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
@@ -21,11 +22,15 @@ module Basement.IntegralConv
import GHC.Types
import GHC.Prim
+#if __GLASGOW_HASKELL__ >= 903
+ hiding (word64ToWord#)
+#endif
import GHC.Int
import GHC.Word
import Prelude (Integer, fromIntegral)
import Basement.Compat.Base
import Basement.Compat.Natural
......@@ -731,7 +759,7 @@ index aff92b1..ed99b1d 100644
import Basement.Numerical.Number
import Basement.Numerical.Conversion
@@ -58,69 +59,69 @@ instance IsNatural a => IntegralUpsize a Natural where
@@ -58,69 +63,69 @@ instance IsNatural a => IntegralUpsize a Natural where
integralUpsize = toNatural
instance IntegralUpsize Int8 Int16 where
......@@ -826,7 +854,7 @@ index aff92b1..ed99b1d 100644
integralDownsizeCheck = integralDownsizeBounded integralDownsize
instance IntegralDownsize Int64 Int8 where
@@ -137,34 +138,34 @@ instance IntegralDownsize Int64 Int where
@@ -137,34 +142,34 @@ instance IntegralDownsize Int64 Int where
integralDownsizeCheck = integralDownsizeBounded integralDownsize
instance IntegralDownsize Word64 Word8 where
......@@ -921,18 +949,23 @@ index 7973887..1fd2091 100644
instance Additive Word64 where
azero = 0
diff --git a/Basement/Numerical/Conversion.hs b/Basement/Numerical/Conversion.hs
index a86d195..9fc0005 100644
index a86d195..f967c34 100644
--- a/Basement/Numerical/Conversion.hs
+++ b/Basement/Numerical/Conversion.hs
@@ -18,6 +18,7 @@ module Basement.Numerical.Conversion
@@ -18,8 +18,12 @@ module Basement.Numerical.Conversion
#include "MachDeps.h"
+import Basement.HeadHackageUtils
import GHC.Types
import GHC.Prim
+#if __GLASGOW_HASKELL__ >= 903
+ hiding (word64ToWord#)
+#endif
import GHC.Int
@@ -81,7 +82,7 @@ data Word32x2 = Word32x2 {-# UNPACK #-} !Word32
import GHC.Word
@@ -81,7 +85,7 @@ data Word32x2 = Word32x2 {-# UNPACK #-} !Word32
#if WORD_SIZE_IN_BITS == 64
word64ToWord32s :: Word64 -> Word32x2
......
diff --git a/library/ByteString/StrictBuilder/Population/UncheckedShifting.hs b/library/ByteString/StrictBuilder/Population/UncheckedShifting.hs
index 69ba0ff..9b1d2bc 100644
index 69ba0ff..63b73cc 100644
--- a/library/ByteString/StrictBuilder/Population/UncheckedShifting.hs
+++ b/library/ByteString/StrictBuilder/Population/UncheckedShifting.hs
@@ -62,8 +62,8 @@ shiftr_w w s = fromIntegral $ (`shiftr_w64` s) $ fromIntegral w
@@ -24,6 +24,9 @@ module ByteString.StrictBuilder.Population.UncheckedShifting (
#if !defined(__HADDOCK__)
import GHC.Base
+#if __GLASGOW_HASKELL__ >= 903
+ hiding (uncheckedShiftRL64#)
+#endif
import GHC.Word (Word32(..),Word16(..),Word64(..))
#if WORD_SIZE_IN_BITS < 64 && __GLASGOW_HASKELL__ >= 608
@@ -62,8 +65,8 @@ shiftr_w w s = fromIntegral $ (`shiftr_w64` s) $ fromIntegral w
#endif
#if !defined(__HADDOCK__)
......@@ -13,7 +23,7 @@ index 69ba0ff..9b1d2bc 100644
#if WORD_SIZE_IN_BITS < 64
shiftr_w64 (W64# w) (I# i) = W64# (w `uncheckedShiftRL64#` i)
@@ -77,6 +77,32 @@ shiftr_w32 = shiftR
@@ -77,6 +80,32 @@ shiftr_w32 = shiftR
shiftr_w64 = shiftR
#endif
......
......@@ -255,10 +255,18 @@ index 9803875..659c07f 100644
!rsetTable = "\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
diff --git a/Data/Memory/Hash/FNV.hs b/Data/Memory/Hash/FNV.hs
index 89d78b5..1351acc 100644
index 89d78b5..be572a7 100644
--- a/Data/Memory/Hash/FNV.hs
+++ b/Data/Memory/Hash/FNV.hs
@@ -24,6 +24,7 @@ module Data.Memory.Hash.FNV
@@ -8,6 +8,7 @@
-- Fowler Noll Vo Hash (1 and 1a / 32 / 64 bits versions)
-- <http://en.wikipedia.org/wiki/Fowler%E2%80%93Noll%E2%80%93Vo_hash_function>
--
+{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
@@ -24,12 +25,17 @@ module Data.Memory.Hash.FNV
, fnv1a_64
) where
......@@ -266,7 +274,18 @@ index 89d78b5..1351acc 100644
import Data.Memory.Internal.Compat ()
import Data.Memory.Internal.CompatPrim
import Data.Memory.Internal.CompatPrim64
@@ -44,40 +45,40 @@ newtype FnvHash64 = FnvHash64 Word64
import Data.Memory.Internal.Imports
import GHC.Word
-import GHC.Prim hiding (Word64#, Int64#)
+import GHC.Prim hiding ( Word64#, Int64#
+#if __GLASGOW_HASKELL__ >= 903
+ , timesWord64#, xor64#, wordToWord64#
+#endif
+ )
import GHC.Types
import GHC.Ptr
@@ -44,40 +50,40 @@ newtype FnvHash64 = FnvHash64 Word64
-- | compute FNV1 (32 bit variant) of a raw piece of memory
fnv1 :: Ptr Word8 -> Int -> IO FnvHash32
fnv1 (Ptr addr) (I# n) = IO $ \s -> loop 0x811c9dc5## 0# s
......@@ -315,7 +334,7 @@ index 89d78b5..1351acc 100644
in loop nacc (i +# 1#) s2
fnv64Const :: Word64#
@@ -89,14 +90,14 @@ fnv1_64 (Ptr addr) (I# n) = IO $ \s -> loop fnv64Const 0# s
@@ -89,14 +95,14 @@ fnv1_64 (Ptr addr) (I# n) = IO $ \s -> loop fnv64Const 0# s
-- | compute FNV1a (64 bit variant) of a raw piece of memory
fnv1a_64 :: Ptr Word8 -> Int -> IO FnvHash64
fnv1a_64 (Ptr addr) (I# n) = IO $ \s -> loop fnv64Const 0# s
......@@ -373,6 +392,49 @@ index 0000000..d6ab707
+narrow32WordCompat# :: Word# -> Word#
+narrow32WordCompat# = narrow32Word#
+#endif
diff --git a/Data/Memory/Internal/CompatPrim64.hs b/Data/Memory/Internal/CompatPrim64.hs
index b6d2bd7..5a98617 100644
--- a/Data/Memory/Internal/CompatPrim64.hs
+++ b/Data/Memory/Internal/CompatPrim64.hs
@@ -52,7 +52,37 @@ module Data.Memory.Internal.CompatPrim64
#if WORD_SIZE_IN_BITS == 64
-import GHC.Prim hiding (Word64#, Int64#)
+import GHC.Prim hiding ( Word64#, Int64#
+#if __GLASGOW_HASKELL__ >= 903
+ , eqInt64#
+ , neInt64#
+ , ltInt64#
+ , leInt64#
+ , gtInt64#
+ , geInt64#
+ , quotInt64#
+ , remInt64#
+ , eqWord64#
+ , neWord64#
+ , ltWord64#
+ , leWord64#
+ , gtWord64#
+ , geWord64#
+ , and64#
+ , or64#
+ , xor64#
+ , not64#
+ , timesWord64#
+ , uncheckedShiftL64#
+ , uncheckedShiftRL64#
+ , int64ToWord64#
+ , word64ToInt64#
+ , intToInt64#
+ , int64ToInt#
+ , wordToWord64#
+ , word64ToWord#
+#endif
+ )
#if __GLASGOW_HASKELL__ >= 708
type OutBool = Int#
diff --git a/memory.cabal b/memory.cabal
index 2db3f39..eec3b16 100644
--- a/memory.cabal
......
......@@ -147,7 +147,7 @@ index d208e3f..b02d560 100644
+word32ToWordCompat# x = x
+#endif
diff --git a/Data/Text/Internal/Unsafe/Shift.hs b/Data/Text/Internal/Unsafe/Shift.hs
index b2fef9b..3746b6b 100644
index b2fef9b..8606b96 100644
--- a/Data/Text/Internal/Unsafe/Shift.hs
+++ b/Data/Text/Internal/Unsafe/Shift.hs
@@ -1,3 +1,4 @@
......@@ -155,7 +155,17 @@ index b2fef9b..3746b6b 100644
{-# LANGUAGE MagicHash #-}
-- |
@@ -36,17 +37,17 @@ class UnsafeShift a where
@@ -22,6 +23,9 @@ module Data.Text.Internal.Unsafe.Shift
-- import qualified Data.Bits as Bits
import GHC.Base
+#if __GLASGOW_HASKELL__ >= 903
+ hiding (uncheckedShiftL64#, uncheckedShiftRL64#)
+#endif
import GHC.Word
-- | This is a workaround for poor optimisation in GHC 6.8.2. It
@@ -36,17 +40,17 @@ class UnsafeShift a where
instance UnsafeShift Word16 where
{-# INLINE shiftL #-}
......@@ -177,7 +187,7 @@ index b2fef9b..3746b6b 100644
instance UnsafeShift Word64 where
{-# INLINE shiftL #-}
@@ -70,3 +71,43 @@ instance UnsafeShift Integer where
@@ -70,3 +74,43 @@ instance UnsafeShift Integer where
{-# INLINE shiftR #-}
shiftR = Bits.shiftR
-}
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment