diff --git a/patches/critbit-0.2.0.0.patch b/patches/critbit-0.2.0.0.patch
index 1990be28b9373365475417d67b817bd3a677e7dd..6af749eee638ad1cd55a4d283a251047e8eb89b6 100644
--- a/patches/critbit-0.2.0.0.patch
+++ b/patches/critbit-0.2.0.0.patch
@@ -97,3 +97,19 @@ index e50738b..9a3c3d4 100644
  {-# INLINABLE deleteFindMax #-}
  
  -- | /O(k')/. Retrieves the value associated with minimal key of the
+diff --git a/Data/CritBit/Types/Internal.hs b/Data/CritBit/Types/Internal.hs
+index d278b5a..4008ec7 100644
+--- a/Data/CritBit/Types/Internal.hs
++++ b/Data/CritBit/Types/Internal.hs
+@@ -192,7 +192,11 @@ instance CritBitKey Text where
+         | n < len `shiftL` 1 =
+             let word       = T.unsafeIndex arr (off + (n `shiftR` 1))
+                 byteInWord = (word `shiftR` ((n .&. 1) `shiftL` 3)) .&. 0xff
++#if MIN_VERSION_text(2,0,0)
++            in fromIntegral (byteInWord .|. 256)
++#else
+             in byteInWord .|. 256
++#endif
+         | otherwise       = 0
+     {-# INLINE getByte #-}
+ 
diff --git a/patches/deferred-folds-0.9.17.patch b/patches/deferred-folds-0.9.17.patch
index d431acf9f40effe9e549f7cce735350bb3b4c05f..b4b278277e606a2b63a9f6566bd8c79bc8895bfd 100644
--- a/patches/deferred-folds-0.9.17.patch
+++ b/patches/deferred-folds-0.9.17.patch
@@ -1,3 +1,16 @@
+diff --git a/deferred-folds.cabal b/deferred-folds.cabal
+index a4cb13b..c9b1694 100644
+--- a/deferred-folds.cabal
++++ b/deferred-folds.cabal
+@@ -44,7 +44,7 @@ library
+     foldl >=1 && <2,
+     hashable >=1 && <2,
+     primitive >=0.6.4 && <0.8,
+-    text >=1.2 && <1.3,
++    text >=1.2 && <1.3 || >=2.0 && <2.1,
+     transformers >=0.5 && <0.6,
+     unordered-containers >=0.2 && <0.3,
+     vector >=0.12 && <0.13
 diff --git a/library/DeferredFolds/Prelude.hs b/library/DeferredFolds/Prelude.hs
 index 095cdff..4046d16 100644
 --- a/library/DeferredFolds/Prelude.hs
@@ -20,3 +33,36 @@ index 095cdff..4046d16 100644
  import System.Environment as Exports
  import System.Exit as Exports
  import System.IO as Exports
+diff --git a/library/DeferredFolds/Util/TextArray.hs b/library/DeferredFolds/Util/TextArray.hs
+index 6ad5db4..78ac9c8 100644
+--- a/library/DeferredFolds/Util/TextArray.hs
++++ b/library/DeferredFolds/Util/TextArray.hs
+@@ -1,3 +1,5 @@
++{-# LANGUAGE CPP #-}
++
+ module DeferredFolds.Util.TextArray
+ where
+ 
+@@ -6,6 +8,7 @@ import Data.Text.Array
+ import qualified Data.Text.Internal as TextInternal
+ import qualified Data.Text.Internal.Encoding.Utf16 as TextUtf16
+ import qualified Data.Text.Internal.Unsafe.Char as TextChar
++import qualified Data.Text.Unsafe as TextUnsafe
+ 
+ 
+ {-|
+@@ -16,6 +19,9 @@ uses a continuation and passes the next offset to it instead of delta.
+ {-# INLINE iter #-}
+ iter :: Array -> Int -> (Char -> Int -> a) -> a
+ iter arr offset cont =
++#if MIN_VERSION_text(2,0,0)
++  let TextUnsafe.Iter c d = TextUnsafe.iterArray arr offset in cont c (offset + d)
++#else
+   let
+     b1 =
+       unsafeIndex arr offset
+@@ -28,3 +34,4 @@ iter arr offset cont =
+         in cont char (offset + 2)
+       else
+         cont (TextChar.unsafeChr b1) (offset + 1)
++#endif
diff --git a/patches/double-conversion-2.0.2.0.patch b/patches/double-conversion-2.0.2.0.patch
index 0ca3796523f189ca2e5e0943ad913667155cafad..dfd9111f1374609b7adf7397cdd604963000ddf2 100644
--- a/patches/double-conversion-2.0.2.0.patch
+++ b/patches/double-conversion-2.0.2.0.patch
@@ -1,15 +1,110 @@
 diff --git a/Data/Double/Conversion/Text.hs b/Data/Double/Conversion/Text.hs
-index 2e89705..5e2a0cd 100644
+index 2e89705..0b9c5c8 100644
 --- a/Data/Double/Conversion/Text.hs
 +++ b/Data/Double/Conversion/Text.hs
-@@ -75,8 +75,8 @@ convert :: String -> CInt
+@@ -75,8 +75,13 @@ convert :: String -> CInt
  convert func len act val = runST go
    where
      go = do
--      buf <- A.new (fromIntegral len)
--      size <- unsafeIOToST $ act (realToFrac val) (A.maBA buf)
-+      buf@(A.ByteArray buf#) <- A.new (fromIntegral len)
-+      size <- unsafeIOToST $ act (realToFrac val) buf#
++#if MIN_VERSION_text(2,0,0)
++      buf@(A.MutableByteArray mba) <- A.new (fromIntegral len)
++      size <- unsafeIOToST $ act (realToFrac val) mba
++#else
+       buf <- A.new (fromIntegral len)
+       size <- unsafeIOToST $ act (realToFrac val) (A.maBA buf)
++#endif
        when (size == -1) .
          fail $ "Data.Double.Conversion.Text." ++ func ++
                 ": conversion failed (invalid precision requested)"
+diff --git a/cbits/hs-double-conversion.cc b/cbits/hs-double-conversion.cc
+index 15d979b..c7b7148 100644
+--- a/cbits/hs-double-conversion.cc
++++ b/cbits/hs-double-conversion.cc
+@@ -40,7 +40,7 @@ int _hs_ToPrecisionLength(void)
+   return kToPrecisionLength;
+ }
+ 
+-static int copy(uint16_t *buf, const StringBuilder& builder, const char *cbuf)
++static int copy(TEXT_WORD_SIZE *buf, const StringBuilder& builder, const char *cbuf)
+ {
+   const int pos = builder.position();
+   for (int i = 0; i < pos; i++)
+@@ -48,7 +48,7 @@ static int copy(uint16_t *buf, const StringBuilder& builder, const char *cbuf)
+   return pos;
+ }
+ 
+-static int copy(uint16_t *buf, const char *cbuf, const int len)
++static int copy(TEXT_WORD_SIZE *buf, const char *cbuf, const int len)
+ {
+   for (int i = 0; i < len; i++)
+     buf[i] = cbuf[i];
+@@ -76,7 +76,7 @@ int _hs_ToShortest(double value, char *buf)
+ }
+ 
+ extern "C"
+-int _hs_Text_ToShortest(double value, uint16_t *buf)
++int _hs_Text_ToShortest(double value, TEXT_WORD_SIZE *buf)
+ {
+   char cbuf[kToShortestLength];
+   return copy(buf, cbuf, _hs_ToShortest(value, cbuf));
+@@ -91,7 +91,7 @@ int _hs_ToFixed(double value, char *buf, const int ndigits)
+ }
+ 
+ extern "C"
+-int _hs_Text_ToFixed(double value, uint16_t *buf, const int ndigits)
++int _hs_Text_ToFixed(double value, TEXT_WORD_SIZE *buf, const int ndigits)
+ {
+   char cbuf[kToFixedLength];
+   return copy(buf, cbuf, _hs_ToFixed(value, cbuf, ndigits));
+@@ -106,7 +106,7 @@ int _hs_ToExponential(double value, char *buf, const int ndigits)
+ }
+ 
+ extern "C"
+-int _hs_Text_ToExponential(double value, uint16_t *buf, const int ndigits)
++int _hs_Text_ToExponential(double value, TEXT_WORD_SIZE *buf, const int ndigits)
+ {
+   char cbuf[kToExponentialLength];
+   return copy(buf, cbuf, _hs_ToExponential(value, cbuf, ndigits));
+@@ -121,7 +121,7 @@ int _hs_ToPrecision(double value, char *buf, const int precision)
+ }
+ 
+ extern "C"
+-int _hs_Text_ToPrecision(double value, uint16_t *buf, const int precision)
++int _hs_Text_ToPrecision(double value, TEXT_WORD_SIZE *buf, const int precision)
+ {
+   char cbuf[kToPrecisionLength];
+   return copy(buf, cbuf, _hs_ToPrecision(value, cbuf, precision));
+diff --git a/include/hs-double-conversion.h b/include/hs-double-conversion.h
+index 5849a16..d3c8c6f 100644
+--- a/include/hs-double-conversion.h
++++ b/include/hs-double-conversion.h
+@@ -7,18 +7,25 @@ extern "C"
+ #endif
+ 
+ #include <stddef.h>
++#include "cabal_macros.h"
++
++#if MIN_VERSION_text(2,0,0)
++#define TEXT_WORD_SIZE uint8_t
++#else
++#define TEXT_WORD_SIZE uint16_t
++#endif
+ 
+ int _hs_ToShortestLength(void);
+-int _hs_Text_ToShortest(double value, uint16_t *buf);
++int _hs_Text_ToShortest(double value, TEXT_WORD_SIZE *buf);
+ int _hs_ToShortest(double value, char *buf);
+ int _hs_ToFixedLength(void);
+-int _hs_Text_ToFixed(double value, uint16_t *buf, int ndigits);
++int _hs_Text_ToFixed(double value, TEXT_WORD_SIZE *buf, int ndigits);
+ int _hs_ToFixed(double value, char *buf, int ndigits);
+ int _hs_ToExponentialLength(void);
+-int _hs_Text_ToExponential(double value, uint16_t *buf, int ndigits);
++int _hs_Text_ToExponential(double value, TEXT_WORD_SIZE *buf, int ndigits);
+ int _hs_ToExponential(double value, char *buf, int ndigits);
+ int _hs_ToPrecisionLength(void);
+-int _hs_Text_ToPrecision(double value, uint16_t *buf, int ndigits);
++int _hs_Text_ToPrecision(double value, TEXT_WORD_SIZE *buf, int ndigits);
+ int _hs_ToPrecision(double value, char *buf, int ndigits);
+ 
+ #ifdef __cplusplus
diff --git a/patches/streaming-commons-0.2.2.2.patch b/patches/streaming-commons-0.2.2.2.patch
new file mode 100644
index 0000000000000000000000000000000000000000..e0940fb14f1317864ed2f6e6a092889e9adf5542
--- /dev/null
+++ b/patches/streaming-commons-0.2.2.2.patch
@@ -0,0 +1,844 @@
+diff --git a/Data/Streaming/Text.hs b/Data/Streaming/Text.hs
+index 543f950..7084793 100644
+--- a/Data/Streaming/Text.hs
++++ b/Data/Streaming/Text.hs
+@@ -5,6 +5,7 @@
+ {-# LANGUAGE MagicHash                  #-}
+ {-# LANGUAGE Rank2Types                 #-}
+ {-# LANGUAGE UnliftedFFITypes           #-}
++{-# LANGUAGE ViewPatterns           #-}
+ 
+ --
+ -- Module      : Data.Text.Lazy.Encoding.Fusion
+@@ -59,10 +60,10 @@ import           Data.Text.Internal                (text)
+ import qualified Data.Text.Internal.Encoding.Utf16 as U16
+ import qualified Data.Text.Internal.Encoding.Utf32 as U32
+ import qualified Data.Text.Internal.Encoding.Utf8  as U8
+-import           Data.Text.Internal.Unsafe.Char    (unsafeChr, unsafeChr32,
++import           Data.Text.Internal.Unsafe.Char    (unsafeChr32,
+                                                     unsafeChr8)
+ import           Data.Text.Internal.Unsafe.Char    (unsafeWrite)
+-import           Data.Text.Internal.Unsafe.Shift   (shiftL)
++import           Data.Bits                         (shiftL)
+ import           Data.Word                         (Word32, Word8)
+ import           Foreign.C.Types                   (CSize (..))
+ import           Foreign.ForeignPtr                (withForeignPtr)
+@@ -72,6 +73,15 @@ import           Foreign.Ptr                       (Ptr, minusPtr, nullPtr,
+ import           Foreign.Storable                  (Storable, peek, poke)
+ import           GHC.Base                          (MutableByteArray#)
+ 
++#if MIN_VERSION_text(2,0,0)
++import Data.Text.Internal.Unsafe.Char (unsafeChr16)
++#else
++import Data.Text.Internal.Unsafe.Char (unsafeChr)
++unsafeChr16 = unsafeChr
++#endif
++
++
++
+ data S = S0
+        | S1 {-# UNPACK #-} !Word8
+        | S2 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8
+@@ -132,8 +142,14 @@ decodeUtf8 = decodeChunk B.empty 0 0
+         let end = ptr `plusPtr` (off + len)
+             loop curPtr = do
+               poke curPtrPtr curPtr
++#if MIN_VERSION_text(2,0,0)
++              let (A.MutableByteArray buf) = dest
++              _ <- c_decode_utf8_with_state buf destOffPtr
++                         curPtrPtr end codepointPtr statePtr
++#else
+               _ <- c_decode_utf8_with_state (A.maBA dest) destOffPtr
+                          curPtrPtr end codepointPtr statePtr
++#endif
+               state <- peek statePtr
+               n <- peek destOffPtr
+               chunkText <- unsafeSTToIO $ do
+@@ -172,8 +188,13 @@ decodeUtf8Pure =
+             _  -> DecodeResultFailure T.empty $ toBS s
+     beginChunk s0 ps = runST $ do
+         let initLen = B.length ps
++#if MIN_VERSION_text(2,0,0)
++        marr <- A.new (initLen + 3)
++#else
+         marr <- A.new (initLen + 1)
++#endif
+         let start !i !j
++
+                 | i >= len = do
+                     t <- getText j marr
+                     return $! DecodeResultSuccess t (beginChunk S0)
+@@ -237,12 +258,18 @@ decodeUtf16LE =
+             _  -> DecodeResultFailure T.empty $ toBS s
+     beginChunk s0 ps = runST $ do
+         let initLen = B.length ps
+-        marr <- A.new (initLen + 1)
++#if MIN_VERSION_text(2,0,0)
++        -- Worst-case scenario: each Word16 in UTF16 gives three Word8 in UTF8
++        -- and left-over from a previous chunk gives four Word8 in UTF8
++        marr <- A.new ((initLen `div` 2) * 3 + 4) -- of Word8
++#else
++        marr <- A.new (initLen + 1) -- of Word16
++#endif
+         let start !i !j
+                 | i >= len = do
+                     t <- getText j marr
+                     return $! DecodeResultSuccess t (beginChunk S0)
+-                | i + 1 < len && U16.validate1 x1    = addChar' 2 (unsafeChr x1)
++                | i + 1 < len && U16.validate1 x1    = addChar' 2 (unsafeChr16 x1)
+                 | i + 3 < len && U16.validate2 x1 x2 = addChar' 4 (U16.chr2 x1 x2)
+                 | i + 3 < len = do
+                     t <- getText j marr
+@@ -271,7 +298,7 @@ decodeUtf16LE =
+                     S1 a ->
+                         let x1 = combine a x
+                          in if U16.validate1 x1
+-                                then addChar' (unsafeChr x1)
++                                then addChar' (unsafeChr16 x1)
+                                 else checkCont (S2 a x) (i + 1)
+                     S2 a b -> checkCont (S3 a b x) (i + 1)
+                     S3 a b c ->
+@@ -293,6 +320,7 @@ decodeUtf16LE =
+         combine w1 w2 = fromIntegral w1 .|. (fromIntegral w2 `shiftL` 8)
+     {-# INLINE beginChunk #-}
+ 
++
+ -- | /O(n)/ Convert a 'ByteString' into a 'Stream Char', using big
+ -- endian UTF-16 encoding.
+ decodeUtf16BE :: B.ByteString -> DecodeResult
+@@ -306,12 +334,18 @@ decodeUtf16BE =
+             _  -> DecodeResultFailure T.empty $ toBS s
+     beginChunk s0 ps = runST $ do
+         let initLen = B.length ps
+-        marr <- A.new (initLen + 1)
++#if MIN_VERSION_text(2,0,0)
++        -- Worst-case scenario: each Word16 in UTF16 gives three Word8 in UTF8
++        -- and left-over from a previous chunk gives four Word8 in UTF8
++        marr <- A.new ((initLen `div` 2) * 3 + 4) -- of Word8
++#else
++        marr <- A.new (initLen + 1) -- of Word16
++#endif
+         let start !i !j
+                 | i >= len = do
+                     t <- getText j marr
+                     return $! DecodeResultSuccess t (beginChunk S0)
+-                | i + 1 < len && U16.validate1 x1    = addChar' 2 (unsafeChr x1)
++                | i + 1 < len && U16.validate1 x1    = addChar' 2 (unsafeChr16 x1)
+                 | i + 3 < len && U16.validate2 x1 x2 = addChar' 4 (U16.chr2 x1 x2)
+                 | i + 3 < len = do
+                     t <- getText j marr
+@@ -340,7 +374,7 @@ decodeUtf16BE =
+                     S1 a ->
+                         let x1 = combine a x
+                          in if U16.validate1 x1
+-                                then addChar' (unsafeChr x1)
++                                then addChar' (unsafeChr16 x1)
+                                 else checkCont (S2 a x) (i + 1)
+                     S2 a b -> checkCont (S3 a b x) (i + 1)
+                     S3 a b c ->
+@@ -375,7 +409,11 @@ decodeUtf32LE =
+             _  -> DecodeResultFailure T.empty $ toBS s
+     beginChunk s0 ps = runST $ do
+         let initLen = B.length ps `div` 2
+-        marr <- A.new (initLen + 1)
++#if MIN_VERSION_text(2,0,0)
++        marr <- A.new (initLen * 2 + 4) -- of Word8
++#else
++        marr <- A.new (initLen + 1) -- of Word16
++#endif
+         let start !i !j
+                 | i >= len = do
+                     t <- getText j marr
+@@ -441,7 +479,11 @@ decodeUtf32BE =
+             _  -> DecodeResultFailure T.empty $ toBS s
+     beginChunk s0 ps = runST $ do
+         let initLen = B.length ps `div` 2
+-        marr <- A.new (initLen + 1)
++#if MIN_VERSION_text(2,0,0)
++        marr <- A.new (initLen * 2 + 4) -- of Word8
++#else
++        marr <- A.new (initLen + 1) -- of Word16
++#endif
+         let start !i !j
+                 | i >= len = do
+                     t <- getText j marr
+diff --git a/Data/Text/Internal/Encoding/Utf16.hs b/Data/Text/Internal/Encoding/Utf16.hs
+deleted file mode 100644
+index 4f929f3..0000000
+--- a/Data/Text/Internal/Encoding/Utf16.hs
++++ /dev/null
+@@ -1,54 +0,0 @@
+-{-# LANGUAGE CPP #-}
+-{-# LANGUAGE MagicHash, BangPatterns #-}
+-
+--- |
+--- Module      : Data.Text.Internal.Encoding.Utf16
+--- Copyright   : (c) 2008, 2009 Tom Harper,
+---               (c) 2009 Bryan O'Sullivan,
+---               (c) 2009 Duncan Coutts
+---
+--- License     : BSD-style
+--- Maintainer  : bos@serpentine.com
+--- Stability   : experimental
+--- Portability : GHC
+---
+--- /Warning/: this is an internal module, and does not have a stable
+--- API or name. Functions in this module may not check or enforce
+--- preconditions expected by public modules. Use at your own risk!
+---
+--- Basic UTF-16 validation and character manipulation.
+-module Data.Text.Internal.Encoding.Utf16
+-    (
+-      chr2
+-    , validate1
+-    , validate2
+-    ) where
+-
+-import GHC.Exts
+-import GHC.Word (Word16(..))
+-
+-chr2 :: Word16 -> Word16 -> Char
+-chr2 (W16# a#) (W16# b#) = C# (chr# (upper# +# lower# +# 0x10000#))
+-    where
+-      !x# = word2Int# (word16ToWordCompat# a#)
+-      !y# = word2Int# (word16ToWordCompat# b#)
+-      !upper# = uncheckedIShiftL# (x# -# 0xD800#) 10#
+-      !lower# = y# -# 0xDC00#
+-{-# INLINE chr2 #-}
+-
+-validate1    :: Word16 -> Bool
+-validate1 x1 = x1 < 0xD800 || x1 > 0xDFFF
+-{-# INLINE validate1 #-}
+-
+-validate2       ::  Word16 -> Word16 -> Bool
+-validate2 x1 x2 = x1 >= 0xD800 && x1 <= 0xDBFF &&
+-                  x2 >= 0xDC00 && x2 <= 0xDFFF
+-{-# INLINE validate2 #-}
+-
+-#if MIN_VERSION_base(4,16,0)
+-word16ToWordCompat# :: Word16# -> Word#
+-word16ToWordCompat# = word16ToWord#
+-#else
+-word16ToWordCompat# :: Word# -> Word#
+-word16ToWordCompat# x = x
+-#endif
+diff --git a/Data/Text/Internal/Encoding/Utf32.hs b/Data/Text/Internal/Encoding/Utf32.hs
+deleted file mode 100644
+index 4e8e9b4..0000000
+--- a/Data/Text/Internal/Encoding/Utf32.hs
++++ /dev/null
+@@ -1,26 +0,0 @@
+--- |
+--- Module      : Data.Text.Internal.Encoding.Utf32
+--- Copyright   : (c) 2008, 2009 Tom Harper,
+---               (c) 2009, 2010 Bryan O'Sullivan,
+---               (c) 2009 Duncan Coutts
+---
+--- License     : BSD-style
+--- Maintainer  : bos@serpentine.com
+--- Stability   : experimental
+--- Portability : portable
+---
+--- /Warning/: this is an internal module, and does not have a stable
+--- API or name. Functions in this module may not check or enforce
+--- preconditions expected by public modules. Use at your own risk!
+---
+--- Basic UTF-32 validation.
+-module Data.Text.Internal.Encoding.Utf32
+-    (
+-      validate
+-    ) where
+-
+-import Data.Word (Word32)
+-
+-validate    :: Word32 -> Bool
+-validate x1 = x1 < 0xD800 || (x1 > 0xDFFF && x1 <= 0x10FFFF)
+-{-# INLINE validate #-}
+diff --git a/Data/Text/Internal/Encoding/Utf8.hs b/Data/Text/Internal/Encoding/Utf8.hs
+deleted file mode 100644
+index 952cf30..0000000
+--- a/Data/Text/Internal/Encoding/Utf8.hs
++++ /dev/null
+@@ -1,176 +0,0 @@
+-{-# LANGUAGE CPP, MagicHash, BangPatterns #-}
+-
+--- |
+--- Module      : Data.Text.Internal.Encoding.Utf8
+--- Copyright   : (c) 2008, 2009 Tom Harper,
+---               (c) 2009, 2010 Bryan O'Sullivan,
+---               (c) 2009 Duncan Coutts
+---
+--- License     : BSD-style
+--- Maintainer  : bos@serpentine.com
+--- Stability   : experimental
+--- Portability : GHC
+---
+--- /Warning/: this is an internal module, and does not have a stable
+--- API or name. Functions in this module may not check or enforce
+--- preconditions expected by public modules. Use at your own risk!
+---
+--- Basic UTF-8 validation and character manipulation.
+-module Data.Text.Internal.Encoding.Utf8
+-    (
+-    -- Decomposition
+-      ord2
+-    , ord3
+-    , ord4
+-    -- Construction
+-    , chr2
+-    , chr3
+-    , chr4
+-    -- * Validation
+-    , validate1
+-    , validate2
+-    , validate3
+-    , validate4
+-    ) where
+-
+-#if defined(TEST_SUITE)
+-# undef ASSERTS
+-#endif
+-
+-#if defined(ASSERTS)
+-import Control.Exception (assert)
+-#endif
+-import Data.Bits ((.&.))
+-import Data.Text.Internal.Unsafe.Char (ord)
+-import Data.Text.Internal.Unsafe.Shift (shiftR)
+-import GHC.Exts
+-import GHC.Word (Word8(..))
+-
+-default(Int)
+-
+-between :: Word8                -- ^ byte to check
+-        -> Word8                -- ^ lower bound
+-        -> Word8                -- ^ upper bound
+-        -> Bool
+-between x y z = x >= y && x <= z
+-{-# INLINE between #-}
+-
+-ord2 :: Char -> (Word8,Word8)
+-ord2 c =
+-#if defined(ASSERTS)
+-    assert (n >= 0x80 && n <= 0x07ff)
+-#endif
+-    (x1,x2)
+-    where
+-      n  = ord c
+-      x1 = fromIntegral $ (n `shiftR` 6) + 0xC0
+-      x2 = fromIntegral $ (n .&. 0x3F)   + 0x80
+-
+-ord3 :: Char -> (Word8,Word8,Word8)
+-ord3 c =
+-#if defined(ASSERTS)
+-    assert (n >= 0x0800 && n <= 0xffff)
+-#endif
+-    (x1,x2,x3)
+-    where
+-      n  = ord c
+-      x1 = fromIntegral $ (n `shiftR` 12) + 0xE0
+-      x2 = fromIntegral $ ((n `shiftR` 6) .&. 0x3F) + 0x80
+-      x3 = fromIntegral $ (n .&. 0x3F) + 0x80
+-
+-ord4 :: Char -> (Word8,Word8,Word8,Word8)
+-ord4 c =
+-#if defined(ASSERTS)
+-    assert (n >= 0x10000)
+-#endif
+-    (x1,x2,x3,x4)
+-    where
+-      n  = ord c
+-      x1 = fromIntegral $ (n `shiftR` 18) + 0xF0
+-      x2 = fromIntegral $ ((n `shiftR` 12) .&. 0x3F) + 0x80
+-      x3 = fromIntegral $ ((n `shiftR` 6) .&. 0x3F) + 0x80
+-      x4 = fromIntegral $ (n .&. 0x3F) + 0x80
+-
+-chr2 :: Word8 -> Word8 -> Char
+-chr2 (W8# x1#) (W8# x2#) = C# (chr# (z1# +# z2#))
+-    where
+-      !y1# = word2Int# (word8ToWordCompat# x1#)
+-      !y2# = word2Int# (word8ToWordCompat# x2#)
+-      !z1# = uncheckedIShiftL# (y1# -# 0xC0#) 6#
+-      !z2# = y2# -# 0x80#
+-{-# INLINE chr2 #-}
+-
+-chr3 :: Word8 -> Word8 -> Word8 -> Char
+-chr3 (W8# x1#) (W8# x2#) (W8# x3#) = C# (chr# (z1# +# z2# +# z3#))
+-    where
+-      !y1# = word2Int# (word8ToWordCompat# x1#)
+-      !y2# = word2Int# (word8ToWordCompat# x2#)
+-      !y3# = word2Int# (word8ToWordCompat# x3#)
+-      !z1# = uncheckedIShiftL# (y1# -# 0xE0#) 12#
+-      !z2# = uncheckedIShiftL# (y2# -# 0x80#) 6#
+-      !z3# = y3# -# 0x80#
+-{-# INLINE chr3 #-}
+-
+-chr4             :: Word8 -> Word8 -> Word8 -> Word8 -> Char
+-chr4 (W8# x1#) (W8# x2#) (W8# x3#) (W8# x4#) =
+-    C# (chr# (z1# +# z2# +# z3# +# z4#))
+-    where
+-      !y1# = word2Int# (word8ToWordCompat# x1#)
+-      !y2# = word2Int# (word8ToWordCompat# x2#)
+-      !y3# = word2Int# (word8ToWordCompat# x3#)
+-      !y4# = word2Int# (word8ToWordCompat# x4#)
+-      !z1# = uncheckedIShiftL# (y1# -# 0xF0#) 18#
+-      !z2# = uncheckedIShiftL# (y2# -# 0x80#) 12#
+-      !z3# = uncheckedIShiftL# (y3# -# 0x80#) 6#
+-      !z4# = y4# -# 0x80#
+-{-# INLINE chr4 #-}
+-
+-validate1 :: Word8 -> Bool
+-validate1 x1 = x1 <= 0x7F
+-{-# INLINE validate1 #-}
+-
+-validate2 :: Word8 -> Word8 -> Bool
+-validate2 x1 x2 = between x1 0xC2 0xDF && between x2 0x80 0xBF
+-{-# INLINE validate2 #-}
+-
+-validate3 :: Word8 -> Word8 -> Word8 -> Bool
+-{-# INLINE validate3 #-}
+-validate3 x1 x2 x3 = validate3_1 || validate3_2 || validate3_3 || validate3_4
+-  where
+-    validate3_1 = (x1 == 0xE0) &&
+-                  between x2 0xA0 0xBF &&
+-                  between x3 0x80 0xBF
+-    validate3_2 = between x1 0xE1 0xEC &&
+-                  between x2 0x80 0xBF &&
+-                  between x3 0x80 0xBF
+-    validate3_3 = x1 == 0xED &&
+-                  between x2 0x80 0x9F &&
+-                  between x3 0x80 0xBF
+-    validate3_4 = between x1 0xEE 0xEF &&
+-                  between x2 0x80 0xBF &&
+-                  between x3 0x80 0xBF
+-
+-validate4 :: Word8 -> Word8 -> Word8 -> Word8 -> Bool
+-{-# INLINE validate4 #-}
+-validate4 x1 x2 x3 x4 = validate4_1 || validate4_2 || validate4_3
+-  where
+-    validate4_1 = x1 == 0xF0 &&
+-                  between x2 0x90 0xBF &&
+-                  between x3 0x80 0xBF &&
+-                  between x4 0x80 0xBF
+-    validate4_2 = between x1 0xF1 0xF3 &&
+-                  between x2 0x80 0xBF &&
+-                  between x3 0x80 0xBF &&
+-                  between x4 0x80 0xBF
+-    validate4_3 = x1 == 0xF4 &&
+-                  between x2 0x80 0x8F &&
+-                  between x3 0x80 0xBF &&
+-                  between x4 0x80 0xBF
+-
+-#if MIN_VERSION_base(4,16,0)
+-word8ToWordCompat# :: Word8# -> Word#
+-word8ToWordCompat# = word8ToWord#
+-#else
+-word8ToWordCompat# :: Word# -> Word#
+-word8ToWordCompat# x = x
+-#endif
+diff --git a/Data/Text/Internal/Unsafe/Char.hs b/Data/Text/Internal/Unsafe/Char.hs
+deleted file mode 100644
+index b02d560..0000000
+--- a/Data/Text/Internal/Unsafe/Char.hs
++++ /dev/null
+@@ -1,119 +0,0 @@
+-{-# LANGUAGE CPP, MagicHash #-}
+-
+--- |
+--- Module      : Data.Text.Internal.Unsafe.Char
+--- Copyright   : (c) 2008, 2009 Tom Harper,
+---               (c) 2009, 2010 Bryan O'Sullivan,
+---               (c) 2009 Duncan Coutts
+---
+--- License     : BSD-style
+--- Maintainer  : bos@serpentine.com
+--- Stability   : experimental
+--- Portability : GHC
+---
+--- /Warning/: this is an internal module, and does not have a stable
+--- API or name. Functions in this module may not check or enforce
+--- preconditions expected by public modules. Use at your own risk!
+---
+--- Fast character manipulation functions.
+-module Data.Text.Internal.Unsafe.Char
+-    (
+-      ord
+-    , unsafeChr
+-    , unsafeChr8
+-    , unsafeChr32
+-    , unsafeWrite
+-    -- , unsafeWriteRev
+-    ) where
+-
+-#ifdef ASSERTS
+-import Control.Exception (assert)
+-#endif
+-import Control.Monad.ST (ST)
+-import Data.Bits ((.&.))
+-import Data.Text.Internal.Unsafe.Shift (shiftR)
+-import GHC.Exts (Char(..), Int(..), Word#, chr#, ord#, word2Int#)
+-import GHC.Word (Word8(..), Word16(..), Word32(..))
+-import qualified Data.Text.Array as A
+-
+-#if MIN_VERSION_base(4,16,0)
+-import GHC.Exts (Word8#, Word16#, Word32#, word8ToWord#, word16ToWord#, word32ToWord#)
+-#endif
+-
+-ord :: Char -> Int
+-ord (C# c#) = I# (ord# c#)
+-{-# INLINE ord #-}
+-
+-unsafeChr :: Word16 -> Char
+-unsafeChr (W16# w#) = C# (chr# (word2Int# (word16ToWordCompat# w#)))
+-{-# INLINE unsafeChr #-}
+-
+-unsafeChr8 :: Word8 -> Char
+-unsafeChr8 (W8# w#) = C# (chr# (word2Int# (word8ToWordCompat# w#)))
+-{-# INLINE unsafeChr8 #-}
+-
+-unsafeChr32 :: Word32 -> Char
+-unsafeChr32 (W32# w#) = C# (chr# (word2Int# (word32ToWordCompat# w#)))
+-{-# INLINE unsafeChr32 #-}
+-
+--- | Write a character into the array at the given offset.  Returns
+--- the number of 'Word16's written.
+-unsafeWrite :: A.MArray s -> Int -> Char -> ST s Int
+-unsafeWrite marr i c
+-    | n < 0x10000 = do
+-#if defined(ASSERTS)
+-        assert (i >= 0) . assert (i < A.length marr) $ return ()
+-#endif
+-        A.unsafeWrite marr i (fromIntegral n)
+-        return 1
+-    | otherwise = do
+-#if defined(ASSERTS)
+-        assert (i >= 0) . assert (i < A.length marr - 1) $ return ()
+-#endif
+-        A.unsafeWrite marr i lo
+-        A.unsafeWrite marr (i+1) hi
+-        return 2
+-    where n = ord c
+-          m = n - 0x10000
+-          lo = fromIntegral $ (m `shiftR` 10) + 0xD800
+-          hi = fromIntegral $ (m .&. 0x3FF) + 0xDC00
+-{-# INLINE unsafeWrite #-}
+-
+-{-
+-unsafeWriteRev :: A.MArray s Word16 -> Int -> Char -> ST s Int
+-unsafeWriteRev marr i c
+-    | n < 0x10000 = do
+-        assert (i >= 0) . assert (i < A.length marr) $
+-          A.unsafeWrite marr i (fromIntegral n)
+-        return (i-1)
+-    | otherwise = do
+-        assert (i >= 1) . assert (i < A.length marr) $
+-          A.unsafeWrite marr (i-1) lo
+-        A.unsafeWrite marr i hi
+-        return (i-2)
+-    where n = ord c
+-          m = n - 0x10000
+-          lo = fromIntegral $ (m `shiftR` 10) + 0xD800
+-          hi = fromIntegral $ (m .&. 0x3FF) + 0xDC00
+-{-# INLINE unsafeWriteRev #-}
+--}
+-
+-#if MIN_VERSION_base(4,16,0)
+-word8ToWordCompat# :: Word8# -> Word#
+-word8ToWordCompat# = word8ToWord#
+-
+-word16ToWordCompat# :: Word16# -> Word#
+-word16ToWordCompat# = word16ToWord#
+-
+-word32ToWordCompat# :: Word32# -> Word#
+-word32ToWordCompat# = word32ToWord#
+-#else
+-word8ToWordCompat# :: Word# -> Word#
+-word8ToWordCompat# x = x
+-
+-word16ToWordCompat# :: Word# -> Word#
+-word16ToWordCompat# x = x
+-
+-word32ToWordCompat# :: Word# -> Word#
+-word32ToWordCompat# x = x
+-#endif
+diff --git a/Data/Text/Internal/Unsafe/Shift.hs b/Data/Text/Internal/Unsafe/Shift.hs
+deleted file mode 100644
+index 8606b96..0000000
+--- a/Data/Text/Internal/Unsafe/Shift.hs
++++ /dev/null
+@@ -1,116 +0,0 @@
+-{-# LANGUAGE CPP #-}
+-{-# LANGUAGE MagicHash #-}
+-
+--- |
+--- Module      : Data.Text.Internal.Unsafe.Shift
+--- Copyright   : (c) Bryan O'Sullivan 2009
+---
+--- License     : BSD-style
+--- Maintainer  : bos@serpentine.com
+--- Stability   : experimental
+--- Portability : GHC
+---
+--- /Warning/: this is an internal module, and does not have a stable
+--- API or name. Functions in this module may not check or enforce
+--- preconditions expected by public modules. Use at your own risk!
+---
+--- Fast, unchecked bit shifting functions.
+-
+-module Data.Text.Internal.Unsafe.Shift
+-    (
+-      UnsafeShift(..)
+-    ) where
+-
+--- import qualified Data.Bits as Bits
+-import GHC.Base
+-#if __GLASGOW_HASKELL__ >= 903
+-  hiding (uncheckedShiftL64#, uncheckedShiftRL64#)
+-#endif
+-import GHC.Word
+-
+--- | This is a workaround for poor optimisation in GHC 6.8.2.  It
+--- fails to notice constant-width shifts, and adds a test and branch
+--- to every shift.  This imposes about a 10% performance hit.
+---
+--- These functions are undefined when the amount being shifted by is
+--- greater than the size in bits of a machine Int#.
+-class UnsafeShift a where
+-    shiftL :: a -> Int -> a
+-    shiftR :: a -> Int -> a
+-
+-instance UnsafeShift Word16 where
+-    {-# INLINE shiftL #-}
+-    shiftL (W16# x#) (I# i#) = W16# (narrow16WordCompat# (word16ToWordCompat# x# `uncheckedShiftL#` i#))
+-
+-    {-# INLINE shiftR #-}
+-    shiftR (W16# x#) (I# i#) = W16# (wordToWord16Compat# (word16ToWordCompat# x# `uncheckedShiftRL#` i#))
+-
+-instance UnsafeShift Word32 where
+-    {-# INLINE shiftL #-}
+-    shiftL (W32# x#) (I# i#) = W32# (narrow32WordCompat# (word32ToWordCompat# x# `uncheckedShiftL#` i#))
+-
+-    {-# INLINE shiftR #-}
+-    shiftR (W32# x#) (I# i#) = W32# (wordToWord32Compat# (word32ToWordCompat# x# `uncheckedShiftRL#` i#))
+-
+-instance UnsafeShift Word64 where
+-    {-# INLINE shiftL #-}
+-    shiftL (W64# x#) (I# i#) = W64# (x# `uncheckedShiftL64#` i#)
+-
+-    {-# INLINE shiftR #-}
+-    shiftR (W64# x#) (I# i#) = W64# (x# `uncheckedShiftRL64#` i#)
+-
+-instance UnsafeShift Int where
+-    {-# INLINE shiftL #-}
+-    shiftL (I# x#) (I# i#) = I# (x# `iShiftL#` i#)
+-
+-    {-# INLINE shiftR #-}
+-    shiftR (I# x#) (I# i#) = I# (x# `iShiftRA#` i#)
+-
+-{-
+-instance UnsafeShift Integer where
+-    {-# INLINE shiftL #-}
+-    shiftL = Bits.shiftL
+-
+-    {-# INLINE shiftR #-}
+-    shiftR = Bits.shiftR
+--}
+-
+-#if MIN_VERSION_base(4,16,0)
+-word16ToWordCompat# :: Word16# -> Word#
+-word16ToWordCompat# = word16ToWord#
+-
+-word32ToWordCompat# :: Word32# -> Word#
+-word32ToWordCompat# = word32ToWord#
+-
+-wordToWord16Compat# :: Word# -> Word16#
+-wordToWord16Compat# = wordToWord16#
+-
+-wordToWord32Compat# :: Word# -> Word32#
+-wordToWord32Compat# = wordToWord32#
+-
+-narrow16WordCompat# :: Word# -> Word16#
+-narrow16WordCompat# = wordToWord16#
+-
+-narrow32WordCompat# :: Word# -> Word32#
+-narrow32WordCompat# = wordToWord32#
+-#else
+--- No-ops
+-word16ToWordCompat# :: Word# -> Word#
+-word16ToWordCompat# x = x
+-
+-word32ToWordCompat# :: Word# -> Word#
+-word32ToWordCompat# x = x
+-
+-wordToWord16Compat# :: Word# -> Word#
+-wordToWord16Compat# x = x
+-
+-wordToWord32Compat# :: Word# -> Word#
+-wordToWord32Compat# x = x
+-
+--- Actual narrowing
+-narrow16WordCompat# :: Word# -> Word#
+-narrow16WordCompat# = narrow16Word#
+-
+-narrow32WordCompat# :: Word# -> Word#
+-narrow32WordCompat# = narrow32Word#
+-#endif
+diff --git a/cbits/text-helper.c b/cbits/text-helper.c
+index c0a9d69..58820c2 100644
+--- a/cbits/text-helper.c
++++ b/cbits/text-helper.c
+@@ -10,6 +10,8 @@
+ #include <stdint.h>
+ #include <stdio.h>
+ #include "text_cbits.h"
++#include "cabal_macros.h"
++
+ 
+ void _hs_streaming_commons_memcpy(void *dest, size_t doff, const void *src, size_t soff,
+ 		     size_t n)
+@@ -72,7 +74,7 @@ decode(uint32_t *state, uint32_t* codep, uint32_t byte) {
+  * an UTF16 array
+  */
+ void
+-_hs_streaming_commons_decode_latin1(uint16_t *dest, const uint8_t *src,
++_hs_streaming_commons_decode_latin1(TEXT_WORD_SIZE *dest, const uint8_t *src,
+                        const uint8_t *srcend)
+ {
+   const uint8_t *p = src;
+@@ -133,24 +135,23 @@ _hs_streaming_commons_decode_latin1(uint16_t *dest, const uint8_t *src,
+  */
+ #if defined(__GNUC__) || defined(__clang__)
+ static inline uint8_t const *
+-_hs_streaming_commons_decode_utf8_int(uint16_t *const dest, size_t *destoff,
++_hs_streaming_commons_decode_utf8_int(TEXT_WORD_SIZE *const dest, size_t *destoff,
+ 			 const uint8_t **src, const uint8_t *srcend,
+ 			 uint32_t *codepoint0, uint32_t *state0)
+   __attribute((always_inline));
+ #endif
+ 
+ static inline uint8_t const *
+-_hs_streaming_commons_decode_utf8_int(uint16_t *const dest, size_t *destoff,
++_hs_streaming_commons_decode_utf8_int(TEXT_WORD_SIZE *const dest, size_t *destoff,
+ 			 const uint8_t **src, const uint8_t *srcend,
+ 			 uint32_t *codepoint0, uint32_t *state0)
+ {
+-  uint16_t *d = dest + *destoff;
++  TEXT_WORD_SIZE *d = dest + *destoff;
+   const uint8_t *s = *src, *last = *src;
+   uint32_t state = *state0;
+   uint32_t codepoint = *codepoint0;
+ 
+   while (s < srcend) {
+-#if defined(__i386__) || defined(__x86_64__)
+     /*
+      * This code will only work on a little-endian system that
+      * supports unaligned loads.
+@@ -172,14 +173,13 @@ _hs_streaming_commons_decode_utf8_int(uint16_t *const dest, size_t *destoff,
+ 	 * slowed the code down.
+ 	 */
+ 
+-	*d++ = (uint16_t) (codepoint & 0xff);
+-	*d++ = (uint16_t) ((codepoint >> 8) & 0xff);
+-	*d++ = (uint16_t) ((codepoint >> 16) & 0xff);
+-	*d++ = (uint16_t) ((codepoint >> 24) & 0xff);
++	*d++ = (TEXT_WORD_SIZE) (codepoint & 0xff);
++	*d++ = (TEXT_WORD_SIZE) ((codepoint >> 8) & 0xff);
++	*d++ = (TEXT_WORD_SIZE) ((codepoint >> 16) & 0xff);
++	*d++ = (TEXT_WORD_SIZE) ((codepoint >> 24) & 0xff);
+       }
+       last = s;
+     }
+-#endif
+ 
+     if (decode(&state, &codepoint, *s++) != UTF8_ACCEPT) {
+       if (state != UTF8_REJECT)
+@@ -187,12 +187,33 @@ _hs_streaming_commons_decode_utf8_int(uint16_t *const dest, size_t *destoff,
+       break;
+     }
+ 
++#if MIN_VERSION_text(2,0,0)
++    if (codepoint <= 0x7f){
++      *d++ = (TEXT_WORD_SIZE) codepoint;
++    }
++    else if (codepoint <=  0x7ff ) {
++      *d++ = (TEXT_WORD_SIZE) (0xc0 | (0x1f & (codepoint >> 6 )));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & codepoint));
++    }
++    else if (codepoint <=  0xffff) {
++      *d++ = (TEXT_WORD_SIZE) (0xe0 | (0x0f & (codepoint >> 12 )));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & (codepoint >> 6)));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & codepoint));
++    }
++    else {
++      *d++ = (TEXT_WORD_SIZE) (0xf0 | (0x07 & (codepoint >> 18 )));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & (codepoint >> 12 )));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & (codepoint >> 6)));
++      *d++ = (TEXT_WORD_SIZE) (0x80 | (0x3f & codepoint));
++    }
++#else
+     if (codepoint <= 0xffff)
+       *d++ = (uint16_t) codepoint;
+     else {
+       *d++ = (uint16_t) (0xD7C0 + (codepoint >> 10));
+       *d++ = (uint16_t) (0xDC00 + (codepoint & 0x3FF));
+     }
++#endif
+     last = s;
+   }
+ 
+@@ -205,7 +226,7 @@ _hs_streaming_commons_decode_utf8_int(uint16_t *const dest, size_t *destoff,
+ }
+ 
+ uint8_t const *
+-_hs_streaming_commons_decode_utf8_state(uint16_t *const dest, size_t *destoff,
++_hs_streaming_commons_decode_utf8_state(TEXT_WORD_SIZE *const dest, size_t *destoff,
+                            const uint8_t **src,
+ 			   const uint8_t *srcend,
+                            uint32_t *codepoint0, uint32_t *state0)
+@@ -221,7 +242,7 @@ _hs_streaming_commons_decode_utf8_state(uint16_t *const dest, size_t *destoff,
+  * Helper to decode buffer and discard final decoder state
+  */
+ const uint8_t *
+-_hs_streaming_commons_decode_utf8(uint16_t *const dest, size_t *destoff,
++_hs_streaming_commons_decode_utf8(TEXT_WORD_SIZE *const dest, size_t *destoff,
+                      const uint8_t *src, const uint8_t *const srcend)
+ {
+   uint32_t codepoint;
+diff --git a/include/text_cbits.h b/include/text_cbits.h
+index 3523efe..84e09e7 100644
+--- a/include/text_cbits.h
++++ b/include/text_cbits.h
+@@ -1,10 +1,17 @@
+ /*
+  * Copyright (c) 2013 Bryan O'Sullivan <bos@serpentine.com>.
+  */
++#include "cabal_macros.h"
+ 
+ #ifndef _text_cbits_h
+ #define _text_cbits_h
+ 
++#if MIN_VERSION_text(2,0,0)
++#define TEXT_WORD_SIZE uint8_t
++#else
++#define TEXT_WORD_SIZE uint16_t
++#endif
++
+ #define UTF8_ACCEPT 0
+ #define UTF8_REJECT 12
+ 
+diff --git a/streaming-commons.cabal b/streaming-commons.cabal
+index c28b929..789da34 100644
+--- a/streaming-commons.cabal
++++ b/streaming-commons.cabal
+@@ -40,11 +40,6 @@ library
+ 
+   -- Due to cabal bugs, not making inclusion of this dependent on text version.
+   -- For more information, see: https://github.com/fpco/text-stream-decode/issues/1
+-  other-modules:       Data.Text.Internal.Unsafe.Char
+-                       Data.Text.Internal.Unsafe.Shift
+-                       Data.Text.Internal.Encoding.Utf8
+-                       Data.Text.Internal.Encoding.Utf16
+-                       Data.Text.Internal.Encoding.Utf32
+ 
+   build-depends:       base >= 4.12 && < 5
+                      , array
diff --git a/patches/text-metrics-0.3.1.patch b/patches/text-metrics-0.3.1.patch
index 1b890a192dc0c68f83074e733083899023ed5333..2f928dcf4e2cb6dacf8a9355bc6bfe52d0c50f53 100644
--- a/patches/text-metrics-0.3.1.patch
+++ b/patches/text-metrics-0.3.1.patch
@@ -1,36 +1,87 @@
-commit e918c469c6fde93d6cb48254fe1c7442de31ea12
-Author: Ben Gamari <ben@smart-cactus.org>
-Date:   Mon Nov 22 17:57:04 2021 -0500
-
-    hi
-
 diff --git a/Data/Text/Metrics.hs b/Data/Text/Metrics.hs
-index ccf55aa..8c158d9 100644
+index ccf55aa..dfb9209 100644
 --- a/Data/Text/Metrics.hs
 +++ b/Data/Text/Metrics.hs
-@@ -258,7 +258,11 @@ hamming a b =
+@@ -43,6 +43,7 @@ import qualified Data.Map.Strict as M
+ import Data.Ratio
+ import Data.Text
+ import qualified Data.Text as T
++import qualified Data.Text.Internal as T
+ import qualified Data.Text.Unsafe as TU
+ import qualified Data.Vector.Unboxed.Mutable as VUM
+ import GHC.Exts (inline)
+@@ -246,7 +247,7 @@ unionSize a b = M.foldl' (+) 0 (M.unionWith max a b)
+ -- __Heads up__, before version /0.3.0/ this function returned @'Maybe'
+ -- 'Data.Numeric.Natural'@.
+ hamming :: Text -> Text -> Maybe Int
+-hamming a b =
++hamming a@(T.Text _ _ len) b =
+   if T.length a == T.length b
+     then Just (go 0 0 0)
+     else Nothing
+@@ -258,7 +259,6 @@ hamming a b =
                | na == len -> r
                | cha /= chb -> go (na + da) (nb + db) (r + 1)
                | otherwise -> go (na + da) (nb + db) r
-+#if MIN_VERSION_text(2,0)
-+    len = TU.lengthWord8 a
-+#else
-     len = TU.lengthWord16 a
-+#endif
+-    len = TU.lengthWord16 a
  
  -- | Return the Jaro distance between two 'Text' values. Returned value is
  -- in the range from 0 (no similarity) to 1 (exact match).
-@@ -358,8 +362,13 @@ commonPrefix a b = go 0 0 0
+@@ -348,7 +348,7 @@ jaroWinkler a b = dj + (1 % 10) * l * (1 - dj)
+ 
+ -- | Return the length of the common prefix two 'Text' values have.
+ commonPrefix :: Text -> Text -> Int
+-commonPrefix a b = go 0 0 0
++commonPrefix a@(T.Text _ _ lena) b@(T.Text _ _ lenb) = go 0 0 0
+   where
+     go !na !nb !r =
+       let !(TU.Iter cha da) = TU.iter a na
+@@ -358,8 +358,6 @@ commonPrefix a b = go 0 0 0
                | nb == lenb -> r
                | cha == chb -> go (na + da) (nb + db) (r + 1)
                | otherwise -> r
-+#if MIN_VERSION_text(2,0)
-+    lena = TU.lengthWord8 a
-+    lenb = TU.lengthWord8 b
-+#else
-     lena = TU.lengthWord16 a
-     lenb = TU.lengthWord16 b
-+#endif
+-    lena = TU.lengthWord16 a
+-    lenb = TU.lengthWord16 b
  {-# INLINE commonPrefix #-}
  
  ----------------------------------------------------------------------------
+diff --git a/text-metrics.cabal b/text-metrics.cabal
+index d3b7283..51ee12f 100644
+--- a/text-metrics.cabal
++++ b/text-metrics.cabal
+@@ -31,7 +31,7 @@ library
+     build-depends:
+         base >=4.13 && <5.0,
+         containers >=0.5 && <0.7,
+-        text >=0.2 && <1.3,
++        text >=0.2 && <1.3 || >=2.0 && <2.1,
+         vector >=0.11 && <0.13
+ 
+     if flag(dev)
+@@ -49,7 +49,7 @@ test-suite tests
+         QuickCheck >=2.8 && <3.0,
+         base >=4.13 && <5.0,
+         hspec >=2.0 && <3.0,
+-        text >=0.2 && <1.3,
++        text >=0.2 && <1.3 || >=2.0 && <2.1,
+         text-metrics
+ 
+     if flag(dev)
+@@ -72,7 +72,7 @@ benchmark bench-speed
+         base >=4.13 && <5.0,
+         criterion >=0.6.2.1 && <1.6,
+         deepseq >=1.3 && <1.5,
+-        text >=0.2 && <1.3,
++        text >=0.2 && <1.3 || >=2.0 && <2.1,
+         text-metrics
+ 
+     if flag(dev)
+@@ -89,7 +89,7 @@ benchmark bench-memory
+     build-depends:
+         base >=4.13 && <5.0,
+         deepseq >=1.3 && <1.5,
+-        text >=0.2 && <1.3,
++        text >=0.2 && <1.3 || >=2.0 && <2.1,
+         text-metrics,
+         weigh >=0.0.4
+ 
diff --git a/patches/unicode-transforms-0.3.8.patch b/patches/unicode-transforms-0.3.8.patch
new file mode 100644
index 0000000000000000000000000000000000000000..514b54e3062cca6e1fbbbd349b7d9d0355e0148b
--- /dev/null
+++ b/patches/unicode-transforms-0.3.8.patch
@@ -0,0 +1,109 @@
+diff --git a/Data/Unicode/Internal/NormalizeStream.hs b/Data/Unicode/Internal/NormalizeStream.hs
+index b5265d0..e5fb2c3 100644
+--- a/Data/Unicode/Internal/NormalizeStream.hs
++++ b/Data/Unicode/Internal/NormalizeStream.hs
+@@ -1,5 +1,6 @@
+ {-# OPTIONS_GHC -funbox-strict-fields #-}
+ {-# LANGUAGE BangPatterns #-}
++{-# LANGUAGE CPP #-}
+ {-# LANGUAGE LambdaCase #-}
+ {-# LANGUAGE TupleSections #-}
+ -- |
+@@ -22,7 +23,6 @@ module Data.Unicode.Internal.NormalizeStream
+     )
+     where
+ 
+-import Data.Bits (shiftR)
+ import Data.Char (chr, ord)
+ import GHC.ST (ST(..))
+ import GHC.Types (SPEC(..))
+@@ -30,13 +30,21 @@ import GHC.Types (SPEC(..))
+ import qualified Data.Text.Array as A
+ import qualified Unicode.Char as UC
+ 
++#if MIN_VERSION_text(2,0,0)
++import Data.Text.Internal.Fusion (stream)
++#else
++import Data.Bits (shiftR)
++import Data.Text.Internal.Unsafe.Char (unsafeChr)
++import Data.Text.Internal.Fusion.Size (betweenSize)
++import Data.Text.Internal.Encoding.Utf16 (chr2)
++#endif
++
+ -- Internal modules
+ import Data.Text.Internal (Text(..))
+-import Data.Text.Internal.Fusion.Size (betweenSize, upperBound)
++import Data.Text.Internal.Fusion.Size (upperBound)
+ import Data.Text.Internal.Fusion.Types (Step(..), Stream(..))
+ import Data.Text.Internal.Private (runText)
+-import Data.Text.Internal.Unsafe.Char (unsafeChr, unsafeWrite)
+-import Data.Text.Internal.Encoding.Utf16 (chr2)
++import Data.Text.Internal.Unsafe.Char (unsafeWrite)
+ 
+ -------------------------------------------------------------------------------
+ -- Reorder buffer to hold characters till the next starter boundary
+@@ -142,6 +150,7 @@ decomposeChar mode marr index reBuf ch
+             n <- unsafeWrite arr j c
+             return (j + n, Empty)
+ 
++#if !MIN_VERSION_text(2,0,0)
+ -- | /O(n)/ Convert a 'Text' into a 'Stream Char'.
+ stream :: Text -> Stream Char
+ stream (Text arr off len) = Stream next off (betweenSize (len `shiftR` 1) len)
+@@ -158,6 +167,7 @@ stream (Text arr off len) = Stream next off (betweenSize (len `shiftR` 1) len)
+             n  = A.unsafeIndex arr i
+             n2 = A.unsafeIndex arr (i + 1)
+ {-# INLINE [0] stream #-}
++#endif
+ 
+ -- | /O(n)/ Convert a 'Stream Char' into a decompose-normalized 'Text'.
+ unstream :: UC.DecomposeMode -> Stream Char -> Text
+diff --git a/unicode-transforms.cabal b/unicode-transforms.cabal
+index a8826b8..877a8cf 100644
+--- a/unicode-transforms.cabal
++++ b/unicode-transforms.cabal
+@@ -89,7 +89,7 @@ library
+ 
+     -- We depend on a lot of internal modules in text. We keep the upper bound
+     -- inclusive of the latest stable version.
+-    , text >= 1.1.1 && <= 1.2.4.1
++    , text >=1.1.1 && <=1.2.5.0 || >=2.0 && <2.1
+   if flag(dev)
+     ghc-options: -O0
+   else
+@@ -110,7 +110,7 @@ test-suite extras
+       QuickCheck >=2.1 && <2.15
+     , base >=4.7 && <5
+     , deepseq >=1.1 && <1.5
+-    , text >=1.1.1 && <1.3
++    , text
+     , unicode-transforms
+   if flag(dev)
+     ghc-options: -O0
+@@ -134,7 +134,7 @@ test-suite quickcheck
+     , base >=4.7 && <5
+     , deepseq >=1.1 && <1.5
+     , hspec >= 2.0 && < 3
+-    , text >=1.1.1 && <1.3
++    , text
+     , unicode-transforms
+   if flag(dev)
+     ghc-options: -O0
+@@ -158,7 +158,7 @@ test-suite ucd
+       base >=4.7 && <5
+     , getopt-generics >=0.11 && <0.14
+     , split >=0.1 && <0.3
+-    , text >=1.1.1 && <1.3
++    , text
+     , unicode-transforms
+   if flag(dev)
+     ghc-options: -O0
+@@ -180,7 +180,7 @@ benchmark bench
+     , filepath >=1.0 && <2
+     , path >=0.0.0 && <0.9
+     , path-io >=0.1.0 && <1.7
+-    , text >=1.1.1 && <1.3
++    , text
+     , unicode-transforms
+   if flag(use-gauge)
+     build-depends: gauge >=0.2.0 && <0.3