From 848c962ce1a40be302b61110f8f85f641cf54fc9 Mon Sep 17 00:00:00 2001
From: Ryan Scott <rscott@galois.com>
Date: Thu, 28 Jul 2022 08:35:02 -0400
Subject: [PATCH] Remove outdated Hackage patches

---
 patches/Spock-core-0.14.0.0.patch       |  22 -
 patches/arithmoi-0.12.0.1.patch         |  13 -
 patches/basement-0.0.14.patch           | 530 ------------------------
 patches/cereal-0.5.8.2.patch            |  16 -
 patches/foundation-0.0.28.patch         |  76 ----
 patches/generic-data-0.9.2.1.patch      |  36 --
 patches/ghc-check-0.5.0.6.patch         |  49 ---
 patches/heterocephalus-1.0.5.6.patch    |  18 -
 patches/libBF-0.6.3.patch               |  16 -
 patches/vector-algorithms-0.8.0.4.patch | 153 -------
 10 files changed, 929 deletions(-)
 delete mode 100644 patches/Spock-core-0.14.0.0.patch
 delete mode 100644 patches/arithmoi-0.12.0.1.patch
 delete mode 100644 patches/basement-0.0.14.patch
 delete mode 100644 patches/cereal-0.5.8.2.patch
 delete mode 100644 patches/foundation-0.0.28.patch
 delete mode 100644 patches/generic-data-0.9.2.1.patch
 delete mode 100644 patches/ghc-check-0.5.0.6.patch
 delete mode 100644 patches/heterocephalus-1.0.5.6.patch
 delete mode 100644 patches/libBF-0.6.3.patch
 delete mode 100644 patches/vector-algorithms-0.8.0.4.patch

diff --git a/patches/Spock-core-0.14.0.0.patch b/patches/Spock-core-0.14.0.0.patch
deleted file mode 100644
index 85b0bb1e..00000000
--- a/patches/Spock-core-0.14.0.0.patch
+++ /dev/null
@@ -1,22 +0,0 @@
-diff --git a/src/Web/Spock/Core.hs b/src/Web/Spock/Core.hs
-index 88d31cc..31345c3 100644
---- a/src/Web/Spock/Core.hs
-+++ b/src/Web/Spock/Core.hs
-@@ -77,7 +77,7 @@ instance RouteM SpockCtxT where
-     addMiddleware = SpockCtxT . AR.middleware
-     wireAny m action =
-         SpockCtxT $
--        do hookLift <- lift $ asks unLiftHooked
-+        do hookLift <- lift $ asks (\e -> unLiftHooked e)
-            case m of
-              MethodAny ->
-                  do forM_ allStdMethods $ \mReg ->
-@@ -103,7 +103,7 @@ withPrehookImpl hook (SpockCtxT hookBody) =
- wireRouteImpl :: forall xs ctx m ps. (HasRep xs, Monad m) => SpockMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- wireRouteImpl m path action =
-     SpockCtxT $
--    do hookLift <- lift $ asks unLiftHooked
-+    do hookLift <- lift $ asks (\e -> unLiftHooked e)
-        let actionPacker :: HVectElim xs (ActionCtxT ctx m ()) -> HVect xs -> ActionCtxT () m ()
-            actionPacker act captures = hookLift (uncurry act captures)
-        case m of
diff --git a/patches/arithmoi-0.12.0.1.patch b/patches/arithmoi-0.12.0.1.patch
deleted file mode 100644
index 20161313..00000000
--- a/patches/arithmoi-0.12.0.1.patch
+++ /dev/null
@@ -1,13 +0,0 @@
-diff --git a/Math/NumberTheory/Primes/Testing/Probabilistic.hs b/Math/NumberTheory/Primes/Testing/Probabilistic.hs
-index 6497617..423f6d3 100644
---- a/Math/NumberTheory/Primes/Testing/Probabilistic.hs
-+++ b/Math/NumberTheory/Primes/Testing/Probabilistic.hs
-@@ -22,7 +22,7 @@ module Math.NumberTheory.Primes.Testing.Probabilistic
- import Data.Bits
- import Data.Mod
- import Data.Proxy
--import GHC.Base
-+import GHC.Base (Int(..), Word(..), (-#), (<#), isTrue#)
- import GHC.Integer.GMP.Internals
- import GHC.TypeNats (KnownNat, SomeNat(..), someNatVal)
- 
diff --git a/patches/basement-0.0.14.patch b/patches/basement-0.0.14.patch
deleted file mode 100644
index 1b052052..00000000
--- a/patches/basement-0.0.14.patch
+++ /dev/null
@@ -1,530 +0,0 @@
-diff --git a/Basement/Bits.hs b/Basement/Bits.hs
-index ae73b8c..4a1e5ac 100644
---- a/Basement/Bits.hs
-+++ b/Basement/Bits.hs
-@@ -31,6 +31,7 @@ module Basement.Bits
- 
- import Basement.Compat.Base
- import Basement.Compat.Natural
-+import Basement.HeadHackageUtils
- import Basement.Numerical.Additive
- import Basement.Numerical.Subtractive
- import Basement.Numerical.Multiplicative
-@@ -291,9 +292,9 @@ instance FiniteBitsOps Word where
-     rotateL w (CountOf i) = w `OldBits.rotateL` i
-     rotateR w (CountOf i) = w `OldBits.rotateR` i
-     bitFlip = OldBits.complement
--    popCount (W# x#) = CountOf $ wordToInt (W# (popCnt64# x#))
--    countLeadingZeros (W# w#) = CountOf $ wordToInt (W# (clz64# w#))
--    countTrailingZeros (W# w#) = CountOf $ wordToInt (W# (ctz64# w#))
-+    popCount (W# x#) = CountOf $ wordToInt (W# (popCnt64# (wordToWord64Compat# x#)))
-+    countLeadingZeros (W# w#) = CountOf $ wordToInt (W# (clz64# (wordToWord64Compat# w#)))
-+    countTrailingZeros (W# w#) = CountOf $ wordToInt (W# (ctz64# (wordToWord64Compat# w#)))
- #else
- instance FiniteBitsOps Word where
-     numberOfBits _ = 32
-@@ -433,9 +434,9 @@ instance FiniteBitsOps Int64 where
-     rotateL w (CountOf i) = w `OldBits.rotateL` i
-     rotateR w (CountOf i) = w `OldBits.rotateR` i
-     bitFlip = OldBits.complement
--    popCount (I64# x#) = CountOf $ wordToInt (W# (popCnt64# (int2Word# x#)))
--    countLeadingZeros (I64# w#) = CountOf $ wordToInt (W# (clz64# (int2Word# w#)))
--    countTrailingZeros (I64# w#) = CountOf $ wordToInt (W# (ctz64# (int2Word# w#)))
-+    popCount (I64# x#) = CountOf $ wordToInt (W# (popCnt64# (int64ToWord64Compat# x#)))
-+    countLeadingZeros (I64# w#) = CountOf $ wordToInt (W# (clz64# (int64ToWord64Compat# w#)))
-+    countTrailingZeros (I64# w#) = CountOf $ wordToInt (W# (ctz64# (int64ToWord64Compat# w#)))
- instance BitOps Int64 where
-     (.&.)    a b    = (a OldBits..&. b)
-     (.|.)    a b    = (a OldBits..|. b)
-diff --git a/Basement/Cast.hs b/Basement/Cast.hs
-index e89de3e..1502100 100644
---- a/Basement/Cast.hs
-+++ b/Basement/Cast.hs
-@@ -19,6 +19,7 @@ import qualified Basement.Block.Base as Block
- import           Basement.Compat.Base
- import           Basement.Compat.Natural
- import           Basement.Compat.Primitive
-+import           Basement.HeadHackageUtils
- import           Basement.Numerical.Number
- import           Basement.Numerical.Conversion
- import           Basement.PrimType
-@@ -82,24 +83,24 @@ instance Cast Word   Int where
- 
- #if WORD_SIZE_IN_BITS == 64
- instance Cast Word   Word64 where
--    cast (W# w) = W64# w
-+    cast (W# w) = W64# (wordToWord64Compat# w)
- instance Cast Word64 Word where
--    cast (W64# w) = W# w
-+    cast (W64# w) = W# (word64ToWordCompat# w)
- 
- instance Cast Word   Int64 where
--    cast (W# w) = I64# (word2Int# w)
-+    cast (W# w) = I64# (intToInt64Compat# (word2Int# w))
- instance Cast Int64  Word where
--    cast (I64# i) = W# (int2Word# i)
-+    cast (I64# i) = W# (int2Word# (int64ToIntCompat# i))
- 
- instance Cast Int    Int64 where
--    cast (I# i) = I64# i
-+    cast (I# i) = I64# (intToInt64Compat# i)
- instance Cast Int64  Int where
--    cast (I64# i) = I# i
-+    cast (I64# i) = I# (int64ToIntCompat# i)
- 
- instance Cast Int    Word64 where
--    cast (I# i) = W64# (int2Word# i)
-+    cast (I# i) = W64# (wordToWord64Compat# (int2Word# i))
- instance Cast Word64 Int where
--    cast (W64# w) = I# (word2Int# w)
-+    cast (W64# w) = I# (word2Int# (word64ToWordCompat# w))
- #else
- instance Cast Word   Word32 where
-     cast (W# w) = W32# (wordToWord32# w)
-diff --git a/Basement/From.hs b/Basement/From.hs
-index 700e9ec..acd39e4 100644
---- a/Basement/From.hs
-+++ b/Basement/From.hs
-@@ -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
-@@ -55,6 +59,7 @@ import           Basement.PrimType (PrimType, PrimSize)
- import           Basement.Types.OffsetSize
- import           Basement.Compat.Natural
- import           Basement.Compat.Primitive
-+import           Basement.HeadHackageUtils
- import qualified Prelude (fromIntegral)
- 
- -- nat instances
-@@ -271,11 +276,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
--    from = narrow . unZn64 where narrow (W64# w) = W8# (wordToWord8# (word64ToWord# w))
-+    from = narrow . unZn64 where narrow (W64# w) = W8# (wordToWord8# (word64ToWordCompat# w))
- instance (KnownNat n, NatWithinBound Word16 n) => From (Zn64 n) Word16 where
--    from = narrow . unZn64 where narrow (W64# w) = W16# (wordToWord16# (word64ToWord# w))
-+    from = narrow . unZn64 where narrow (W64# w) = W16# (wordToWord16# (word64ToWordCompat# w))
- instance (KnownNat n, NatWithinBound Word32 n) => From (Zn64 n) Word32 where
--    from = narrow . unZn64 where narrow (W64# w) = W32# (wordToWord32# (word64ToWord# w))
-+    from = narrow . unZn64 where narrow (W64# w) = W32# (wordToWord32# (word64ToWordCompat# w))
- instance From (Zn64 n) Word64 where
-     from = unZn64
- instance From (Zn64 n) Word128 where
-@@ -284,11 +289,11 @@ instance From (Zn64 n) Word256 where
-     from = from . unZn64
- 
- instance (KnownNat n, NatWithinBound Word8 n) => From (Zn n) Word8 where
--    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W8# (wordToWord8# (word64ToWord# w))
-+    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W8# (wordToWord8# (word64ToWordCompat# w))
- instance (KnownNat n, NatWithinBound Word16 n) => From (Zn n) Word16 where
--    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W16# (wordToWord16# (word64ToWord# w))
-+    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W16# (wordToWord16# (word64ToWordCompat# w))
- instance (KnownNat n, NatWithinBound Word32 n) => From (Zn n) Word32 where
--    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W32# (wordToWord32# (word64ToWord# w))
-+    from = narrow . naturalToWord64 . unZn where narrow (W64# w) = W32# (wordToWord32# (word64ToWordCompat# w))
- instance (KnownNat n, NatWithinBound Word64 n) => From (Zn n) Word64 where
-     from = naturalToWord64 . unZn
- instance (KnownNat n, NatWithinBound Word128 n) => From (Zn n) Word128 where
-diff --git a/Basement/HeadHackageUtils.hs b/Basement/HeadHackageUtils.hs
-new file mode 100644
-index 0000000..e4294ee
---- /dev/null
-+++ b/Basement/HeadHackageUtils.hs
-@@ -0,0 +1,85 @@
-+{-# LANGUAGE CPP #-}
-+{-# LANGUAGE MagicHash #-}
-+module Basement.HeadHackageUtils where
-+
-+import GHC.Exts
-+
-+#if __GLASGOW_HASKELL__ >= 903
-+and64Compat# :: Word64# -> Word64# -> Word64#
-+and64Compat# = and64#
-+
-+int64ToIntCompat# :: Int64# -> Int#
-+int64ToIntCompat# = int64ToInt#
-+
-+intToInt64Compat# :: Int# -> Int64#
-+intToInt64Compat# = intToInt64#
-+
-+int64ToWord64Compat# :: Int64# -> Word64#
-+int64ToWord64Compat# = int64ToWord64#
-+
-+or64Compat# :: Word64# -> Word64# -> Word64#
-+or64Compat# = or64#
-+
-+plusInt64Compat# :: Int64# -> Int64# -> Int64#
-+plusInt64Compat# = plusInt64#
-+
-+plusWord64Compat# :: Word64# -> Word64# -> Word64#
-+plusWord64Compat# = plusWord64#
-+
-+uncheckedShiftL64Compat# :: Word64# -> Int# -> Word64#
-+uncheckedShiftL64Compat# = uncheckedShiftL64#
-+
-+uncheckedShiftRL64Compat# :: Word64# -> Int# -> Word64#
-+uncheckedShiftRL64Compat# = uncheckedShiftRL64#
-+
-+word64ToInt64Compat# :: Word64# -> Int64#
-+word64ToInt64Compat# = word64ToInt64#
-+
-+word64ToWordCompat# :: Word64# -> Word#
-+word64ToWordCompat# = word64ToWord#
-+
-+wordToWord64Compat# :: Word# -> Word64#
-+wordToWord64Compat# = wordToWord64#
-+
-+xor64Compat# :: Word64# -> Word64# -> Word64#
-+xor64Compat# = xor64#
-+#else
-+and64Compat# :: Word# -> Word# -> Word#
-+and64Compat# = and#
-+
-+int64ToIntCompat# :: Int# -> Int#
-+int64ToIntCompat# x = x
-+
-+intToInt64Compat# :: Int# -> Int#
-+intToInt64Compat# x = x
-+
-+int64ToWord64Compat# :: Int# -> Word#
-+int64ToWord64Compat# = int2Word#
-+
-+or64Compat# :: Word# -> Word# -> Word#
-+or64Compat# = or#
-+
-+plusInt64Compat# :: Int# -> Int# -> Int#
-+plusInt64Compat# = (+#)
-+
-+plusWord64Compat# :: Word# -> Word# -> Word#
-+plusWord64Compat# = plusWord#
-+
-+uncheckedShiftL64Compat# :: Word# -> Int# -> Word#
-+uncheckedShiftL64Compat# = uncheckedShiftL#
-+
-+uncheckedShiftRL64Compat# :: Word# -> Int# -> Word#
-+uncheckedShiftRL64Compat# = uncheckedShiftRL#
-+
-+word64ToInt64Compat# :: Word# -> Int#
-+word64ToInt64Compat# = word2Int#
-+
-+word64ToWordCompat# :: Word# -> Word#
-+word64ToWordCompat# x = x
-+
-+wordToWord64Compat# :: Word# -> Word#
-+wordToWord64Compat# x = x
-+
-+xor64Compat# :: Word# -> Word# -> Word#
-+xor64Compat# = xor#
-+#endif
-diff --git a/Basement/IntegralConv.hs b/Basement/IntegralConv.hs
-index f441675..76bd105 100644
---- a/Basement/IntegralConv.hs
-+++ b/Basement/IntegralConv.hs
-@@ -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
-+import Basement.HeadHackageUtils
- import Basement.Compat.Primitive
- import Basement.Numerical.Number
- import Basement.Numerical.Conversion
-@@ -138,13 +143,13 @@ instance IntegralDownsize Int64 Int where
-     integralDownsizeCheck = integralDownsizeBounded integralDownsize
- 
- instance IntegralDownsize Word64 Word8 where
--    integralDownsize      (W64# i) = W8# (wordToWord8# (word64ToWord# i))
-+    integralDownsize      (W64# i) = W8# (wordToWord8# (word64ToWordCompat# i))
-     integralDownsizeCheck = integralDownsizeBounded integralDownsize
- instance IntegralDownsize Word64 Word16 where
--    integralDownsize      (W64# i) = W16# (wordToWord16# (word64ToWord# i))
-+    integralDownsize      (W64# i) = W16# (wordToWord16# (word64ToWordCompat# i))
-     integralDownsizeCheck = integralDownsizeBounded integralDownsize
- instance IntegralDownsize Word64 Word32 where
--    integralDownsize      (W64# i) = W32# (wordToWord32# (word64ToWord# i))
-+    integralDownsize      (W64# i) = W32# (wordToWord32# (word64ToWordCompat# i))
-     integralDownsizeCheck = integralDownsizeBounded integralDownsize
- 
- instance IntegralDownsize Word Word8 where
-diff --git a/Basement/Numerical/Additive.hs b/Basement/Numerical/Additive.hs
-index 256495d..b5b3e57 100644
---- a/Basement/Numerical/Additive.hs
-+++ b/Basement/Numerical/Additive.hs
-@@ -22,6 +22,7 @@ import           GHC.Prim (plusWord#, plusFloat#, (+#), (+##))
- import           GHC.Int
- import           GHC.Word
- import           Basement.Bounded
-+import           Basement.HeadHackageUtils
- import           Basement.Nat
- import           Basement.Types.Word128 (Word128)
- import           Basement.Types.Word256 (Word256)
-@@ -79,7 +80,7 @@ instance Additive Int32 where
- instance Additive Int64 where
-     azero = 0
- #if WORD_SIZE_IN_BITS == 64
--    (I64# a) + (I64# b) = I64# (a +# b)
-+    (I64# a) + (I64# b) = I64# (a `plusInt64Compat#` b)
- #else
-     (I64# a) + (I64# b) = I64# (a `plusInt64#` b)
- #endif
-@@ -107,7 +108,7 @@ instance Additive Word32 where
- instance Additive Word64 where
-     azero = 0
- #if WORD_SIZE_IN_BITS == 64
--    (W64# a) + (W64# b) = W64# (a `plusWord#` b)
-+    (W64# a) + (W64# b) = W64# (a `plusWord64Compat#` b)
- #else
-     (W64# a) + (W64# b) = W64# (int64ToWord64# (word64ToInt64# a `plusInt64#` word64ToInt64# b))
- #endif
-diff --git a/Basement/Numerical/Conversion.hs b/Basement/Numerical/Conversion.hs
-index 1bdab09..f8b48d9 100644
---- a/Basement/Numerical/Conversion.hs
-+++ b/Basement/Numerical/Conversion.hs
-@@ -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
- import GHC.Word
- import Basement.Compat.Primitive
-@@ -30,42 +34,42 @@ import GHC.IntWord64
- 
- intToInt64 :: Int -> Int64
- #if WORD_SIZE_IN_BITS == 64
--intToInt64 (I# i) = I64# i
-+intToInt64 (I# i) = I64# (intToInt64Compat# i)
- #else
- intToInt64 (I# i) = I64# (intToInt64# i)
- #endif
- 
- int64ToInt :: Int64 -> Int
- #if WORD_SIZE_IN_BITS == 64
--int64ToInt (I64# i) = I# i
-+int64ToInt (I64# i) = I# (int64ToIntCompat# i)
- #else
- int64ToInt (I64# i) = I# (int64ToInt# i)
- #endif
- 
- wordToWord64 :: Word -> Word64
- #if WORD_SIZE_IN_BITS == 64
--wordToWord64 (W# i) = W64# i
-+wordToWord64 (W# i) = W64# (wordToWord64Compat# i)
- #else
- wordToWord64 (W# i) = W64# (wordToWord64# i)
- #endif
- 
- word64ToWord :: Word64 -> Word
- #if WORD_SIZE_IN_BITS == 64
--word64ToWord (W64# i) = W# i
-+word64ToWord (W64# i) = W# (word64ToWordCompat# i)
- #else
- word64ToWord (W64# i) = W# (word64ToWord# i)
- #endif
- 
- word64ToInt64 :: Word64 -> Int64
- #if WORD_SIZE_IN_BITS == 64
--word64ToInt64 (W64# i) = I64# (word2Int# i)
-+word64ToInt64 (W64# i) = I64# (word64ToInt64Compat# i)
- #else
- word64ToInt64 (W64# i) = I64# (word64ToInt64# i)
- #endif
- 
- int64ToWord64 :: Int64 -> Word64
- #if WORD_SIZE_IN_BITS == 64
--int64ToWord64 (I64# i) = W64# (int2Word# i)
-+int64ToWord64 (I64# i) = W64# (int64ToWord64Compat# i)
- #else
- int64ToWord64 (I64# i) = W64# (int64ToWord64# i)
- #endif
-@@ -82,7 +86,7 @@ data Word32x2 = Word32x2 {-# UNPACK #-} !Word32
- 
- #if WORD_SIZE_IN_BITS == 64
- word64ToWord32s :: Word64 -> Word32x2
--word64ToWord32s (W64# w64) = Word32x2 (W32# (wordToWord32# (uncheckedShiftRL# w64 32#))) (W32# (wordToWord32# w64))
-+word64ToWord32s (W64# w64) = Word32x2 (W32# (wordToWord32# (word64ToWordCompat# (uncheckedShiftRL64Compat# w64 32#)))) (W32# (wordToWord32# (word64ToWordCompat# w64)))
- #else
- word64ToWord32s :: Word64 -> Word32x2
- word64ToWord32s (W64# w64) = Word32x2 (W32# (word64ToWord# (uncheckedShiftRL64# w64 32#))) (W32# (word64ToWord# w64))
-diff --git a/Basement/Types/OffsetSize.hs b/Basement/Types/OffsetSize.hs
-index 06b7d07..591e0a0 100644
---- a/Basement/Types/OffsetSize.hs
-+++ b/Basement/Types/OffsetSize.hs
-@@ -57,6 +57,7 @@ import Data.Bits
- import Basement.Compat.Base
- import Basement.Compat.C.Types
- import Basement.Compat.Semigroup
-+import Basement.HeadHackageUtils
- import Data.Proxy
- import Basement.Numerical.Number
- import Basement.Numerical.Additive
-@@ -227,14 +228,14 @@ csizeOfSize :: CountOf Word8 -> CSize
- #if WORD_SIZE_IN_BITS < 64
- csizeOfSize (CountOf (I# sz)) = CSize (W32# (int2Word# sz))
- #else
--csizeOfSize (CountOf (I# sz)) = CSize (W64# (int2Word# sz))
-+csizeOfSize (CountOf (I# sz)) = CSize (W64# (wordToWord64Compat# (int2Word# sz)))
- #endif
- 
- csizeOfOffset :: Offset8 -> CSize
- #if WORD_SIZE_IN_BITS < 64
- csizeOfOffset (Offset (I# sz)) = CSize (W32# (int2Word# sz))
- #else
--csizeOfOffset (Offset (I# sz)) = CSize (W64# (int2Word# sz))
-+csizeOfOffset (Offset (I# sz)) = CSize (W64# (wordToWord64Compat# (int2Word# sz)))
- #endif
- 
- sizeOfCSSize :: CSsize -> CountOf Word8
-@@ -242,14 +243,14 @@ sizeOfCSSize (CSsize (-1))      = error "invalid size: CSSize is -1"
- #if WORD_SIZE_IN_BITS < 64
- sizeOfCSSize (CSsize (I32# sz)) = CountOf (I# sz)
- #else
--sizeOfCSSize (CSsize (I64# sz)) = CountOf (I# sz)
-+sizeOfCSSize (CSsize (I64# sz)) = CountOf (I# (int64ToIntCompat# sz))
- #endif
- 
- sizeOfCSize :: CSize -> CountOf Word8
- #if WORD_SIZE_IN_BITS < 64
- sizeOfCSize (CSize (W32# sz)) = CountOf (I# (word2Int# sz))
- #else
--sizeOfCSize (CSize (W64# sz)) = CountOf (I# (word2Int# sz))
-+sizeOfCSize (CSize (W64# sz)) = CountOf (I# (word2Int# (word64ToWordCompat# sz)))
- #endif
- 
- natValCountOf :: forall n ty proxy . (KnownNat n, NatWithinBound (CountOf ty) n) => proxy n -> CountOf ty
-diff --git a/Basement/Types/Word128.hs b/Basement/Types/Word128.hs
-index 13d68fa..0a1f038 100644
---- a/Basement/Types/Word128.hs
-+++ b/Basement/Types/Word128.hs
-@@ -37,6 +37,7 @@ import           Foreign.Storable
- import           Basement.Compat.Base
- import           Basement.Compat.Natural
- import           Basement.Compat.Primitive (bool#)
-+import           Basement.HeadHackageUtils
- import           Basement.Numerical.Conversion
- import           Basement.Numerical.Number
- 
-@@ -128,10 +129,15 @@ instance Bits.Bits Word128 where
- #if WORD_SIZE_IN_BITS < 64
- (+) = applyBiWordOnNatural (Prelude.+)
- #else
--(+) (Word128 (W64# a1) (W64# a0)) (Word128 (W64# b1) (W64# b0)) = Word128 (W64# s1) (W64# s0)
-+(+) (Word128 (W64# a1) (W64# a0)) (Word128 (W64# b1) (W64# b0)) = Word128 (W64# (wordToWord64Compat# s1)) (W64# (wordToWord64Compat# s0))
-   where
--    !(# carry, s0 #) = plusWord2# a0 b0
--    s1               = plusWord# (plusWord# a1 b1) carry
-+    !a0' = word64ToWordCompat# a0
-+    !a1' = word64ToWordCompat# a1
-+    !b0' = word64ToWordCompat# b0
-+    !b1' = word64ToWordCompat# b1
-+
-+    !(# carry, s0 #) = plusWord2# a0' b0'
-+    s1               = plusWord# (plusWord# a1' b1') carry
- #endif
- 
- -- temporary available until native operation available
-diff --git a/Basement/Types/Word256.hs b/Basement/Types/Word256.hs
-index 62ed727..7244d6b 100644
---- a/Basement/Types/Word256.hs
-+++ b/Basement/Types/Word256.hs
-@@ -36,6 +36,7 @@ import           Foreign.Storable
- import           Basement.Compat.Base
- import           Basement.Compat.Natural
- import           Basement.Compat.Primitive (bool#)
-+import           Basement.HeadHackageUtils
- import           Basement.Numerical.Conversion
- import           Basement.Numerical.Number
- 
-@@ -149,12 +150,22 @@ instance Bits.Bits Word256 where
- #else
- (+) (Word256 (W64# a3) (W64# a2) (W64# a1) (W64# a0))
-     (Word256 (W64# b3) (W64# b2) (W64# b1) (W64# b0)) =
--    Word256 (W64# s3) (W64# s2) (W64# s1) (W64# s0)
-+    Word256 (W64# (wordToWord64Compat# s3)) (W64# (wordToWord64Compat# s2))
-+            (W64# (wordToWord64Compat# s1)) (W64# (wordToWord64Compat# s0))
-   where
--    !(# c0, s0 #) = plusWord2# a0 b0
--    !(# c1, s1 #) = plusWord3# a1 b1 c0
--    !(# c2, s2 #) = plusWord3# a2 b2 c1
--    !s3           = plusWord3NoCarry# a3 b3 c2
-+    !a0' = word64ToWordCompat# a0
-+    !a1' = word64ToWordCompat# a1
-+    !a2' = word64ToWordCompat# a2
-+    !a3' = word64ToWordCompat# a3
-+    !b0' = word64ToWordCompat# b0
-+    !b1' = word64ToWordCompat# b1
-+    !b2' = word64ToWordCompat# b2
-+    !b3' = word64ToWordCompat# b3
-+
-+    !(# c0, s0 #) = plusWord2# a0' b0'
-+    !(# c1, s1 #) = plusWord3# a1' b1' c0
-+    !(# c2, s2 #) = plusWord3# a2' b2' c1
-+    !s3           = plusWord3NoCarry# a3' b3' c2
- 
-     plusWord3NoCarry# a b c = plusWord# (plusWord# a b) c
-     plusWord3# a b c
-diff --git a/Basement/UArray/Mutable.hs b/Basement/UArray/Mutable.hs
-index 86f1147..dc08a8b 100644
---- a/Basement/UArray/Mutable.hs
-+++ b/Basement/UArray/Mutable.hs
-@@ -40,7 +40,7 @@ module Basement.UArray.Mutable
-     , withMutablePtrHint
-     ) where
- 
--import           GHC.Prim
-+import           GHC.Exts
- import           GHC.Types
- import           GHC.Ptr
- import           Basement.Compat.Base
-@@ -104,7 +104,7 @@ sub :: (PrimMonad prim, PrimType ty)
-     -> prim (MUArray ty (PrimState prim))
- sub (MUArray start sz back) dropElems' takeElems
-     | takeElems <= 0 = empty
--    | Just keepElems <- sz - dropElems, keepElems > 0 
-+    | Just keepElems <- sz - dropElems, keepElems > 0
-                      = pure $ MUArray (start `offsetPlusE` dropElems) (min (CountOf takeElems) keepElems) back
-     | otherwise      = empty
-   where
-diff --git a/basement.cabal b/basement.cabal
-index 7a60516..1d39b81 100644
---- a/basement.cabal
-+++ b/basement.cabal
-@@ -136,6 +136,8 @@ library
- 
-                      Basement.Terminal.Size
- 
-+                     Basement.HeadHackageUtils
-+
-   -- support and dependencies
-   if impl(ghc < 8.8)
-     buildable: False
diff --git a/patches/cereal-0.5.8.2.patch b/patches/cereal-0.5.8.2.patch
deleted file mode 100644
index 13a780e4..00000000
--- a/patches/cereal-0.5.8.2.patch
+++ /dev/null
@@ -1,16 +0,0 @@
-diff --git a/src/Data/Serialize/Get.hs b/src/Data/Serialize/Get.hs
-index 87fd159..c08ee3e 100644
---- a/src/Data/Serialize/Get.hs
-+++ b/src/Data/Serialize/Get.hs
-@@ -741,7 +741,11 @@ foreign import ccall unsafe "stg_uncheckedShiftL64"
- #endif
- 
- #else
-+# if __GLASGOW_HASKELL__ >= 903
-+shiftl_w64 (W64# w) (I# i) = W64# (w `uncheckedShiftL64#` i)
-+# else
- shiftl_w64 (W64# w) (I# i) = W64# (w `uncheckedShiftL#` i)
-+# endif
- #endif
- 
- #else
diff --git a/patches/foundation-0.0.28.patch b/patches/foundation-0.0.28.patch
deleted file mode 100644
index 7a2cae84..00000000
--- a/patches/foundation-0.0.28.patch
+++ /dev/null
@@ -1,76 +0,0 @@
-diff --git a/Foundation/Array/Bitmap.hs b/Foundation/Array/Bitmap.hs
-index 74386fb..d8c38d3 100644
---- a/Foundation/Array/Bitmap.hs
-+++ b/Foundation/Array/Bitmap.hs
-@@ -13,6 +13,7 @@
- -- unnecessary churn.
- --
- {-# LANGUAGE BangPatterns #-}
-+{-# LANGUAGE CPP #-}
- {-# LANGUAGE DeriveDataTypeable #-}
- module Foundation.Array.Bitmap
-     ( Bitmap
-@@ -43,6 +44,9 @@ import           Basement.Monad
- import qualified Foundation.Collection as C
- import           Foundation.Numerical
- import           Data.Bits
-+#if __GLASGOW_HASKELL__ >= 903
-+  hiding ((.<<.), (.>>.))
-+#endif
- import           Foundation.Bits
- import           GHC.ST
- import qualified Data.List
-diff --git a/Foundation/Bits.hs b/Foundation/Bits.hs
-index 7952f35..295314d 100644
---- a/Foundation/Bits.hs
-+++ b/Foundation/Bits.hs
-@@ -1,4 +1,5 @@
- -- Extra bits stuff
-+{-# LANGUAGE CPP #-}
- module Foundation.Bits
-     ( (.<<.)
-     , (.>>.)
-@@ -10,6 +11,9 @@ module Foundation.Bits
- import Basement.Compat.Base
- import Foundation.Numerical
- import Data.Bits
-+#if __GLASGOW_HASKELL__ >= 903
-+  hiding ((.<<.), (.>>.))
-+#endif
- 
- -- | Unsafe Shift Left Operator
- (.<<.) :: Bits a => a -> Int -> a
-diff --git a/Foundation/Collection/Foldable.hs b/Foundation/Collection/Foldable.hs
-index c019000..14cf052 100644
---- a/Foundation/Collection/Foldable.hs
-+++ b/Foundation/Collection/Foldable.hs
-@@ -13,6 +13,7 @@
- #if MIN_VERSION_base(4,9,0)
- {-# LANGUAGE DataKinds     #-}
- {-# LANGUAGE TypeOperators #-}
-+{-# LANGUAGE UndecidableInstances #-}
- #endif
- 
- module Foundation.Collection.Foldable
-diff --git a/Foundation/Hashing/SipHash.hs b/Foundation/Hashing/SipHash.hs
-index 4dae35f..0b43860 100644
---- a/Foundation/Hashing/SipHash.hs
-+++ b/Foundation/Hashing/SipHash.hs
-@@ -9,6 +9,7 @@
- -- reference: <http://131002.net/siphash/siphash.pdf>
- --
- {-# LANGUAGE BangPatterns #-}
-+{-# LANGUAGE CPP #-}
- {-# LANGUAGE MagicHash #-}
- module Foundation.Hashing.SipHash
-     ( SipKey(..)
-@@ -18,6 +19,9 @@ module Foundation.Hashing.SipHash
-     ) where
- 
- import           Data.Bits
-+#if __GLASGOW_HASKELL__ >= 903
-+  hiding ((.<<.), (.>>.))
-+#endif
- import           Basement.Compat.Base
- import           Basement.Types.OffsetSize
- import           Basement.PrimType
diff --git a/patches/generic-data-0.9.2.1.patch b/patches/generic-data-0.9.2.1.patch
deleted file mode 100644
index 943b92a6..00000000
--- a/patches/generic-data-0.9.2.1.patch
+++ /dev/null
@@ -1,36 +0,0 @@
-diff --git a/src/Generic/Data/Internal/Generically.hs b/src/Generic/Data/Internal/Generically.hs
-index 52ef868..fbaecd6 100644
---- a/src/Generic/Data/Internal/Generically.hs
-+++ b/src/Generic/Data/Internal/Generically.hs
-@@ -22,6 +22,9 @@ import Data.Functor.Classes
- import Data.Semigroup
- import Data.Ix
- import GHC.Generics
-+#if __GLASGOW_HASKELL__ >= 903
-+  hiding (Generically, Generically1)
-+#endif
- import Text.Read
- 
- import Generic.Data.Internal.Prelude hiding (gfoldMap, gtraverse, gsequenceA)
-diff --git a/src/Generic/Data/Internal/Microsurgery.hs b/src/Generic/Data/Internal/Microsurgery.hs
-index b87d8d4..672cb5d 100644
---- a/src/Generic/Data/Internal/Microsurgery.hs
-+++ b/src/Generic/Data/Internal/Microsurgery.hs
-@@ -9,6 +9,7 @@
-     TypeFamilies,
-     TypeOperators,
-     UndecidableInstances #-}
-+{-# LANGUAGE CPP #-}
- 
- -- | Surgeries that are just 'coerce'.
- --
-@@ -24,6 +25,9 @@ module Generic.Data.Internal.Microsurgery where
- 
- import Data.Coerce (Coercible, coerce)
- import GHC.Generics
-+#if __GLASGOW_HASKELL__ >= 903
-+  hiding (Generically, Generically1)
-+#endif
- import GHC.TypeLits (ErrorMessage(..), Symbol, TypeError)
- 
- import Generic.Data.Types (Data)
diff --git a/patches/ghc-check-0.5.0.6.patch b/patches/ghc-check-0.5.0.6.patch
deleted file mode 100644
index 3619d9df..00000000
--- a/patches/ghc-check-0.5.0.6.patch
+++ /dev/null
@@ -1,49 +0,0 @@
-diff --git a/src/GHC/Check/PackageDb.hs b/src/GHC/Check/PackageDb.hs
-index 98b6fd5..7a50b63 100644
---- a/src/GHC/Check/PackageDb.hs
-+++ b/src/GHC/Check/PackageDb.hs
-@@ -34,7 +34,9 @@ import GHC.Unit.State
-   (lookupUnit, explicitUnits,  lookupUnitId,
-     lookupPackageName, GenericUnitInfo (..),
-     UnitInfo, unitPackageNameString)
--import GHC.Unit.Types (indefUnit)
-+#if !MIN_VERSION_ghc(9,3,0)
-+import qualified GHC.Unit.Types as GUT
-+#endif
- #elif MIN_VERSION_ghc(9,0,1)
- import GHC
-   (unitState,  Ghc,
-@@ -46,7 +48,7 @@ import GHC.Unit.State
-   (lookupUnit, explicitUnits,  lookupUnitId,
-     lookupPackageName, GenericUnitInfo (..),
-     UnitInfo, unitPackageNameString)
--import GHC.Unit.Types (indefUnit)
-+import qualified GHC.Unit.Types as GUT
- #else
- import GHC
-   (pkgState,  Ghc,
-@@ -77,13 +79,23 @@ data PackageVersion
- version :: PackageVersion -> Version
- version PackageVersion{ myVersion = MyVersion v} = v
- 
-+#if MIN_VERSION_ghc(9,3,0)
-+indefUnit = id
-+#elif MIN_VERSION_ghc(9,0,1)
-+indefUnit = GUT.indefUnit
-+#endif
-+
- #if MIN_VERSION_ghc(9,2,0)
- -- | @getPackageVersion p@ returns the version of package @p@ that will be used in the Ghc session.
- getPackageVersion :: String -> Ghc (Maybe PackageVersion)
- getPackageVersion pName = runMaybeT $ do
-   hsc_env <- Monad.lift getSession
-   let pkgst   = ue_units $ hsc_unit_env hsc_env
--      depends = explicitUnits pkgst
-+      depends =
-+# if MIN_VERSION_ghc(9,3,0)
-+                map fst
-+#endif
-+                    (explicitUnits pkgst)
- 
-   let explicit = do
-         pkgs <- traverse (MaybeT . return . lookupUnit pkgst) depends
diff --git a/patches/heterocephalus-1.0.5.6.patch b/patches/heterocephalus-1.0.5.6.patch
deleted file mode 100644
index dd2a7d46..00000000
--- a/patches/heterocephalus-1.0.5.6.patch
+++ /dev/null
@@ -1,18 +0,0 @@
-diff --git a/src/Text/Heterocephalus.hs b/src/Text/Heterocephalus.hs
-index 5d8c95d..1347cb5 100644
---- a/src/Text/Heterocephalus.hs
-+++ b/src/Text/Heterocephalus.hs
-@@ -575,7 +575,12 @@ bindingPattern (BindList is) = do
-   return (ListP patterns, concat scopes)
- bindingPattern (BindConstr con is) = do
-   (patterns, scopes) <- fmap unzip $ mapM bindingPattern is
--  return (ConP (mkConName con) patterns, concat scopes)
-+  return (ConP (mkConName con)
-+-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
-+#if __GLASGOW_HASKELL__ >= 901
-+               []
-+#endif
-+               patterns, concat scopes)
- bindingPattern (BindRecord con fields wild) = do
-   let f (Ident field, b) = do
-         (p, s) <- bindingPattern b
diff --git a/patches/libBF-0.6.3.patch b/patches/libBF-0.6.3.patch
deleted file mode 100644
index c5511007..00000000
--- a/patches/libBF-0.6.3.patch
+++ /dev/null
@@ -1,16 +0,0 @@
-diff --git a/libBF.cabal b/libBF.cabal
-index 0fae1a7..7f2a1b1 100644
---- a/libBF.cabal
-+++ b/libBF.cabal
-@@ -38,8 +38,9 @@ library
- 
-   hs-source-dirs:      src
- 
--  if os(windows)
--    extra-libraries: gcc_s
-+  if !impl(ghc >= 9.4)
-+    if os(windows)
-+      extra-libraries: gcc_s
- 
-   if flag(system-libbf)
-     extra-libraries: bf
diff --git a/patches/vector-algorithms-0.8.0.4.patch b/patches/vector-algorithms-0.8.0.4.patch
deleted file mode 100644
index 51b7e584..00000000
--- a/patches/vector-algorithms-0.8.0.4.patch
+++ /dev/null
@@ -1,153 +0,0 @@
-diff --git a/bench/simple/Main.hs b/bench/simple/Main.hs
-index 04028bc..67d541f 100644
---- a/bench/simple/Main.hs
-+++ b/bench/simple/Main.hs
-@@ -12,7 +12,8 @@ import Data.Char
- import Data.Ord  (comparing)
- import Data.List (maximumBy)
- 
--import Data.Vector.Unboxed.Mutable
-+import qualified Data.Vector.Unboxed.Mutable as U
-+import Data.Vector.Unboxed.Mutable (MVector, Unbox)
- 
- import qualified Data.Vector.Algorithms.Insertion    as INS
- import qualified Data.Vector.Algorithms.Intro        as INT
-@@ -35,8 +36,8 @@ noalgo _ = return ()
- -- Allocates a temporary buffer, like mergesort for similar purposes as noalgo.
- alloc :: (Unbox e) => MVector RealWorld e -> IO ()
- alloc arr | len <= 4  = arr `seq` return ()
--          | otherwise = (new (len `div` 2) :: IO (MVector RealWorld Int)) >> return ()
-- where len = length arr
-+          | otherwise = (U.new (len `div` 2) :: IO (MVector RealWorld Int)) >> return ()
-+ where len = U.length arr
- 
- displayTime :: String -> Integer -> IO ()
- displayTime s elapsed = putStrLn $
-@@ -47,7 +48,7 @@ run s t = t >>= displayTime s
- 
- sortSuite :: String -> GenIO -> Int -> (MVector RealWorld Int -> IO ()) -> IO ()
- sortSuite str g n sort = do
--  arr <- new n
-+  arr <- U.new n
-   putStrLn $ "Testing: " ++ str
-   run "Random            " $ speedTest arr n (rand g >=> modulo n) sort
-   run "Sorted            " $ speedTest arr n ascend sort
-diff --git a/src/Data/Vector/Algorithms/Optimal.hs b/src/Data/Vector/Algorithms/Optimal.hs
-index a6a72d4..42a4f07 100644
---- a/src/Data/Vector/Algorithms/Optimal.hs
-+++ b/src/Data/Vector/Algorithms/Optimal.hs
-@@ -40,6 +40,13 @@ import Data.Vector.Generic.Mutable
- 
- import Data.Vector.Algorithms.Common (Comparison)
- 
-+#if MIN_VERSION_vector(0,13,0)
-+import qualified Data.Vector.Internal.Check as Ck
-+# define CHECK_INDEX(name, i, n) Ck.checkIndex Ck.Unsafe (i) (n)
-+#else
-+# define CHECK_INDEX(name, i, n) UNSAFE_CHECK(checkIndex) name (i) (n)
-+#endif
-+
- #include "vector.h"
- 
- -- | Sorts the elements at the positions 'off' and 'off + 1' in the given
-@@ -54,8 +61,8 @@ sort2ByOffset cmp a off = sort2ByIndex cmp a off (off + 1)
- -- be the 'lower' of the two.
- sort2ByIndex :: (PrimMonad m, MVector v e)
-              => Comparison e -> v (PrimState m) e -> Int -> Int -> m ()
--sort2ByIndex cmp a i j = UNSAFE_CHECK(checkIndex) "sort2ByIndex" i (length a)
--                       $ UNSAFE_CHECK(checkIndex) "sort2ByIndex" j (length a) $  do
-+sort2ByIndex cmp a i j = CHECK_INDEX("sort2ByIndex", i, length a)
-+                       $ CHECK_INDEX("sort2ByIndex", j, length a) $  do
-   a0 <- unsafeRead a i
-   a1 <- unsafeRead a j
-   case cmp a0 a1 of
-@@ -75,9 +82,9 @@ sort3ByOffset cmp a off = sort3ByIndex cmp a off (off + 1) (off + 2)
- -- lowest position in the array.
- sort3ByIndex :: (PrimMonad m, MVector v e)
-              => Comparison e -> v (PrimState m) e -> Int -> Int -> Int -> m ()
--sort3ByIndex cmp a i j k = UNSAFE_CHECK(checkIndex) "sort3ByIndex" i (length a)
--                         $ UNSAFE_CHECK(checkIndex) "sort3ByIndex" j (length a)
--                         $ UNSAFE_CHECK(checkIndex) "sort3ByIndex" k (length a) $ do
-+sort3ByIndex cmp a i j k = CHECK_INDEX("sort3ByIndex", i, length a)
-+                         $ CHECK_INDEX("sort3ByIndex", j, length a)
-+                         $ CHECK_INDEX("sort3ByIndex", k, length a) $ do
-   a0 <- unsafeRead a i
-   a1 <- unsafeRead a j
-   a2 <- unsafeRead a k
-@@ -114,10 +121,10 @@ sort4ByOffset cmp a off = sort4ByIndex cmp a off (off + 1) (off + 2) (off + 3)
- -- it can be used to sort medians into particular positions and so on.
- sort4ByIndex :: (PrimMonad m, MVector v e)
-              => Comparison e -> v (PrimState m) e -> Int -> Int -> Int -> Int -> m ()
--sort4ByIndex cmp a i j k l = UNSAFE_CHECK(checkIndex) "sort4ByIndex" i (length a)
--                           $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" j (length a)
--                           $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" k (length a)
--                           $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" l (length a) $ do
-+sort4ByIndex cmp a i j k l = CHECK_INDEX("sort4ByIndex", i, length a)
-+                           $ CHECK_INDEX("sort4ByIndex", j, length a)
-+                           $ CHECK_INDEX("sort4ByIndex", k, length a)
-+                           $ CHECK_INDEX("sort4ByIndex", l, length a) $ do
-   a0 <- unsafeRead a i
-   a1 <- unsafeRead a j
-   a2 <- unsafeRead a k
-diff --git a/tests/properties/Optimal.hs b/tests/properties/Optimal.hs
-index 2db2eda..9007a4a 100644
---- a/tests/properties/Optimal.hs
-+++ b/tests/properties/Optimal.hs
-@@ -8,7 +8,7 @@ module Optimal where
- import Control.Arrow
- import Control.Monad
- 
--import Data.List
-+import qualified Data.List as List
- import Data.Function
- 
- import Data.Vector.Generic hiding (map, zip, concatMap, (++), replicate, foldM)
-@@ -32,18 +32,18 @@ monotones k = atLeastOne 0
- stability :: (Vector v (Int,Int)) => Int -> [v (Int, Int)]
- stability n = concatMap ( map fromList
-                         . foldM interleavings []
--                        . groupBy ((==) `on` fst)
-+                        . List.groupBy ((==) `on` fst)
-                         . flip zip [0..])
-               $ monotones (n-2) n
- 
- sort2 :: (Vector v Int) => [v Int]
--sort2 = map fromList $ permutations [0,1]
-+sort2 = map fromList $ List.permutations [0,1]
- 
- stability2 :: (Vector v (Int,Int)) => [v (Int, Int)]
- stability2 = [fromList [(0, 0), (0, 1)]]
- 
- sort3 :: (Vector v Int) => [v Int]
--sort3 = map fromList $ permutations [0..2]
-+sort3 = map fromList $ List.permutations [0..2]
- 
- {-
- stability3 :: [UArr (Int :*: Int)]
-@@ -58,5 +58,5 @@ stability3 = map toU [ [0:*:0, 0:*:1, 0:*:2]
- -}
- 
- sort4 :: (Vector v Int) => [v Int]
--sort4 = map fromList $ permutations [0..3]
-+sort4 = map fromList $ List.permutations [0..3]
- 
-diff --git a/vector-algorithms.cabal b/vector-algorithms.cabal
-index 44f7544..1723ec1 100644
---- a/vector-algorithms.cabal
-+++ b/vector-algorithms.cabal
-@@ -1,5 +1,6 @@
- name:              vector-algorithms
- version:           0.8.0.4
-+x-revision: 2
- license:           BSD3
- license-file:      LICENSE
- author:            Dan Doel
-@@ -57,7 +58,7 @@ library
-   default-language: Haskell2010
- 
-   build-depends: base >= 4.5 && < 5,
--                 vector >= 0.6 && < 0.13,
-+                 vector >= 0.6 && < 0.14,
-                  primitive >=0.3 && <0.8,
-                  bytestring >= 0.9 && < 1.0
- 
-- 
GitLab