diff --git a/gcc/config/i386/i386-d.cc b/gcc/config/i386/i386-d.cc
index fbe26e012744203558e35004300426f1143fccab..f61b5a50b698038930af9cf5c8a0d871aa25235c 100644
--- a/gcc/config/i386/i386-d.cc
+++ b/gcc/config/i386/i386-d.cc
@@ -44,6 +44,9 @@ ix86_d_target_versions (void)
     d_add_builtin_version ("D_HardFloat");
   else
     d_add_builtin_version ("D_SoftFloat");
+
+  if (flag_cf_protection != CF_NONE)
+    d_add_builtin_version ("GNU_CET");
 }
 
 /* Handle a call to `__traits(getTargetInfo, "floatAbi")'.  */
@@ -79,6 +82,14 @@ ix86_d_handle_target_object_format (void)
   return build_string_literal (strlen (objfmt) + 1, objfmt);
 }
 
+/* Handle a call to `__traits(getTargetInfo, "CET")'.  */
+
+static tree
+ix86_d_handle_target_cf_protection (void)
+{
+  return build_int_cst_type (uint32_type_node, flag_cf_protection & ~CF_SET);
+}
+
 /* Implement TARGET_D_REGISTER_CPU_TARGET_INFO.  */
 
 void
@@ -87,6 +98,7 @@ ix86_d_register_target_info (void)
   const struct d_target_info_spec handlers[] = {
     { "floatAbi", ix86_d_handle_target_float_abi },
     { "objectFormat", ix86_d_handle_target_object_format },
+    { "CET", ix86_d_handle_target_cf_protection },
     { NULL, NULL },
   };
 
diff --git a/gcc/d/implement-d.texi b/gcc/d/implement-d.texi
index a5534792e66fe8c68185669640de62f976e8cccd..a39fd58347637f3298dcf7c62095ee187b517736 100644
--- a/gcc/d/implement-d.texi
+++ b/gcc/d/implement-d.texi
@@ -1892,6 +1892,10 @@ This version is defined by the GNU D compiler.  If all you need to know is
 whether or not your D program is being compiled by GDC, or a non-GDC compiler,
 you can simply test @code{version(GNU)}.
 
+@item GNU_CET
+This version is defined when @option{-fcf-protection} is used.  The protection
+level is also set in @code{__traits(getTargetInfo, "CET")} (@pxref{Traits}).
+
 @item GNU_DWARF2_Exceptions
 @itemx GNU_SEH_Exceptions
 @itemx GNU_SjLj_Exceptions
@@ -2121,6 +2125,10 @@ recognize.  These are documented by the D language specification hosted at
 The following keys are recognized by GNU D.
 
 @table @code
+@item CET
+When @option{-fcf-protection} is used, the first bit is set to 1 for the value
+@code{branch} and the second bit is set to 1 for the value @code{return}.
+
 @item cppRuntimeLibrary
 The C++ runtime library affinity for this toolchain.
 
diff --git a/gcc/testsuite/gdc.dg/target/i386/i386.exp b/gcc/testsuite/gdc.dg/target/i386/i386.exp
new file mode 100644
index 0000000000000000000000000000000000000000..ff092d94ec6439db5f280d4169657d6f98ff5b6e
--- /dev/null
+++ b/gcc/testsuite/gdc.dg/target/i386/i386.exp
@@ -0,0 +1,48 @@
+#   Copyright (C) 2025 Free Software Foundation, Inc.
+
+# This program is free software; you can redistribute it and/or modify
+# it under the terms of the GNU General Public License as published by
+# the Free Software Foundation; either version 3 of the License, or
+# (at your option) any later version.
+#
+# This program is distributed in the hope that it will be useful,
+# but WITHOUT ANY WARRANTY; without even the implied warranty of
+# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+# GNU General Public License for more details.
+#
+# You should have received a copy of the GNU General Public License
+# along with GCC; see the file COPYING3.  If not see
+# <http://www.gnu.org/licenses/>.
+
+# GCC testsuite that uses the `dg.exp' driver.
+
+# Exit immediately if this isn't a x86 target.
+if { ![istarget i?86*-*-*] && ![istarget x86_64-*-*] } then {
+  return
+}
+
+# Load support procs.
+load_lib gdc-dg.exp
+load_lib clearcap.exp
+
+# If a testcase doesn't have special options, use these.
+global DEFAULT_DFLAGS
+if ![info exists DEFAULT_DFLAGS] then {
+    set DEFAULT_DFLAGS ""
+}
+
+# Initialize `dg'.
+dg-init
+clearcap-init
+
+# Main loop.
+gdc-dg-runtest [lsort \
+       [prune [glob -nocomplain $srcdir/$subdir/*.d ] \
+	      $srcdir/$subdir/gcov*.d ] ] "" $DEFAULT_DFLAGS
+
+# All done.
+dg-finish
+
+# All done.
+clearcap-finish
+dg-finish
diff --git a/gcc/testsuite/gdc.dg/target/i386/targetinfo_CET.d b/gcc/testsuite/gdc.dg/target/i386/targetinfo_CET.d
new file mode 100644
index 0000000000000000000000000000000000000000..ff178a36a65b385afe81d95628d09c6d146a4d26
--- /dev/null
+++ b/gcc/testsuite/gdc.dg/target/i386/targetinfo_CET.d
@@ -0,0 +1,3 @@
+// { dg-do compile }
+// { dg-options "-fcf-protection" }
+static assert(__traits(getTargetInfo, "CET") != 0);
diff --git a/libphobos/Makefile.in b/libphobos/Makefile.in
index ea6d790f61e2709a2582709fa7aa09b28a5abf75..162e83bd57e062cbeb59c20c3d3c6acd09dfb3f7 100644
--- a/libphobos/Makefile.in
+++ b/libphobos/Makefile.in
@@ -207,7 +207,6 @@ CC = @CC@
 CCAS = @CCAS@
 CCASFLAGS = @CCASFLAGS@
 CC_FOR_BUILD = @CC_FOR_BUILD@
-CET_DFLAGS = @CET_DFLAGS@
 CET_FLAGS = @CET_FLAGS@
 CFLAGS = @CFLAGS@
 CFLAGS_FOR_BUILD = @CFLAGS_FOR_BUILD@
diff --git a/libphobos/configure b/libphobos/configure
index b9fecbc0175e98a69c16a897494569e336785e0b..df48a6b4d959cfc0a78af80f629483d8027f2bb9 100755
--- a/libphobos/configure
+++ b/libphobos/configure
@@ -731,7 +731,6 @@ CFLAGS_FOR_BUILD
 CC_FOR_BUILD
 AR
 DCFG_ENABLE_CET
-CET_DFLAGS
 CET_FLAGS
 RANLIB
 MAINT
@@ -5667,18 +5666,15 @@ fi
 # To ensure that runtime code for CET is compiled in, add in D version flags.
 if test x$enable_cet = xyes; then :
 
-  CET_DFLAGS="$CET_FLAGS -fversion=CET"
   DCFG_ENABLE_CET=true
 
 else
 
-  CET_DFLAGS=
   DCFG_ENABLE_CET=false
 
 fi
 
 
-
 # This should be inherited in the recursive make, but ensure it is defined.
 test "$AR" || AR=ar
 
@@ -11867,7 +11863,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 11870 "configure"
+#line 11866 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -11973,7 +11969,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 11976 "configure"
+#line 11972 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
diff --git a/libphobos/configure.ac b/libphobos/configure.ac
index 92449feb7e95880d144f5748894b70f382e43a34..3b2ec2c91db8ef616b0c5bdc64c4b74c8c22d213 100644
--- a/libphobos/configure.ac
+++ b/libphobos/configure.ac
@@ -70,13 +70,10 @@ GCC_CET_FLAGS(CET_FLAGS)
 AC_SUBST(CET_FLAGS)
 # To ensure that runtime code for CET is compiled in, add in D version flags.
 AS_IF([test x$enable_cet = xyes], [
-  CET_DFLAGS="$CET_FLAGS -fversion=CET"
   DCFG_ENABLE_CET=true
 ], [
-  CET_DFLAGS=
   DCFG_ENABLE_CET=false
 ])
-AC_SUBST(CET_DFLAGS)
 AC_SUBST(DCFG_ENABLE_CET)
 
 # This should be inherited in the recursive make, but ensure it is defined.
diff --git a/libphobos/libdruntime/Makefile.am b/libphobos/libdruntime/Makefile.am
index fd117eca202835b9ed6b484571cab80e16cb314e..8df0e1c43b91a145fc7eafb9beec8054e43c6430 100644
--- a/libphobos/libdruntime/Makefile.am
+++ b/libphobos/libdruntime/Makefile.am
@@ -25,7 +25,7 @@ D_EXTRA_DFLAGS=-fpreview=dip1000 -fpreview=fieldwise -fpreview=dtorfields \
 # D flags for compilation
 AM_DFLAGS= \
 	$(phobos_lt_pic_flag) $(phobos_compiler_shared_flag) \
-	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_DFLAGS)
+	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_FLAGS)
 
 # Flags for other kinds of sources
 AM_CFLAGS=$(CET_FLAGS)
diff --git a/libphobos/libdruntime/Makefile.in b/libphobos/libdruntime/Makefile.in
index 2d87c8162af453432d27fc3f12831da542ecd032..999064e5221c74e9660307fb628e387415eaf17f 100644
--- a/libphobos/libdruntime/Makefile.in
+++ b/libphobos/libdruntime/Makefile.in
@@ -625,7 +625,6 @@ CC = @CC@
 CCAS = @CCAS@
 CCASFLAGS = @CCASFLAGS@
 CC_FOR_BUILD = @CC_FOR_BUILD@
-CET_DFLAGS = @CET_DFLAGS@
 CET_FLAGS = @CET_FLAGS@
 CFLAGS = @CFLAGS@
 CFLAGS_FOR_BUILD = @CFLAGS_FOR_BUILD@
@@ -784,7 +783,7 @@ D_EXTRA_DFLAGS = -fpreview=dip1000 -fpreview=fieldwise -fpreview=dtorfields \
 # D flags for compilation
 AM_DFLAGS = \
 	$(phobos_lt_pic_flag) $(phobos_compiler_shared_flag) \
-	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_DFLAGS)
+	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_FLAGS)
 
 
 # Flags for other kinds of sources
diff --git a/libphobos/libdruntime/core/thread/fiber/package.d b/libphobos/libdruntime/core/thread/fiber/package.d
index d10a25d683c751d3673194454dc9fea19758660a..591b1dc146cab2b6fb872bdee549c5120b145b19 100644
--- a/libphobos/libdruntime/core/thread/fiber/package.d
+++ b/libphobos/libdruntime/core/thread/fiber/package.d
@@ -73,7 +73,7 @@ package
     {
         version = AlignFiberStackTo16Byte;
 
-        version (CET)
+        version (GNU_CET)
         {
             // fiber_switchContext does not support shadow stack from
             // Intel CET.  So use ucontext implementation.
@@ -94,7 +94,7 @@ package
     {
         version = AlignFiberStackTo16Byte;
 
-        version (CET)
+        version (GNU_CET)
         {
             // fiber_switchContext does not support shadow stack from
             // Intel CET.  So use ucontext implementation.
diff --git a/libphobos/src/Makefile.am b/libphobos/src/Makefile.am
index a8a5ed3a357ddef17f9642af4f244051fbcd0e6e..763ca3beb59f5c25f176fdb92ae9ed5a63d1c906 100644
--- a/libphobos/src/Makefile.am
+++ b/libphobos/src/Makefile.am
@@ -26,7 +26,7 @@ D_EXTRA_DFLAGS=-fpreview=dip1000 -fpreview=dtorfields -fpreview=fieldwise \
 # D flags for compilation
 AM_DFLAGS= \
 	$(phobos_lt_pic_flag) $(phobos_compiler_shared_flag) \
-	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_DFLAGS)
+	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_FLAGS)
 
 # Flags for other kinds of sources
 AM_CFLAGS=$(CET_FLAGS)
diff --git a/libphobos/src/Makefile.in b/libphobos/src/Makefile.in
index 52f2d1a2e3b8f49c12cc66a6f3ea71056845de6a..dcf6425f86f79dde1a6be3314c80e0bdc0f19d05 100644
--- a/libphobos/src/Makefile.in
+++ b/libphobos/src/Makefile.in
@@ -352,7 +352,6 @@ CC = @CC@
 CCAS = @CCAS@
 CCASFLAGS = @CCASFLAGS@
 CC_FOR_BUILD = @CC_FOR_BUILD@
-CET_DFLAGS = @CET_DFLAGS@
 CET_FLAGS = @CET_FLAGS@
 CFLAGS = @CFLAGS@
 CFLAGS_FOR_BUILD = @CFLAGS_FOR_BUILD@
@@ -512,7 +511,7 @@ D_EXTRA_DFLAGS = -fpreview=dip1000 -fpreview=dtorfields -fpreview=fieldwise \
 # D flags for compilation
 AM_DFLAGS = \
 	$(phobos_lt_pic_flag) $(phobos_compiler_shared_flag) \
-	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_DFLAGS)
+	$(WARN_DFLAGS) $(CHECKING_DFLAGS) $(SECTION_FLAGS) $(CET_FLAGS)
 
 
 # Flags for other kinds of sources
diff --git a/libphobos/testsuite/Makefile.in b/libphobos/testsuite/Makefile.in
index 3d3a798f35c10b0bafef68e2a9a25686120ebcd3..b410f17254a68eae1314c3409e8b679652027fab 100644
--- a/libphobos/testsuite/Makefile.in
+++ b/libphobos/testsuite/Makefile.in
@@ -151,7 +151,6 @@ CC = @CC@
 CCAS = @CCAS@
 CCASFLAGS = @CCASFLAGS@
 CC_FOR_BUILD = @CC_FOR_BUILD@
-CET_DFLAGS = @CET_DFLAGS@
 CET_FLAGS = @CET_FLAGS@
 CFLAGS = @CFLAGS@
 CFLAGS_FOR_BUILD = @CFLAGS_FOR_BUILD@
diff --git a/libphobos/testsuite/testsuite_flags.in b/libphobos/testsuite/testsuite_flags.in
index 84af947e8ab0976c79837d9cda144f9c79c0383d..9933667b4eae02985718710cf0cf4da94e221ce6 100755
--- a/libphobos/testsuite/testsuite_flags.in
+++ b/libphobos/testsuite/testsuite_flags.in
@@ -28,7 +28,7 @@ case ${query} in
       ;;
     --gdcflags)
       GDCFLAGS_default="-fmessage-length=0 -fno-show-column"
-      GDCFLAGS_config="@WARN_DFLAGS@ @GDCFLAGS@ @CET_DFLAGS@
+      GDCFLAGS_config="@WARN_DFLAGS@ @GDCFLAGS@ @CET_FLAGS@
 		       @phobos_compiler_shared_flag@
 		       -fall-instantiations -fpreview=dip1000
 		       -fno-release -funittest"