diff --git a/patches/Decimal-0.5.1.patch b/patches/Decimal-0.5.1.patch
deleted file mode 100644
index d4774920ba1c08ea0bbe203017dbba88450bec8b..0000000000000000000000000000000000000000
--- a/patches/Decimal-0.5.1.patch
+++ /dev/null
@@ -1,15 +0,0 @@
-diff --git a/src/Data/Decimal.hs b/src/Data/Decimal.hs
-index 340b49b..5fbd685 100644
---- a/src/Data/Decimal.hs
-+++ b/src/Data/Decimal.hs
-@@ -66,8 +66,8 @@ import Text.ParserCombinators.ReadP
- -- will return \"1.500\".  Conversely the "Read" instance will use the decimal
- -- places to determine the precision.
- data DecimalRaw i = Decimal {
--      decimalPlaces :: ! Word8,
--      decimalMantissa :: ! i}
-+      decimalPlaces :: !Word8,
-+      decimalMantissa :: !i}
-                                   deriving (Typeable)
- 
- 
diff --git a/patches/attoparsec-0.13.2.5.patch b/patches/attoparsec-0.13.2.5.patch
index bd864ca8e5cf9eb5a467cc72309a420f10c220a6..b31c9f22b5bd87418d0781072f3ea3a6ba1676ba 100644
--- a/patches/attoparsec-0.13.2.5.patch
+++ b/patches/attoparsec-0.13.2.5.patch
@@ -55,3 +55,23 @@ index 5e08fc0..0a1ccdb 100644
 +narrow8WordCompat# :: Word# -> Word#
 +narrow8WordCompat# = narrow8Word#
 +#endif
+diff --git a/attoparsec.cabal b/attoparsec.cabal
+index 7093e4e..d15dd54 100644
+--- a/attoparsec.cabal
++++ b/attoparsec.cabal
+@@ -1,5 +1,6 @@
+ name:            attoparsec
+ version:         0.13.2.5
++x-revision: 1
+ license:         BSD3
+ license-file:    LICENSE
+ category:        Text, Parsing
+@@ -46,7 +47,7 @@ library
+                  scientific >= 0.3.1 && < 0.4,
+                  transformers >= 0.2 && (< 0.4 || >= 0.4.1.0) && < 0.6,
+                  text >= 1.1.1.3,
+-                 ghc-prim <0.7
++                 ghc-prim <0.8
+   if impl(ghc < 7.4)
+     build-depends:
+       bytestring < 0.10.4.0
diff --git a/patches/cabal-doctest-1.0.8.patch b/patches/cabal-doctest-1.0.8.patch
index a21514b4dc68618b91a13b2864e2178b19652077..2a150c651fd99305562ca9117804115347c0b640 100644
--- a/patches/cabal-doctest-1.0.8.patch
+++ b/patches/cabal-doctest-1.0.8.patch
@@ -1,3 +1,34 @@
+diff --git a/cabal-doctest.cabal b/cabal-doctest.cabal
+index 3fa9ff7..b6a648d 100644
+--- a/cabal-doctest.cabal
++++ b/cabal-doctest.cabal
+@@ -1,5 +1,6 @@
+ name:               cabal-doctest
+ version:            1.0.8
++x-revision:         2
+ synopsis:           A Setup.hs helper for doctests running
+ description:
+   Currently (beginning of 2017), there isn't @cabal doctest@
+@@ -21,7 +22,7 @@ extra-source-files:
+   ChangeLog.md
+   README.md
+ 
+-tested-with:        GHC ==8.8.1 || >=7.4 && <8.8 || ==7.2.2 || ==7.0.4
++tested-with:        GHC ==8.10.1 || >=7.4 && <8.10 || ==7.2.2 || ==7.0.4
+ 
+ source-repository head
+   type:     git
+@@ -32,8 +33,8 @@ library
+   other-modules:
+   other-extensions:
+   build-depends:
+-      base       >=4.3  && <4.14
+-    , Cabal      >=1.10 && <3.1
++      base       >=4.3  && <4.16
++    , Cabal      >=1.10 && <3.6
+     , directory
+     , filepath
+ 
 diff --git a/src/Distribution/Extra/Doctest.hs b/src/Distribution/Extra/Doctest.hs
 index e434c16..9247816 100644
 --- a/src/Distribution/Extra/Doctest.hs
diff --git a/patches/free-algebras-0.1.0.0.patch b/patches/free-algebras-0.1.0.0.patch
deleted file mode 100644
index cf27cc09652b022e735b3e98fc35a846ed684d31..0000000000000000000000000000000000000000
--- a/patches/free-algebras-0.1.0.0.patch
+++ /dev/null
@@ -1,106 +0,0 @@
-diff --git a/src/Control/Algebra/Free.hs b/src/Control/Algebra/Free.hs
-index 32f0032..97a0426 100644
---- a/src/Control/Algebra/Free.hs
-+++ b/src/Control/Algebra/Free.hs
-@@ -111,7 +111,7 @@ import           Data.Algebra.Free (AlgebraType, AlgebraType0, Proof (..))
- -- well defined if the laws on @'AlgebraType0'@ family are satisfied.  This in
- -- turn guarantees that @m@ composed with this forgetful functor is a monad.
- -- In result we get monadic operations:
---- 
-+--
- --   * @return = 'liftFree'@
- --   * @(>>=)  = 'bindFree1'@
- --   * @join   = 'joinFree1'@
-@@ -177,7 +177,7 @@ class FreeAlgebra1 (m :: (k -> Type) -> k -> Type) where
- --
- wrapFree
-     :: forall (m :: (Type -> Type) -> Type -> Type)
--              (f :: Type -> Type) 
-+              (f :: Type -> Type)
-               a .
-        ( FreeAlgebra1 m
-        , AlgebraType0 m f
-@@ -627,7 +627,7 @@ instance (forall h. c h => Functor h)
- -- | @'Free1'@ is an applicative functor whenever @c f@ implies @'Applicative'
- -- f@.
- --
--instance (forall h. c h => Applicative h)
-+instance (forall h. c h => Applicative h, Functor (Free1 c f))
-          => Applicative (Free1 c f) where
- 
-     pure a = Free1 $ \_ -> pure a
-@@ -643,7 +643,7 @@ instance (forall h. c h => Applicative h)
- 
- -- | @'Free1'@ is a monad whenever @c f@ implies @'Monad' f@.
- --
--instance (forall h. c h => Monad h)
-+instance (forall h. c h => Monad h, Applicative (Free1 c f))
-          => Monad (Free1 c f) where
- 
-     return = pure
-@@ -658,7 +658,7 @@ instance (forall h. c h => Monad h)
- #endif
- 
- 
--instance (forall h. c h => Alternative h)
-+instance (forall h. c h => Alternative h, Applicative (Free1 c f))
-          => Alternative (Free1 c f) where
-     empty = Free1 $ \_ -> empty
- 
-@@ -669,15 +669,15 @@ instance (forall h. c h => Alternative h)
-     many (Free1 f) = Free1 $ \h -> many (f h)
- 
- 
--instance (forall h. c h => MonadPlus h)
-+instance (forall h. c h => MonadPlus h, Alternative (Free1 c f), Monad (Free1 c f))
-          => MonadPlus (Free1 c f) where
- 
-     mzero = Free1 $ \_ -> mzero
- 
--    Free1 f `mplus` Free1 g = Free1 $ \h -> f h `mplus` g h 
-+    Free1 f `mplus` Free1 g = Free1 $ \h -> f h `mplus` g h
- 
- 
--instance (forall h. c h => MonadZip h)
-+instance (forall h. c h => MonadZip h, Monad (Free1 c f))
-          => MonadZip (Free1 c f) where
- 
-     Free1 f `mzip` Free1 g = Free1 $ \h -> f h `mzip` g h
-diff --git a/src/Data/Semigroup/Abelian.hs b/src/Data/Semigroup/Abelian.hs
-index ad4c926..8e9d94d 100644
---- a/src/Data/Semigroup/Abelian.hs
-+++ b/src/Data/Semigroup/Abelian.hs
-@@ -26,7 +26,9 @@ import           Data.Semigroup
-                     , Dual
-                     , Max
-                     , Min
-+#if !(MIN_VERSION_base(4,16,0))
-                     , Option
-+#endif
-                     , Product
-                     , Sum
-                     )
-@@ -60,7 +62,9 @@ instance Ord a => AbelianSemigroup (Max a)
- 
- instance Ord a => AbelianSemigroup (Min a)
- 
-+#if !(MIN_VERSION_base(4,16,0))
- instance AbelianSemigroup a => AbelianSemigroup (Option a)
-+#endif
- 
- instance Num a => AbelianSemigroup (Product a)
- 
-@@ -107,10 +111,10 @@ instance FreeAlgebra FreeAbelianSemigroup where
-     foldMapFree f (FreeAbelianSemigroup as)
-                  = foldMapFree f (toNonEmpty_ as)
-       where
--        replicate_ :: a -> Natural -> [a]                                     
-+        replicate_ :: a -> Natural -> [a]
-         replicate_ _ n | n <= 0 = error "foldMapFree @FreeAbelianSemigroup: impossible"
--        replicate_ a 1 = [a]                                                   
--        replicate_ a n = a : replicate_ a (n - 1)                             
-+        replicate_ a 1 = [a]
-+        replicate_ a n = a : replicate_ a (n - 1)
- 
-         toNonEmpty_ :: Map a Natural -> NonEmpty a
-         toNonEmpty_ = NE.fromList . concatMap (uncurry replicate_) . Map.toList
diff --git a/patches/free-algebras-0.1.0.1.patch b/patches/free-algebras-0.1.0.1.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e27f47f1a72fbb1127373e40f62af964950ff052
--- /dev/null
+++ b/patches/free-algebras-0.1.0.1.patch
@@ -0,0 +1,28 @@
+diff --git a/src/Data/Semigroup/Abelian.hs b/src/Data/Semigroup/Abelian.hs
+index 6567faf..c38b161 100644
+--- a/src/Data/Semigroup/Abelian.hs
++++ b/src/Data/Semigroup/Abelian.hs
+@@ -26,7 +26,9 @@ import           Data.Semigroup
+                     , Dual
+                     , Max
+                     , Min
++#if __GLASGOW_HASKELL__ < 900
+                     , Option
++#endif
+                     , Product
+                     , Sum
+                     )
+@@ -111,10 +113,10 @@ instance FreeAlgebra FreeAbelianSemigroup where
+     foldMapFree f (FreeAbelianSemigroup as)
+                  = foldMapFree f (toNonEmpty_ as)
+       where
+-        replicate_ :: a -> Natural -> [a]                                     
++        replicate_ :: a -> Natural -> [a]
+         replicate_ _ n | n <= 0 = error "foldMapFree @FreeAbelianSemigroup: impossible"
+-        replicate_ a 1 = [a]                                                   
+-        replicate_ a n = a : replicate_ a (n - 1)                             
++        replicate_ a 1 = [a]
++        replicate_ a n = a : replicate_ a (n - 1)
+ 
+         toNonEmpty_ :: Map a Natural -> NonEmpty a
+         toNonEmpty_ = NE.fromList . concatMap (uncurry replicate_) . Map.toList
diff --git a/patches/hedgehog-1.0.4.patch b/patches/hedgehog-1.0.4.patch
deleted file mode 100644
index 258149f1a546b4a40e91036e2272322015996c14..0000000000000000000000000000000000000000
--- a/patches/hedgehog-1.0.4.patch
+++ /dev/null
@@ -1,63 +0,0 @@
-diff --git a/src/Hedgehog/Internal/TH.hs b/src/Hedgehog/Internal/TH.hs
-index 39b3bc1..b6913a6 100644
---- a/src/Hedgehog/Internal/TH.hs
-+++ b/src/Hedgehog/Internal/TH.hs
-@@ -15,7 +15,7 @@ import           Hedgehog.Internal.Discovery
- import           Hedgehog.Internal.Property
- 
- import           Language.Haskell.TH (Exp(..), Q, TExp, location, runIO)
--import           Language.Haskell.TH.Syntax (Loc(..), mkName, unTypeQ, unsafeTExpCoerce)
-+import           Language.Haskell.TH.Syntax (Loc(..), mkName, unsafeTExpCoerce, Code, liftCode, examineCode, unsafeCodeCoerce, unTypeCode)
- 
- type TExpQ a =
-   Q (TExp a)
-@@ -24,11 +24,11 @@ type TExpQ a =
- --
- --   Functions starting with `prop_` are assumed to be properties.
- --
--discover :: TExpQ Group
-+discover :: Code Q Group
- discover = discoverPrefix "prop_"
- 
--discoverPrefix :: String -> TExpQ Group
--discoverPrefix prefix = do
-+discoverPrefix :: String -> Code Q Group
-+discoverPrefix prefix = liftCode $ do
-   file <- getCurrentFile
-   properties <- Map.toList <$> runIO (readProperties prefix file)
- 
-@@ -44,24 +44,24 @@ discoverPrefix prefix = do
-       fmap (mkNamedProperty . fst) $
-       List.sortBy startLine properties
- 
--  [|| Group $$(moduleName) $$(listTE names) ||]
-+  examineCode [|| Group $$(moduleName) $$(listTE names) ||]
- 
--mkNamedProperty :: PropertyName -> TExpQ (PropertyName, Property)
-+mkNamedProperty :: PropertyName -> Code Q (PropertyName, Property)
- mkNamedProperty name = do
-   [|| (name, $$(unsafeProperty name)) ||]
- 
--unsafeProperty :: PropertyName -> TExpQ Property
-+unsafeProperty :: PropertyName -> Code Q Property
- unsafeProperty =
--  unsafeTExpCoerce . pure . VarE . mkName . unPropertyName
-+  unsafeCodeCoerce . pure . VarE . mkName . unPropertyName
- 
--listTE :: [TExpQ a] -> TExpQ [a]
--listTE xs = do
--  unsafeTExpCoerce . pure . ListE =<< traverse unTypeQ xs
-+listTE :: [Code Q a] -> Code Q [a]
-+listTE xs = liftCode $ do
-+  unsafeTExpCoerce . pure . ListE =<< traverse unTypeCode xs
- 
--moduleName :: TExpQ GroupName
--moduleName = do
-+moduleName :: Code Q GroupName
-+moduleName = liftCode $ do
-   loc <- GroupName . loc_module <$> location
--  [|| loc ||]
-+  examineCode [|| loc ||]
- 
- getCurrentFile :: Q FilePath
- getCurrentFile =
diff --git a/patches/hgeometry-ipe-0.11.0.0.patch b/patches/hgeometry-ipe-0.11.0.0.patch
index 99eb5bdf5c65c0c0caab653421c8912039bb61fe..34e58c61cdd43abb121f7f629584f57371b778a5 100644
--- a/patches/hgeometry-ipe-0.11.0.0.patch
+++ b/patches/hgeometry-ipe-0.11.0.0.patch
@@ -1,3 +1,27 @@
+diff --git a/hgeometry-ipe.cabal b/hgeometry-ipe.cabal
+index 09b4df4..3a22c6d 100644
+--- a/hgeometry-ipe.cabal
++++ b/hgeometry-ipe.cabal
+@@ -83,7 +83,7 @@ library
+               , linear           >= 1.10
+               , semigroupoids    >= 5
+               , semigroups       >= 0.18
+-              , singletons       >= 2.0
++              , singletons       >= 2.0 && < 3.0
+               , text             >= 1.1.1.0
+               , vinyl            >= 0.10
+               , deepseq          >= 1.1
+@@ -94,8 +94,8 @@ library
+               , QuickCheck              >= 2.5
+               , quickcheck-instances    >= 0.3
+ 
+-              , hgeometry-combinatorial >= 0.11.0.0
+-              , hgeometry               >= 0.11.0.0
++              , hgeometry-combinatorial >= 0.11.0.0 && < 0.12
++              , hgeometry               >= 0.11.0.0 && < 0.12
+ 
+               -- , validation       >= 0.4
+ 
 diff --git a/src/Data/Geometry/Ipe/Attributes.hs b/src/Data/Geometry/Ipe/Attributes.hs
 index 7aa3a56..13ba092 100644
 --- a/src/Data/Geometry/Ipe/Attributes.hs
diff --git a/patches/integer-roots-1.0.patch b/patches/integer-roots-1.0.patch
index 7f625584a90e30c72b15b840cdcc67e3e5458c04..a9853b31b959ccd0b48935ac11ace0803904d163 100644
--- a/patches/integer-roots-1.0.patch
+++ b/patches/integer-roots-1.0.patch
@@ -51,3 +51,23 @@ index 7654ca1..6dfed19 100644
  spBEx :: Word
  spBEx = 14
  
+diff --git a/integer-roots.cabal b/integer-roots.cabal
+index 010d9e6..516b3a5 100644
+--- a/integer-roots.cabal
++++ b/integer-roots.cabal
+@@ -1,5 +1,6 @@
+ name:          integer-roots
+ version:       1.0
++x-revision: 1
+ cabal-version: >=1.10
+ build-type:    Simple
+ license:       MIT
+@@ -24,7 +25,7 @@ source-repository head
+ library
+   build-depends:
+     base >=4.9 && <5,
+-    integer-gmp <1.1
++    integer-gmp <1.2
+   exposed-modules:
+     Math.NumberTheory.Roots
+   other-modules:
diff --git a/patches/iproute-1.7.10.patch b/patches/iproute-1.7.11.patch
similarity index 100%
rename from patches/iproute-1.7.10.patch
rename to patches/iproute-1.7.11.patch
diff --git a/patches/lens-family-2.1.0.patch b/patches/lens-family-2.1.0.patch
deleted file mode 100644
index ccf04101d766b9901092f762f1700156fe8ca8b0..0000000000000000000000000000000000000000
--- a/patches/lens-family-2.1.0.patch
+++ /dev/null
@@ -1,118 +0,0 @@
-diff --git a/src/Lens/Family2.hs b/src/Lens/Family2.hs
-index 828dd02..53925c3 100644
---- a/src/Lens/Family2.hs
-+++ b/src/Lens/Family2.hs
-@@ -193,13 +193,13 @@ type Reviewer' s a = forall f. LF.Phantom f => LF.GrateLike' f s a
- -- >>> (3 :+ 4, "example")^._1.to(abs)
- -- 5.0 :+ 0.0
- to :: (s -> a) -> Getter s t a b
--to = LF.to
-+to sa = LF.to sa
- 
- -- | 'folding' promotes a \"toList\" function to a read-only traversal called a fold.
- --
- -- To demote a traversal or fold to a \"toList\" function use the section @(^..l)@ or @toListOf l@.
- folding :: Foldable f => (s -> f a) -> Fold s t a b
--folding = LF.folding
-+folding sa = LF.folding sa
- 
- -- | Returns a list of all of the referenced values in order.
- toListOf :: Fold s t a b -> s -> [a]
-diff --git a/src/Lens/Family2/Stock.hs b/src/Lens/Family2/Stock.hs
-index 4c4ee31..635779d 100644
---- a/src/Lens/Family2/Stock.hs
-+++ b/src/Lens/Family2/Stock.hs
-@@ -76,31 +76,31 @@ chosen = Stock.chosen
- 
- -- | Lens on a given point of a function.
- ix :: Eq k => k -> Lens' (k -> v) v
--ix = Stock.ix
-+ix k = Stock.ix k
- 
- -- | Lens on a given point of a 'Map.Map'.
- at :: Ord k => k -> Lens' (Map.Map k v) (Maybe v)
--at = Stock.at
-+at k = Stock.at k
- 
- -- | Lens on a given point of a 'IntMap.IntMap'.
- intAt :: Int -> Lens' (IntMap.IntMap v) (Maybe v)
--intAt = Stock.intAt
-+intAt i = Stock.intAt i
- 
- -- | Lens providing strict access to a given point of a 'Map.Map'.
- at' :: Ord k => k -> Lens' (Map.Map k v) (Maybe v)
--at' = Stock.at'
-+at' k = Stock.at' k
- 
- -- | Lens providing strict access to a given point of a 'IntMap.IntMap'.
- intAt' :: Int -> Lens' (IntMap.IntMap v) (Maybe v)
--intAt' = Stock.intAt'
-+intAt' i = Stock.intAt' i
- 
- -- | Lens on a given point of a 'Set.Set'.
- contains :: Ord k => k -> Lens' (Set.Set k) Bool
--contains = Stock.contains
-+contains k = Stock.contains k
- 
- -- | Lens on a given point of a 'IntSet.IntSet'.
- intContains :: Int -> Lens' IntSet.IntSet Bool
--intContains = Stock.intContains
-+intContains i = Stock.intContains i
- 
- -- | A grate accessing the codomain of a function.
- cod :: Grate (r -> a) (r -> b) a b
-diff --git a/src/Lens/Family2/Unchecked.hs b/src/Lens/Family2/Unchecked.hs
-index aac859b..33515ba 100644
---- a/src/Lens/Family2/Unchecked.hs
-+++ b/src/Lens/Family2/Unchecked.hs
-@@ -242,7 +242,7 @@ type Resetter' s a = forall g. LF.Identical g => LF.GrateLike' g s a
- adapter :: (s -> a) -- ^ yin
-         -> (b -> t) -- ^ yang
-         -> Adapter s t a b
--adapter = LF.adapter
-+adapter sa bt = LF.adapter sa bt
- 
- -- | Build a lens from a @getter@ and @setter@ family.
- --
-@@ -256,7 +256,7 @@ adapter = LF.adapter
- lens :: (s -> a) -- ^ getter
-      -> (s -> b -> t) -- ^ setter
-      -> Lens s t a b
--lens = LF.lens
-+lens sa sbt = LF.lens sa sbt
- 
- grate :: (((s -> a) -> b) -> t) -- ^ grater
-       -> Grate s t a b
-@@ -269,7 +269,7 @@ grate :: (((s -> a) -> b) -> t) -- ^ grater
- -- * @grater (\k -> h (k . grater)) === grater (\k -> h ($ k))@
- --
- -- Note: The grater laws are that of an algebra for the parameterised continuation monad, `Lens.Family.PCont`.
--grate = LF.grate
-+grate sabt = LF.grate sabt
- 
- -- | Build a prism from a @matcher@ and @reviewer@ family.
- --
-@@ -283,7 +283,7 @@ grate = LF.grate
- prism :: (s -> Either t a) -- ^ matcher
-       -> (b -> t) -- ^ reviewer
-       -> Prism s t a b
--prism = LF.prism
-+prism sta bt = LF.prism sta bt
- 
- -- | 'setting' promotes a \"semantic editor combinator\" to a modify-only lens.
- -- To demote a lens to a semantic edit combinator, use the section @(l %~)@ or @over l@ from "Lens.Family2".
-@@ -298,7 +298,7 @@ prism = LF.prism
- -- * @sec f . sec g === sec (f . g)@
- setting :: ((a -> b) -> s -> t) -- ^ sec (semantic editor combinator)
-         -> Setter s t a b
--setting = LF.setting
-+setting abst = LF.setting abst
- 
- -- | 'resetting' promotes a \"semantic editor combinator\" to a form of grate that can only lift unary functions.
- -- To demote a grate to a semantic edit combinator, use @under l@ from "Lens.Family2".
-@@ -310,4 +310,4 @@ setting = LF.setting
- -- * @sec f . sec g === sec (f . g)@
- resetting :: ((a -> b) -> s -> t) -- ^ sec (semantic editor combinator)
-         -> Resetter s t a b
--resetting = LF.resetting
-+resetting abst = LF.resetting abst
diff --git a/patches/quickcheck-instances-0.3.25.2.patch b/patches/quickcheck-instances-0.3.25.2.patch
index 1f1164f4349c1c3d66af89a4f4503e28a2b64175..81977f39fc19bde9106b8f09cc8e10520e667471 100644
--- a/patches/quickcheck-instances-0.3.25.2.patch
+++ b/patches/quickcheck-instances-0.3.25.2.patch
@@ -1,3 +1,23 @@
+diff --git a/quickcheck-instances.cabal b/quickcheck-instances.cabal
+index e3933cb..d1980df 100644
+--- a/quickcheck-instances.cabal
++++ b/quickcheck-instances.cabal
+@@ -1,5 +1,6 @@
+ name:               quickcheck-instances
+ version:            0.3.25.2
++x-revision:         1
+ synopsis:           Common quickcheck instances
+ description:
+   QuickCheck instances.
+@@ -78,7 +79,7 @@ library
+   other-modules:    Test.QuickCheck.Instances.CustomPrelude
+   hs-source-dirs:   src
+   build-depends:
+-      base        >=4.5    && <4.15
++      base        >=4.5    && <4.16
+     , QuickCheck  >=2.14.1 && <2.14.3
+     , splitmix    >=0.0.2  && <0.2
+ 
 diff --git a/src/Test/QuickCheck/Instances/Semigroup.hs b/src/Test/QuickCheck/Instances/Semigroup.hs
 index 90ae0ea..9a47bc6 100644
 --- a/src/Test/QuickCheck/Instances/Semigroup.hs
diff --git a/patches/salak-0.3.6.patch b/patches/salak-0.3.6.patch
index 9e86dcacce472330787fca1082b6dd457fd0b816..f2ba5799116bc977bc33533a5de2592b3c54fdc0 100644
--- a/patches/salak-0.3.6.patch
+++ b/patches/salak-0.3.6.patch
@@ -1,3 +1,40 @@
+diff --git a/salak.cabal b/salak.cabal
+index 155a048..c34c007 100644
+--- a/salak.cabal
++++ b/salak.cabal
+@@ -8,6 +8,7 @@ cabal-version: 1.12
+ 
+ name:           salak
+ version:        0.3.6
++x-revision: 4
+ synopsis:       Configuration (re)Loader and Parser.
+ description:    This library defines a universal procedure to load configurations and parse properties, also supports reload configuration files.
+ category:       Library, Configuration
+@@ -47,12 +48,12 @@ library
+     , exceptions >=0.10.2 && <0.11
+     , filepath >=1.4.2 && <1.5
+     , hashable >=1.2.7.0 && <1.4
+-    , heaps >=0.3.6 && <0.4
+-    , megaparsec >=7.0.5 && <8.1
++    , heaps >=0.3.6 && <1
++    , megaparsec >=7.0.5
+     , mtl >=2.2.2 && <2.3
+     , scientific >=0.3.6 && <0.4
+     , text >=1.2.3 && <1.3
+-    , time >=1.8.0 && <1.10
++    , time >=1.8.0 && <1.11
+     , unliftio-core >=0.1.2 && <0.3
+     , unordered-containers >=0.2.10 && <0.3
+   default-language: Haskell2010
+@@ -71,7 +72,7 @@ test-suite salak-test
+   default-extensions: BangPatterns CPP DefaultSignatures DeriveFunctor DeriveGeneric FlexibleContexts FlexibleInstances GeneralizedNewtypeDeriving MultiParamTypeClasses NoOverloadedLists OverloadedStrings RankNTypes RecordWildCards ScopedTypeVariables TupleSections TypeOperators
+   ghc-options: -Wall -fno-warn-orphans -fno-warn-missing-signatures -rtsopts -threaded -with-rtsopts=-K1K
+   build-depends:
+-      QuickCheck <2.14
++      QuickCheck
+     , base >=4.9 && <5
+     , hspec ==2.*
+     , mtl >=2.2.2 && <2.3
 diff --git a/src/Salak/Internal/Prop.hs b/src/Salak/Internal/Prop.hs
 index 24f5ab6..78aa7f4 100644
 --- a/src/Salak/Internal/Prop.hs
diff --git a/patches/singletons-3.0.patch b/patches/singletons-3.0.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391
diff --git a/patches/singletons-base-3.0.patch b/patches/singletons-base-3.0.patch
new file mode 100644
index 0000000000000000000000000000000000000000..7723774a2fb94387798f530b0355a9265917570e
--- /dev/null
+++ b/patches/singletons-base-3.0.patch
@@ -0,0 +1,84 @@
+diff --git a/src/GHC/Num/Singletons.hs b/src/GHC/Num/Singletons.hs
+index 2e85699..1463f9a 100644
+--- a/src/GHC/Num/Singletons.hs
++++ b/src/GHC/Num/Singletons.hs
+@@ -3,6 +3,7 @@
+              DefaultSignatures, FlexibleContexts, InstanceSigs, NoStarIsType,
+              TypeApplications, StandaloneKindSignatures
+   #-}
++{-# LANGUAGE FlexibleInstances #-}
+ 
+ -----------------------------------------------------------------------------
+ -- |
+diff --git a/src/GHC/TypeLits/Singletons.hs b/src/GHC/TypeLits/Singletons.hs
+index ae295f1..a724506 100644
+--- a/src/GHC/TypeLits/Singletons.hs
++++ b/src/GHC/TypeLits/Singletons.hs
+@@ -1,6 +1,7 @@
+ {-# LANGUAGE TemplateHaskell, ScopedTypeVariables, ConstraintKinds,
+              GADTs, TypeApplications, TypeFamilies, UndecidableInstances,
+              DataKinds, PolyKinds, StandaloneKindSignatures #-}
++{-# LANGUAGE CPP #-}
+ 
+ -----------------------------------------------------------------------------
+ -- |
+@@ -60,6 +61,7 @@ import GHC.TypeNats (Div, Mod, SomeNat(..))
+ import Numeric.Natural (Natural)
+ import Unsafe.Coerce
+ 
++#if __GLASGOW_HASKELL__ < 901
+ -- | This bogus 'Num' instance is helpful for people who want to define
+ -- functions over Nats that will only be used at the type level or
+ -- as singletons. A correct SNum instance for Nat singletons exists.
+@@ -86,6 +88,7 @@ instance Enum Nat where
+ 
+ instance Show Nat where
+   showsPrec      = no_term_level_nats
++#endif
+ 
+ -- | This bogus instance is helpful for people who want to define
+ -- functions over Symbols that will only be used at the type level or
+@@ -108,8 +111,10 @@ instance Monoid Symbol where
+ instance Show Symbol where
+   showsPrec = no_term_level_syms
+ 
++#if __GLASGOW_HASKELL__ < 901
+ no_term_level_nats :: a
+ no_term_level_nats = error "The kind `Nat` may not be used at the term level."
++#endif
+ 
+ no_term_level_syms :: a
+ no_term_level_syms = error "The kind `Symbol` may not be used at the term level."
+diff --git a/src/GHC/TypeLits/Singletons/Internal.hs b/src/GHC/TypeLits/Singletons/Internal.hs
+index 5fee1bb..0926d96 100644
+--- a/src/GHC/TypeLits/Singletons/Internal.hs
++++ b/src/GHC/TypeLits/Singletons/Internal.hs
+@@ -244,13 +244,13 @@ instance SingI x => SingI ((^@#@$$) x) where
+ -- with libraries with APIs built around '<=?'.  New code should use
+ -- 'CmpNat', exposed through this library through the 'POrd' and 'SOrd'
+ -- instances for 'Nat'.
+-(%<=?) :: Sing a -> Sing b -> Sing (a <=? b)
++(%<=?) :: forall (a :: Nat) (b :: Nat). Sing a -> Sing b -> Sing (a <=? b)
+ sa %<=? sb = unsafeCoerce (sa %<= sb)
+ infix 4 %<=?
+ 
+ -- Defunctionalization symbols for (<=?)
+ $(genDefunSymbols [''(<=?)])
+-instance SingI (<=?@#@$) where
++instance SingI ((<=?@#@$) :: Nat ~> Nat ~> Bool) where
+   sing = singFun2 (%<=?)
+-instance SingI x => SingI ((<=?@#@$$) x) where
++instance forall (x :: Nat). SingI x => SingI ((<=?@#@$$) x) where
+   sing = singFun1 (sing @x %<=?)
+diff --git a/src/Text/Show/Singletons.hs b/src/Text/Show/Singletons.hs
+index e413037..e0bd978 100644
+--- a/src/Text/Show/Singletons.hs
++++ b/src/Text/Show/Singletons.hs
+@@ -2,6 +2,7 @@
+ {-# LANGUAGE DefaultSignatures #-}
+ {-# LANGUAGE EmptyCase #-}
+ {-# LANGUAGE FlexibleContexts #-}
++{-# LANGUAGE FlexibleInstances #-}
+ {-# LANGUAGE GADTs #-}
+ {-# LANGUAGE InstanceSigs #-}
+ {-# LANGUAGE PolyKinds #-}
diff --git a/patches/subcategories-0.1.0.0.patch b/patches/subcategories-0.1.1.0.patch
similarity index 95%
rename from patches/subcategories-0.1.0.0.patch
rename to patches/subcategories-0.1.1.0.patch
index 373f617f7bbe095c469a21905bfa0958425e6a3e..0a3a2ecd4cf6e3183796db2a25cba0221080f8d5 100644
--- a/patches/subcategories-0.1.0.0.patch
+++ b/patches/subcategories-0.1.1.0.patch
@@ -161,16 +161,6 @@ index 7bdd8a0..b94ccd4 100644
  
  deriving via WrapFunctor ZipList instance CSemialign ZipList
  deriving via WrapFunctor ZipList instance CAlign ZipList
-diff --git a/src/Control/Subcategory/Wrapper/Internal.hs b/src/Control/Subcategory/Wrapper/Internal.hs
-index 3b006cd..e65d61f 100644
---- a/src/Control/Subcategory/Wrapper/Internal.hs
-+++ b/src/Control/Subcategory/Wrapper/Internal.hs
-@@ -52,4 +52,4 @@ withMonoCoercible
-   :: (Coercible (WrapMono mono (Element mono)) mono => r)
-   -> r
- {-# INLINE withMonoCoercible #-}
--withMonoCoercible = id
-+withMonoCoercible x = x
 diff --git a/src/Control/Subcategory/Zip.hs b/src/Control/Subcategory/Zip.hs
 index 1810935..76e2ccd 100644
 --- a/src/Control/Subcategory/Zip.hs
diff --git a/patches/text-short-0.1.3.patch b/patches/text-short-0.1.3.patch
index 8b96fdd9b0cbb9a598f359aff64adb36bf662ff2..61453bb02570e7835c08e691c7a19e7f6a37d810 100644
--- a/patches/text-short-0.1.3.patch
+++ b/patches/text-short-0.1.3.patch
@@ -46,3 +46,41 @@ index 876985e..f3b1d92 100644
  {-# INLINE copyAddrToByteArray #-}
  copyAddrToByteArray :: Ptr a -> MBA RealWorld -> B -> B -> ST RealWorld ()
  copyAddrToByteArray (Ptr src#) (MBA# dst#) (B (I# dst_off#)) (B (I# len#))
+diff --git a/text-short.cabal b/text-short.cabal
+index a72d7a2..6580149 100644
+--- a/text-short.cabal
++++ b/text-short.cabal
+@@ -2,6 +2,7 @@ cabal-version:       1.18
+ 
+ name:                text-short
+ version:             0.1.3
++x-revision: 3
+ synopsis:            Memory-efficient representation of Unicode text strings
+ license:             BSD3
+ license-file:        LICENSE
+@@ -14,7 +15,7 @@ description:         This package provides the 'ShortText' type which is suitabl
+                      .
+                      The main difference between 'Text' and 'ShortText' is that 'ShortText' uses UTF-8 instead of UTF-16 internally and also doesn't support zero-copy slicing (thereby saving 2 words). Consequently, the memory footprint of a (boxed) 'ShortText' value is 4 words (2 words when unboxed) plus the length of the UTF-8 encoded payload.
+ 
+-tested-with:         GHC==8.6.5, GHC==8.4.4, GHC==8.2.2, GHC==8.0.2, GHC==7.10.3, GHC==7.8.4
++tested-with:         GHC==8.10.1, GHC==8.8.3, GHC==8.6.5, GHC==8.4.4, GHC==8.2.2, GHC==8.0.2, GHC==7.10.3, GHC==7.8.4
+ extra-source-files:  ChangeLog.md
+ 
+ Source-Repository head
+@@ -33,13 +34,13 @@ library
+ 
+   other-modules:       Data.Text.Short.Internal
+ 
+-  build-depends:       base        >= 4.7    && < 4.13
+-                     , bytestring  >= 0.10.4 && < 0.11
++  build-depends:       base        >= 4.7    && < 4.16
++                     , bytestring  >= 0.10.4 && < 0.12
+                      , hashable    >= 1.2.6  && < 1.4
+                      , deepseq     >= 1.3    && < 1.5
+                      , text        >= 1.0    && < 1.3
+                      , binary      >= 0.7.1  && < 0.9
+-                     , ghc-prim    >= 0.3.1  && < 0.6
++                     , ghc-prim    >= 0.3.1  && < 0.8
+ 
+   if !impl(ghc >= 8.0)
+      build-depends: semigroups >= 0.18.2 && < 0.20
diff --git a/patches/th-desugar-1.12.patch b/patches/th-desugar-1.12.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e0a86dc79926b305e4a2143fb2514797119f9fa7
--- /dev/null
+++ b/patches/th-desugar-1.12.patch
@@ -0,0 +1,75 @@
+diff --git a/Language/Haskell/TH/Desugar/Core.hs b/Language/Haskell/TH/Desugar/Core.hs
+index 0a6fe1d..ea00a8b 100644
+--- a/Language/Haskell/TH/Desugar/Core.hs
++++ b/Language/Haskell/TH/Desugar/Core.hs
+@@ -89,8 +89,18 @@ dsExp (LamCaseE matches) = do
+ dsExp (TupE exps) = dsTup tupleDataName exps
+ dsExp (UnboxedTupE exps) = dsTup unboxedTupleDataName exps
+ dsExp (CondE e1 e2 e3) =
+-  dsExp (CaseE e1 [ Match (ConP 'True [])  (NormalB e2) []
+-                  , Match (ConP 'False []) (NormalB e3) [] ])
++  dsExp (CaseE e1 [ Match (ConP 'True
++-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
++#if __GLASGOW_HASKELL__ >= 901
++                                 []
++#endif
++                                 [])  (NormalB e2) []
++                  , Match (ConP 'False
++-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
++#if __GLASGOW_HASKELL__ >= 901
++                                 []
++#endif
++                                 []) (NormalB e3) [] ])
+ dsExp (MultiIfE guarded_exps) =
+   let failure = DAppE (DVarE 'error) (DLitE (StringL "Non-exhaustive guards in multi-way if")) in
+   dsGuards guarded_exps failure
+@@ -558,7 +568,12 @@ dsPat (VarP n) = return $ DVarP n
+ dsPat (TupP pats) = DConP (tupleDataName (length pats)) <$> mapM dsPat pats
+ dsPat (UnboxedTupP pats) = DConP (unboxedTupleDataName (length pats)) <$>
+                            mapM dsPat pats
+-dsPat (ConP name pats) = DConP name <$> mapM dsPat pats
++dsPat (ConP name
++-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
++#if __GLASGOW_HASKELL__ >= 901
++            _
++#endif
++            pats) = DConP name <$> mapM dsPat pats
+ dsPat (InfixP p1 name p2) = DConP name <$> mapM dsPat [p1, p2]
+ dsPat (UInfixP _ _ _) =
+   fail "Cannot desugar unresolved infix operators."
+diff --git a/Language/Haskell/TH/Desugar/Sweeten.hs b/Language/Haskell/TH/Desugar/Sweeten.hs
+index 1512ddb..f7475c2 100644
+--- a/Language/Haskell/TH/Desugar/Sweeten.hs
++++ b/Language/Haskell/TH/Desugar/Sweeten.hs
+@@ -74,7 +74,12 @@ matchToTH (DMatch pat exp) = Match (patToTH pat) (NormalB (expToTH exp)) []
+ patToTH :: DPat -> Pat
+ patToTH (DLitP lit)    = LitP lit
+ patToTH (DVarP n)      = VarP n
+-patToTH (DConP n pats) = ConP n (map patToTH pats)
++patToTH (DConP n pats) = ConP n
++-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
++#if __GLASGOW_HASKELL__ >= 901
++                              []
++#endif
++                              (map patToTH pats)
+ patToTH (DTildeP pat)  = TildeP (patToTH pat)
+ patToTH (DBangP pat)   = BangP (patToTH pat)
+ patToTH (DSigP pat ty) = SigP (patToTH pat) (typeToTH ty)
+diff --git a/Language/Haskell/TH/Desugar/Util.hs b/Language/Haskell/TH/Desugar/Util.hs
+index 6ad206c..73da83a 100644
+--- a/Language/Haskell/TH/Desugar/Util.hs
++++ b/Language/Haskell/TH/Desugar/Util.hs
+@@ -417,7 +417,12 @@ extractBoundNamesPat (LitP _)              = OS.empty
+ extractBoundNamesPat (VarP name)           = OS.singleton name
+ extractBoundNamesPat (TupP pats)           = foldMap extractBoundNamesPat pats
+ extractBoundNamesPat (UnboxedTupP pats)    = foldMap extractBoundNamesPat pats
+-extractBoundNamesPat (ConP _ pats)         = foldMap extractBoundNamesPat pats
++extractBoundNamesPat (ConP _
++-- TODO: Use MIN_VERSION_template_haskell(2,18,0) here (see https://gitlab.haskell.org/ghc/ghc/-/issues/19083)
++#if __GLASGOW_HASKELL__ >= 901
++                           _
++#endif
++                             pats)         = foldMap extractBoundNamesPat pats
+ extractBoundNamesPat (InfixP p1 _ p2)      = extractBoundNamesPat p1 `OS.union`
+                                              extractBoundNamesPat p2
+ extractBoundNamesPat (UInfixP p1 _ p2)     = extractBoundNamesPat p1 `OS.union`
diff --git a/patches/th-expand-syns-0.4.6.0.patch b/patches/th-expand-syns-0.4.6.0.patch
deleted file mode 100644
index 01226a19481af2e5d3d8f013f76c802f37bbeba1..0000000000000000000000000000000000000000
--- a/patches/th-expand-syns-0.4.6.0.patch
+++ /dev/null
@@ -1,76 +0,0 @@
-diff --git a/Language/Haskell/TH/ExpandSyns.hs b/Language/Haskell/TH/ExpandSyns.hs
-index c443722..4fd5814 100644
---- a/Language/Haskell/TH/ExpandSyns.hs
-+++ b/Language/Haskell/TH/ExpandSyns.hs
-@@ -30,17 +30,28 @@ packagename = "th-expand-syns"
- 
- 
- -- Compatibility layer for TH >=2.4 vs. 2.3
--tyVarBndrGetName :: TyVarBndr -> Name
-+tyVarBndrGetName :: TyVarBndr_ spec -> Name
- #if !MIN_VERSION_template_haskell(2,10,0)
- mapPred :: (Type -> Type) -> Pred -> Pred
- #endif
- bindPred :: (Type -> Q Type) -> Pred -> Q Pred
--tyVarBndrSetName :: Name -> TyVarBndr -> TyVarBndr
-+tyVarBndrSetName :: Name -> TyVarBndr_ spec -> TyVarBndr_ spec
- 
- #if MIN_VERSION_template_haskell(2,4,0)
-+# if MIN_VERSION_template_haskell(2,17,0)
-+tyVarBndrGetName (PlainTV n _) = n
-+tyVarBndrGetName (KindedTV n _ _) = n
-+
-+tyVarBndrSetName n (PlainTV _ spec) = PlainTV n spec
-+tyVarBndrSetName n (KindedTV _ spec k) = KindedTV n spec k
-+# else
- tyVarBndrGetName (PlainTV n) = n
- tyVarBndrGetName (KindedTV n _) = n
- 
-+tyVarBndrSetName n (PlainTV _) = PlainTV n
-+tyVarBndrSetName n (KindedTV _ k) = KindedTV n k
-+# endif
-+
- #if MIN_VERSION_template_haskell(2,10,0)
- bindPred = id
- #else
-@@ -50,9 +61,6 @@ mapPred f (EqualP t1 t2) = EqualP (f t1) (f t2)
- bindPred f (ClassP n ts) = ClassP n <$> mapM f ts
- bindPred f (EqualP t1 t2) = EqualP <$> f t1 <*> f t2
- #endif
--
--tyVarBndrSetName n (PlainTV _) = PlainTV n
--tyVarBndrSetName n (KindedTV _ k) = KindedTV n k
- #else
- 
- type TyVarBndr = Name
-@@ -542,7 +550,7 @@ instance SubstTypeVariable Con where
- 
- 
- class HasForallConstruct a where
--    mkForall :: [TyVarBndr] -> Cxt -> a -> a
-+    mkForall :: [TyVarBndrSpec] -> Cxt -> a -> a
- 
- instance HasForallConstruct Type where
-     mkForall = ForallT
-@@ -555,8 +563,8 @@ instance HasForallConstruct Con where
- -- Apply a substitution to something underneath a @forall@. The continuation
- -- argument provides new substitutions and fresh type variable binders to avoid
- -- the outer substitution from capturing the thing underneath the @forall@.
--commonForallCase :: (Name, Type) -> [TyVarBndr]
--                 -> ([(Name, Type)] -> [TyVarBndr] -> a)
-+commonForallCase :: (Name, Type) -> [TyVarBndr_ spec]
-+                 -> ([(Name, Type)] -> [TyVarBndr_ spec] -> a)
-                  -> a
- commonForallCase vt@(v,t) bndrs k
-             -- If a variable with the same name as the one to be replaced is bound by the forall,
-@@ -584,3 +592,10 @@ substInType = subst
- -- | Capture-free substitution
- substInCon :: (Name,Type) -> Con -> Con
- substInCon = subst
-+
-+#if MIN_VERSION_template_haskell(2,17,0)
-+type TyVarBndr_ spec = TyVarBndr spec
-+#else
-+type TyVarBndr_ spec = TyVarBndr
-+type TyVarBndrSpec   = TyVarBndr
-+#endif