diff options
Diffstat (limited to 'gnu/packages/patches')
-rw-r--r-- | gnu/packages/patches/ghc-basement-fix-32bit.patch | 177 | ||||
-rw-r--r-- | gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch | 303 | ||||
-rw-r--r-- | gnu/packages/patches/ghc-memory-fix-32bit.patch | 40 | ||||
-rw-r--r-- | gnu/packages/patches/ghc-persistent-fix-32bit.patch | 25 |
4 files changed, 242 insertions, 303 deletions
diff --git a/gnu/packages/patches/ghc-basement-fix-32bit.patch b/gnu/packages/patches/ghc-basement-fix-32bit.patch new file mode 100644 index 0000000000..7407b2ef75 --- /dev/null +++ b/gnu/packages/patches/ghc-basement-fix-32bit.patch @@ -0,0 +1,177 @@ +https://github.com/haskell-foundation/foundation/pull/573 +https://github.com/haskell-foundation/foundation/commit/38be2c93acb6f459d24ed6c626981c35ccf44095.patch + +Changes made: +Changed '904' to '902' to use the fix with GHC-9.2. + +diff --git a/Basement/Bits.hs b/Basement/Bits.hs +index 7eeea0f..b1e9afd 100644 +--- a/Basement/Bits.hs ++++ b/Basement/Bits.hs +@@ -54,8 +54,12 @@ import GHC.Int + import Basement.Compat.Primitive + + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++import GHC.Exts ++#else + import GHC.IntWord64 + #endif ++#endif + + -- | operation over finite bits + class FiniteBitsOps bits where +diff --git a/Basement/Numerical/Additive.hs b/Basement/Numerical/Additive.hs +index d0dfb97..79b7033 100644 +--- a/Basement/Numerical/Additive.hs ++++ b/Basement/Numerical/Additive.hs +@@ -30,8 +30,12 @@ import qualified Basement.Types.Word128 as Word128 + import qualified Basement.Types.Word256 as Word256 + + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++import GHC.Exts ++#else + import GHC.IntWord64 + #endif ++#endif + + -- | Represent class of things that can be added together, + -- contains a neutral element and is commutative. +diff --git a/Basement/Numerical/Conversion.hs b/Basement/Numerical/Conversion.hs +index db502c0..abb6d93 100644 +--- a/Basement/Numerical/Conversion.hs ++++ b/Basement/Numerical/Conversion.hs +@@ -26,8 +26,12 @@ import GHC.Word + import Basement.Compat.Primitive + + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++import GHC.Exts ++#else + import GHC.IntWord64 + #endif ++#endif + + intToInt64 :: Int -> Int64 + #if WORD_SIZE_IN_BITS == 64 +@@ -96,11 +100,22 @@ int64ToWord64 (I64# i) = W64# (int64ToWord64# i) + #endif + + #if WORD_SIZE_IN_BITS == 64 ++#if __GLASGOW_HASKELL__ >= 904 ++word64ToWord# :: Word64# -> Word# ++word64ToWord# i = word64ToWord# i ++#else + word64ToWord# :: Word# -> Word# + word64ToWord# i = i ++#endif + {-# INLINE word64ToWord# #-} + #endif + ++#if WORD_SIZE_IN_BITS < 64 ++word64ToWord32# :: Word64# -> Word32# ++word64ToWord32# i = wordToWord32# (word64ToWord# i) ++{-# INLINE word64ToWord32# #-} ++#endif ++ + -- | 2 Word32s + data Word32x2 = Word32x2 {-# UNPACK #-} !Word32 + {-# UNPACK #-} !Word32 +@@ -113,9 +128,14 @@ word64ToWord32s (W64# w64) = Word32x2 (W32# (wordToWord32# (uncheckedShiftRL# (G + word64ToWord32s (W64# w64) = Word32x2 (W32# (wordToWord32# (uncheckedShiftRL# w64 32#))) (W32# (wordToWord32# w64)) + #endif + #else ++#if __GLASGOW_HASKELL__ >= 902 ++word64ToWord32s :: Word64 -> Word32x2 ++word64ToWord32s (W64# w64) = Word32x2 (W32# (word64ToWord32# (uncheckedShiftRL64# w64 32#))) (W32# (word64ToWord32# w64)) ++#else + word64ToWord32s :: Word64 -> Word32x2 + word64ToWord32s (W64# w64) = Word32x2 (W32# (word64ToWord# (uncheckedShiftRL64# w64 32#))) (W32# (word64ToWord# w64)) + #endif ++#endif + + wordToChar :: Word -> Char + wordToChar (W# word) = C# (chr# (word2Int# word)) +diff --git a/Basement/PrimType.hs b/Basement/PrimType.hs +index f8ca292..b8fbaf7 100644 +--- a/Basement/PrimType.hs ++++ b/Basement/PrimType.hs +@@ -54,7 +54,11 @@ import Basement.Nat + import qualified Prelude (quot) + + #if WORD_SIZE_IN_BITS < 64 +-import GHC.IntWord64 ++#if __GLASGOW_HASKELL__ >= 902 ++import GHC.Exts ++#else ++import GHC.IntWord64 ++#endif + #endif + + #ifdef FOUNDATION_BOUNDS_CHECK +diff --git a/Basement/Types/OffsetSize.hs b/Basement/Types/OffsetSize.hs +index cd94492..b2903ba 100644 +--- a/Basement/Types/OffsetSize.hs ++++ b/Basement/Types/OffsetSize.hs +@@ -70,8 +70,12 @@ import Data.List (foldl') + import qualified Prelude + + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++import GHC.Exts ++#else + import GHC.IntWord64 + #endif ++#endif + + -- | File size in bytes + newtype FileSize = FileSize Word64 +@@ -225,7 +229,11 @@ countOfRoundUp alignment (CountOf n) = CountOf ((n + (alignment-1)) .&. compleme + + csizeOfSize :: CountOf Word8 -> CSize + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++csizeOfSize (CountOf (I# sz)) = CSize (W32# (wordToWord32# (int2Word# sz))) ++#else + csizeOfSize (CountOf (I# sz)) = CSize (W32# (int2Word# sz)) ++#endif + #else + #if __GLASGOW_HASKELL__ >= 904 + csizeOfSize (CountOf (I# sz)) = CSize (W64# (wordToWord64# (int2Word# sz))) +@@ -238,7 +246,11 @@ csizeOfSize (CountOf (I# sz)) = CSize (W64# (int2Word# sz)) + + csizeOfOffset :: Offset8 -> CSize + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++csizeOfOffset (Offset (I# sz)) = CSize (W32# (wordToWord32# (int2Word# sz))) ++#else + csizeOfOffset (Offset (I# sz)) = CSize (W32# (int2Word# sz)) ++#endif + #else + #if __GLASGOW_HASKELL__ >= 904 + csizeOfOffset (Offset (I# sz)) = CSize (W64# (wordToWord64# (int2Word# sz))) +@@ -250,7 +262,11 @@ csizeOfOffset (Offset (I# sz)) = CSize (W64# (int2Word# sz)) + sizeOfCSSize :: CSsize -> CountOf Word8 + sizeOfCSSize (CSsize (-1)) = error "invalid size: CSSize is -1" + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++sizeOfCSSize (CSsize (I32# sz)) = CountOf (I# (int32ToInt# sz)) ++#else + sizeOfCSSize (CSsize (I32# sz)) = CountOf (I# sz) ++#endif + #else + #if __GLASGOW_HASKELL__ >= 904 + sizeOfCSSize (CSsize (I64# sz)) = CountOf (I# (int64ToInt# sz)) +@@ -261,7 +277,11 @@ sizeOfCSSize (CSsize (I64# sz)) = CountOf (I# sz) + + sizeOfCSize :: CSize -> CountOf Word8 + #if WORD_SIZE_IN_BITS < 64 ++#if __GLASGOW_HASKELL__ >= 902 ++sizeOfCSize (CSize (W32# sz)) = CountOf (I# (word2Int# (word32ToWord# sz))) ++#else + sizeOfCSize (CSize (W32# sz)) = CountOf (I# (word2Int# sz)) ++#endif + #else + #if __GLASGOW_HASKELL__ >= 904 + sizeOfCSize (CSize (W64# sz)) = CountOf (I# (word2Int# (word64ToWord# sz))) diff --git a/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch b/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch deleted file mode 100644 index 97caf2cc9b..0000000000 --- a/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch +++ /dev/null @@ -1,303 +0,0 @@ -Taken from https://github.com/bos/bloomfilter/pull/20 - -From fb79b39c44404fd791a3bed973e9d844fb084f1e Mon Sep 17 00:00:00 2001 -From: Simon Jakobi <simon.jakobi@gmail.com> -Date: Fri, 12 Nov 2021 01:37:36 +0100 -Subject: [PATCH] Fix build with GHC 9.2 - -The `FastShift.shift{L,R}` methods are replaced with `unsafeShift{L,R}` -introduced in base-4.5. - -Fixes #19. ---- - Data/BloomFilter.hs | 16 +++++------ - Data/BloomFilter/Hash.hs | 15 +++++----- - Data/BloomFilter/Mutable.hs | 20 +++++++------- - Data/BloomFilter/Util.hs | 55 ++++++------------------------------- - bloomfilter.cabal | 2 +- - 5 files changed, 34 insertions(+), 74 deletions(-) - -diff --git a/Data/BloomFilter.hs b/Data/BloomFilter.hs -index 2210cef..6b47c21 100644 ---- a/Data/BloomFilter.hs -+++ b/Data/BloomFilter.hs -@@ -78,8 +78,8 @@ import Control.DeepSeq (NFData(..)) - import Data.Array.Base (unsafeAt) - import qualified Data.Array.Base as ST - import Data.Array.Unboxed (UArray) --import Data.Bits ((.&.)) --import Data.BloomFilter.Util (FastShift(..), (:*)(..)) -+import Data.Bits ((.&.), unsafeShiftL, unsafeShiftR) -+import Data.BloomFilter.Util ((:*)(..)) - import qualified Data.BloomFilter.Mutable as MB - import qualified Data.BloomFilter.Mutable.Internal as MB - import Data.BloomFilter.Mutable.Internal (Hash, MBloom) -@@ -98,7 +98,7 @@ data Bloom a = B { - } - - instance Show (Bloom a) where -- show ub = "Bloom { " ++ show ((1::Int) `shiftL` shift ub) ++ " bits } " -+ show ub = "Bloom { " ++ show ((1::Int) `unsafeShiftL` shift ub) ++ " bits } " - - instance NFData (Bloom a) where - rnf !_ = () -@@ -172,7 +172,7 @@ singleton hash numBits elt = create hash numBits (\mb -> MB.insert mb elt) - -- | Given a filter's mask and a hash value, compute an offset into - -- a word array and a bit offset within that word. - hashIdx :: Int -> Word32 -> (Int :* Int) --hashIdx mask x = (y `shiftR` logBitsInHash) :* (y .&. hashMask) -+hashIdx mask x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask) - where hashMask = 31 -- bitsInHash - 1 - y = fromIntegral x .&. mask - -@@ -191,7 +191,7 @@ hashesU ub elt = hashIdx (mask ub) `map` hashes ub elt - -- /still/ some possibility that @True@ will be returned. - elem :: a -> Bloom a -> Bool - elem elt ub = all test (hashesU ub elt) -- where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) /= 0 -+ where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` bit) /= 0 - - modify :: (forall s. (MBloom s a -> ST s z)) -- ^ mutation function (result is discarded) - -> Bloom a -@@ -255,11 +255,11 @@ insertList elts = modify $ \mb -> mapM_ (MB.insert mb) elts - -- is /still/ some possibility that @True@ will be returned. - notElem :: a -> Bloom a -> Bool - notElem elt ub = any test (hashesU ub elt) -- where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) == 0 -+ where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` bit) == 0 - - -- | Return the size of an immutable Bloom filter, in bits. - length :: Bloom a -> Int --length = shiftL 1 . shift -+length = unsafeShiftL 1 . shift - - -- | Build an immutable Bloom filter from a seed value. The seeding - -- function populates the filter as follows. -@@ -318,7 +318,7 @@ fromList hashes numBits = unfold hashes numBits convert - logPower2 :: Int -> Int - logPower2 k = go 0 k - where go j 1 = j -- go j n = go (j+1) (n `shiftR` 1) -+ go j n = go (j+1) (n `unsafeShiftR` 1) - - -- $overview - -- -diff --git a/Data/BloomFilter/Hash.hs b/Data/BloomFilter/Hash.hs -index 132a3a4..d071fd4 100644 ---- a/Data/BloomFilter/Hash.hs -+++ b/Data/BloomFilter/Hash.hs -@@ -38,8 +38,7 @@ module Data.BloomFilter.Hash - ) where - - import Control.Monad (foldM) --import Data.Bits ((.&.), (.|.), xor) --import Data.BloomFilter.Util (FastShift(..)) -+import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR, xor) - import Data.List (unfoldr) - import Data.Int (Int8, Int16, Int32, Int64) - import Data.Word (Word8, Word16, Word32, Word64) -@@ -91,11 +90,11 @@ class Hashable a where - -> Word64 -- ^ salt - -> IO Word64 - hashIO64 v salt = do -- let s1 = fromIntegral (salt `shiftR` 32) .&. maxBound -+ let s1 = fromIntegral (salt `unsafeShiftR` 32) .&. maxBound - s2 = fromIntegral salt - h1 <- hashIO32 v s1 - h2 <- hashIO32 v s2 -- return $ (fromIntegral h1 `shiftL` 32) .|. fromIntegral h2 -+ return $ (fromIntegral h1 `unsafeShiftL` 32) .|. fromIntegral h2 - - -- | Compute a 32-bit hash. - hash32 :: Hashable a => a -> Word32 -@@ -149,8 +148,8 @@ cheapHashes :: Hashable a => Int -- ^ number of hashes to compute - cheapHashes k v = go 0 - where go i | i == j = [] - | otherwise = hash : go (i + 1) -- where !hash = h1 + (h2 `shiftR` i) -- h1 = fromIntegral (h `shiftR` 32) -+ where !hash = h1 + (h2 `unsafeShiftR` i) -+ h1 = fromIntegral (h `unsafeShiftR` 32) - h2 = fromIntegral h - h = hashSalt64 0x9150a946c4a8966e v - j = fromIntegral k -@@ -163,7 +162,7 @@ instance Hashable Integer where - (salt `xor` 0x3ece731e) - | otherwise = hashIO32 (unfoldr go k) salt - where go 0 = Nothing -- go i = Just (fromIntegral i :: Word32, i `shiftR` 32) -+ go i = Just (fromIntegral i :: Word32, i `unsafeShiftR` 32) - - instance Hashable Bool where - hashIO32 = hashOne32 -@@ -224,7 +223,7 @@ instance Hashable Word64 where - -- | A fast unchecked shift. Nasty, but otherwise GHC 6.8.2 does a - -- test and branch on every shift. - div4 :: CSize -> CSize --div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `shiftR` 2) -+div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `unsafeShiftR` 2) - - alignedHash :: Ptr a -> CSize -> Word32 -> IO Word32 - alignedHash ptr bytes salt -diff --git a/Data/BloomFilter/Mutable.hs b/Data/BloomFilter/Mutable.hs -index edff1fc..0bb5cc9 100644 ---- a/Data/BloomFilter/Mutable.hs -+++ b/Data/BloomFilter/Mutable.hs -@@ -65,9 +65,9 @@ module Data.BloomFilter.Mutable - import Control.Monad (liftM, forM_) - import Control.Monad.ST (ST) - import Data.Array.Base (unsafeRead, unsafeWrite) --import Data.Bits ((.&.), (.|.)) -+import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR) - import Data.BloomFilter.Array (newArray) --import Data.BloomFilter.Util (FastShift(..), (:*)(..), nextPowerOfTwo) -+import Data.BloomFilter.Util ((:*)(..), nextPowerOfTwo) - import Data.Word (Word32) - import Data.BloomFilter.Mutable.Internal - -@@ -86,9 +86,9 @@ new hash numBits = MB hash shft msk `liftM` newArray numElems numBytes - | numBits > maxHash = maxHash - | isPowerOfTwo numBits = numBits - | otherwise = nextPowerOfTwo numBits -- numElems = max 2 (twoBits `shiftR` logBitsInHash) -- numBytes = numElems `shiftL` logBytesInHash -- trueBits = numElems `shiftL` logBitsInHash -+ numElems = max 2 (twoBits `unsafeShiftR` logBitsInHash) -+ numBytes = numElems `unsafeShiftL` logBytesInHash -+ trueBits = numElems `unsafeShiftL` logBitsInHash - shft = logPower2 trueBits - msk = trueBits - 1 - isPowerOfTwo n = n .&. (n - 1) == 0 -@@ -109,7 +109,7 @@ logBytesInHash = 2 -- logPower2 (sizeOf (undefined :: Hash)) - -- | Given a filter's mask and a hash value, compute an offset into - -- a word array and a bit offset within that word. - hashIdx :: Int -> Word32 -> (Int :* Int) --hashIdx msk x = (y `shiftR` logBitsInHash) :* (y .&. hashMask) -+hashIdx msk x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask) - where hashMask = 31 -- bitsInHash - 1 - y = fromIntegral x .&. msk - -@@ -125,7 +125,7 @@ insert mb elt = do - let mu = bitArray mb - forM_ (hashesM mb elt) $ \(word :* bit) -> do - old <- unsafeRead mu word -- unsafeWrite mu word (old .|. (1 `shiftL` bit)) -+ unsafeWrite mu word (old .|. (1 `unsafeShiftL` bit)) - - -- | Query a mutable Bloom filter for membership. If the value is - -- present, return @True@. If the value is not present, there is -@@ -135,7 +135,7 @@ elem elt mb = loop (hashesM mb elt) - where mu = bitArray mb - loop ((word :* bit):wbs) = do - i <- unsafeRead mu word -- if i .&. (1 `shiftL` bit) == 0 -+ if i .&. (1 `unsafeShiftL` bit) == 0 - then return False - else loop wbs - loop _ = return True -@@ -145,7 +145,7 @@ elem elt mb = loop (hashesM mb elt) - - -- | Return the size of a mutable Bloom filter, in bits. - length :: MBloom s a -> Int --length = shiftL 1 . shift -+length = unsafeShiftL 1 . shift - - - -- | Slow, crummy way of computing the integer log of an integer known -@@ -153,7 +153,7 @@ length = shiftL 1 . shift - logPower2 :: Int -> Int - logPower2 k = go 0 k - where go j 1 = j -- go j n = go (j+1) (n `shiftR` 1) -+ go j n = go (j+1) (n `unsafeShiftR` 1) - - -- $overview - -- -diff --git a/Data/BloomFilter/Util.hs b/Data/BloomFilter/Util.hs -index 7f695dc..6ade6e5 100644 ---- a/Data/BloomFilter/Util.hs -+++ b/Data/BloomFilter/Util.hs -@@ -2,15 +2,11 @@ - - module Data.BloomFilter.Util - ( -- FastShift(..) -- , nextPowerOfTwo -+ nextPowerOfTwo - , (:*)(..) - ) where - --import Data.Bits ((.|.)) --import qualified Data.Bits as Bits --import GHC.Base --import GHC.Word -+import Data.Bits ((.|.), unsafeShiftR) - - -- | A strict pair type. - data a :* b = !a :* !b -@@ -22,46 +18,11 @@ nextPowerOfTwo :: Int -> Int - {-# INLINE nextPowerOfTwo #-} - nextPowerOfTwo n = - let a = n - 1 -- b = a .|. (a `shiftR` 1) -- c = b .|. (b `shiftR` 2) -- d = c .|. (c `shiftR` 4) -- e = d .|. (d `shiftR` 8) -- f = e .|. (e `shiftR` 16) -- g = f .|. (f `shiftR` 32) -- in case we're on a 64-bit host -+ b = a .|. (a `unsafeShiftR` 1) -+ c = b .|. (b `unsafeShiftR` 2) -+ d = c .|. (c `unsafeShiftR` 4) -+ e = d .|. (d `unsafeShiftR` 8) -+ f = e .|. (e `unsafeShiftR` 16) -+ g = f .|. (f `unsafeShiftR` 32) -- in case we're on a 64-bit host - !h = g + 1 - in h -- ---- | This is a workaround for poor optimisation in GHC 6.8.2. It ---- fails to notice constant-width shifts, and adds a test and branch ---- to every shift. This imposes about a 10% performance hit. --class FastShift a where -- shiftL :: a -> Int -> a -- shiftR :: a -> Int -> a -- --instance FastShift Word32 where -- {-# INLINE shiftL #-} -- shiftL (W32# x#) (I# i#) = W32# (x# `uncheckedShiftL#` i#) -- -- {-# INLINE shiftR #-} -- shiftR (W32# x#) (I# i#) = W32# (x# `uncheckedShiftRL#` i#) -- --instance FastShift Word64 where -- {-# INLINE shiftL #-} -- shiftL (W64# x#) (I# i#) = W64# (x# `uncheckedShiftL64#` i#) -- -- {-# INLINE shiftR #-} -- shiftR (W64# x#) (I# i#) = W64# (x# `uncheckedShiftRL64#` i#) -- --instance FastShift Int where -- {-# INLINE shiftL #-} -- shiftL (I# x#) (I# i#) = I# (x# `iShiftL#` i#) -- -- {-# INLINE shiftR #-} -- shiftR (I# x#) (I# i#) = I# (x# `iShiftRA#` i#) -- --instance FastShift Integer where -- {-# INLINE shiftL #-} -- shiftL = Bits.shiftL -- -- {-# INLINE shiftR #-} -- shiftR = Bits.shiftR -diff --git a/bloomfilter.cabal b/bloomfilter.cabal -index 821a5d7..c621f7f 100644 ---- a/bloomfilter.cabal -+++ b/bloomfilter.cabal -@@ -18,7 +18,7 @@ extra-source-files: README.markdown cbits/lookup3.c cbits/lookup3.h - library - build-depends: - array, -- base >= 4.4 && < 5, -+ base >= 4.5 && < 5, - bytestring >= 0.9, - deepseq - exposed-modules: Data.BloomFilter diff --git a/gnu/packages/patches/ghc-memory-fix-32bit.patch b/gnu/packages/patches/ghc-memory-fix-32bit.patch new file mode 100644 index 0000000000..cb81b42521 --- /dev/null +++ b/gnu/packages/patches/ghc-memory-fix-32bit.patch @@ -0,0 +1,40 @@ +https://github.com/vincenthz/hs-memory/commit/2738929ce15b4c8704bbbac24a08539b5d4bf30e.patch +https://github.com/vincenthz/hs-memory/pull/99 +Adjusted so the '904' becomes '902' + +From 2738929ce15b4c8704bbbac24a08539b5d4bf30e Mon Sep 17 00:00:00 2001 +From: sternenseemann <sternenseemann@systemli.org> +Date: Mon, 14 Aug 2023 10:51:30 +0200 +Subject: [PATCH] Data.Memory.Internal.CompatPrim64: fix 32 bit with GHC >= 9.4 + +Since 9.4, GHC.Prim exports Word64# operations like timesWord64# even on +i686 whereas GHC.IntWord64 no longer exists. Therefore, we can just use +the ready made solution. + +Closes #98, as it should be the better solution. +--- + Data/Memory/Internal/CompatPrim64.hs | 4 ++++ + 1 file changed, 4 insertions(+) + +diff --git a/Data/Memory/Internal/CompatPrim64.hs b/Data/Memory/Internal/CompatPrim64.hs +index b9eef8a..a134c88 100644 +--- a/Data/Memory/Internal/CompatPrim64.hs ++++ b/Data/Memory/Internal/CompatPrim64.hs +@@ -150,6 +150,7 @@ w64# :: Word# -> Word# -> Word# -> Word64# + w64# w _ _ = w + + #elif WORD_SIZE_IN_BITS == 32 ++#if __GLASGOW_HASKELL__ < 902 + import GHC.IntWord64 + import GHC.Prim (Word#) + +@@ -158,6 +159,9 @@ timesWord64# a b = + let !ai = word64ToInt64# a + !bi = word64ToInt64# b + in int64ToWord64# (timesInt64# ai bi) ++#else ++import GHC.Prim ++#endif + + w64# :: Word# -> Word# -> Word# -> Word64# + w64# _ hw lw = diff --git a/gnu/packages/patches/ghc-persistent-fix-32bit.patch b/gnu/packages/patches/ghc-persistent-fix-32bit.patch new file mode 100644 index 0000000000..d0aace2445 --- /dev/null +++ b/gnu/packages/patches/ghc-persistent-fix-32bit.patch @@ -0,0 +1,25 @@ +https://sources.debian.org/data/main/h/haskell-persistent/2.13.3.5-2/debian/patches/fix-tests-32-bit +Inspired by: https://github.com/yesodweb/persistent/pull/1429 + +--- a/test/Database/Persist/THSpec.hs ++++ b/test/Database/Persist/THSpec.hs +@@ -25,6 +25,7 @@ module Database.Persist.THSpec where + + import Control.Applicative (Const(..)) + import Data.Aeson (decode, encode) ++import Data.Bits (bitSizeMaybe) + import Data.ByteString.Lazy.Char8 () + import Data.Coerce + import Data.Functor.Identity (Identity(..)) +@@ -237,7 +238,10 @@ spec = describe "THSpec" $ do + it "should have usual haskell name" $ do + fieldHaskell `shouldBe` FieldNameHS "Id" + it "should have correct underlying sql type" $ do +- fieldSqlType `shouldBe` SqlInt64 ++ fieldSqlType `shouldBe` ++ if bitSizeMaybe (0 :: Int) <= Just 32 ++ then SqlInt32 ++ else SqlInt64 + it "should have correct haskell type" $ do + fieldType `shouldBe` FTTypeCon Nothing "Int" + |