diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index e7b904736debbae14ee0b3cd0e7c60b3ed2b503d..829a789d36ebfc0619436215330d25b06b314365 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -1320,6 +1320,11 @@ hsExprNeedsParens p = go
     go (NegApp{})                     = p > topPrec
     go (SectionL{})                   = True
     go (SectionR{})                   = True
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go (ExplicitTuple _ [L _ Present{}] Boxed)
+                                      = p >= appPrec
     go (ExplicitTuple{})              = False
     go (ExplicitSum{})                = False
     go (HsLam{})                      = p > topPrec
diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs
index 62de0ab18298574efc2cc38eda74c1cd5c5dcadc..b1507f0adc4116a0860e4b9e74a2e9e48fac57ab 100644
--- a/compiler/GHC/Hs/Pat.hs
+++ b/compiler/GHC/Hs/Pat.hs
@@ -857,7 +857,12 @@ patNeedsParens p = go
     go (BangPat {})      = False
     go (ParPat {})       = False
     go (AsPat {})        = False
-    go (TuplePat {})     = False
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go (TuplePat _ [_] Boxed)
+                         = p >= appPrec
+    go (TuplePat{})      = False
     go (SumPat {})       = False
     go (ListPat {})      = False
     go (LitPat _ l)      = hsLitNeedsParens p l
diff --git a/compiler/GHC/Hs/Type.hs b/compiler/GHC/Hs/Type.hs
index c6960c9c779675abf8f4de27305e622572788733..343cc1d1ba8740a524dd11ae19c34c79682006e8 100644
--- a/compiler/GHC/Hs/Type.hs
+++ b/compiler/GHC/Hs/Type.hs
@@ -1979,6 +1979,15 @@ hsTypeNeedsParens p = go_hs_ty
     go_hs_ty (HsRecTy{})              = False
     go_hs_ty (HsTyVar{})              = False
     go_hs_ty (HsFunTy{})              = p >= funPrec
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go_hs_ty (HsTupleTy _ con [L _ ty])
+      = case con of
+          HsBoxedTuple               -> p >= appPrec
+          HsBoxedOrConstraintTuple   -> p >= appPrec
+          HsConstraintTuple          -> go_hs_ty ty
+          HsUnboxedTuple             -> False
     go_hs_ty (HsTupleTy{})            = False
     go_hs_ty (HsSumTy{})              = False
     go_hs_ty (HsKindSig{})            = p >= sigPrec
@@ -1986,6 +1995,11 @@ hsTypeNeedsParens p = go_hs_ty
     go_hs_ty (HsIParamTy{})           = p > topPrec
     go_hs_ty (HsSpliceTy{})           = False
     go_hs_ty (HsExplicitListTy{})     = False
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Proxy ('Solo x)`, not `Proxy 'Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go_hs_ty (HsExplicitTupleTy _ [_])
+                                      = p >= appPrec
     go_hs_ty (HsExplicitTupleTy{})    = False
     go_hs_ty (HsTyLit{})              = False
     go_hs_ty (HsWildCardTy{})         = False
diff --git a/testsuite/tests/th/T18612.hs b/testsuite/tests/th/T18612.hs
new file mode 100644
index 0000000000000000000000000000000000000000..ea7c007c519c864e2e53826930a626613fc1bc9c
--- /dev/null
+++ b/testsuite/tests/th/T18612.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -ddump-splices #-}
+module T18612 where
+
+import Data.Functor.Identity
+import Data.Proxy
+import Language.Haskell.TH
+
+f :: $(arrowT `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+              `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0))))
+f $(conP 'Identity [tupP [tupP []]]) = $(conE 'Identity `appE` tupE [tupE []])
+
+type G = $(conT ''Proxy `appT` (promotedTupleT 1 `appT` (tupleT 0)))
diff --git a/testsuite/tests/th/T18612.stderr b/testsuite/tests/th/T18612.stderr
new file mode 100644
index 0000000000000000000000000000000000000000..25286ef671707107767f29d3ce3e5f1818b0c44e
--- /dev/null
+++ b/testsuite/tests/th/T18612.stderr
@@ -0,0 +1,13 @@
+T18612.hs:14:11-68: Splicing type
+    conT ''Proxy `appT` (promotedTupleT 1 `appT` (tupleT 0))
+  ======>
+    Proxy ('Solo ())
+T18612.hs:(10,7)-(11,75): Splicing type
+    arrowT `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+      `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+  ======>
+    Identity (Solo ()) -> Identity (Solo ())
+T18612.hs:12:4-36: Splicing pattern
+    conP 'Identity [tupP [tupP []]] ======> Identity (Solo())
+T18612.hs:12:41-78: Splicing expression
+    conE 'Identity `appE` tupE [tupE []] ======> Identity (Solo ())
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 6d4a5036d787f83ccb22369ec39c6549e9cf51c5..e53b0d872af6c9b3ed81d918f5d3db7272812f99 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -513,3 +513,4 @@ test('T18102b', extra_files(['T18102b_aux.hs']), compile_and_run, [''])
 test('T18121', normal, compile, [''])
 test('T18123', normal, compile, [''])
 test('T18388', normal, compile, [''])
+test('T18612', normal, compile, [''])