diff --git a/patches/bytestring-strict-builder-0.4.5.3.patch b/patches/bytestring-strict-builder-0.4.5.4.patch
similarity index 73%
rename from patches/bytestring-strict-builder-0.4.5.3.patch
rename to patches/bytestring-strict-builder-0.4.5.4.patch
index db67f51e2b4d899afb261c0116af58e18d433230..1c6a6d374a06da33c58356846171ed06a3ad5abf 100644
--- a/patches/bytestring-strict-builder-0.4.5.3.patch
+++ b/patches/bytestring-strict-builder-0.4.5.4.patch
@@ -46,27 +46,3 @@ index 69ba0ff..9b1d2bc 100644
  
  -- | Select an implementation depending on the bit-size of 'Word's.
  -- Currently, it produces a runtime failure if the bitsize is different.
-diff --git a/library/ByteString/StrictBuilder/UTF8.hs b/library/ByteString/StrictBuilder/UTF8.hs
-index c1bb7f4..7e6d964 100644
---- a/library/ByteString/StrictBuilder/UTF8.hs
-+++ b/library/ByteString/StrictBuilder/UTF8.hs
-@@ -19,8 +19,8 @@ type UTF8Char =
- 
- {-# INLINE char #-}
- char :: Char -> UTF8Char
--char =
--  unicodeCodePoint . ord
-+char x =
-+  unicodeCodePoint (ord x)
- 
- {-# INLINE unicodeCodePoint #-}
- unicodeCodePoint :: Int -> UTF8Char
-@@ -28,7 +28,7 @@ unicodeCodePoint x f1 f2 f3 f4 =
-   if x <= 0x7F
-     then
-       f1 (fromIntegral x)
--    else 
-+    else
-       if x <= 0x07FF
-         then
-           f2
diff --git a/patches/constraints-extras-0.3.0.2.patch b/patches/constraints-extras-0.3.0.2.patch
deleted file mode 100644
index 5d61b2f63e26491924a618ef099eec3e2af668a8..0000000000000000000000000000000000000000
--- a/patches/constraints-extras-0.3.0.2.patch
+++ /dev/null
@@ -1,57 +0,0 @@
-diff --git a/constraints-extras.cabal b/constraints-extras.cabal
-index 029e5a8..0e8c49c 100644
---- a/constraints-extras.cabal
-+++ b/constraints-extras.cabal
-@@ -1,5 +1,6 @@
- name: constraints-extras
- version: 0.3.0.2
-+x-revision: 2
- synopsis: Utility package for constraints
- description: Convenience functions and TH for working with constraints. See <https://github.com/obsidiansystems/constraints-extras/blob/develop/README.md README.md> for example usage.
- category: Constraints
-@@ -32,18 +33,18 @@ library
-                   , TypeOperators
-                   , ConstraintKinds
-                   , TemplateHaskell
--  build-depends: base >=4.9 && <4.14
--               , constraints >= 0.9 && < 0.12
--               , template-haskell >=2.11 && <2.16
-+  build-depends: base >=4.9 && <4.15
-+               , constraints >= 0.9 && < 0.13
-+               , template-haskell >=2.11 && <2.17
-   hs-source-dirs:  src
-   default-language: Haskell2010
- 
- executable readme
-   if !flag(build-readme)
-     buildable: False
--  build-depends: base >=4.9 && <4.14
-+  build-depends: base >=4.9 && <4.15
-                , aeson
--               , constraints >= 0.9 && < 0.12
-+               , constraints >= 0.9 && < 0.13
-                , constraints-extras
-   main-is: README.lhs
-   ghc-options: -Wall -optL -q
-diff --git a/src/Data/Constraint/Extras/TH.hs b/src/Data/Constraint/Extras/TH.hs
-index 148ff3e..52b2ec3 100644
---- a/src/Data/Constraint/Extras/TH.hs
-+++ b/src/Data/Constraint/Extras/TH.hs
-@@ -1,3 +1,4 @@
-+{-# LANGUAGE CPP #-}
- {-# LANGUAGE LambdaCase #-}
- {-# LANGUAGE QuasiQuotes #-}
- {-# LANGUAGE TemplateHaskell #-}
-@@ -55,7 +56,11 @@ matches c n argDictName = do
-                     Nothing -> WildP : rest done
-                     Just _ -> VarP v : rest True
-                 pat = foldr patf (const []) ps False
--            in [Match (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
-+            in [Match (ConP name
-+#if MIN_VERSION_template_haskell(2,18,0)
-+                            []
-+#endif
-+                            pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
-       ForallC _ _ (GadtC [name] _ _) -> return $
-         [Match (RecP name []) (NormalB $ ConE 'Dict) []]
-       a -> error $ "deriveArgDict matches: Unmatched 'Dec': " ++ show a
diff --git a/patches/constraints-extras-0.3.1.0.patch b/patches/constraints-extras-0.3.1.0.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e0fb07e9414ddcffd9926e173ffa42d08f3bade5
--- /dev/null
+++ b/patches/constraints-extras-0.3.1.0.patch
@@ -0,0 +1,35 @@
+diff --git a/constraints-extras.cabal b/constraints-extras.cabal
+index c27b0a7..1504c33 100644
+--- a/constraints-extras.cabal
++++ b/constraints-extras.cabal
+@@ -33,7 +33,7 @@ library
+                   , ConstraintKinds
+                   , TemplateHaskell
+   build-depends: base >=4.9 && <4.16
+-               , constraints >= 0.9 && < 0.13
++               , constraints >= 0.9 && < 0.14
+                , template-haskell >=2.11 && <2.18
+   hs-source-dirs:  src
+   default-language: Haskell2010
+diff --git a/src/Data/Constraint/Extras/TH.hs b/src/Data/Constraint/Extras/TH.hs
+index 9259409..b22c80b 100644
+--- a/src/Data/Constraint/Extras/TH.hs
++++ b/src/Data/Constraint/Extras/TH.hs
+@@ -1,3 +1,4 @@
++{-# LANGUAGE CPP #-}
+ {-# LANGUAGE LambdaCase #-}
+ {-# LANGUAGE QuasiQuotes #-}
+ {-# LANGUAGE TemplateHaskell #-}
+@@ -52,7 +53,11 @@ matches c constrs argDictName = do
+                   Nothing -> WildP : rest done
+                   Just _ -> VarP v : rest True
+               pat = foldr patf (const []) ps False
+-          in [Match (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
++            in [Match (ConP name
++#if MIN_VERSION_template_haskell(2,18,0)
++                            []
++#endif
++                            pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
+     ForallC _ _ (GadtC [name] _ _) -> return $
+       [Match (RecP name []) (NormalB $ ConE 'Dict) []]
+     a -> error $ "deriveArgDict matches: Unmatched 'Dec': " ++ show a
diff --git a/patches/parameterized-utils-2.1.2.0.patch b/patches/parameterized-utils-2.1.3.0.patch
similarity index 52%
rename from patches/parameterized-utils-2.1.2.0.patch
rename to patches/parameterized-utils-2.1.3.0.patch
index 92043608ce41bffd751674df7bc684cd8112c42a..d951eae3b9ee37e0d858e3fa3f9fd899e3041e4a 100644
--- a/patches/parameterized-utils-2.1.2.0.patch
+++ b/patches/parameterized-utils-2.1.3.0.patch
@@ -1,59 +1,5 @@
-diff --git a/src/Data/Parameterized/Context/Safe.hs b/src/Data/Parameterized/Context/Safe.hs
-index d4c20f8..0fa5597 100644
---- a/src/Data/Parameterized/Context/Safe.hs
-+++ b/src/Data/Parameterized/Context/Safe.hs
-@@ -506,7 +506,7 @@ type instance IndexF   (Assignment (f :: k -> Type) ctx) = Index ctx
- type instance IxValueF (Assignment (f :: k -> Type) ctx) = f
- 
- instance forall k (f :: k -> Type) ctx. IxedF k (Assignment f ctx) where
--  ixF :: Index ctx x -> Lens.Lens' (Assignment f ctx) (f x)
-+  ixF :: Index ctx x -> Lens.Traversal' (Assignment f ctx) (f x)
-   ixF idx f = adjustM f idx
- 
- instance forall k (f :: k -> Type) ctx. IxedF' k (Assignment f ctx) where
-@@ -544,7 +544,7 @@ testEq _ AssignmentEmpty AssignmentExtend{} = Nothing
- testEq _ AssignmentExtend{} AssignmentEmpty = Nothing
- 
- instance TestEqualityFC Assignment where
--   testEqualityFC = testEq
-+   testEqualityFC f = testEq f
- instance TestEquality f => TestEquality (Assignment f) where
-    testEquality x y = testEq testEquality x y
- instance TestEquality f => PolyEq (Assignment f x) (Assignment f y) where
-@@ -565,7 +565,7 @@ compareAsgn test (AssignmentExtend ctx1 x) (AssignmentExtend ctx2 y) =
-               EQF -> EQF
- 
- instance OrdFC Assignment where
--  compareFC = compareAsgn
-+  compareFC f = compareAsgn f
- 
- instance OrdF f => OrdF (Assignment f) where
-   compareF = compareAsgn compareF
-@@ -598,11 +598,11 @@ instance FoldableFC Assignment where
-   foldMapFC = foldMapFCDefault
- 
- instance TraversableFC Assignment where
--  traverseFC = traverseF
-+  traverseFC f = traverseF f
- 
- -- | Map assignment
- map :: (forall tp . f tp -> g tp) -> Assignment f c -> Assignment g c
--map = fmapFC
-+map f = fmapFC f
- 
- traverseF :: forall k (f:: k -> Type) (g::k -> Type) (m:: Type -> Type) (c::Ctx k)
-            . Applicative m
-@@ -616,7 +616,7 @@ traverseF f (AssignmentExtend asgn x) = pure AssignmentExtend <*> traverseF f as
- toList :: (forall tp . f tp -> a)
-        -> Assignment f c
-        -> [a]
--toList = toListFC
-+toList f = toListFC f
- 
- zipWithM :: Applicative m
-          => (forall tp . f tp -> g tp -> m (h tp))
 diff --git a/src/Data/Parameterized/Context/Unsafe.hs b/src/Data/Parameterized/Context/Unsafe.hs
-index 0627cf5..3e1569d 100644
+index f44f521..ec44346 100644
 --- a/src/Data/Parameterized/Context/Unsafe.hs
 +++ b/src/Data/Parameterized/Context/Unsafe.hs
 @@ -1,5 +1,6 @@
@@ -63,17 +9,8 @@ index 0627cf5..3e1569d 100644
  {-# LANGUAGE FlexibleInstances #-}
  {-# LANGUAGE InstanceSigs #-}
  {-# LANGUAGE GADTs #-}
-@@ -870,7 +871,7 @@ instance forall k (f :: k -> Type) ctx. IxedF' k (Assignment (f :: k -> Type) ct
-   ixF' idx f = adjustM f idx
- 
- instance forall k (f :: k -> Type) ctx. IxedF k (Assignment f ctx) where
--  ixF = ixF'
-+  ixF idx = ixF' idx
- 
- -- This is an unsafe version of update that changes the type of the expression.
- unsafeUpdate :: Int -> Assignment f ctx -> f u -> Assignment f ctx'
 diff --git a/src/Data/Parameterized/NatRepr.hs b/src/Data/Parameterized/NatRepr.hs
-index bde0080..4e95448 100644
+index 94db5bf..4e95448 100644
 --- a/src/Data/Parameterized/NatRepr.hs
 +++ b/src/Data/Parameterized/NatRepr.hs
 @@ -129,6 +129,8 @@ module Data.Parameterized.NatRepr
@@ -111,15 +48,6 @@ index bde0080..4e95448 100644
  
  addIsLeq :: f n -> g m -> LeqProof n (n + m)
  addIsLeq n m = leqAdd (leqRefl n) m
-@@ -540,7 +542,7 @@ natFromZero :: forall h a
-             . NatRepr h
-            -> (forall n. (n <= h) => NatRepr n -> a)
-            -> [a]
--natFromZero = natForEach (knownNat @0)
-+natFromZero h f = natForEach (knownNat @0) h f
- 
- -- | Recursor for natural numbeers.
- natRec :: forall p f
 diff --git a/src/Data/Parameterized/TH/GADT.hs b/src/Data/Parameterized/TH/GADT.hs
 index fc6563c..73b4069 100644
 --- a/src/Data/Parameterized/TH/GADT.hs
@@ -162,10 +90,10 @@ index fc6563c..73b4069 100644
 +#endif
 +                           pats
 diff --git a/src/Data/Parameterized/Vector.hs b/src/Data/Parameterized/Vector.hs
-index 2aec6f0..fb54062 100644
+index 9d4b653..c3b93c3 100644
 --- a/src/Data/Parameterized/Vector.hs
 +++ b/src/Data/Parameterized/Vector.hs
-@@ -80,6 +80,8 @@ module Data.Parameterized.Vector
+@@ -92,6 +92,8 @@ module Data.Parameterized.Vector
  import qualified Data.Vector as Vector
  import Data.Functor.Compose
  import Data.Coerce
@@ -174,21 +102,12 @@ index 2aec6f0..fb54062 100644
  import Data.Vector.Mutable (MVector)
  import qualified Data.Vector.Mutable as MVector
  import Control.Monad.ST
-@@ -219,7 +221,7 @@ mapAt :: (i + w <= n, 1 <= w) =>
-             NatRepr i {- ^ Start index -} ->
-             NatRepr w {- ^ Section width -} ->
-             (Vector w a -> Vector w a) {-^ map for the sub-vector -} ->
--            Vector n a -> Vector n a 
-+            Vector n a -> Vector n a
- mapAt i w f vn = runIdentity $ mapAtM i w (pure . f) vn
- 
- -- | Replace a sub-section of a vector with the given sub-vector.
-@@ -386,7 +388,7 @@ generate' h gen =
-       natRecBounded (decNat h) (decNat h) base step
+@@ -462,7 +464,7 @@ unfoldrWithIndexM' h gen start =
+         snd <$> getCompose3 (natRecBounded (decNat h) (decNat h) base step)
        }
-   where base :: Vector' a 0
--        base = MkVector' $ singleton (gen (knownNat @0))
-+        base = MkVector' $ singleton (case zeroLe @h of Dict -> gen (knownNat @0))
-         step :: forall m. (1 <= h, m <= h - 1)
-              => NatRepr m -> Vector' a m -> Vector' a (m + 1)
-         step m v =
+   where base :: Compose3 m ((,) b) (Vector' a) 0
+-        base = Compose3 $ (\(hd, b) -> (b, MkVector' (singleton hd))) <$> gen (knownNat @0) start
++        base = case zeroLe @h of Dict -> Compose3 $ (\(hd, b) -> (b, MkVector' (singleton hd))) <$> gen (knownNat @0) start
+         step :: forall p. (1 <= h, p <= h - 1)
+              => NatRepr p
+              -> Compose3 m ((,) b) (Vector' a) p