diff --git a/compiler/GHC/Builtin/Names.hs b/compiler/GHC/Builtin/Names.hs
index 70a48dd350175fe20b4b5dee4df4cbf72820b82d..d6eacd9562f106a3c7eb68c7dec1a3a0d1eb42b4 100644
--- a/compiler/GHC/Builtin/Names.hs
+++ b/compiler/GHC/Builtin/Names.hs
@@ -111,6 +111,10 @@ by the user. For those things that *can* appear in source programs,
 
      See also Note [Built-in syntax and the OrigNameCache]
 
+Note that one-tuples are an exception to the rule, as they do get assigned
+known keys. See
+Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)
+in GHC.Builtin.Types.
 
 Note [The integer library]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Builtin/Types.hs b/compiler/GHC/Builtin/Types.hs
index c1241fa7dd74225482da34cf61c5a95c0df955fa..51d3ff608b439506d24f83acb7504e1c92fb87bc 100644
--- a/compiler/GHC/Builtin/Types.hs
+++ b/compiler/GHC/Builtin/Types.hs
@@ -71,7 +71,7 @@ module GHC.Builtin.Types (
 
         -- * Tuples
         mkTupleTy, mkTupleTy1, mkBoxedTupleTy, mkTupleStr,
-        tupleTyCon, tupleDataCon, tupleTyConName,
+        tupleTyCon, tupleDataCon, tupleTyConName, tupleDataConName,
         promotedTupleDataCon,
         unitTyCon, unitDataCon, unitDataConId, unitTy, unitTyConKey,
         pairTyCon,
@@ -725,9 +725,13 @@ for one-tuples.  So in ghc-prim:GHC.Tuple we see the declarations:
   data Unit a = Unit a
   data (a,b)  = (a,b)
 
-There is no way to write a boxed one-tuple in Haskell, but it can be
-created in Template Haskell or in, e.g., `deriving` code. There is
-nothing special about one-tuples in Core; in particular, they have no
+There is no way to write a boxed one-tuple in Haskell using tuple syntax.
+They can, however, be written using other methods:
+
+1. They can be written directly by importing them from GHC.Tuple.
+2. They can be generated by way of Template Haskell or in `deriving` code.
+
+There is nothing special about one-tuples in Core; in particular, they have no
 custom pretty-printing, just using `Unit`.
 
 Note that there is *not* a unary constraint tuple, unlike for other forms of
@@ -737,6 +741,29 @@ details.
 See also Note [Flattening one-tuples] in GHC.Core.Make and
 Note [Don't flatten tuples from HsSyn] in GHC.Core.Make.
 
+-----
+-- Wrinkle: Make boxed one-tuple names have known keys
+-----
+
+We make boxed one-tuple names have known keys so that `data Unit a = Unit a`,
+defined in GHC.Tuple, will be used when one-tuples are spliced in through
+Template Haskell. This program (from #18097) crucially relies on this:
+
+  case $( tupE [ [| "ok" |] ] ) of Unit x -> putStrLn x
+
+Unless Unit has a known key, the type of `$( tupE [ [| "ok" |] ] )` (an
+ExplicitTuple of length 1) will not match the type of Unit (an ordinary
+data constructor used in a pattern). Making Unit known-key allows GHC to make
+this connection.
+
+Unlike Unit, every other tuple is /not/ known-key
+(see Note [Infinite families of known-key names] in GHC.Builtin.Names). The
+main reason for this exception is that other tuples are written with special
+syntax, and as a result, they are renamed using a special `isBuiltInOcc_maybe`
+function (see Note [Built-in syntax and the OrigNameCache] in GHC.Types.Name.Cache).
+In contrast, Unit is just an ordinary data type with no special syntax, so it
+doesn't really make sense to handle it in `isBuiltInOcc_maybe`. Making Unit
+known-key is the next-best way to teach the internals of the compiler about it.
 -}
 
 -- | Built-in syntax isn't "in scope" so these OccNames map to wired-in Names
@@ -760,6 +787,8 @@ isBuiltInOcc_maybe occ =
       "->"   -> Just funTyConName
 
       -- boxed tuple data/tycon
+      -- We deliberately exclude Unit (the boxed 1-tuple).
+      -- See Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)
       "()"    -> Just $ tup_name Boxed 0
       _ | Just rest <- "(" `BS.stripPrefix` name
         , (commas, rest') <- BS.span (==',') rest
@@ -889,6 +918,9 @@ tupleDataCon sort i | i > mAX_TUPLE_SIZE = snd (mk_tuple sort i)    -- Build one
 tupleDataCon Boxed   i = snd (boxedTupleArr   ! i)
 tupleDataCon Unboxed i = snd (unboxedTupleArr ! i)
 
+tupleDataConName :: Boxity -> Arity -> Name
+tupleDataConName sort i = dataConName (tupleDataCon sort i)
+
 boxedTupleArr, unboxedTupleArr :: Array Int (TyCon,DataCon)
 boxedTupleArr   = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Boxed   i | i <- [0..mAX_TUPLE_SIZE]]
 unboxedTupleArr = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Unboxed i | i <- [0..mAX_TUPLE_SIZE]]
diff --git a/compiler/GHC/Builtin/Utils.hs b/compiler/GHC/Builtin/Utils.hs
index dc03f051bbe43749963dcd7deba7bffcd64c1237..ab2aeed9613fb7c51983a3309c23784d2aae1094 100644
--- a/compiler/GHC/Builtin/Utils.hs
+++ b/compiler/GHC/Builtin/Utils.hs
@@ -59,6 +59,7 @@ import GHC.Core.Opt.ConstantFold
 import GHC.Types.Avail
 import GHC.Builtin.PrimOps
 import GHC.Core.DataCon
+import GHC.Types.Basic
 import GHC.Types.Id
 import GHC.Types.Name
 import GHC.Types.Name.Env
@@ -124,14 +125,17 @@ knownKeyNames
   = all_names
   where
     all_names =
+      -- We exclude most tuples from this list—see
+      -- Note [Infinite families of known-key names] in GHC.Builtin.Names.
+      -- We make an exception for Unit (i.e., the boxed 1-tuple), since it does
+      -- not use special syntax like other tuples.
+      -- See Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)
+      -- in GHC.Builtin.Types.
+      tupleTyConName BoxedTuple 1 : tupleDataConName Boxed 1 :
       concat [ wired_tycon_kk_names funTyCon
              , concatMap wired_tycon_kk_names primTyCons
-
              , concatMap wired_tycon_kk_names wiredInTyCons
-               -- Does not include tuples
-
              , concatMap wired_tycon_kk_names typeNatTyCons
-
              , map idName wiredInIds
              , map (idName . primOpId) allThePrimOps
              , map (idName . primOpWrapperId) allThePrimOps
diff --git a/testsuite/tests/th/T18097.hs b/testsuite/tests/th/T18097.hs
new file mode 100644
index 0000000000000000000000000000000000000000..2263dfe0186f1ecca2052f07944324249ae1e529
--- /dev/null
+++ b/testsuite/tests/th/T18097.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T18097 where
+
+import Language.Haskell.TH
+import GHC.Tuple
+
+f = case $( tupE [ [| "ok" |] ] ) of Unit x -> putStrLn x
+g = case Unit "ok" of $( tupP [ [p| x |] ] ) -> putStrLn x
+
+h :: $( tupleT 1 ) String
+h = Unit "ok"
+
+i :: Unit String
+i = $( tupE [ [| "ok" |] ] )
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 458b45d67f018077153bc10449dfa5845fbe83da..8e747cbefab6368ce94aed45d3c7d5427f109d71 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -502,6 +502,7 @@ test('T17511', normal, compile, [''])
 test('T17608', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T17688a', normal, compile, [''])
 test('T17688b', normal, compile, [''])
+test('T18097', normal, compile, [''])
 test('TH_PprStar', normal, compile, ['-v0 -dsuppress-uniques'])
 test('TH_StringLift', normal, compile, [''])
 test('TH_BytesShowEqOrd', normal, compile_and_run, [''])
diff --git a/testsuite/tests/typecheck/should_compile/holes.stderr b/testsuite/tests/typecheck/should_compile/holes.stderr
index 892f875f3c9007fe0c7546a328c67f6b7fce50fd..ec5e1bf2290c18486cc4a0ceebd3e28949966c88 100644
--- a/testsuite/tests/typecheck/should_compile/holes.stderr
+++ b/testsuite/tests/typecheck/should_compile/holes.stderr
@@ -90,6 +90,7 @@ holes.hs:11:15: warning: [-Wtyped-holes (in -Wdefault)]
         Nothing :: forall a. Maybe a
         Just :: forall a. a -> Maybe a
         [] :: forall a. [a]
+        Unit :: forall a. a -> Unit a
         asTypeOf :: forall a. a -> a -> a
         id :: forall a. a -> a
         until :: forall a. (a -> Bool) -> (a -> a) -> a -> a
diff --git a/testsuite/tests/typecheck/should_compile/holes3.stderr b/testsuite/tests/typecheck/should_compile/holes3.stderr
index ea1f5a6c2c9a09baf9c55689b9f6d35e2ec8a465..fa9590663b00469794a41ac70997abd748b8da00 100644
--- a/testsuite/tests/typecheck/should_compile/holes3.stderr
+++ b/testsuite/tests/typecheck/should_compile/holes3.stderr
@@ -93,6 +93,7 @@ holes3.hs:11:15: error:
         Nothing :: forall a. Maybe a
         Just :: forall a. a -> Maybe a
         [] :: forall a. [a]
+        Unit :: forall a. a -> Unit a
         asTypeOf :: forall a. a -> a -> a
         id :: forall a. a -> a
         until :: forall a. (a -> Bool) -> (a -> a) -> a -> a