diff --git a/tests/Tests/Regressions.hs b/tests/Tests/Regressions.hs
index 8cd8efeeea7b2c3cdfa43b7c50833e074d1873cb..4d236d19d60ee5916ae61a90ddbd03ba969d5017 100644
--- a/tests/Tests/Regressions.hs
+++ b/tests/Tests/Regressions.hs
@@ -1,6 +1,9 @@
 -- | Regression tests for specific bugs.
 --
-{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
 module Tests.Regressions
     (
       tests
@@ -8,6 +11,7 @@ module Tests.Regressions
 
 import Control.Exception (SomeException, handle)
 import Data.Char (isLetter)
+import GHC.Exts (Int(..), sizeofByteArray#)
 import System.IO
 import Test.Tasty.HUnit (assertBool, assertEqual, assertFailure)
 import qualified Data.ByteString as B
@@ -105,8 +109,8 @@ t227 =
 t301 :: IO ()
 t301 = do
     assertEqual "The length of the array remains the same despite slicing"
-                (TA.length originalArr)
-                (TA.length newArr)
+                (I# (sizeofByteArray# (TA.aBA originalArr)))
+                (I# (sizeofByteArray# (TA.aBA newArr)))
 
     assertEqual "The new array still contains the original value"
                 (T.Text newArr originalOff originalLen)
diff --git a/tests/cbits b/tests/cbits
deleted file mode 120000
index 904f446c7060ea30f3b7114d1ecd0cfa814a6bef..0000000000000000000000000000000000000000
--- a/tests/cbits
+++ /dev/null
@@ -1 +0,0 @@
-../cbits
\ No newline at end of file
diff --git a/tests/include b/tests/include
deleted file mode 120000
index f5030fe889982444316aa710b12026d377e187e0..0000000000000000000000000000000000000000
--- a/tests/include
+++ /dev/null
@@ -1 +0,0 @@
-../include
\ No newline at end of file
diff --git a/tests/src b/tests/src
deleted file mode 120000
index 5cd551cf2693e4b4f65d7954ec621454c2b20326..0000000000000000000000000000000000000000
--- a/tests/src
+++ /dev/null
@@ -1 +0,0 @@
-../src
\ No newline at end of file
diff --git a/tests/text-tests.cabal b/tests/text-tests.cabal
index 83d65719a0938ad6fab76ef677e5728fbd4d227d..3ce6fc20686635e86f6e8b3edbff75c0a66c9d8d 100644
--- a/tests/text-tests.cabal
+++ b/tests/text-tests.cabal
@@ -60,36 +60,12 @@ tested-with:    GHC==9.0.1,
                 GHC==8.10.4, GHC==8.8.4, GHC==8.6.5, GHC==8.4.4,
                 GHC==8.2.2, GHC==8.0.2, GHC==7.10.3, GHC==7.8.4,
                 GHC==7.6.3, GHC==7.4.2, GHC==7.2.2, GHC==7.0.4
-extra-source-files:
-    include/*.h
-
-flag bytestring-builder
-  description:
-    Depend on the [bytestring-builder](https://hackage.haskell.org/package/bytestring-builder)
-    package for backwards compatibility.
-  default: False
-  manual: False
-
-flag integer-simple
-  description:
-    Use the [simple integer library](http://hackage.haskell.org/package/integer-simple)
-    instead of [integer-gmp](http://hackage.haskell.org/package/integer-gmp)
-  default: False
-  manual: False
 
 test-suite tests
   type:           exitcode-stdio-1.0
-  c-sources:      cbits/cbits.c
-  include-dirs:   include
-  hs-source-dirs: src
-
   ghc-options:
     -Wall -threaded -rtsopts
 
-  cpp-options:
-    -DASSERTS -DTEST_SUITE
-
-  -- modules specific to test-suite
   hs-source-dirs: .
   main-is:        Tests.hs
   other-modules:
@@ -100,95 +76,18 @@ test-suite tests
     Tests.SlowFunctions
     Tests.Utils
 
-  -- This can be merged back to `text` package, when cabal
-  -- will support per-component solving. Otherwise we have loops.
-  --
-  -- Same as in `library` stanza; this is needed by cabal for accurate
-  -- file-monitoring as well as to avoid `-Wmissing-home-modules`
-  -- warnings We can't use an inter-package library dependency because
-  -- of different `ghc-options`/`cpp-options` (as a side-benefitt,
-  -- this enables per-component build parallelism in `cabal
-  -- new-build`!); We could, however, use cabal-version:2.2's `common`
-  -- blocks at some point in the future to reduce the duplication.
-  other-modules:
-    Data.Text
-    Data.Text.Array
-    Data.Text.Encoding
-    Data.Text.Encoding.Error
-    Data.Text.Foreign
-    Data.Text.IO
-    Data.Text.Internal
-    Data.Text.Internal.Builder
-    Data.Text.Internal.Builder.Functions
-    Data.Text.Internal.Builder.Int.Digits
-    Data.Text.Internal.Builder.RealFloat.Functions
-    Data.Text.Internal.ByteStringCompat
-    Data.Text.Internal.PrimCompat
-    Data.Text.Internal.Encoding.Fusion
-    Data.Text.Internal.Encoding.Fusion.Common
-    Data.Text.Internal.Encoding.Utf16
-    Data.Text.Internal.Encoding.Utf32
-    Data.Text.Internal.Encoding.Utf8
-    Data.Text.Internal.Functions
-    Data.Text.Internal.Fusion
-    Data.Text.Internal.Fusion.CaseMapping
-    Data.Text.Internal.Fusion.Common
-    Data.Text.Internal.Fusion.Size
-    Data.Text.Internal.Fusion.Types
-    Data.Text.Internal.IO
-    Data.Text.Internal.Lazy
-    Data.Text.Internal.Lazy.Encoding.Fusion
-    Data.Text.Internal.Lazy.Fusion
-    Data.Text.Internal.Lazy.Search
-    Data.Text.Internal.Private
-    Data.Text.Internal.Read
-    Data.Text.Internal.Search
-    Data.Text.Internal.Unsafe
-    Data.Text.Internal.Unsafe.Char
-    Data.Text.Internal.Unsafe.Shift
-    Data.Text.Lazy
-    Data.Text.Lazy.Builder
-    Data.Text.Lazy.Builder.Int
-    Data.Text.Lazy.Builder.RealFloat
-    Data.Text.Lazy.Encoding
-    Data.Text.Lazy.IO
-    Data.Text.Lazy.Internal
-    Data.Text.Lazy.Read
-    Data.Text.Read
-    Data.Text.Unsafe
-    Data.Text.Show
-
   build-depends:
     QuickCheck >= 2.14.1 && < 2.15,
-    array,
     base <5,
-    binary,
+    bytestring,
     deepseq,
     directory,
-    ghc-prim,
     quickcheck-unicode >= 1.0.1.0,
     random,
-    template-haskell,
     tasty,
     tasty-hunit,
-    tasty-quickcheck
-
-  if flag(bytestring-builder)
-    build-depends: bytestring         >= 0.9    && < 0.10.4,
-                   bytestring-builder >= 0.10.4
-  else
-    build-depends: bytestring         >= 0.10.4
-
-  if impl(ghc >= 8.11)
-    build-depends: ghc-bignum
-
-  if impl(ghc < 8.11)
-    if flag(integer-simple)
-      cpp-options: -DINTEGER_SIMPLE
-      build-depends: integer-simple >= 0.1 && < 0.5
-    else
-      cpp-options: -DINTEGER_GMP
-      build-depends: integer-gmp >= 0.2
+    tasty-quickcheck,
+    text
 
   default-language: Haskell2010
   default-extensions: NondecreasingIndentation
@@ -196,7 +95,3 @@ test-suite tests
 source-repository head
   type:     git
   location: https://github.com/haskell/text
-
-source-repository head
-  type:     mercurial
-  location: https://bitbucket.org/bos/text