diff --git a/ci/config.sh b/ci/config.sh
index 9dc53665f263c80384f91d473a4403d41483b24f..2137bf4d01e3e46c22811bbd4689aea3db26f928 100644
--- a/ci/config.sh
+++ b/ci/config.sh
@@ -76,13 +76,12 @@ case $version in
 
   9.2.*)
     #       package                   ticket
-    broken  "constraints"             6066 # ghc!6066, that is
-    broken  "hgeometry-combinatorial" 6066 # ghc!6066, that is
     ;;
 
   9.3.*)
     #       package                   ticket
     broken  "Agda"                    20294
+    broken  "diagrams-core"           20539
     broken  "doctest"                 30 # head.hackage#30, that is
     ;;
 
@@ -96,7 +95,7 @@ esac
 #
 # These are packages which we don't have patches for but want to test anyways.
 extra_package lens
-extra_package aeson
+extra_package aeson 1.5.6.0
 extra_package criterion
 extra_package scotty
 extra_package generic-lens 2.2.0.0
diff --git a/patches/blaze-textual-0.2.1.0.patch b/patches/blaze-textual-0.2.1.0.patch
deleted file mode 100644
index 392cbd1dbfea50d98dda94d5aca9648b14399e14..0000000000000000000000000000000000000000
--- a/patches/blaze-textual-0.2.1.0.patch
+++ /dev/null
@@ -1,13 +0,0 @@
-diff --git a/Blaze/Text/Int.hs b/Blaze/Text/Int.hs
-index 58cdbf4..2e8809d 100644
---- a/Blaze/Text/Int.hs
-+++ b/Blaze/Text/Int.hs
-@@ -27,7 +27,7 @@ import GHC.Num (quotRemInteger)
- import GHC.Types (Int(..))
- 
- #if defined(INTEGER_GMP)
--import GHC.Integer.GMP.Internals
-+import GHC.Integer.GMP.Internals hiding (quotRemInteger)
- #elif defined(INTEGER_SIMPLE)
- import GHC.Integer.Simple.Internals
- #endif
diff --git a/patches/byteslice-0.2.5.2.patch b/patches/byteslice-0.2.5.2.patch
deleted file mode 100644
index c81cc9a01ac02a640393a29f704e466ecf5d7830..0000000000000000000000000000000000000000
--- a/patches/byteslice-0.2.5.2.patch
+++ /dev/null
@@ -1,118 +0,0 @@
-diff --git a/byteslice.cabal b/byteslice.cabal
-index 62af985..98c30a0 100644
---- a/byteslice.cabal
-+++ b/byteslice.cabal
-@@ -42,6 +42,7 @@ library
-     , run-st >=0.1.1 && <0.2
-     , tuples >=0.1 && <0.2
-     , vector >=0.12 && <0.13
-+    , ghc-prim
-   hs-source-dirs: src
-   ghc-options: -Wall -O2
-   if impl(ghc>=8.10)
-diff --git a/src-unlifted-newtypes/UnliftedBytes.hs b/src-unlifted-newtypes/UnliftedBytes.hs
-index 2270bbd..43a825b 100644
---- a/src-unlifted-newtypes/UnliftedBytes.hs
-+++ b/src-unlifted-newtypes/UnliftedBytes.hs
-@@ -1,3 +1,4 @@
-+{-# language CPP #-}
- {-# language GADTSyntax #-}
- {-# language KindSignatures #-}
- {-# language MagicHash #-}
-@@ -10,7 +11,10 @@ module UnliftedBytes
-   ) where
- 
- import GHC.Exts (ByteArray#,Int#,RuntimeRep(..),TYPE)
-+#if MIN_VERSION_ghc_prim(0,8,0)
-+import GHC.Types (UnliftedRep)
-+#endif
- 
--newtype Bytes# :: TYPE ('TupleRep '[ 'UnliftedRep,'IntRep,'IntRep]) where
-+newtype Bytes# :: TYPE ('TupleRep '[ UnliftedRep,'IntRep,'IntRep]) where
-   Bytes# :: (# ByteArray#, Int#, Int# #) -> Bytes#
- 
-diff --git a/src/Data/Bytes.hs b/src/Data/Bytes.hs
-index f865a63..6d3fe0e 100644
---- a/src/Data/Bytes.hs
-+++ b/src/Data/Bytes.hs
-@@ -1,5 +1,6 @@
- {-# language BangPatterns #-}
- {-# language BlockArguments #-}
-+{-# language CPP #-}
- {-# language DuplicateRecordFields #-}
- {-# language MagicHash #-}
- {-# language NamedFieldPuns #-}
-@@ -210,7 +211,7 @@ isPrefixOf :: Bytes -> Bytes -> Bool
- isPrefixOf (Bytes a aOff aLen) (Bytes b bOff bLen) =
-   -- For prefix and suffix testing, we do not use
-   -- the sameByteArray optimization that we use in
--  -- the Eq instance. Prefix and suffix testing seldom 
-+  -- the Eq instance. Prefix and suffix testing seldom
-   -- compares a byte array with the same in-memory
-   -- byte array.
-   if aLen <= bLen
-@@ -324,14 +325,14 @@ stripOptionalSuffix !suf !str = if suf `isSuffixOf` str
- 
- -- | Is the byte a member of the byte sequence?
- elem :: Word8 -> Bytes -> Bool
--elem (W8# w) b = case elemLoop 0# w b of
-+elem (W8# w) b = case elemLoop 0# (word8ToWordCompat# w) b of
-   1# -> True
-   _ -> False
- 
- elemLoop :: Int# -> Word# -> Bytes -> Int#
- elemLoop !r !w (Bytes arr@(ByteArray arr# ) off@(I# off# ) len) = case len of
-   0 -> r
--  _ -> elemLoop (Exts.orI# r (Exts.eqWord# w (Exts.indexWord8Array# arr# off# ) )) w (Bytes arr (off + 1) (len - 1))
-+  _ -> elemLoop (Exts.orI# r (Exts.eqWord# w (word8ToWordCompat# (Exts.indexWord8Array# arr# off# ) ))) w (Bytes arr (off + 1) (len - 1))
- 
- -- | Take bytes while the predicate is true.
- takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
-@@ -404,7 +405,7 @@ countWhileEnd k (Bytes arr off0 len0) = go (off0 + len0 - 1) (len0 - 1) 0 where
- foldl :: (a -> Word8 -> a) -> a -> Bytes -> a
- {-# inline foldl #-}
- foldl f a0 (Bytes arr off0 len0) =
--  go (off0 + len0 - 1) (len0 - 1) 
-+  go (off0 + len0 - 1) (len0 - 1)
-   where
-   go !off !ix = case ix of
-     (-1) -> a0
-@@ -431,7 +432,7 @@ ifoldl' f a0 (Bytes arr off0 len0) = go a0 0 off0 len0 where
- foldr' :: (Word8 -> a -> a) -> a -> Bytes -> a
- {-# inline foldr' #-}
- foldr' f a0 (Bytes arr off0 len0) =
--  go a0 (off0 + len0 - 1) (len0 - 1) 
-+  go a0 (off0 + len0 - 1) (len0 - 1)
-   where
-   go !a !off !ix = case ix of
-     (-1) -> a
-@@ -454,7 +455,7 @@ fromLatinString =
- 
- -- | Interpret a byte sequence as text encoded by ISO-8859-1.
- toLatinString :: Bytes -> String
--toLatinString = foldr (\(W8# w) xs -> C# (chr# (word2Int# w)) : xs) []
-+toLatinString = foldr (\(W8# w) xs -> C# (chr# (word2Int# (word8ToWordCompat# w))) : xs) []
- 
- -- | Copy a primitive string literal into managed memory.
- fromCString# :: Addr# -> Bytes
-@@ -762,7 +763,7 @@ toLowerAsciiByteArrayClone (Bytes src off0 len0) =
- -- | /O(n)/ Copy a 'ByteString' to a byte sequence.
- fromByteString :: ByteString -> Bytes
- fromByteString !b = Bytes
--  ( runByteArrayST $ unsafeIOToST $ do 
-+  ( runByteArrayST $ unsafeIOToST $ do
-       dst@(PM.MutableByteArray dst# ) <- PM.newByteArray len
-       ByteString.unsafeUseAsCString b $ \src -> do
-         PM.copyPtrToMutablePrimArray (PM.MutablePrimArray dst# ) 0 src len
-@@ -770,3 +771,11 @@ fromByteString !b = Bytes
-   ) 0 len
-   where
-   !len = ByteString.length b
-+
-+#if MIN_VERSION_base(4,16,0)
-+word8ToWordCompat# :: Exts.Word8# -> Word#
-+word8ToWordCompat# = Exts.word8ToWord#
-+#else
-+word8ToWordCompat# :: Word# -> Word#
-+word8ToWordCompat# x = x
-+#endif
diff --git a/patches/byteslice-0.2.6.0.patch b/patches/byteslice-0.2.6.0.patch
new file mode 100644
index 0000000000000000000000000000000000000000..d5a503af976e9a57cf73067751cc8b951f7e09ad
--- /dev/null
+++ b/patches/byteslice-0.2.6.0.patch
@@ -0,0 +1,134 @@
+diff --git a/src-unlifted-newtypes/UnliftedBytes.hs b/src-unlifted-newtypes/UnliftedBytes.hs
+index 861de4a..25b4fd2 100644
+--- a/src-unlifted-newtypes/UnliftedBytes.hs
++++ b/src-unlifted-newtypes/UnliftedBytes.hs
+@@ -1,3 +1,4 @@
++{-# language CPP #-}
+ {-# language GADTSyntax #-}
+ {-# language KindSignatures #-}
+ {-# language MagicHash #-}
+@@ -14,8 +15,11 @@ module UnliftedBytes
+ import Data.Bytes.Internal (Bytes(Bytes))
+ import Data.Primitive (ByteArray(ByteArray))
+ import GHC.Exts (Int(I#),ByteArray#,Int#,RuntimeRep(..),TYPE)
++#if MIN_VERSION_base(4,16,0)
++import GHC.Exts (UnliftedRep)
++#endif
+ 
+-newtype Bytes# :: TYPE ('TupleRep '[ 'UnliftedRep,'IntRep,'IntRep]) where
++newtype Bytes# :: TYPE ('TupleRep '[ UnliftedRep,'IntRep,'IntRep]) where
+   Bytes# :: (# ByteArray#, Int#, Int# #) -> Bytes#
+ 
+ lift :: Bytes# -> Bytes
+diff --git a/src/Data/Bytes.hs b/src/Data/Bytes.hs
+index 3cf7e15..90095fa 100644
+--- a/src/Data/Bytes.hs
++++ b/src/Data/Bytes.hs
+@@ -1,5 +1,6 @@
+ {-# language BangPatterns #-}
+ {-# language BlockArguments #-}
++{-# language CPP #-}
+ {-# language DuplicateRecordFields #-}
+ {-# language MagicHash #-}
+ {-# language NamedFieldPuns #-}
+@@ -222,7 +223,7 @@ isPrefixOf :: Bytes -> Bytes -> Bool
+ isPrefixOf (Bytes a aOff aLen) (Bytes b bOff bLen) =
+   -- For prefix and suffix testing, we do not use
+   -- the sameByteArray optimization that we use in
+-  -- the Eq instance. Prefix and suffix testing seldom 
++  -- the Eq instance. Prefix and suffix testing seldom
+   -- compares a byte array with the same in-memory
+   -- byte array.
+   if aLen <= bLen
+@@ -237,7 +238,7 @@ isSuffixOf (Bytes a aOff aLen) (Bytes b bOff bLen) =
+     else False
+ 
+ -- | Is the first argument an infix of the second argument?
+--- 
++--
+ -- Uses the Rabin-Karp algorithm: expected time @O(n+m)@, worst-case @O(nm)@.
+ isInfixOf :: Bytes -- ^ String to search for
+           -> Bytes -- ^ String to search in
+@@ -397,14 +398,14 @@ stripOptionalSuffix !suf !str = if suf `isSuffixOf` str
+ 
+ -- | Is the byte a member of the byte sequence?
+ elem :: Word8 -> Bytes -> Bool
+-elem (W8# w) b = case elemLoop 0# w b of
++elem (W8# w) b = case elemLoop 0# (word8ToWordCompat# w) b of
+   1# -> True
+   _ -> False
+ 
+ elemLoop :: Int# -> Word# -> Bytes -> Int#
+ elemLoop !r !w (Bytes arr@(ByteArray arr# ) off@(I# off# ) len) = case len of
+   0 -> r
+-  _ -> elemLoop (Exts.orI# r (Exts.eqWord# w (Exts.indexWord8Array# arr# off# ) )) w (Bytes arr (off + 1) (len - 1))
++  _ -> elemLoop (Exts.orI# r (Exts.eqWord# w (word8ToWordCompat# (Exts.indexWord8Array# arr# off# ) ))) w (Bytes arr (off + 1) (len - 1))
+ 
+ -- | Take bytes while the predicate is true.
+ takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
+@@ -718,3 +719,11 @@ toLowerAsciiByteArrayClone :: Bytes -> ByteArray
+ {-# DEPRECATED toLowerAsciiByteArrayClone "use Data.Bytes/Text/AsciiExt.toLowerU" #-}
+ {-# INLINE toLowerAsciiByteArrayClone #-}
+ toLowerAsciiByteArrayClone = AsciiExt.toLowerU
++
++#if MIN_VERSION_base(4,16,0)
++word8ToWordCompat# :: Exts.Word8# -> Word#
++word8ToWordCompat# = Exts.word8ToWord#
++#else
++word8ToWordCompat# :: Word# -> Word#
++word8ToWordCompat# x = x
++#endif
+diff --git a/src/Data/Bytes/Text/Latin1.hs b/src/Data/Bytes/Text/Latin1.hs
+index ba7ce1e..20bac7b 100644
+--- a/src/Data/Bytes/Text/Latin1.hs
++++ b/src/Data/Bytes/Text/Latin1.hs
+@@ -1,4 +1,5 @@
+ {-# LANGUAGE BangPatterns #-}
++{-# LANGUAGE CPP #-}
+ {-# LANGUAGE MagicHash #-}
+ {-# LANGUAGE TypeApplications #-}
+ 
+@@ -10,8 +11,8 @@
+ --
+ -- Strictly, ISO-8859-1 is not to be confused with ISO/IEC 8859-1 (which was the
+ -- default encoding for webpages before HTML5). ISO/IEC 8859-1 lacks encodings
+--- for the C0 and C1 control characters. 
+--- 
++-- for the C0 and C1 control characters.
++--
+ -- With HTML5, the default encoding of webpages was changed to Windows-1252,
+ -- which is _not_ compatible with ISO-8859-1. Windows-1252 uses the C1 Control
+ -- range (@U+0080@ -- @U+009F@) mostly to encode a variety of printable
+@@ -37,7 +38,10 @@ module Data.Bytes.Text.Latin1
+ import Data.Bytes.Types (Bytes(..))
+ import Data.Char (ord)
+ import Data.Primitive (ByteArray(ByteArray))
+-import GHC.Exts (Int(I#),Char(C#),word2Int#,chr#)
++import GHC.Exts (Int(I#),Char(C#),Word#,word2Int#,chr#)
++#if MIN_VERSION_base(4,16,0)
++import GHC.Exts (Word8#, word8ToWord#)
++#endif
+ import GHC.Word (Word8(W8#))
+ 
+ import qualified Data.Bytes.Pure as Bytes
+@@ -54,7 +58,7 @@ fromString =
+ -- | Interpret a byte sequence as text encoded by ISO-8859-1.
+ toString :: Bytes -> String
+ {-# INLINE toString #-}
+-toString = Bytes.foldr (\(W8# w) xs -> C# (chr# (word2Int# w)) : xs) []
++toString = Bytes.foldr (\(W8# w) xs -> C# (chr# (word2Int# (word8ToWordCompat# w))) : xs) []
+ 
+ -- TODO presumably also fromText and fromShortText
+ 
+@@ -212,3 +216,11 @@ equals12 !c0 !c1 !c2 !c3 !c4 !c5 !c6 !c7 !c8 !c9 !c10 !c11 (Bytes arr off len) =
+ 
+ indexCharArray :: ByteArray -> Int -> Char
+ indexCharArray (ByteArray arr) (I# off) = C# (Exts.indexCharArray# arr off)
++
++#if MIN_VERSION_base(4,16,0)
++word8ToWordCompat# :: Word8# -> Word#
++word8ToWordCompat# = word8ToWord#
++#else
++word8ToWordCompat# :: Word# -> Word#
++word8ToWordCompat# x = x
++#endif
diff --git a/patches/constraints-0.13.patch b/patches/constraints-0.13.patch
index e921b47d86fb5d4e9d78e198d890fa0f93b28375..54e5e9a38c2bf32d092dc67396a2374db7d9e4ef 100644
--- a/patches/constraints-0.13.patch
+++ b/patches/constraints-0.13.patch
@@ -1,10 +1,15 @@
 diff --git a/src/Data/Constraint/Nat.hs b/src/Data/Constraint/Nat.hs
-index ac1a78f..a49320b 100644
+index ac1a78f..1dcece0 100644
 --- a/src/Data/Constraint/Nat.hs
 +++ b/src/Data/Constraint/Nat.hs
-@@ -77,10 +77,10 @@ magic f = Sub $ unsafeCoerce (Magic Dict) (natVal (Proxy :: Proxy n) `f` natVal
- axiom :: forall a b. Dict (a ~ b)
- axiom = unsafeCoerce (Dict :: Dict (a ~ a))
+@@ -74,13 +74,13 @@ newtype Magic n = Magic (KnownNat n => Dict (KnownNat n))
+ magic :: forall n m o. (Integer -> Integer -> Integer) -> (KnownNat n, KnownNat m) :- KnownNat o
+ magic f = Sub $ unsafeCoerce (Magic Dict) (natVal (Proxy :: Proxy n) `f` natVal (Proxy :: Proxy m))
+ 
+-axiom :: forall a b. Dict (a ~ b)
+-axiom = unsafeCoerce (Dict :: Dict (a ~ a))
++axiom :: Dict c
++axiom = unsafeCoerce (Dict :: Dict ())
  
 -axiomLe :: forall a b. Dict (a <= b)
 +axiomLe :: forall (a :: Nat) (b :: Nat). Dict (a <= b)
@@ -54,3 +59,18 @@ index ac1a78f..a49320b 100644
 -leTrans :: forall a b c. (b <= c, a <= b) :- (a <= c)
 +leTrans :: forall (a :: Nat) (b :: Nat) (c :: Nat). (b <= c, a <= b) :- (a <= c)
  leTrans = Sub (axiomLe @a @c)
+diff --git a/src/Data/Constraint/Symbol.hs b/src/Data/Constraint/Symbol.hs
+index 0b360ff..5e0256c 100644
+--- a/src/Data/Constraint/Symbol.hs
++++ b/src/Data/Constraint/Symbol.hs
+@@ -68,8 +68,8 @@ magicSSS f = Sub $ unsafeCoerce (Magic Dict) (symbolVal (Proxy :: Proxy n) `f` s
+ magicSN :: forall a n. (String -> Int) -> KnownSymbol a :- KnownNat n
+ magicSN f = Sub $ unsafeCoerce (Magic Dict) (toInteger (f (symbolVal (Proxy :: Proxy a))))
+ 
+-axiom :: forall a b. Dict (a ~ b)
+-axiom = unsafeCoerce (Dict :: Dict (a ~ a))
++axiom :: Dict c
++axiom = unsafeCoerce (Dict :: Dict ())
+ 
+ -- axioms and operations
+ 
diff --git a/patches/deriving-compat-0.5.10.patch b/patches/deriving-compat-0.5.10.patch
deleted file mode 100644
index a282ceae66eeecbacb714d6739aae2adaabdcb90..0000000000000000000000000000000000000000
--- a/patches/deriving-compat-0.5.10.patch
+++ /dev/null
@@ -1,229 +0,0 @@
-diff --git a/src/Data/Deriving/Internal.hs b/src/Data/Deriving/Internal.hs
-index 3c1e37b..ec14c9c 100644
---- a/src/Data/Deriving/Internal.hs
-+++ b/src/Data/Deriving/Internal.hs
-@@ -35,7 +35,7 @@ import           Data.Functor.Classes (Eq1(..), Ord1(..), Read1(..), Show1(..))
- import           Data.Functor.Classes (Eq2(..), Ord2(..), Read2(..), Show2(..))
- # endif
- #endif
--import           Data.List
-+import           Data.List (foldl', union)
- import qualified Data.Map as Map
- import           Data.Map (Map)
- import           Data.Maybe
-@@ -2146,16 +2146,36 @@ eqWord16HashValName :: Name
- eqWord16HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "eqWord16#"
- 
- extendInt8HashValName :: Name
--extendInt8HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "extendInt8#"
-+extendInt8HashValName = mkNameG_v "ghc-prim" "GHC.Prim"
-+# if MIN_VERSION_base(4,16,0)
-+                                                        "int8ToInt#"
-+# else
-+                                                        "extendInt8#"
-+# endif
- 
- extendInt16HashValName :: Name
--extendInt16HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "extendInt16#"
-+extendInt16HashValName = mkNameG_v "ghc-prim" "GHC.Prim"
-+# if MIN_VERSION_base(4,16,0)
-+                                                         "int16ToInt#"
-+# else
-+                                                         "extendInt16#"
-+# endif
- 
- extendWord8HashValName :: Name
--extendWord8HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "extendWord8#"
-+extendWord8HashValName = mkNameG_v "ghc-prim" "GHC.Prim"
-+# if MIN_VERSION_base(4,16,0)
-+                                                         "word8ToWord#"
-+# else
-+                                                         "extendWord8#"
-+# endif
- 
- extendWord16HashValName :: Name
--extendWord16HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "extendWord16#"
-+extendWord16HashValName = mkNameG_v "ghc-prim" "GHC.Prim"
-+# if MIN_VERSION_base(4,16,0)
-+                                                          "word16ToWord#"
-+# else
-+                                                          "extendWord16#"
-+# endif
- 
- geInt8HashValName :: Name
- geInt8HashValName = mkNameG_v "ghc-prim" "GHC.Prim" "geInt8#"
-diff --git a/src/Data/Deriving/Via/Internal.hs b/src/Data/Deriving/Via/Internal.hs
-index 49aec0c..259407a 100644
---- a/src/Data/Deriving/Via/Internal.hs
-+++ b/src/Data/Deriving/Via/Internal.hs
-@@ -46,12 +46,11 @@ $('deriveGND' [t| forall a. 'Eq' a => 'Eq' (Foo a) |])
- deriveGND :: Q Type -> Q [Dec]
- deriveGND qty = do
-   ty <- qty
--  let (instanceTvbs, instanceCxt, instanceTy) = decomposeType ty
-+  let (_instanceTvbs, instanceCxt, instanceTy) = decomposeType ty
-   instanceTy' <- (resolveTypeSynonyms <=< resolveInfixT) instanceTy
-   decs <- deriveViaDecs instanceTy' Nothing
--  let instanceHeader = ForallT instanceTvbs instanceCxt instanceTy
--  (:[]) `fmap` instanceD (return [])
--                         (return instanceHeader)
-+  (:[]) `fmap` instanceD (return instanceCxt)
-+                         (return instanceTy)
-                          (map return decs)
- 
- {- | Generates an instance for a type class by emulating the behavior of the
-@@ -71,7 +70,7 @@ correctly across all the types being used (e.g., to make sure that the same
- deriveVia :: Q Type -> Q [Dec]
- deriveVia qty = do
-   ty <- qty
--  let (instanceTvbs, instanceCxt, viaApp) = decomposeType ty
-+  let (_instanceTvbs, instanceCxt, viaApp) = decomposeType ty
-   viaApp' <- (resolveTypeSynonyms <=< resolveInfixT) viaApp
-   (instanceTy, viaTy)
-     <- case unapplyTy viaApp' of
-@@ -84,9 +83,8 @@ deriveVia qty = do
-                 , "\t[t| forall a. C (T a) `Via` V a |]"
-                 ]
-   decs <- deriveViaDecs instanceTy (Just viaTy)
--  let instanceHeader = ForallT instanceTvbs instanceCxt instanceTy
--  (:[]) `fmap` instanceD (return [])
--                         (return instanceHeader)
-+  (:[]) `fmap` instanceD (return instanceCxt)
-+                         (return instanceTy)
-                          (map return decs)
- 
- deriveViaDecs :: Type       -- ^ The instance head (e.g., @Eq (Foo a)@)
-diff --git a/src/Data/Functor/Deriving/Internal.hs b/src/Data/Functor/Deriving/Internal.hs
-index 57d8f9c..5472f12 100644
---- a/src/Data/Functor/Deriving/Internal.hs
-+++ b/src/Data/Functor/Deriving/Internal.hs
-@@ -56,7 +56,7 @@ module Data.Functor.Deriving.Internal (
- import           Control.Monad (guard)
- 
- import           Data.Deriving.Internal
--import           Data.List
-+import           Data.List (foldl')
- import qualified Data.Map as Map ((!), keys, lookup, member, singleton)
- import           Data.Maybe
- 
-@@ -703,7 +703,7 @@ functorFunTrivial fmapE traverseE ff z = go ff
- conWildPat :: ConstructorInfo -> Pat
- conWildPat (ConstructorInfo { constructorName = conName
-                             , constructorFields = ts }) =
--  ConP conName $ replicate (length ts) WildP
-+  conPCompat conName $ replicate (length ts) WildP
- 
- -------------------------------------------------------------------------------
- -- Generic traversal for functor-like deriving
-@@ -861,7 +861,7 @@ mkSimpleConMatch :: (Name -> [a] -> Q Exp)
-                  -> Q Match
- mkSimpleConMatch fold conName insides = do
-   varsNeeded <- newNameList "_arg" $ length insides
--  let pat = ConP conName (map VarP varsNeeded)
-+  let pat = conPCompat conName (map VarP varsNeeded)
-   rhs <- fold conName (zipWith (\i v -> i $ VarE v) insides varsNeeded)
-   return $ Match pat (NormalB rhs) []
- 
-@@ -885,7 +885,7 @@ mkSimpleConMatch2 :: (Exp -> [Exp] -> Q Exp)
-                   -> Q Match
- mkSimpleConMatch2 fold conName insides = do
-   varsNeeded <- newNameList "_arg" lengthInsides
--  let pat = ConP conName (map VarP varsNeeded)
-+  let pat = conPCompat conName (map VarP varsNeeded)
-       -- Make sure to zip BEFORE invoking catMaybes. We want the variable
-       -- indicies in each expression to match up with the argument indices
-       -- in conExpr (defined below).
-@@ -933,3 +933,10 @@ mkSimpleTupleCase matchForCon tupSort insides x = do
- #endif
-   m <- matchForCon tupDataName insides
-   return $ CaseE x [m]
-+
-+conPCompat :: Name -> [Pat] -> Pat
-+conPCompat n pats = ConP n
-+#if MIN_VERSION_template_haskell(2,18,0)
-+                         []
-+#endif
-+                         pats
-diff --git a/src/Text/Show/Deriving/Internal.hs b/src/Text/Show/Deriving/Internal.hs
-index 75e10c2..7110284 100644
---- a/src/Text/Show/Deriving/Internal.hs
-+++ b/src/Text/Show/Deriving/Internal.hs
-@@ -52,7 +52,7 @@ module Text.Show.Deriving.Internal (
-     ) where
- 
- import           Data.Deriving.Internal
--import           Data.List
-+import           Data.List (intersperse)
- import qualified Data.Map as Map
- import           Data.Map (Map)
- import           Data.Maybe (fromMaybe)
-@@ -694,22 +694,42 @@ primShowTbl = Map.fromList
-     , (int8HashTypeName,   PrimShow
-                              { primShowBoxer      = appE (conE iHashDataName) . appE (varE extendInt8HashValName)
-                              , primShowPostfixMod = oneHashE
--                             , primShowConv       = mkNarrowE "narrowInt8#"
-+                             , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                              "intToInt8#"
-+# else
-+                                                              "narrowInt8#"
-+# endif
-                              })
-     , (int16HashTypeName,  PrimShow
-                              { primShowBoxer      = appE (conE iHashDataName) . appE (varE extendInt16HashValName)
-                              , primShowPostfixMod = oneHashE
--                             , primShowConv       = mkNarrowE "narrowInt16#"
-+                             , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                              "intToInt16#"
-+# else
-+                                                              "narrowInt16#"
-+# endif
-                              })
-     , (word8HashTypeName,  PrimShow
-                              { primShowBoxer      = appE (conE wHashDataName) . appE (varE extendWord8HashValName)
-                              , primShowPostfixMod = twoHashE
--                             , primShowConv       = mkNarrowE "narrowWord8#"
-+                             , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                              "wordToWord8#"
-+# else
-+                                                              "narrowWord8#"
-+# endif
-                              })
-     , (word16HashTypeName, PrimShow
-                              { primShowBoxer      = appE (conE wHashDataName) . appE (varE extendWord16HashValName)
-                              , primShowPostfixMod = twoHashE
--                             , primShowConv       = mkNarrowE "narrowWord16#"
-+                             , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                              "wordToWord16#"
-+# else
-+                                                              "narrowWord16#"
-+# endif
-                              })
- #endif
-     ]
-diff --git a/tests/GH27Spec.hs b/tests/GH27Spec.hs
-index 3e5d372..5eb152a 100644
---- a/tests/GH27Spec.hs
-+++ b/tests/GH27Spec.hs
-@@ -30,6 +30,10 @@ import Prelude.Compat
- 
- import Test.Hspec
- 
-+{-
-+Unfortunately, this cannot be made to work on GHC 9.2.
-+See https://github.com/haskell-compat/deriving-compat/issues/34.
-+
- #if MIN_VERSION_template_haskell(2,12,0)
- import Data.Deriving.Via
- import Data.Functor.Const
-@@ -37,6 +41,7 @@ import Data.Functor.Const
- newtype Age = MkAge Int
- $(deriveVia [t| forall a. Show Age `Via` Const Int a |])
- #endif
-+-}
- 
- main :: IO ()
- main = hspec spec
diff --git a/patches/extra-1.7.9.patch b/patches/extra-1.7.10.patch
similarity index 86%
rename from patches/extra-1.7.9.patch
rename to patches/extra-1.7.10.patch
index 3ab5d8ed8c59b0f6895a27fe3727e4f9a914a5b4..ab1720bb081f057840859a3c7dbe423f233baf36 100644
--- a/patches/extra-1.7.9.patch
+++ b/patches/extra-1.7.10.patch
@@ -1,5 +1,5 @@
 diff --git a/src/Data/List/Extra.hs b/src/Data/List/Extra.hs
-index 5a79bde..cce1813 100644
+index 8df178f..c1b1b5f 100644
 --- a/src/Data/List/Extra.hs
 +++ b/src/Data/List/Extra.hs
 @@ -6,6 +6,7 @@
@@ -20,22 +20,18 @@ index 5a79bde..cce1813 100644
  import Data.Function
  import Data.Char
 diff --git a/src/Data/List/NonEmpty/Extra.hs b/src/Data/List/NonEmpty/Extra.hs
-index 80f753e..e28a312 100644
+index 6e408f9..7722da1 100644
 --- a/src/Data/List/NonEmpty/Extra.hs
 +++ b/src/Data/List/NonEmpty/Extra.hs
-@@ -11,9 +11,10 @@ module Data.List.NonEmpty.Extra(
+@@ -11,6 +11,7 @@ module Data.List.NonEmpty.Extra(
      maximum1, minimum1, maximumBy1, minimumBy1, maximumOn1, minimumOn1
      ) where
  
 +import           Data.Foldable hiding (toList)
  import           Data.Function
  import qualified Data.List.Extra as List
--import           Data.List.NonEmpty
-+import           Data.List.NonEmpty 
- 
- #if __GLASGOW_HASKELL__ <= 802
- import Data.Semigroup ((<>))
-@@ -88,21 +89,21 @@ unionBy eq xs ys = fromList $ List.unionBy eq (toList xs) (toList ys)
+ import           Data.List.NonEmpty
+@@ -100,21 +101,21 @@ unionBy eq xs ys = fromList $ List.unionBy eq (toList xs) (toList ys)
  
  -- | The largest element of a non-empty list.
  maximum1 :: Ord a => NonEmpty a -> a
diff --git a/patches/generic-deriving-1.14.patch b/patches/generic-deriving-1.14.patch
deleted file mode 100644
index 5e2e3999f8e49276e56ef5d3522e7f8c1caf39ad..0000000000000000000000000000000000000000
--- a/patches/generic-deriving-1.14.patch
+++ /dev/null
@@ -1,14 +0,0 @@
-diff --git a/src/Generics/Deriving/TH/Internal.hs b/src/Generics/Deriving/TH/Internal.hs
-index 303f49e..98598e1 100644
---- a/src/Generics/Deriving/TH/Internal.hs
-+++ b/src/Generics/Deriving/TH/Internal.hs
-@@ -17,8 +17,7 @@ module Generics.Deriving.TH.Internal where
- import           Control.Monad (unless)
- 
- import           Data.Char (isAlphaNum, ord)
--import           Data.Foldable (foldr')
--import           Data.List
-+import           Data.Foldable (foldr', foldl')
- import qualified Data.Map as Map
- import           Data.Map as Map (Map)
- import           Data.Maybe (mapMaybe)
diff --git a/patches/hgeometry-0.12.0.4.patch b/patches/hgeometry-0.12.0.4.patch
index 2a70728e743a8572eec31e18e0f12f7c745da4c6..44927bc10b187f35a770adffdb749639009b8b70 100644
--- a/patches/hgeometry-0.12.0.4.patch
+++ b/patches/hgeometry-0.12.0.4.patch
@@ -57,6 +57,16 @@ index a7bc078..02a03e8 100644
  import           Data.Vinyl
  import           Data.Vinyl.CoRec
  import           Prelude                        hiding (max, min)
+diff --git a/src/Data/Geometry/RangeTree.hs b/src/Data/Geometry/RangeTree.hs
+index e08b39d..d6ec9b6 100644
+--- a/src/Data/Geometry/RangeTree.hs
++++ b/src/Data/Geometry/RangeTree.hs
+@@ -1,4 +1,5 @@
+ {-# LANGUAGE UndecidableInstances #-}
++{-# LANGUAGE UndecidableSuperClasses #-}
+ --------------------------------------------------------------------------------
+ -- |
+ -- Module      :  Data.Geometry.RangeTree
 diff --git a/src/Data/Geometry/RangeTree/Measure.hs b/src/Data/Geometry/RangeTree/Measure.hs
 index ed61048..d33ef27 100644
 --- a/src/Data/Geometry/RangeTree/Measure.hs
diff --git a/patches/hgeometry-combinatorial-0.12.0.3.patch b/patches/hgeometry-combinatorial-0.12.0.3.patch
new file mode 100644
index 0000000000000000000000000000000000000000..acd87a25c7d71cd23d9fa65b0e11d05e775b858f
--- /dev/null
+++ b/patches/hgeometry-combinatorial-0.12.0.3.patch
@@ -0,0 +1,11 @@
+diff --git a/src/Data/LSeq.hs b/src/Data/LSeq.hs
+index d7d7426..8e10c34 100644
+--- a/src/Data/LSeq.hs
++++ b/src/Data/LSeq.hs
+@@ -1,5 +1,6 @@
+ {-# LANGUAGE ScopedTypeVariables #-}
+ {-# LANGUAGE BangPatterns #-}
++{-# LANGUAGE UndecidableInstances #-}
+ --------------------------------------------------------------------------------
+ -- |
+ -- Module      :  Data.LSeq
diff --git a/patches/list-t-1.0.4.patch b/patches/list-t-1.0.5.patch
similarity index 88%
rename from patches/list-t-1.0.4.patch
rename to patches/list-t-1.0.5.patch
index d2fbaebd3f158c73d62a9b0ff42e6aaf5e87085d..6cbdef1dc196438770ed3d159676bbcf00035723 100644
--- a/patches/list-t-1.0.4.patch
+++ b/patches/list-t-1.0.5.patch
@@ -1,5 +1,5 @@
 diff --git a/library/ListT/Prelude.hs b/library/ListT/Prelude.hs
-index 1d5b2ce..87eabd5 100644
+index 2335195..9f9e9ee 100644
 --- a/library/ListT/Prelude.hs
 +++ b/library/ListT/Prelude.hs
 @@ -1,5 +1,5 @@
@@ -7,9 +7,9 @@ index 1d5b2ce..87eabd5 100644
 -( 
 +(
    module Exports,
- )
- where
-@@ -37,7 +37,7 @@ import Data.Functor as Exports
+   bimapPair',
+   secondPair',
+@@ -42,7 +42,7 @@ import Data.Functor.Classes as Exports
  import Data.Int as Exports
  import Data.IORef as Exports
  import Data.Ix as Exports
diff --git a/patches/mono-traversable-1.0.15.1.patch b/patches/mono-traversable-1.0.15.2.patch
similarity index 85%
rename from patches/mono-traversable-1.0.15.1.patch
rename to patches/mono-traversable-1.0.15.2.patch
index fe4e9cebff8d1a8999e630aa4a7795f84274ec4a..34bd7e1c75654e4b1b15170b80c15d2f5522f852 100644
--- a/patches/mono-traversable-1.0.15.1.patch
+++ b/patches/mono-traversable-1.0.15.2.patch
@@ -1,8 +1,8 @@
 diff --git a/src/Data/MonoTraversable.hs b/src/Data/MonoTraversable.hs
-index 3c9f883..8badfa6 100644
+index 2387a21..9499372 100644
 --- a/src/Data/MonoTraversable.hs
 +++ b/src/Data/MonoTraversable.hs
-@@ -92,7 +92,11 @@ import qualified Data.Vector as V
+@@ -94,7 +94,11 @@ import qualified Data.Vector as V
  import qualified Data.Vector.Unboxed as U
  import qualified Data.Vector.Storable as VS
  import qualified Data.IntSet as IntSet
@@ -15,7 +15,7 @@ index 3c9f883..8badfa6 100644
  import qualified Data.ByteString.Unsafe as SU
  import Control.Monad.Trans.Identity (IdentityT)
  
-@@ -113,7 +117,9 @@ type instance Element (ViewL a) = a
+@@ -115,7 +119,9 @@ type instance Element (ViewL a) = a
  type instance Element (ViewR a) = a
  type instance Element (IntMap a) = a
  type instance Element IntSet = Int
@@ -25,7 +25,7 @@ index 3c9f883..8badfa6 100644
  type instance Element (NonEmpty a) = a
  type instance Element (Identity a) = a
  type instance Element (r -> a) = a
-@@ -184,7 +190,9 @@ instance MonoFunctor (Seq a)
+@@ -188,7 +194,9 @@ instance MonoFunctor (Seq a)
  instance MonoFunctor (ViewL a)
  instance MonoFunctor (ViewR a)
  instance MonoFunctor (IntMap a)
@@ -35,7 +35,7 @@ index 3c9f883..8badfa6 100644
  instance MonoFunctor (NonEmpty a)
  instance MonoFunctor (Identity a)
  instance MonoFunctor (r -> a)
-@@ -360,7 +368,7 @@ class MonoFoldable mono where
+@@ -366,7 +374,7 @@ class MonoFoldable mono where
      -- /See 'Data.NonNull.ofoldMap1' from "Data.NonNull" for a total version of this function./
      ofoldMap1Ex :: Semigroup m => (Element mono -> m) -> mono -> m
      ofoldMap1Ex f = fromMaybe (Prelude.error "Data.MonoTraversable.ofoldMap1Ex")
@@ -44,7 +44,7 @@ index 3c9f883..8badfa6 100644
  
      -- | Right-associative fold of a monomorphic container with no base element.
      --
-@@ -651,7 +659,9 @@ instance MonoFoldable (Seq a) where
+@@ -657,7 +665,9 @@ instance MonoFoldable (Seq a) where
  instance MonoFoldable (ViewL a)
  instance MonoFoldable (ViewR a)
  instance MonoFoldable (IntMap a)
@@ -54,7 +54,7 @@ index 3c9f883..8badfa6 100644
  instance MonoFoldable (NonEmpty a)
  instance MonoFoldable (Identity a)
  instance MonoFoldable (Map k v) where
-@@ -1058,7 +1068,9 @@ instance MonoTraversable (Seq a)
+@@ -1066,7 +1076,9 @@ instance MonoTraversable (Seq a)
  instance MonoTraversable (ViewL a)
  instance MonoTraversable (ViewR a)
  instance MonoTraversable (IntMap a)
@@ -64,7 +64,7 @@ index 3c9f883..8badfa6 100644
  instance MonoTraversable (NonEmpty a)
  instance MonoTraversable (Identity a)
  instance MonoTraversable (Map k v)
-@@ -1199,7 +1211,9 @@ instance MonoPointed TL.Text where
+@@ -1209,7 +1221,9 @@ instance MonoPointed TL.Text where
  -- Applicative
  instance MonoPointed [a]
  instance MonoPointed (Maybe a)
diff --git a/patches/partial-isomorphisms-0.2.2.1.patch b/patches/partial-isomorphisms-0.2.2.1.patch
deleted file mode 100644
index 711fa17064624b291a5b30fbc55abb6487d3da94..0000000000000000000000000000000000000000
--- a/patches/partial-isomorphisms-0.2.2.1.patch
+++ /dev/null
@@ -1,74 +0,0 @@
-diff --git a/src/Control/Isomorphism/Partial/TH.hs b/src/Control/Isomorphism/Partial/TH.hs
-index a024daa..234d46b 100644
---- a/src/Control/Isomorphism/Partial/TH.hs
-+++ b/src/Control/Isomorphism/Partial/TH.hs
-@@ -1,3 +1,4 @@
-+{-# LANGUAGE CPP #-}
- {-# LANGUAGE TemplateHaskell #-}
- module Control.Isomorphism.Partial.TH
-   ( constructorIso
-@@ -34,7 +35,7 @@ conFields (GadtC _ _ _)       =   gadtError
- conFields (RecGadtC _ _ _)    =   gadtError
- 
- -- Data dec information
--data DecInfo = DecInfo Type [TyVarBndr] [Con]
-+data DecInfo = DecInfo Type [TyVarBndrUnit] [Con]
- 
- -- | Extract data or newtype declaration information
- decInfo :: Dec -> Q DecInfo
-@@ -43,12 +44,17 @@ decInfo (NewtypeD _ name tyVars _ c _) =  return $ DecInfo (ConT name) tyVars [c
- decInfo _ = fail "partial isomorphisms can only be derived for constructors of data type or newtype declarations."
- 
- -- | Convert tyVarBndr to type
--tyVarBndrToType :: TyVarBndr -> Type
-+tyVarBndrToType :: TyVarBndr_ spec -> Type
-+#if MIN_VERSION_template_haskell(2,17,0)
-+tyVarBndrToType (PlainTV  n _)   = VarT n
-+tyVarBndrToType (KindedTV n _ k) = SigT (VarT n) k
-+#else
- tyVarBndrToType (PlainTV  n)   = VarT n
- tyVarBndrToType (KindedTV n k) = SigT (VarT n) k
-+#endif
- 
- -- | Create Iso type for specified type and conctructor fields (Iso (a, b) (CustomType a b c))
--isoType :: Type -> [TyVarBndr] -> [Type] -> Q Type
-+isoType :: Type -> [TyVarBndrSpec] -> [Type] -> Q Type
- isoType typ tyVarBndrs fields = do
-     isoCon <- [t| Iso |]
-     return $ ForallT tyVarBndrs [] $ isoCon `AppT` (isoArgs fields) `AppT` (applyAll typ $ map tyVarBndrToType tyVarBndrs)
-@@ -96,10 +102,10 @@ defineIsomorphisms d = do
- --   The name of the partial isomorphisms is constructed by
- --   spelling the constructor name with an initial lower-case
- --   letter.
--defFromCon :: [MatchQ] -> Type -> [TyVarBndr] -> Con -> DecsQ
-+defFromCon :: [MatchQ] -> Type -> [TyVarBndrUnit] -> Con -> DecsQ
- defFromCon matches t tyVarBndrs con = do
-     let funName = rename $ conName con
--    sig <- SigD funName `fmap` isoType t tyVarBndrs (conFields con)
-+    sig <- SigD funName `fmap` isoType t (changeSpecs SpecifiedSpec tyVarBndrs) (conFields con)
-     fun <- funD funName [ clause [] (normalB (isoFromCon matches con)) [] ]
-     return [sig, fun]
- 
-@@ -130,3 +136,22 @@ nested :: ([t] -> t) -> [t] -> t
- nested tup []      =  tup []
- nested _   [x]     =  x
- nested tup (x:xs)  =  tup [x, nested tup xs]
-+
-+#if MIN_VERSION_template_haskell(2,17,0)
-+type TyVarBndr_ spec = TyVarBndr spec
-+#else
-+type TyVarBndr_ spec = TyVarBndr
-+type TyVarBndrSpec   = TyVarBndr
-+type TyVarBndrUnit   = TyVarBndr
-+
-+data Specificity
-+  = SpecifiedSpec
-+  -- | InferredSpec
-+#endif
-+
-+changeSpecs :: newSpec -> [TyVarBndr_ oldSpec] -> [TyVarBndr_ newSpec]
-+#if MIN_VERSION_template_haskell(2,17,0)
-+changeSpecs newSpec = map (newSpec <$)
-+#else
-+changeSpecs _ = id
-+#endif
diff --git a/patches/partial-isomorphisms-0.2.3.0.patch b/patches/partial-isomorphisms-0.2.3.0.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391
diff --git a/patches/persistent-2.13.0.3.patch b/patches/persistent-2.13.0.3.patch
deleted file mode 100644
index e7eaaef7f1263a353284ec316787e7910156c675..0000000000000000000000000000000000000000
--- a/patches/persistent-2.13.0.3.patch
+++ /dev/null
@@ -1,162 +0,0 @@
-diff --git a/Database/Persist/TH.hs b/Database/Persist/TH.hs
-index 1014702..af903de 100644
---- a/Database/Persist/TH.hs
-+++ b/Database/Persist/TH.hs
-@@ -91,7 +91,6 @@ import Data.Either
- import qualified Data.HashMap.Strict as HM
- import Data.Int (Int64)
- import Data.Ix (Ix)
--import Data.List (foldl')
- import qualified Data.List as List
- import Data.List.NonEmpty (NonEmpty(..))
- import qualified Data.List.NonEmpty as NEL
-@@ -108,7 +107,7 @@ import GHC.TypeLits
- import Instances.TH.Lift ()
-     -- Bring `Lift (fmap k v)` instance into scope, as well as `Lift Text`
-     -- instance on pre-1.2.4 versions of `text`
--import Data.Foldable (toList)
-+import Data.Foldable (foldl', toList)
- import qualified Data.Set as Set
- import Language.Haskell.TH.Lib
-        (appT, conE, conK, conT, litT, strTyLit, varE, varP, varT)
-@@ -1284,7 +1283,7 @@ mkToPersistFields mps ed = do
-     go = do
-         xs <- sequence $ replicate fieldCount $ newName "x"
-         let name = mkEntityDefName ed
--            pat = ConP name $ fmap VarP xs
-+            pat = conPCompat name $ fmap VarP xs
-         sp <- [|SomePersistField|]
-         let bod = ListE $ fmap (AppE sp . VarE) xs
-         return $ normalClause [pat] bod
-@@ -1306,7 +1305,7 @@ mkToPersistFields mps ed = do
-                 , [sp `AppE` VarE x]
-                 , after
-                 ]
--        return $ normalClause [ConP name [VarP x]] body
-+        return $ normalClause [conPCompat name [VarP x]] body
- 
- mkToFieldNames :: [UniqueDef] -> Q Dec
- mkToFieldNames pairs = do
-@@ -1328,7 +1327,7 @@ mkUniqueToValues pairs = do
-     go :: UniqueDef -> Q Clause
-     go (UniqueDef constr _ names _) = do
-         xs <- mapM (const $ newName "x") names
--        let pat = ConP (mkConstraintName constr) $ fmap VarP $ toList xs
-+        let pat = conPCompat (mkConstraintName constr) $ fmap VarP $ toList xs
-         tpv <- [|toPersistValue|]
-         let bod = ListE $ fmap (AppE tpv . VarE) $ toList xs
-         return $ normalClause [pat] bod
-@@ -1367,7 +1366,7 @@ mkFromPersistValues mps entDef
-     mkClauses _ [] = return []
-     mkClauses before (field:after) = do
-         x <- newName "x"
--        let null' = ConP 'PersistNull []
-+        let null' = conPCompat 'PersistNull []
-             pat = ListP $ mconcat
-                 [ fmap (const null') before
-                 , [VarP x]
-@@ -1404,20 +1403,20 @@ mkLensClauses mps entDef = do
-     valName <- newName "value"
-     xName <- newName "x"
-     let idClause = normalClause
--            [ConP (keyIdName entDef) []]
-+            [conPCompat (keyIdName entDef) []]
-             (lens' `AppE` getId `AppE` setId)
-     return $ idClause : if unboundEntitySum entDef
-         then fmap (toSumClause lens' keyVar valName xName) (getUnboundFieldDefs entDef)
-         else fmap (toClause lens' getVal dot keyVar valName xName) (getUnboundFieldDefs entDef)
-   where
-     toClause lens' getVal dot keyVar valName xName fieldDef = normalClause
--        [ConP (filterConName mps entDef fieldDef) []]
-+        [conPCompat (filterConName mps entDef fieldDef) []]
-         (lens' `AppE` getter `AppE` setter)
-       where
-         fieldName = fieldDefToRecordName mps entDef fieldDef
-         getter = InfixE (Just $ VarE fieldName) dot (Just getVal)
-         setter = LamE
--            [ ConP 'Entity [VarP keyVar, VarP valName]
-+            [ conPCompat 'Entity [VarP keyVar, VarP valName]
-             , VarP xName
-             ]
-             $ ConE 'Entity `AppE` VarE keyVar `AppE` RecUpdE
-@@ -1425,20 +1424,20 @@ mkLensClauses mps entDef = do
-                 [(fieldName, VarE xName)]
- 
-     toSumClause lens' keyVar valName xName fieldDef = normalClause
--        [ConP (filterConName mps entDef fieldDef) []]
-+        [conPCompat (filterConName mps entDef fieldDef) []]
-         (lens' `AppE` getter `AppE` setter)
-       where
-         emptyMatch = Match WildP (NormalB $ VarE 'error `AppE` LitE (StringL "Tried to use fieldLens on a Sum type")) []
-         getter = LamE
--            [ ConP 'Entity [WildP, VarP valName]
-+            [ conPCompat 'Entity [WildP, VarP valName]
-             ] $ CaseE (VarE valName)
--            $ Match (ConP (sumConstrName mps entDef fieldDef) [VarP xName]) (NormalB $ VarE xName) []
-+            $ Match (conPCompat (sumConstrName mps entDef fieldDef) [VarP xName]) (NormalB $ VarE xName) []
- 
-             -- FIXME It would be nice if the types expressed that the Field is
-             -- a sum type and therefore could result in Maybe.
-             : if length (getUnboundFieldDefs entDef) > 1 then [emptyMatch] else []
-         setter = LamE
--            [ ConP 'Entity [VarP keyVar, WildP]
-+            [ conPCompat 'Entity [VarP keyVar, WildP]
-             , VarP xName
-             ]
-             $ ConE 'Entity `AppE` VarE keyVar `AppE` (ConE (sumConstrName mps entDef fieldDef) `AppE` VarE xName)
-@@ -2360,7 +2359,7 @@ mkUniqueKeys def = do
-             x' <- newName $ '_' : unpack (unFieldNameHS x)
-             return (x, x')
-         let pcs = fmap (go xs) $ entityUniques $ unboundEntityDef def
--        let pat = ConP
-+        let pat = conPCompat
-                 (mkEntityDefName def)
-                 (fmap (VarP . snd) xs)
-         return $ normalClause [pat] (ListE pcs)
-@@ -2549,7 +2548,7 @@ mkField mps entityMap et fieldDef = do
-             maybeIdType mps entityMap fieldDef Nothing Nothing
-     bod <- mkLookupEntityField et (unboundFieldNameHS fieldDef)
-     let cla = normalClause
--                [ConP name []]
-+                [conPCompat name []]
-                 bod
-     return $ EntityFieldTH con cla
-   where
-@@ -2579,7 +2578,7 @@ mkIdField mps ued = do
-                 [mkEqualP (VarT $ mkName "typ") entityIdType]
-                 $ NormalC name []
-         , entityFieldTHClause =
--            normalClause [ConP name []] clause
-+            normalClause [conPCompat name []] clause
-         }
- 
- lookupEntityField
-@@ -2658,7 +2657,7 @@ mkJSON mps (fixEntityDef -> def) = do
-             typeInstanceD ''ToJSON (mpsGeneric mps) typ [toJSON']
-           where
-             toJSON' = FunD 'toJSON $ return $ normalClause
--                [ConP conName $ fmap VarP xs]
-+                [conPCompat conName $ fmap VarP xs]
-                 (objectE `AppE` ListE pairs)
-               where
-                 pairs = zipWith toPair fields xs
-@@ -2670,7 +2669,7 @@ mkJSON mps (fixEntityDef -> def) = do
-             typeInstanceD ''FromJSON (mpsGeneric mps) typ [parseJSON']
-           where
-             parseJSON' = FunD 'parseJSON
--                [ normalClause [ConP 'Object [VarP obj]]
-+                [ normalClause [conPCompat 'Object [VarP obj]]
-                     (foldl'
-                         (\x y -> InfixE (Just x) apE' (Just y))
-                         (pureE `AppE` ConE conName)
-@@ -3132,3 +3131,10 @@ setNull (fd :| fds) =
-         else error $
-             "foreign key columns must all be nullable or non-nullable"
-            ++ show (fmap (unFieldNameHS . unboundFieldNameHS) (fd:fds))
-+
-+conPCompat :: Name -> [Pat] -> Pat
-+conPCompat n pats = ConP n
-+#if MIN_VERSION_template_haskell(2,18,0)
-+                         []
-+#endif
-+                         pats
diff --git a/patches/persistent-2.13.1.1.patch b/patches/persistent-2.13.1.2.patch
similarity index 100%
rename from patches/persistent-2.13.1.1.patch
rename to patches/persistent-2.13.1.2.patch
diff --git a/patches/row-types-1.0.1.0.patch b/patches/row-types-1.0.1.0.patch
deleted file mode 100644
index d0e22310286fab2066a8ba868baaa1c7cceeb04f..0000000000000000000000000000000000000000
--- a/patches/row-types-1.0.1.0.patch
+++ /dev/null
@@ -1,53 +0,0 @@
-diff --git a/src/Data/Row/Records.hs b/src/Data/Row/Records.hs
-index 9b352e6..3a8321e 100644
---- a/src/Data/Row/Records.hs
-+++ b/src/Data/Row/Records.hs
-@@ -399,7 +399,7 @@ mapF f = unRFMap . biMetamorph @_ @_ @ϕ @ρ @c @(,) @RecAp @(RFMap g) @App Prox
- 
- -- | A function to map over a record given no constraint.
- map' :: forall f r. FreeForall r => (forall a. a -> f a) -> Rec r -> Rec (Map f r)
--map' = map @Unconstrained1
-+map' f = map @Unconstrained1 f
- 
- -- | Lifts a natural transformation over a record.  In other words, it acts as a
- -- record transformer to convert a record of @f a@ values to a record of @g a@
-@@ -420,7 +420,7 @@ transform f = unRMap . metamorph @_ @r @c @(,) @(RMap f) @(RMap g) @f Proxy doNi
- 
- -- | A version of 'transform' for when there is no constraint.
- transform' :: forall r f g. FreeForall r => (forall a. f a -> g a) -> Rec (Map f r) -> Rec (Map g r)
--transform' = transform @Unconstrained1 @r
-+transform' f = transform @Unconstrained1 @r f
- 
- 
- data RecMapPair f g ρ = RecMapPair (Rec (Map f ρ)) (Rec (Map g ρ))
-@@ -445,7 +445,7 @@ zipTransform f x y = unRMap $ metamorph @_ @r @c @(,) @(RecMapPair f g) @(RMap h
- -- | A version of 'zipTransform' for when there is no constraint.
- zipTransform' :: forall r f g h .
-   FreeForall r => (forall a. f a -> g a -> h a) -> Rec (Map f r) -> Rec (Map g r) -> Rec (Map h r)
--zipTransform' = zipTransform @Unconstrained1 @r
-+zipTransform' f = zipTransform @Unconstrained1 @r f
- 
- -- | Traverse a function over a record.  Note that the fields of the record will
- -- be accessed in lexicographic order by the labels.
-diff --git a/src/Data/Row/Variants.hs b/src/Data/Row/Variants.hs
-index e7d0009..360a6ab 100644
---- a/src/Data/Row/Variants.hs
-+++ b/src/Data/Row/Variants.hs
-@@ -300,7 +300,7 @@ map f = unVMap . metamorph @_ @r @c @Either @Var @(VMap f) @Identity Proxy impos
- 
- -- | A function to map over a variant given no constraint.
- map' :: forall f r. FreeForall r => (forall a. a -> f a) -> Var r -> Var (Map f r)
--map' = map @Unconstrained1
-+map' f = map @Unconstrained1 f
- 
- -- | Lifts a natrual transformation over a variant.  In other words, it acts as a
- -- variant transformer to convert a variant of @f a@ values to a variant of @g a@
-@@ -325,7 +325,7 @@ transform f = unVMap . metamorph @_ @r @c @Either @(VMap f) @(VMap g) @f Proxy d
- 
- -- | A form of @transformC@ that doesn't have a constraint on @a@
- transform' :: forall r f g . FreeForall r => (forall a. f a -> g a) -> Var (Map f r) -> Var (Map g r)
--transform' = transform @Unconstrained1 @r
-+transform' f = transform @Unconstrained1 @r f
- 
- -- | Traverse a function over a variant.
- traverse :: forall c f r. (Forall r c, Functor f) => (forall a. c a => a -> f a) -> Var r -> f (Var r)
diff --git a/patches/row-types-1.0.1.2.patch b/patches/row-types-1.0.1.2.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391
diff --git a/patches/shake-0.19.5.patch b/patches/shake-0.19.6.patch
similarity index 99%
rename from patches/shake-0.19.5.patch
rename to patches/shake-0.19.6.patch
index b4d55d0d41cb9f8b34756a9f6e522692f7271c65..3cc9fd5b354bb48c3dbcf825ac5f536b469492d4 100644
--- a/patches/shake-0.19.5.patch
+++ b/patches/shake-0.19.6.patch
@@ -12,7 +12,7 @@ index e366220..22f8df6 100644
  import qualified Data.HashSet as Set
  import Data.Maybe
 diff --git a/src/Development/Shake/Internal/Core/Action.hs b/src/Development/Shake/Internal/Core/Action.hs
-index f9bde58..3404cc0 100644
+index 5cddddb..a65b166 100644
 --- a/src/Development/Shake/Internal/Core/Action.hs
 +++ b/src/Development/Shake/Internal/Core/Action.hs
 @@ -33,7 +33,7 @@ import Control.Concurrent.Extra
@@ -154,7 +154,7 @@ index 3946ee2..3984e0d 100644
  import qualified Data.ByteString.Char8 as BS
  import qualified Data.HashSet as Set
 diff --git a/src/Development/Shake/Internal/Rules/Files.hs b/src/Development/Shake/Internal/Rules/Files.hs
-index a490578..5ca3e69 100644
+index 9e12fd2..a00ef0f 100644
 --- a/src/Development/Shake/Internal/Rules/Files.hs
 +++ b/src/Development/Shake/Internal/Rules/Files.hs
 @@ -8,7 +8,7 @@ module Development.Shake.Internal.Rules.Files(
diff --git a/patches/text-show-3.9.patch b/patches/text-show-3.9.patch
deleted file mode 100644
index e37d83a1abfbb68c48faedc8f85fa37680028845..0000000000000000000000000000000000000000
--- a/patches/text-show-3.9.patch
+++ /dev/null
@@ -1,243 +0,0 @@
-diff --git a/src/TextShow/TH/Internal.hs b/src/TextShow/TH/Internal.hs
-index c83c70e..c5c61d2 100644
---- a/src/TextShow/TH/Internal.hs
-+++ b/src/TextShow/TH/Internal.hs
-@@ -78,7 +78,11 @@ import           GHC.Exts ( Char(..), Double(..), Float(..), Int(..), Word(..)
-                           , Char#, Double#, Float#, Int#, Word#
- #if MIN_VERSION_base(4,13,0)
-                           , Int8#, Int16#, Word8#, Word16#
-+# if MIN_VERSION_base(4,16,0)
-+                          , int8ToInt#, int16ToInt#, word8ToWord#, word16ToWord#
-+# else
-                           , extendInt8#, extendInt16#, extendWord8#, extendWord16#
-+# endif
- #endif
-                           )
- import           GHC.Show (appPrec, appPrec1)
-@@ -1258,24 +1262,68 @@ primShowTbl = Map.fromList
-                     })
- #if MIN_VERSION_base(4,13,0)
-     , (''Int8#,   PrimShow
--                    { primShowBoxer      = appE (conE 'I#) . appE (varE 'extendInt8#)
-+                    { primShowBoxer      = appE (conE 'I#) . appE (varE
-+# if MIN_VERSION_base(4,16,0)
-+                                                                        'int8ToInt#
-+# else
-+                                                                        'extendInt8#
-+# endif
-+                                                                  )
-                     , primShowPostfixMod = oneHashE
--                    , primShowConv       = mkNarrowE "narrowInt8#"
-+                    , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                     "intToInt8#"
-+# else
-+                                                     "narrowInt8#"
-+# endif
-                     })
-     , (''Int16#,  PrimShow
--                    { primShowBoxer      = appE (conE 'I#) . appE (varE 'extendInt16#)
-+                    { primShowBoxer      = appE (conE 'I#) . appE (varE
-+# if MIN_VERSION_base(4,16,0)
-+                                                                        'int16ToInt#
-+# else
-+                                                                        'extendInt16#
-+# endif
-+                                                                  )
-                     , primShowPostfixMod = oneHashE
--                    , primShowConv       = mkNarrowE "narrowInt16#"
-+                    , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                     "intToInt16#"
-+# else
-+                                                     "narrowInt16#"
-+# endif
-                     })
-     , (''Word8#,  PrimShow
--                    { primShowBoxer      = appE (conE 'W#) . appE (varE 'extendWord8#)
-+                    { primShowBoxer      = appE (conE 'W#) . appE (varE
-+# if MIN_VERSION_base(4,16,0)
-+                                                                        'word8ToWord#
-+# else
-+                                                                        'extendWord8#
-+# endif
-+                                                                  )
-                     , primShowPostfixMod = twoHashE
--                    , primShowConv       = mkNarrowE "narrowWord8#"
-+                    , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                     "wordToWord8#"
-+# else
-+                                                     "narrowWord8#"
-+# endif
-                     })
-     , (''Word16#, PrimShow
--                    { primShowBoxer      = appE (conE 'W#) . appE (varE 'extendWord16#)
-+                    { primShowBoxer      = appE (conE 'W#) . appE (varE
-+# if MIN_VERSION_base(4,16,0)
-+                                                                        'word16ToWord#
-+# else
-+                                                                        'extendWord16#
-+# endif
-+                                                                  )
-                     , primShowPostfixMod = twoHashE
--                    , primShowConv       = mkNarrowE "narrowWord16#"
-+                    , primShowConv       = mkNarrowE
-+# if MIN_VERSION_base(4,16,0)
-+                                                     "wordToWord16#"
-+# else
-+                                                     "narrowWord16#"
-+# endif
-                     })
- #endif
-     ]
-diff --git a/tests/Derived/MagicHash.hs b/tests/Derived/MagicHash.hs
-index 7421618..3b938f1 100644
---- a/tests/Derived/MagicHash.hs
-+++ b/tests/Derived/MagicHash.hs
-@@ -124,8 +124,8 @@ instance (Arbitrary a, Arbitrary b) => Arbitrary (TyCon'# a b) where
-       I# i2 <- arbitrary
-       W# w1 <- arbitrary
-       W# w2 <- arbitrary
--      pure $ TyCon'# a b (narrowInt8# i1)  (narrowInt16# i2)
--                         (narrowWord8# w1) (narrowWord16# w2)
-+      pure $ TyCon'# a b (intToInt8Compat# i1)   (intToInt16Compat# i2)
-+                         (wordToWord8Compat# w1) (wordToWord16Compat# w2)
- 
- instance (Arbitrary a, Arbitrary b) => Arbitrary (TyFamily'# a b) where
-     arbitrary = do
-@@ -135,8 +135,35 @@ instance (Arbitrary a, Arbitrary b) => Arbitrary (TyFamily'# a b) where
-       I# i2 <- arbitrary
-       W# w1 <- arbitrary
-       W# w2 <- arbitrary
--      pure $ TyFamily'# a b (narrowInt8# i1)  (narrowInt16# i2)
--                            (narrowWord8# w1) (narrowWord16# w2)
-+      pure $ TyFamily'# a b (intToInt8Compat# i1)   (intToInt16Compat# i2)
-+                            (wordToWord8Compat# w1) (wordToWord16Compat# w2)
-+
-+
-+# if MIN_VERSION_base(4,16,0)
-+intToInt8Compat# :: Int# -> Int8#
-+intToInt8Compat# = intToInt8#
-+
-+intToInt16Compat# :: Int# -> Int16#
-+intToInt16Compat# = intToInt16#
-+
-+wordToWord8Compat# :: Word# -> Word8#
-+wordToWord8Compat# = wordToWord8#
-+
-+wordToWord16Compat# :: Word# -> Word16#
-+wordToWord16Compat# = wordToWord16#
-+# else
-+intToInt8Compat# :: Int# -> Int8#
-+intToInt8Compat# = narrowInt8#
-+
-+intToInt16Compat# :: Int# -> Int16#
-+intToInt16Compat# = narrowInt16#
-+
-+wordToWord8Compat# :: Word# -> Word8#
-+wordToWord8Compat# = narrowWord8#
-+
-+wordToWord16Compat# :: Word# -> Word16#
-+wordToWord16Compat# = narrowWord16#
-+# endif
- #endif
- 
- -------------------------------------------------------------------------------
-diff --git a/tests/Derived/TypeSynonyms.hs b/tests/Derived/TypeSynonyms.hs
-index 3882bd9..12deec2 100644
---- a/tests/Derived/TypeSynonyms.hs
-+++ b/tests/Derived/TypeSynonyms.hs
-@@ -78,10 +78,12 @@ newtype instance TyFamily a b = TyFamily
- -------------------------------------------------------------------------------
- 
- -- TODO: Replace these with non-orphan instances
-+#if !(MIN_VERSION_base(4,16,0))
- $(deriveShow1 ''(,,,))
- #if defined(NEW_FUNCTOR_CLASSES)
- $(deriveShow2 ''(,,,))
- #endif
-+#endif
- 
- $(deriveShow1 ''TyCon)
- #if defined(NEW_FUNCTOR_CLASSES)
-diff --git a/tests/Instances/Data/Tuple.hs b/tests/Instances/Data/Tuple.hs
-index e96b6ad..019bb83 100644
---- a/tests/Instances/Data/Tuple.hs
-+++ b/tests/Instances/Data/Tuple.hs
-@@ -1,3 +1,4 @@
-+{-# LANGUAGE CPP                #-}
- {-# LANGUAGE DeriveGeneric      #-}
- {-# LANGUAGE StandaloneDeriving #-}
- {-# OPTIONS_GHC -fno-warn-orphans #-}
-@@ -99,8 +100,10 @@ instance ( Arbitrary a
-          ) => Arbitrary (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
-     arbitrary = genericArbitrary
- 
-+#if !(MIN_VERSION_base(4,16,0))
- deriving instance Generic (a, b, c, d, e, f, g, h, i, j, k)
- deriving instance Generic (a, b, c, d, e, f, g, h, i, j, k, l)
- deriving instance Generic (a, b, c, d, e, f, g, h, i, j, k, l, m)
- deriving instance Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
- deriving instance Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-+#endif
-diff --git a/tests/Instances/Data/Typeable.hs b/tests/Instances/Data/Typeable.hs
-index 2812c05..890c2fd 100644
---- a/tests/Instances/Data/Typeable.hs
-+++ b/tests/Instances/Data/Typeable.hs
-@@ -37,7 +37,11 @@ import Data.Typeable.Internal (TyCon(..))
- #if MIN_VERSION_base(4,10,0)
- import GHC.Exts (Int(..), Ptr(..))
- import GHC.Types (KindRep(..), RuntimeRep(..), TypeLitSort(..),
--                  VecCount(..), VecElem(..))
-+                  VecCount(..), VecElem(..)
-+# if MIN_VERSION_base(4,16,0)
-+                 , Levity(..)
-+# endif
-+                 )
- import Type.Reflection (SomeTypeRep(..), Typeable, TypeRep, typeRep)
- #else
- import Data.Typeable.Internal (TypeRep(..))
-@@ -80,8 +84,13 @@ instance Arbitrary RuntimeRep where
-     arbitrary = oneof [ VecRep <$> arbitrary <*> arbitrary
-                       , pure $ TupleRep []
-                       , pure $ SumRep []
-+#if MIN_VERSION_base(4,16,0)
-+                      , pure $ BoxedRep Lifted
-+                      , pure $ BoxedRep Unlifted
-+#else
-                       , pure LiftedRep
-                       , pure UnliftedRep
-+#endif
-                       , pure IntRep
-                       , pure WordRep
-                       , pure Int64Rep
-diff --git a/text-show.cabal b/text-show.cabal
-index b328593..c69a876 100644
---- a/text-show.cabal
-+++ b/text-show.cabal
-@@ -1,5 +1,6 @@
- name:                text-show
- version:             3.9
-+x-revision: 1
- synopsis:            Efficient conversion of values into Text
- description:         @text-show@ offers a replacement for the @Show@ typeclass intended
-                      for use with @Text@ instead of @String@s. This package was created
-@@ -157,7 +158,7 @@ library
-   build-depends:       array                 >= 0.3    && < 0.6
-                      , base-compat-batteries >= 0.11   && < 0.12
-                      , bifunctors            >= 5.1    && < 6
--                     , bytestring            >= 0.9    && < 0.11
-+                     , bytestring            >= 0.9    && < 0.12
-                      , bytestring-builder
-                      , containers            >= 0.1    && < 0.7
-                      , generic-deriving      >= 1.11   && < 2
-@@ -341,7 +342,7 @@ test-suite spec
-   build-depends:       array                 >= 0.3    && < 0.6
-                      , base-compat-batteries >= 0.11   && < 0.12
-                      , base-orphans          >= 0.8.2  && < 0.9
--                     , bytestring            >= 0.9    && < 0.11
-+                     , bytestring            >= 0.9    && < 0.12
-                      , bytestring-builder
-                      , deriving-compat       >= 0.5.6  && < 1
-                      , generic-deriving      >= 1.11   && < 2
diff --git a/patches/yaml-0.11.5.0.patch b/patches/yaml-0.11.6.0.patch
similarity index 100%
rename from patches/yaml-0.11.5.0.patch
rename to patches/yaml-0.11.6.0.patch