diff --git a/libstdc++-v3/acinclude.m4 b/libstdc++-v3/acinclude.m4
index b957c728ba117af6996573ba2efd24eeaeffb311..f73946a491818c94d652d45a682c18f667f0a931 100644
--- a/libstdc++-v3/acinclude.m4
+++ b/libstdc++-v3/acinclude.m4
@@ -5140,6 +5140,33 @@ AC_DEFUN([GLIBCXX_EMERGENCY_EH_ALLOC], [
   AC_SUBST(EH_POOL_FLAGS)
 ])
 
+dnl
+dnl Allow the location of tzdata files to be configured.
+dnl
+dnl --with-libstdcxx-zoneinfo-dir=PATH will set the directory to PATH.
+dnl
+dnl Defines:
+dnl  _GLIBCXX_ZONEINFO_DIR if std::chrono::tzdb should use a non-default
+dnl    directory for the tzdata.zi and leapseconds files.
+dnl
+AC_DEFUN([GLIBCXX_ZONEINFO_DIR], [
+  AC_ARG_WITH([libstdcxx-zoneinfo-dir],
+    AC_HELP_STRING([--with-libstdcxx-zoneinfo-dir],
+		   [the directory to search for tzdata files]),
+    [zoneinfo_dir="${withval}"
+     AC_DEFINE(_GLIBCXX_ZONEINFO_DIR, "${withval}",
+       [Define if a non-default location should be used for tzdata files.])
+    ],
+    [
+    case "$host" in
+      # *-*-aix*) zoneinfo_dir="/usr/share/lib/zoneinfo" ;;
+      *) zoneinfo_dir="/usr/share/zoneinfo" ;;
+    esac
+    ])
+
+  AC_MSG_NOTICE([zoneinfo data directory: ${zoneinfo_dir}])
+])
+
 # Macros from the top-level gcc directory.
 m4_include([../config/gc++filt.m4])
 m4_include([../config/tls.m4])
diff --git a/libstdc++-v3/config.h.in b/libstdc++-v3/config.h.in
index acdfa999543afbfab2fda8634b84f024bb03c089..759378e3a2c29321f4ce37fd222be2df5bea1be9 100644
--- a/libstdc++-v3/config.h.in
+++ b/libstdc++-v3/config.h.in
@@ -1037,6 +1037,9 @@
 /* Defined if as can handle rdseed. */
 #undef _GLIBCXX_X86_RDSEED
 
+/* Define if a non-default location should be used for tzdata files. */
+#undef _GLIBCXX_ZONEINFO_DIR
+
 /* Define to 1 if mutex_timedlock is available. */
 #undef _GTHREAD_USE_MUTEX_TIMEDLOCK
 
diff --git a/libstdc++-v3/config/abi/pre/gnu.ver b/libstdc++-v3/config/abi/pre/gnu.ver
index 667cc4dfca4a6e7f20297210750869d6aa90a267..570ffca871020a56073d3f879844c1815158c9cb 100644
--- a/libstdc++-v3/config/abi/pre/gnu.ver
+++ b/libstdc++-v3/config/abi/pre/gnu.ver
@@ -28,7 +28,8 @@ GLIBCXX_3.4 {
       std::a[a-c]*;
       std::ad[a-n]*;
       std::ad[p-z]*;
-      std::a[e-z]*;
+      std::a[e-s]*;
+      std::a[u-z]*;
 #     std::ba[a-r]*;
       std::basic_[a-e]*;
       std::basic_f[a-h]*;
@@ -2485,6 +2486,23 @@ GLIBCXX_3.4.31 {
 
     _ZSt15__try_use_facet*;
 
+    _ZNSt6chrono11reload_tzdbEv;
+    _ZNSt6chrono8get_tzdbEv;
+    _ZNSt6chrono13get_tzdb_listEv;
+    _ZNSt6chrono14remote_version*;
+    _ZNSt6chrono12current_zoneEv;
+    _ZNSt6chrono11locate_zoneESt17basic_string_viewIcSt11char_traitsIcEE;
+    _ZNKSt6chrono9time_zone15_M_get_sys_info*;
+    _ZNKSt6chrono9time_zone17_M_get_local_info*;
+    _ZNKSt6chrono4tzdb12current_zoneEv;
+    _ZNKSt6chrono4tzdb11locate_zoneESt17basic_string_viewIcSt11char_traitsIcEE;
+    _ZNKSt6chrono9tzdb_list5beginEv;
+    _ZNKSt6chrono9tzdb_list5frontEv;
+    _ZNSt6chrono9tzdb_list11erase_afterENS0_14const_iteratorE;
+    _ZNKSt6chrono9tzdb_list14const_iteratordeEv;
+    _ZNSt6chrono9tzdb_list14const_iteratorppEv;
+    _ZNSt6chrono9tzdb_list14const_iteratorppEi;
+
 } GLIBCXX_3.4.30;
 
 # Symbols in the support library (libsupc++) have their own tag.
diff --git a/libstdc++-v3/configure b/libstdc++-v3/configure
index 1f7017c08a4c08c8d868a873bc85cceec244c6db..4b0ee147f409c9e3dd76558b3c68695a18ebf93d 100755
--- a/libstdc++-v3/configure
+++ b/libstdc++-v3/configure
@@ -961,6 +961,7 @@ enable_libstdcxx_filesystem_ts
 enable_libstdcxx_backtrace
 enable_libstdcxx_static_eh_pool
 with_libstdcxx_eh_pool_obj_count
+with_libstdcxx_zoneinfo_dir
 enable_cet
 with_gxx_include_dir
 enable_version_specific_runtime_libs
@@ -1704,6 +1705,8 @@ Optional Packages:
   --with-libstdcxx-eh-pool-obj-count
                           the number of exceptions that can be allocated from
                           the pool if malloc fails
+  --with-libstdcxx-zoneinfo-dir
+                          the directory to search for tzdata files
   --with-gxx-include-dir=DIR
                           installation directory for include files
   --with-toolexeclibdir=DIR
@@ -12182,7 +12185,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 12185 "configure"
+#line 12188 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -12288,7 +12291,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 12291 "configure"
+#line 12294 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -16012,7 +16015,7 @@ $as_echo "$glibcxx_cv_atomic_long_long" >&6; }
   # Fake what AC_TRY_COMPILE does.
 
     cat > conftest.$ac_ext << EOF
-#line 16015 "configure"
+#line 16018 "configure"
 int main()
 {
   typedef bool atomic_type;
@@ -16047,7 +16050,7 @@ $as_echo "$glibcxx_cv_atomic_bool" >&6; }
     rm -f conftest*
 
     cat > conftest.$ac_ext << EOF
-#line 16050 "configure"
+#line 16053 "configure"
 int main()
 {
   typedef short atomic_type;
@@ -16082,7 +16085,7 @@ $as_echo "$glibcxx_cv_atomic_short" >&6; }
     rm -f conftest*
 
     cat > conftest.$ac_ext << EOF
-#line 16085 "configure"
+#line 16088 "configure"
 int main()
 {
   // NB: _Atomic_word not necessarily int.
@@ -16118,7 +16121,7 @@ $as_echo "$glibcxx_cv_atomic_int" >&6; }
     rm -f conftest*
 
     cat > conftest.$ac_ext << EOF
-#line 16121 "configure"
+#line 16124 "configure"
 int main()
 {
   typedef long long atomic_type;
@@ -16274,7 +16277,7 @@ $as_echo "mutex" >&6; }
   # unnecessary for this test.
 
     cat > conftest.$ac_ext << EOF
-#line 16277 "configure"
+#line 16280 "configure"
 int main()
 {
   _Decimal32 d1;
@@ -16316,7 +16319,7 @@ ac_compiler_gnu=$ac_cv_cxx_compiler_gnu
   # unnecessary for this test.
 
   cat > conftest.$ac_ext << EOF
-#line 16319 "configure"
+#line 16322 "configure"
 template<typename T1, typename T2>
   struct same
   { typedef T2 type; };
@@ -71511,6 +71514,30 @@ fi
 
 
 
+# For src/c++20/tzdb.cc defaults.
+
+
+# Check whether --with-libstdcxx-zoneinfo-dir was given.
+if test "${with_libstdcxx_zoneinfo_dir+set}" = set; then :
+  withval=$with_libstdcxx_zoneinfo_dir; zoneinfo_dir="${withval}"
+
+$as_echo "#define _GLIBCXX_ZONEINFO_DIR \"\${withval}\"" >>confdefs.h
+
+
+else
+
+    case "$host" in
+      # *-*-aix*) zoneinfo_dir="/usr/share/lib/zoneinfo" ;;
+      *) zoneinfo_dir="/usr/share/zoneinfo" ;;
+    esac
+
+fi
+
+
+  { $as_echo "$as_me:${as_lineno-$LINENO}: zoneinfo data directory: ${zoneinfo_dir}" >&5
+$as_echo "$as_me: zoneinfo data directory: ${zoneinfo_dir}" >&6;}
+
+
 # Define documentation rules conditionally.
 
 # See if makeinfo has been installed and is modern enough
diff --git a/libstdc++-v3/configure.ac b/libstdc++-v3/configure.ac
index 3e89d09fdd8b65fd1d338059fda88cc55664f058..0dd550a4b4b1f5e31c4a84f4af258e723744657c 100644
--- a/libstdc++-v3/configure.ac
+++ b/libstdc++-v3/configure.ac
@@ -535,6 +535,9 @@ GLIBCXX_CHECK_EXCEPTION_PTR_SYMVER
 # For libsupc++/eh_alloc.cc defaults.
 GLIBCXX_EMERGENCY_EH_ALLOC
 
+# For src/c++20/tzdb.cc defaults.
+GLIBCXX_ZONEINFO_DIR
+
 # Define documentation rules conditionally.
 
 # See if makeinfo has been installed and is modern enough
diff --git a/libstdc++-v3/include/std/chrono b/libstdc++-v3/include/std/chrono
index 33653f8efb1709408aeabe8d3f4708e1614f0fb6..aeb8f6f462fa54b765769d9181202c18c6d902be 100644
--- a/libstdc++-v3/include/std/chrono
+++ b/libstdc++-v3/include/std/chrono
@@ -46,11 +46,17 @@
 # include <string>
 # include <vector>
 # include <bits/charconv.h> // __to_chars_len, __to_chars_10_impl
-# include <bits/stl_algo.h> // upper_bound TODO: move leap_second_info to .so
+# include <bits/stl_algo.h> // upper_bound
 # include <bits/shared_ptr.h>
 # include <bits/unique_ptr.h>
 #endif
 
+#if __cplusplus >= 202002L
+// TODO formatting and parsing
+// # undef __cpp_lib_chrono
+// # define __cpp_lib_chrono 201907L
+#endif
+
 namespace std _GLIBCXX_VISIBILITY(default)
 {
 _GLIBCXX_BEGIN_NAMESPACE_VERSION
@@ -140,7 +146,7 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 	{
 	  using _CDur = common_type_t<_Duration, seconds>;
 	  const auto __li = chrono::get_leap_second_info(__t);
-	  sys_time<_CDur> __s{__t.time_since_epoch() - seconds{__li.elapsed}};
+	  sys_time<_CDur> __s{__t.time_since_epoch() - __li.elapsed};
 	  if (__li.is_leap_second)
 	    __s = chrono::floor<seconds>(__s) + seconds{1} - _CDur{1};
 	  return __s;
@@ -149,13 +155,7 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
       template<typename _Duration>
 	[[nodiscard]]
 	static utc_time<common_type_t<_Duration, seconds>>
-	from_sys(const sys_time<_Duration>& __t)
-	{
-	  using _CDur = common_type_t<_Duration, seconds>;
-	  utc_time<_Duration> __u(__t.time_since_epoch());
-	  const auto __li = chrono::get_leap_second_info(__u);
-	  return utc_time<_CDur>{__u} + seconds{__li.elapsed};
-	}
+	from_sys(const sys_time<_Duration>& __t);
     };
 
     /** A clock that measures International Atomic Time.
@@ -2056,7 +2056,7 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 		    - chrono::weekday{sys_days{_M_y / _M_m / 1}}
 		    + days((_M_wdi.index()-1)*7 + 1));
 	__glibcxx_assert(__d.count() >= 1);
-	return __d.count() <= unsigned{(_M_y / _M_m / last).day()};
+	return (unsigned)__d.count() <= (unsigned)(_M_y / _M_m / last).day();
       }
 
       friend constexpr bool
@@ -2500,8 +2500,11 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 	}
     }
 
+#if _GLIBCXX_USE_CXX11_ABI || ! _GLIBCXX_USE_DUAL_ABI
     // C++20 [time.zones] Time zones
 
+    struct tzdb;
+
     struct sys_info
     {
       sys_seconds begin;
@@ -2532,9 +2535,25 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 	{ __glibcxx_assert(__i.result == local_info::nonexistent); }
 
     private:
-      template<typename _Duration> // TODO
+      template<typename _Duration>
 	static string
-	_S_make_what_str(const local_time<_Duration>&, const local_info&);
+	_S_make_what_str(const local_time<_Duration>& __tp,
+			 const local_info& __i)
+	{
+#if 1
+	  return "local time is non-existent";
+#else
+	  std::ostringstream __os;
+	  __os << __tp << " is in a gap between\n"
+	       << local_seconds(__i.first.end.time_since_epoch())
+	       + __i.first.offset << ' ' << __i.first.abbrev << " and\n"
+	       << local_seconds(__i.second.begin.time_since_epoch())
+	       + __i.second.offset << ' ' << __i.second.abbrev
+	       << " which are both equivalent to\n"
+	       << __i.first.end << " UTC";
+	  return std::move(__os).str();
+#endif
+	}
     };
 
     class ambiguous_local_time : public runtime_error
@@ -2542,16 +2561,44 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
     public:
       template<typename _Duration>
 	ambiguous_local_time(const local_time<_Duration>& __tp,
-			       const local_info& __i)
+			     const local_info& __i)
 	: runtime_error(_S_make_what_str(__tp, __i))
-	{ __glibcxx_assert(__i.result == local_info::nonexistent); }
+	{ __glibcxx_assert(__i.result == local_info::ambiguous); }
 
     private:
-      template<typename _Duration> // TODO
+      template<typename _Duration>
 	static string
-	_S_make_what_str(const local_time<_Duration>&, const local_info&);
+	_S_make_what_str(const local_time<_Duration>& __tp,
+			 const local_info& __i)
+	{
+#if 1
+	  return "local time is ambiguous";
+#else
+	  std::ostringstream __os;
+	  __os << __tp << " is ambiguous.  It could be\n"
+	       << __tp << ' ' << __i.first.abbrev << " == "
+	       << __tp - __i.first.offset << " UTC or\n"
+	       << __tp << ' ' << __i.second.abbrev << " == "
+	       << __tp - __i.second.offset << " UTC";
+	  return std::move(__os).str();
+#endif
+	}
     };
 
+    template<typename _Duration>
+      [[noreturn]] void
+      __throw_bad_local_time(const local_time<_Duration>& __tp,
+			     const local_info& __i)
+      {
+#if __cpp_exceptions
+	if (__i.result == local_info::nonexistent)
+	  throw nonexistent_local_time(__tp, __i);
+	throw ambiguous_local_time(__tp, __i);
+#else
+	__builtin_abort();
+#endif
+      }
+
     enum class choose { earliest, latest };
 
     class time_zone
@@ -2560,46 +2607,188 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
       time_zone(time_zone&&) = default;
       time_zone& operator=(time_zone&&) = default;
 
+      ~time_zone();
+
+      [[nodiscard]]
       string_view name() const noexcept { return _M_name; }
 
       template<typename _Duration>
 	sys_info
-	get_info(const sys_time<_Duration>& __st) const;
+	get_info(const sys_time<_Duration>& __st) const
+	{ return _M_get_sys_info(chrono::floor<seconds>(__st)); }
 
       template<typename _Duration>
 	local_info
-	get_info(const local_time<_Duration>& __tp) const;
+	get_info(const local_time<_Duration>& __tp) const
+	{ return _M_get_local_info(chrono::floor<seconds>(__tp)); }
 
       template<typename _Duration>
 	sys_time<common_type_t<_Duration, seconds>>
-	to_sys(const local_time<_Duration>& __tp) const;
+	to_sys(const local_time<_Duration>& __tp) const
+	{
+	  local_info __info = get_info(__tp);
+
+	  if (__info.result != local_info::unique)
+	    __throw_bad_local_time(__tp, __info);
+
+	  return sys_time<_Duration>(__tp.time_since_epoch())
+		   - __info.first.offset;
+	}
 
       template<typename _Duration>
 	sys_time<common_type_t<_Duration, seconds>>
-	to_sys(const local_time<_Duration>& __tp, choose __z) const;
+	to_sys(const local_time<_Duration>& __tp, choose __z) const
+	{
+	  local_info __info = get_info(__tp);
+
+	  if (__info.result == local_info::nonexistent)
+	    return __info.first.end; // Last second of the previous sys_info.
+
+	  sys_time<_Duration> __st(__tp.time_since_epoch());
+
+	  if (__info.result == local_info::ambiguous && __z == choose::latest)
+	    return __st - __info.second.offset; // Time in the later sys_info.
+	  // else if __z == earliest, use __info.first.offset as below:
+
+	  return __st - __info.first.offset;
+	}
 
       template<typename _Duration>
 	local_time<common_type_t<_Duration, seconds>>
-	to_local(const sys_time<_Duration>& __tp) const;
+	to_local(const sys_time<_Duration>& __tp) const
+	{
+	  auto __d = (__tp + get_info(__tp).offset).time_since_epoch();
+	  return local_time<common_type_t<_Duration, seconds>>(__d);
+	}
 
-      friend bool
+      [[nodiscard]] friend bool
       operator==(const time_zone& __x, const time_zone& __y) noexcept
-      { return __x.name() == __y.name(); }
+      { return __x._M_name == __y._M_name; }
 
-      friend strong_ordering
+      [[nodiscard]] friend strong_ordering
       operator<=>(const time_zone& __x, const time_zone& __y) noexcept
-      { return __x.name() <=> __y.name(); }
+      { return __x._M_name <=> __y._M_name; }
 
     private:
-      string _M_name;
+      sys_info _M_get_sys_info(sys_seconds) const;
+      local_info _M_get_local_info(local_seconds) const;
+
+      friend const tzdb& reload_tzdb();
+      friend struct tzdb;
+      friend class tzdb_list;
+
       struct _Impl;
+
+      explicit time_zone(unique_ptr<_Impl> __p);
+      string _M_name;
       unique_ptr<_Impl> _M_impl;
     };
 
-    struct tzdb;
     const time_zone* locate_zone(string_view __tz_name);
     const time_zone* current_zone();
 
+    /** The list of `chrono::tzdb` objects
+     *
+     * A single object of this type is constructed by the C++ runtime,
+     * and can be accessed by calling `chrono::get_tzdb_list()`.
+     *
+     * The front of the list is the current `tzdb` object and can be accessed
+     * via `chrono::get_tzdb_list().front()` or `chrono::get_tzdb()` or
+     * `*chrono::get_tzdb_list().begin()`.
+     *
+     * The `chrono::reload_tzdb()` function will check for a newer version
+     * and if found, insert it at the front of the list.
+     *
+     * @since C++20
+     */
+    class tzdb_list
+    {
+      struct _Node;
+
+    public:
+      tzdb_list(const tzdb_list&) = delete;
+      tzdb_list& operator=(const tzdb_list&) = delete;
+
+      /** An iterator into the `tzdb_list`
+       *
+       * As a extension, in libstdc++ each `tzdb` is reference-counted
+       * and the `const_iterator` type shares ownership of the object it
+       * refers to. This ensures that a `tzdb` erased from the list will
+       * not be destroyed while there is an iterator that refers to it.
+       */
+      class const_iterator
+      {
+      public:
+	using value_type        = tzdb;
+	using reference         = const tzdb&;
+	using pointer           = const tzdb*;
+	using difference_type   = ptrdiff_t;
+	using iterator_category = forward_iterator_tag;
+
+	constexpr const_iterator() = default;
+	const_iterator(const const_iterator&) = default;
+	const_iterator(const_iterator&&) = default;
+	const_iterator& operator=(const const_iterator&) = default;
+	const_iterator& operator=(const_iterator&&) = default;
+
+	reference operator*() const noexcept;
+	pointer operator->() const noexcept { return &**this; }
+	const_iterator& operator++();
+	const_iterator operator++(int);
+
+	bool operator==(const const_iterator&) const noexcept = default;
+
+      private:
+	explicit const_iterator(const shared_ptr<_Node>&) noexcept;
+
+	friend class tzdb_list;
+
+	shared_ptr<_Node> _M_node;
+	void* _M_reserved = nullptr;
+      };
+
+      /** Access the current `tzdb` at the front of the list.
+       *
+       * This returns a reference to the same object as `chrono::get_tzdb()`.
+       *
+       * @returns A reference to the current tzdb object.
+       * @since C++20
+       */
+      const tzdb& front() const noexcept;
+
+      /** Remove the tzdb object _after_ the one the iterator refers to.
+       *
+       * Calling this function concurently with any of `front()`, `begin()`,
+       * or `end()` does not cause a data race, but in general this function
+       * is not thread-safe. The behaviour may be undefined if erasing an
+       * element from the list while another thread is calling the same
+       * function, or incrementing an iterator into the list, or accessing
+       * the element being erased (unless it is accessed through an iterator).
+       *
+       * @param __p A dereferenceable iterator.
+       * @returns An iterator the element after the one that was erased
+       *          (or `end()` if there is no such element).
+       * @since C++20
+       */
+      const_iterator erase_after(const_iterator __p);
+
+      const_iterator begin() const noexcept;
+      const_iterator end() const noexcept { return {}; }
+      const_iterator cbegin() const noexcept { return begin(); }
+      const_iterator cend() const noexcept { return end(); }
+
+    private:
+      constexpr explicit tzdb_list(nullptr_t);
+
+      friend tzdb_list& get_tzdb_list();
+      friend const tzdb& get_tzdb();
+      friend const tzdb& reload_tzdb();
+      friend struct tzdb;
+      friend class leap_second;
+      friend struct time_zone::_Impl;
+      friend class time_zone_link;
+    };
+
     class time_zone_link
     {
     public:
@@ -2619,7 +2808,10 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 
     private:
       friend const tzdb& reload_tzdb();
-      // TODO unspecified additional constructors
+      friend class tzdb_list::_Node;
+
+      explicit time_zone_link(nullptr_t) { }
+
       string _M_name;
       string _M_target;
     };
@@ -2720,10 +2912,13 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
     private:
       explicit leap_second(seconds::rep __s) : _M_s(__s) { }
 
+      friend class tzdb_list::_Node;
+
       friend const tzdb& reload_tzdb();
-      template<typename _Dur>
+
+      template<typename _Duration>
 	friend leap_second_info
-	get_leap_second_info(const utc_time<_Dur>&);
+	get_leap_second_info(const utc_time<_Duration>&);
 
       seconds _M_s; // == date().time_since_epoch() * value().count()
     };
@@ -2745,9 +2940,9 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
     struct tzdb
     {
       string version;
-      vector<time_zone> zones;
-      vector<time_zone_link> links;
-      vector<leap_second> leap_seconds;
+      _GLIBCXX_STD_C::vector<time_zone> zones;
+      _GLIBCXX_STD_C::vector<time_zone_link> links;
+      _GLIBCXX_STD_C::vector<leap_second> leap_seconds;
 
       const time_zone*
       locate_zone(string_view __tz_name) const;
@@ -2757,146 +2952,353 @@ _GLIBCXX_BEGIN_NAMESPACE_VERSION
 
     private:
       friend const tzdb& reload_tzdb();
-
-      struct _Rule;
-      vector<_Rule> _M_rules;
+      friend class time_zone;
+      friend class tzdb_list::_Node;
     };
 
-    class tzdb_list
-    {
-      struct _Node;
-    public:
-      tzdb_list(const tzdb_list&) = delete;
-      tzdb_list& operator=(const tzdb_list&) = delete;
+    tzdb_list& get_tzdb_list();
+    const tzdb& get_tzdb();
 
-      class const_iterator
+    const tzdb& reload_tzdb();
+    string remote_version();
+
+    template<typename _Duration, typename _TimeZonePtr = const time_zone*>
+      class zoned_time
       {
+	static_assert(__is_duration_v<_Duration>);
+
+	using _Traits = zoned_traits<_TimeZonePtr>;
+
+	// Every constructor that accepts a string_view as its first parameter
+	// does not participate in class template argument deduction.
+	using string_view = type_identity_t<std::string_view>;
+
       public:
-	using value_type        = tzdb;
-	using reference         = const tzdb&;
-	using pointer           = const tzdb*;
-	using difference_type   = ptrdiff_t;
-	using iterator_category = forward_iterator_tag;
+	using duration = common_type_t<_Duration, seconds>;
 
-	constexpr const_iterator() = default;
-	const_iterator(const const_iterator&) = default;
-	const_iterator(const_iterator&&) = default;
-	const_iterator& operator=(const const_iterator&) = default;
-	const_iterator& operator=(const_iterator&&) = default;
+	zoned_time() requires requires { _Traits::default_zone(); }
+	{ }
 
-	reference operator*() const noexcept;
-	pointer operator->() const noexcept { return &**this; }
-	const_iterator& operator++();
-	const_iterator operator++(int);
+	zoned_time(const zoned_time&) = default;
+	zoned_time& operator=(const zoned_time&) = default;
 
-	bool operator==(const const_iterator&) const noexcept = default;
+	zoned_time(const sys_time<_Duration>& __st)
+	  requires requires { _Traits::default_zone(); }
+	: _M_tp(__st)
+	{ }
 
-      private:
-	explicit const_iterator(const shared_ptr<_Node>&) noexcept;
+	explicit
+	zoned_time(_TimeZonePtr __z) : _M_zone(std::move(__z)) { }
 
-	shared_ptr<_Node> _M_node;
-	void* _M_reserved = nullptr;
-      };
+	explicit
+	zoned_time(string_view __name)
+	  requires requires {
+	    _TimeZonePtr{_Traits::locate_zone(std::string_view{})};
+	  }
+	: _M_zone(_Traits::locate_zone(__name))
+	{ }
 
-      // TODO const tzdb& front() const noexcept;
+	template<typename _Duration2>
+	  zoned_time(const zoned_time<_Duration2, _TimeZonePtr>& __zt)
+	  requires is_convertible_v<sys_time<_Duration2>, sys_time<_Duration>>
+	  : _M_zone(__zt._M_zone), _M_tp(__zt._M_tp)
+	  { }
 
-      const_iterator erase_after(const_iterator);
+	zoned_time(_TimeZonePtr __z, const sys_time<_Duration>& __st)
+	: _M_zone(std::move(__z)), _M_tp(__st)
+	{ }
 
-      const_iterator begin() const noexcept;
-      const_iterator end() const noexcept { return {}; }
-      const_iterator cbegin() const noexcept { return begin(); }
-      const_iterator cend() const noexcept { return end(); }
+	zoned_time(string_view __name, const sys_time<_Duration>& __st)
+	: zoned_time(_Traits::locate_zone(__name), __st)
+	{ }
 
-    private:
-      constexpr explicit tzdb_list(nullptr_t);
+	zoned_time(_TimeZonePtr __z, const local_time<_Duration>& __tp)
+	requires requires {
+	  { __z->to_sys(__tp) } -> convertible_to<sys_time<_Duration>>;
+	}
+	: _M_zone(std::move(__z)), _M_tp(_M_zone->to_sys(__tp))
+	{ }
 
-      friend const tzdb_list& get_tzdb_list();
-      friend const tzdb& get_tzdb();
-      friend const tzdb& reload_tzdb();
+	zoned_time(string_view __name, const local_time<_Duration>& __tp)
+	requires requires (_TimeZonePtr __z) {
+	  { _Traits::locate_zone(__name) } -> convertible_to<_TimeZonePtr>;
+	  { __z->to_sys(__tp) } -> convertible_to<sys_time<_Duration>>;
+	}
+	: zoned_time(_Traits::locate_zone(__name), __tp)
+	{ }
 
-      static _Node* _S_head;
-      static shared_ptr<_Node> _S_head_owner;
-    };
+	zoned_time(_TimeZonePtr __z, const local_time<_Duration>& __tp,
+		   choose __c)
+	requires requires {
+	  { __z->to_sys(__tp, __c) } -> convertible_to<sys_time<_Duration>>;
+	}
+	: _M_zone(std::move(__z)), _M_tp(_M_zone->to_sys(__tp, __c))
+	{ }
 
-    // TODO
-    // const tzdb_list& get_tzdb_list();
-    // const tzdb& get_tzdb();
+	zoned_time(string_view __name, const local_time<_Duration>& __tp,
+		   choose __c)
+	requires requires (_TimeZonePtr __z) {
+	  { _Traits::locate_zone(__name) } -> convertible_to<_TimeZonePtr>;
+	  { __z->to_sys(__tp, __c) } -> convertible_to<sys_time<_Duration>>;
+	}
+	: _M_zone(_Traits::locate_zone(__name)),
+	  _M_tp(_M_zone->to_sys(__tp, __c))
+	{ }
 
-    // const tzdb& reload_tzdb();
-    // string remove_version();
+	template<typename _Duration2, typename _TimeZonePtr2>
+	  zoned_time(_TimeZonePtr __z,
+		     const zoned_time<_Duration2, _TimeZonePtr2>& __zt)
+	  requires is_convertible_v<sys_time<_Duration2>, sys_time<_Duration>>
+	  : _M_zone(__z), _M_tp(__zt._M_tp)
+	  { }
+
+	template<typename _Duration2, typename _TimeZonePtr2>
+	  zoned_time(_TimeZonePtr __z,
+		     const zoned_time<_Duration2, _TimeZonePtr2>& __zt,
+		     choose __c)
+	  requires is_convertible_v<sys_time<_Duration2>, sys_time<_Duration>>
+	  : _M_zone(__z), _M_tp(__zt._M_tp)
+	  { }
+
+	template<typename _Duration2, typename _TimeZonePtr2>
+	  zoned_time(string_view __name,
+		     const zoned_time<_Duration2, _TimeZonePtr2>& __zt)
+	  requires is_convertible_v<sys_time<_Duration2>, sys_time<_Duration>>
+	  && requires {
+	    { _Traits::locate_zone(__name) } -> convertible_to<_TimeZonePtr>;
+	  }
+	  : _M_zone(_Traits::locate_zone(__name)), _M_tp(__zt._M_tp)
+	  { }
+
+	template<typename _Duration2, typename _TimeZonePtr2>
+	  zoned_time(string_view __name,
+		     const zoned_time<_Duration2, _TimeZonePtr2>& __zt,
+		     choose __c)
+	  requires is_convertible_v<sys_time<_Duration2>, sys_time<_Duration>>
+	  && requires {
+	    { _Traits::locate_zone(__name) } -> convertible_to<_TimeZonePtr>;
+	  }
+	  : _M_zone(_Traits::locate_zone(__name)), _M_tp(__zt._M_tp)
+	  { }
 
-    template<typename _Duration, typename _TimeZonePtr = const time_zone*>
-      class zoned_time; // TODO
+	zoned_time&
+	operator=(const sys_time<_Duration>& __st)
+	{
+	  _M_tp = __st;
+	  return *this;
+	}
+
+	zoned_time&
+	operator=(const local_time<_Duration>& __lt)
+	{
+	  _M_tp = _M_zone->to_sys(__lt);
+	  return *this;
+	}
+
+	[[nodiscard]]
+	operator sys_time<duration>() const { return _M_tp; }
+
+	[[nodiscard]]
+	explicit operator local_time<duration>() const
+	{ return get_local_time(); }
+
+	[[nodiscard]]
+	_TimeZonePtr
+	get_time_zone() const
+	{ return _M_zone; }
+
+	[[nodiscard]]
+	local_time<duration>
+	get_local_time() const
+	{ return _M_zone->to_local(_M_tp); }
+
+	[[nodiscard]]
+	sys_time<duration>
+	get_sys_time() const
+	{ return _M_tp; }
+
+	[[nodiscard]]
+	sys_info
+	get_info() const
+	{ return _M_zone->get_info(_M_tp); }
+
+	[[nodiscard]] friend bool
+	operator==(const zoned_time&, const zoned_time&) = default;
+
+      private:
+	_TimeZonePtr       _M_zone{ _Traits::default_zone() };
+	sys_time<duration> _M_tp{};
+
+	template<typename _Duration2, typename _TimeZonePtr2>
+	  friend class zoned_time;
+      };
+
+    zoned_time() -> zoned_time<seconds>;
+
+    template<typename _Duration>
+    zoned_time(sys_time<_Duration>)
+      -> zoned_time<common_type_t<_Duration, seconds>>;
+
+  /// @cond undocumented
+  template<typename _TimeZonePtrOrName>
+    using __time_zone_representation
+      = __conditional_t<is_convertible_v<_TimeZonePtrOrName, string_view>,
+			const time_zone*,
+			remove_cvref_t<_TimeZonePtrOrName>>;
+  /// @endcond
+
+  template<typename _TimeZonePtrOrName>
+    zoned_time(_TimeZonePtrOrName&&)
+      -> zoned_time<seconds, __time_zone_representation<_TimeZonePtrOrName>>;
+
+  template<typename _TimeZonePtrOrName, typename _Duration>
+    zoned_time(_TimeZonePtrOrName&&, sys_time<_Duration>)
+      -> zoned_time<common_type_t<_Duration, seconds>,
+                    __time_zone_representation<_TimeZonePtrOrName>>;
+
+  template<typename _TimeZonePtrOrName, typename _Duration>
+    zoned_time(_TimeZonePtrOrName&&, local_time<_Duration>,
+               choose = choose::earliest)
+      -> zoned_time<common_type_t<_Duration, seconds>,
+                    __time_zone_representation<_TimeZonePtrOrName>>;
+
+  template<typename _Duration, typename _TimeZonePtrOrName,
+	   typename _TimeZonePtr2>
+    zoned_time(_TimeZonePtrOrName&&, zoned_time<_Duration, _TimeZonePtr2>,
+               choose = choose::earliest)
+      -> zoned_time<common_type_t<_Duration, seconds>,
+                    __time_zone_representation<_TimeZonePtrOrName>>;
+
+  template<typename _Dur1, typename _TZPtr1, typename _Dur2, typename _TZPtr2>
+    [[nodiscard]]
+    inline bool
+    operator==(const zoned_time<_Dur1, _TZPtr1>& __x,
+	       const zoned_time<_Dur2, _TZPtr2>& __y)
+    {
+      return __x.get_time_zone() == __y.get_time_zone()
+	       && __x.get_sys_time() == __y.get_sys_time();
+    }
 
     using zoned_seconds = zoned_time<seconds>;
+#endif // _GLIBCXX_USE_CXX11_ABI || ! _GLIBCXX_USE_DUAL_ABI
+
+namespace __detail
+{
+    inline leap_second_info
+    __get_leap_second_info(sys_seconds __ss, bool __is_utc)
+    {
+      if (__ss < sys_seconds{}) [[unlikely]]
+	return {};
+
+      const seconds::rep __leaps[] {
+	  78796800, // 1 Jul 1972
+	  94694400, // 1 Jan 1973
+	 126230400, // 1 Jan 1974
+	 157766400, // 1 Jan 1975
+	 189302400, // 1 Jan 1976
+	 220924800, // 1 Jan 1977
+	 252460800, // 1 Jan 1978
+	 283996800, // 1 Jan 1979
+	 315532800, // 1 Jan 1980
+	 362793600, // 1 Jul 1981
+	 394329600, // 1 Jul 1982
+	 425865600, // 1 Jul 1983
+	 489024000, // 1 Jul 1985
+	 567993600, // 1 Jan 1988
+	 631152000, // 1 Jan 1990
+	 662688000, // 1 Jan 1991
+	 709948800, // 1 Jul 1992
+	 741484800, // 1 Jul 1993
+	 773020800, // 1 Jul 1994
+	 820454400, // 1 Jan 1996
+	 867715200, // 1 Jul 1997
+	 915148800, // 1 Jan 1999
+	1136073600, // 1 Jan 2006
+	1230768000, // 1 Jan 2009
+	1341100800, // 1 Jul 2012
+	1435708800, // 1 Jul 2015
+	1483228800, // 1 Jan 2017
+      };
+      // The list above is known to be valid until (at least) this date
+      // and only contains positive leap seconds.
+      const sys_seconds __expires(1687910400s); // 2023-06-28 00:00:00 UTC
+
+#if _GLIBCXX_USE_CXX11_ABI || ! _GLIBCXX_USE_DUAL_ABI
+      if (__ss > __expires)
+	{
+	  // Use updated leap_seconds from tzdb.
+	  size_t __n = std::size(__leaps);
+
+	  auto __db = get_tzdb_list().begin();
+	  auto __first = __db->leap_seconds.begin() + __n;
+	  auto __last = __db->leap_seconds.end();
+	  auto __pos = std::upper_bound(__first, __last, __ss);
+	  seconds __elapsed(__n);
+	  for (auto __i = __first; __i != __pos; ++__i)
+	    __elapsed += __i->value();
+
+	  if (__is_utc)
+	    {
+	      // Convert utc_time to sys_time:
+	      __ss -= __elapsed;
+	      // See if that sys_time is before (or during) previous leap sec:
+	      if (__pos != __first && __ss < __pos[-1])
+		{
+		  if ((__ss + 1s) >= __pos[-1])
+		    return {true, __elapsed};
+		  __elapsed -= __pos[-1].value();
+		}
+	    }
+	  return {false, __elapsed};
+	}
+      else
+#endif
+	{
+	  seconds::rep __s = __ss.time_since_epoch().count();
+	  const seconds::rep* __first = std::begin(__leaps);
+	  const seconds::rep* __last = std::end(__leaps);
+
+	  // Don't bother searching the list if we're after the last one.
+	  if (__s > (__last[-1] + (__last - __first) + 1))
+	    return { false, seconds(__last - __first) };
+
+	  auto __pos = std::upper_bound(__first, __last, __s);
+	  seconds __elapsed{__pos - __first};
+	  if (__is_utc)
+	    {
+	      // Convert utc_time to sys_time:
+	      __s -= __elapsed.count();
+	      // See if that sys_time is before (or during) previous leap sec:
+	      if (__pos != __first && __s < __pos[-1])
+		{
+		  if ((__s + 1) >= __pos[-1])
+		    return {true, __elapsed};
+		  --__elapsed;
+		}
+	    }
+	  return {false, __elapsed};
+	}
+    }
+} // namespace __detail
 
     template<typename _Duration>
-      leap_second_info
+      [[nodiscard]]
+      inline leap_second_info
       get_leap_second_info(const utc_time<_Duration>& __ut)
       {
-	if constexpr (is_same_v<_Duration, seconds>)
-	  {
-	    const seconds::rep __leaps[] {
-		78796800, // 1 Jul 1972
-		94694400, // 1 Jan 1973
-	       126230400, // 1 Jan 1974
-	       157766400, // 1 Jan 1975
-	       189302400, // 1 Jan 1976
-	       220924800, // 1 Jan 1977
-	       252460800, // 1 Jan 1978
-	       283996800, // 1 Jan 1979
-	       315532800, // 1 Jan 1980
-	       362793600, // 1 Jul 1981
-	       394329600, // 1 Jul 1982
-	       425865600, // 1 Jul 1983
-	       489024000, // 1 Jul 1985
-	       567993600, // 1 Jan 1988
-	       631152000, // 1 Jan 1990
-	       662688000, // 1 Jan 1991
-	       709948800, // 1 Jul 1992
-	       741484800, // 1 Jul 1993
-	       773020800, // 1 Jul 1994
-	       820454400, // 1 Jan 1996
-	       867715200, // 1 Jul 1997
-	       915148800, // 1 Jan 1999
-	      1136073600, // 1 Jan 2006
-	      1230768000, // 1 Jan 2009
-	      1341100800, // 1 Jul 2012
-	      1435708800, // 1 Jul 2015
-	      1483228800, // 1 Jan 2017
-	    };
-	    // The list above is known to be valid until 2023-06-28 00:00:00 UTC
-	    const seconds::rep __expires = 1687910400;
-	    const seconds::rep __s = __ut.time_since_epoch().count();
-
-	    const seconds::rep* __first = std::begin(__leaps);
-	    const seconds::rep* __last = std::end(__leaps);
-
-	    if (__s > __expires)
-	      {
-		// TODO: use updated leap_seconds from tzdb
-#if 0
-		auto __db = get_tzdb_list().begin();
-		__first = __db->leap_seconds.data();
-		__last = __first + __db->leap_seconds.size();
-#endif
-	      }
-
-	    // Don't bother searching the list if we're after the last one.
-	    if (__s > __last[-1])
-	      return { false, seconds(__last - __first) };
+	auto __s = chrono::duration_cast<seconds>(__ut.time_since_epoch());
+	return __detail::__get_leap_second_info(sys_seconds(__s), true);
+      }
 
-	    auto __pos = std::upper_bound(__first, __last, __s);
-	    return {
-	      __pos != begin(__leaps) && __pos[-1] == __s,
-	      seconds{__pos - __first}
-	    };
-	  }
-	else
-	  {
-	    auto __s = chrono::time_point_cast<seconds>(__ut);
-	    return chrono::get_leap_second_info(__s);
-	  }
+    template<typename _Duration>
+      [[nodiscard]]
+      inline utc_time<common_type_t<_Duration, seconds>>
+      utc_clock::from_sys(const sys_time<_Duration>& __t)
+      {
+	using _CDur = common_type_t<_Duration, seconds>;
+	auto __s = chrono::time_point_cast<seconds>(__t);
+	const auto __li = __detail::__get_leap_second_info(__s, false);
+	return utc_time<_CDur>{__t.time_since_epoch()} + __li.elapsed;
       }
 
     /// @} group chrono
diff --git a/libstdc++-v3/include/std/version b/libstdc++-v3/include/std/version
index 576eebc7dc8271820b3f9bd653f2ab1875cbc7b0..c1a9896b0c228fffbbbd7465420bbdf636a0397f 100644
--- a/libstdc++-v3/include/std/version
+++ b/libstdc++-v3/include/std/version
@@ -251,6 +251,8 @@
 #  define __cpp_lib_barrier 201907L
 # endif
 #endif
+// #undef __cpp_lib_chrono
+// #define __cpp_lib_chrono 201907L
 // FIXME: #define __cpp_lib_execution 201902L
 #define __cpp_lib_constexpr_algorithms 201806L
 #ifdef __cpp_lib_is_constant_evaluated
diff --git a/libstdc++-v3/src/c++20/Makefile.am b/libstdc++-v3/src/c++20/Makefile.am
index d4c1e26e40eda16d33879f3d01b348e5a0a77a92..a95b8c24d2108c843925df88ed78e5025b7a8e7f 100644
--- a/libstdc++-v3/src/c++20/Makefile.am
+++ b/libstdc++-v3/src/c++20/Makefile.am
@@ -36,7 +36,7 @@ else
 inst_sources =
 endif
 
-sources =
+sources = tzdb.cc
 
 vpath % $(top_srcdir)/src/c++20
 
diff --git a/libstdc++-v3/src/c++20/Makefile.in b/libstdc++-v3/src/c++20/Makefile.in
index 9db70a3e7fb7e6a1244a932529becbeac3a6af75..2adc1eb712ea27473acfd18e786254c8fd45bf5d 100644
--- a/libstdc++-v3/src/c++20/Makefile.in
+++ b/libstdc++-v3/src/c++20/Makefile.in
@@ -121,7 +121,7 @@ CONFIG_CLEAN_FILES =
 CONFIG_CLEAN_VPATH_FILES =
 LTLIBRARIES = $(noinst_LTLIBRARIES)
 libc__20convenience_la_LIBADD =
-am__objects_1 =
+am__objects_1 = tzdb.lo
 @ENABLE_EXTERN_TEMPLATE_TRUE@am__objects_2 = sstream-inst.lo
 am_libc__20convenience_la_OBJECTS = $(am__objects_1) $(am__objects_2)
 libc__20convenience_la_OBJECTS = $(am_libc__20convenience_la_OBJECTS)
@@ -431,7 +431,7 @@ headers =
 @ENABLE_EXTERN_TEMPLATE_TRUE@inst_sources = \
 @ENABLE_EXTERN_TEMPLATE_TRUE@	sstream-inst.cc
 
-sources = 
+sources = tzdb.cc
 libc__20convenience_la_SOURCES = $(sources)  $(inst_sources)
 
 # AM_CXXFLAGS needs to be in each subdirectory so that it can be
diff --git a/libstdc++-v3/src/c++20/tzdb.cc b/libstdc++-v3/src/c++20/tzdb.cc
new file mode 100644
index 0000000000000000000000000000000000000000..dcff021d9d49557989cfa0cb34db70348acefb85
--- /dev/null
+++ b/libstdc++-v3/src/c++20/tzdb.cc
@@ -0,0 +1,1806 @@
+// chrono::tzdb -*- C++ -*-
+
+// Copyright The GNU Toolchain Authors
+//
+// This file is part of the GNU ISO C++ Library.  This library 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, or (at your option)
+// any later version.
+
+// This library 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.
+
+// Under Section 7 of GPL version 3, you are granted additional
+// permissions described in the GCC Runtime Library Exception, version
+// 3.1, as published by the Free Software Foundation.
+
+// You should have received a copy of the GNU General Public License and
+// a copy of the GCC Runtime Library Exception along with this program;
+// see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+// <http://www.gnu.org/licenses/>.
+
+// The -Wabi warnings in this file are all for non-exported symbols.
+#pragma GCC diagnostic ignored "-Wabi"
+
+#include <chrono>
+#include <fstream>    // ifstream
+#include <sstream>    // istringstream
+#include <algorithm>  // ranges::upper_bound, ranges::lower_bound, ranges::sort
+#include <atomic>     // atomic<T*>, atomic<int_least32_t>
+#include <memory>     // atomic<shared_ptr<T>>
+#include <mutex>      // mutex
+#include <filesystem> // filesystem::read_symlink
+
+#ifdef __GTHREADS
+# if _WIN32
+// std::mutex cannot be constinit, so Windows must use atomic<shared_ptr<>>.
+#  define USE_ATOMIC_SHARED_PTR 1
+# else
+// TODO benchmark atomic<shared_ptr<>> vs mutex.
+#  define USE_ATOMIC_SHARED_PTR 1
+# endif
+#endif
+
+#if ! __cpp_constinit
+# if __has_cpp_attribute(clang::require_constant_initialization)
+#  define constinit [[clang::require_constant_initialization]]
+#else // YOLO
+# define constinit
+# endif
+#endif
+
+namespace __gnu_cxx
+{
+#ifdef _AIX
+  // Cannot override weak symbols on AIX.
+  const char* (*zoneinfo_dir_override)() = nullptr;
+#else
+  [[gnu::weak]] const char* zoneinfo_dir_override();
+#endif
+}
+
+namespace std::chrono
+{
+  namespace
+  {
+    struct Rule;
+  }
+
+  // The tzdb list is a singly-linked list of _Node objects, using shared_ptr
+  // for the links. Iterators into the list share ownership of the nodes.
+  // Each _Node contains a tzdb and a vector<Rule> with the rule set.
+  struct tzdb_list::_Node
+  {
+    shared_ptr<_Node> next;
+    tzdb db;
+    vector<Rule> rules;
+
+    // The following static members are here because making them members
+    // of this type gives them access to the private members of time_zone
+    // and tzdb, without needing them declared in the <chrono> header.
+
+    static tzdb_list _S_the_list;
+
+#if USE_ATOMIC_SHARED_PTR
+    using head_ptr = atomic<shared_ptr<_Node>>;
+#else
+    // Non-atomic, list_mutex must be locked to access it.
+    using head_ptr = shared_ptr<_Node>;
+#endif
+    // This is the owning reference to the first tzdb in the list.
+    static head_ptr _S_head_owner;
+
+    // Lock-free access to the head of the list.
+    static atomic<_Node*> _S_head;
+
+    static const tzdb& _S_init_tzdb();
+    static const tzdb& _S_replace_head(shared_ptr<_Node>, shared_ptr<_Node>);
+
+    static pair<vector<leap_second>, bool> _S_read_leap_seconds();
+  };
+
+  // Implementation of the private constructor used for the singleton object.
+  constexpr tzdb_list::tzdb_list(nullptr_t) { }
+
+  // The tzdb_list singleton. This doesn't contain the actual linked list,
+  // but it has member functions that give access to it.
+  constinit tzdb_list tzdb_list::_Node::_S_the_list(nullptr);
+
+  // Shared pointer to the first Node in the list.
+  constinit tzdb_list::_Node::head_ptr tzdb_list::_Node::_S_head_owner{nullptr};
+
+  // Lock-free access to the first Node in the list.
+  constinit atomic<tzdb_list::_Node*> tzdb_list::_Node::_S_head{nullptr};
+
+  // The data structures defined in this file (Rule, on_day, at_time etc.)
+  // are used to represent the information parsed from the tzdata.zi file
+  // described at https://man7.org/linux/man-pages/man8/zic.8.html#FILES
+
+  // N.B. Most stream extraction operations for time zones, rules etc.
+  // assume that setting failbit will throw an exception, so individual
+  // input operations are not always checked for success.
+
+  namespace
+  {
+#if ! USE_ATOMIC_SHARED_PTR
+#ifndef __GTHREADS
+    // Dummy no-op mutex type for single-threaded targets.
+    struct mutex { void lock() { } void unlock() { } };
+#endif
+    /// XXX std::mutex::mutex() not constexpr on Windows, so can't be constinit
+    constinit mutex list_mutex;
+#endif
+
+    // Used for reading a possibly-quoted string from a stream.
+    struct quoted
+    {
+      string& str;
+
+      friend istream& operator>>(istream& in, quoted&& q)
+      {
+	if (ws(in).peek() == '"')
+	  in >> std::quoted(q.str);
+	else
+	  in >> q.str;
+	return in;
+      }
+    };
+
+    // 32-bit version of chrono::seconds for offsets in the range [-24h,24h].
+    // Care must be taken to avoid overflow when using this in arithmetic.
+    // For example, if sys_days::rep is also 32-bit then the result of
+    // sys_days(1850y/January/1) + sec32_t(0) will be incorrect.
+    using sec32_t = duration<int_least32_t>;
+
+    // A time relative to midnight, as measured by the indicator clock.
+    struct at_time
+    {
+      sec32_t time{};
+      enum Indicator : unsigned char { Wall, Universal, Standard, Daylight };
+      Indicator indicator = Wall;
+
+      static pair<Indicator, bool> is_indicator(int c) noexcept
+      {
+	switch (c)
+	{
+	  case 's':
+	    return {Standard, true};
+	  case 'u':
+	  case 'g':
+	  case 'z':
+	    return {Universal, true};
+	  case 'w':
+	    return {Wall, true};
+	  case 'd':
+	    return {Daylight, true};
+	  default:
+	    return {Wall, false};
+	}
+      }
+
+      // Checks if the next character in the stream is an indicator.
+      // If not, indic is unchanged. Callers should set a default first.
+      friend istream& operator>>(istream& in, Indicator& indic)
+      {
+	auto [val, yes] = at_time::is_indicator(in.peek());
+	if (yes)
+	  {
+	    in.ignore(1);
+	    indic = val;
+	  }
+	return in;
+      }
+
+      friend istream& operator>>(istream& in, at_time& at);
+    };
+
+    // Wrapper for chrono::month that can be extracted from an istream
+    // as an abbreviated month name.
+    // The month name can be any unambiguous portion of a month name,
+    // e.g. "S" (September) or "Ja" (January), but not "Ju" (June/July).
+    struct abbrev_month
+    {
+      month m;
+
+      friend istream& operator>>(istream& in, abbrev_month& am);
+    };
+
+    // The IN and ON fields of a RULE record, e.g. "March lastSunday".
+    struct on_day
+    {
+      using rep = uint_least16_t;
+      // Equivalent to Kind, chrono::month, chrono::day, chrono::weekday,
+      // but half the size.
+      enum Kind : rep { DayOfMonth=0, LastWeekday, LessEq, GreaterEq };
+      Kind kind : 2 = DayOfMonth;
+      rep month : 4 = 0;        // [1,12]
+      rep day_of_month : 5 = 0; // [1,31]
+      rep day_of_week : 3 = 0;  // [0,6]
+
+      chrono::month
+      get_month() const noexcept
+      { return chrono::month{month}; }
+
+      chrono::day
+      get_day() const noexcept
+      { return chrono::day{day_of_month}; }
+
+      chrono::month_day
+      get_month_day() const noexcept
+      { return chrono::month_day{get_month(), get_day()}; }
+
+      bool ok() const noexcept
+      {
+	switch (kind)
+	{
+	case DayOfMonth:
+	  return day_of_month != 0;
+	case LastWeekday:
+	  return day_of_week != 7 && day_of_month == 0;
+	case LessEq:
+	case GreaterEq:
+	  return day_of_week != 7 && day_of_month != 0;
+	}
+      }
+
+      // Convert date like "last Sunday in June" or "Sunday <= June 30"
+      // to a specific date in the given year.
+      year_month_day pin(year y) const
+      {
+	year_month_day ymd;
+	if (kind == LastWeekday) // Last Sunday in June
+	  {
+	    month_weekday_last mwdl{get_month(),
+				    weekday_last{weekday{day_of_week}}};
+	    ymd = year_month_day{sys_days{y/mwdl}};
+	  }
+	else if (kind != DayOfMonth) // Sunday <= June 30 or Sunday >= June 30
+	  {
+	    sys_days date{y/get_month_day()};
+	    days diff;
+	    if (kind == LessEq)
+	      diff = -(weekday{date} - weekday{day_of_week});
+	    else
+	      diff = weekday{day_of_week} - weekday{date};
+	    // XXX need to handle underflow/overflow to another year?
+	    ymd = year_month_day{date + diff};
+	  }
+	else
+	  ymd = year_month_day{y, get_month(), get_day()};
+	return ymd;
+      }
+
+      friend istream& operator>>(istream&, on_day&);
+    };
+
+    // Wrapper for chrono::year that reads a year, or one of the keywords
+    // "minimum" or "maximum", or an unambiguous prefix of a keyword.
+    struct minmax_year
+    {
+      year& y;
+
+      friend istream& operator>>(istream& in, minmax_year&& y)
+      {
+	if (ws(in).peek() == 'm') // keywords "minimum" or "maximum"
+	  {
+	    string s;
+	    in >> s; // extract the rest of the word, but only look at s[1]
+	    if (s[1] == 'a')
+	      y.y = year::max();
+	    else if (s[1] == 'i')
+	      y.y = year::min();
+	    else
+	      in.setstate(ios::failbit);
+	  }
+	else if (int num = 0; in >> num)
+	  y.y = year{num};
+	return in;
+      }
+    };
+
+    // As above for minmax_year, but also supports the keyword "only",
+    // meaning that the TO year is the same as the FROM year.
+    struct minmax_year2
+    {
+      minmax_year to;
+      year from;
+
+      friend istream& operator>>(istream& in, minmax_year2&& y)
+      {
+	if (ws(in).peek() == 'o') // keyword "only"
+	  {
+	    string s;
+	    in >> s; // extract the whole keyword
+	    y.to.y = y.from;
+	  }
+	else
+	  in >> std::move(y.to);
+	return in;
+      }
+    };
+
+    // A time zone information record.
+    // Zone  NAME        STDOFF  RULES   FORMAT  [UNTIL]
+    // Zone  Asia/Amman  2:00    Jordan  EE%sT   2017 Oct 27 01:00
+    // Will be lazily expanded into sys_info objects as needed.
+    struct ZoneInfo
+    {
+      ZoneInfo() = default;
+
+      ZoneInfo(sys_info&& info)
+      : m_buf(std::move(info.abbrev)), m_expanded(true), m_save(info.save),
+	m_offset(info.offset), m_until(info.end)
+      { }
+
+      ZoneInfo(const pair<sys_info, string_view>& info)
+      : m_expanded(true), m_save(info.first.save), m_offset(info.first.offset),
+	m_until(info.first.end)
+      {
+	if (info.second.size())
+	  {
+	    m_buf = info.second; // LETTERS field
+	    m_buf += ' ';
+	    m_pos = m_buf.size();
+	  }
+	m_buf += info.first.abbrev;
+      }
+
+      // STDOFF: Seconds from UTC during standard time.
+      seconds
+      offset() const noexcept { return m_offset; }
+
+      // RULES: The name of the rules that apply for this period.
+      string_view
+      rules() const noexcept
+      {
+	string_view r;
+	if (m_pos != 0)
+	  r = {m_buf.data(), m_pos - 1u};
+	return r;
+      }
+
+      // FORMAT: The name of the time zone (might contain %s or %z).
+      string_view
+      format() const noexcept
+      { return {m_buf.data() + m_pos, m_buf.size() - m_pos}; }
+
+      // UNTIL: The time when this info no longer applies.
+      sys_seconds
+      until() const noexcept { return m_until; }
+
+      friend istream& operator>>(istream&, ZoneInfo&);
+
+      bool
+      expanded() const noexcept
+      { return m_expanded; }
+
+      // For an expanded ZoneInfo this returns the LETTERS that apply to the
+      // **next** sys_info after this one.
+      string_view
+      next_letters() const noexcept
+      { return m_expanded ? rules() : string_view{}; }
+
+
+      bool
+      to(sys_info& info) const
+      {
+	// If this object references a named Rule then we can't populate
+	// a sys_info yet.
+	if (!m_expanded)
+	  return false;
+
+	info.end = until();
+	info.offset = offset();
+	info.save = minutes(m_save);
+	info.abbrev = format();
+	return true;
+      }
+
+    private:
+      friend class time_zone;
+
+      void
+      set_abbrev(const string& abbrev)
+      {
+	// In practice, the FORMAT field never needs expanding here.
+	if (abbrev.find_first_of("/%") != abbrev.npos)
+	  __throw_runtime_error("std::chrono::time_zone: invalid data");
+	m_buf = abbrev;
+	m_pos = 0;
+	m_expanded = true;
+      }
+
+      void
+      set_rules_and_format(const string& rls, const string& fmt)
+      {
+	// Both strings are typically short enough to fit in one SSO string.
+	// As of tzdata 2022f the maximum is 14 chars, e.g. "AU +0845/+0945".
+	m_buf.reserve(rls.size() + 1 + fmt.size());
+	m_buf = rls;
+	m_buf += ' ';
+	m_buf += fmt;
+	m_pos = rls.size() + 1;
+      }
+
+      string m_buf;     // rules() + ' ' + format() OR letters + ' ' + format()
+      uint_least16_t m_pos : 15 = 0; // offset of format() in m_buf
+      uint_least16_t m_expanded : 1 = 0;
+      duration<int_least16_t, ratio<60>> m_save{};
+      sec32_t m_offset{};
+      sys_seconds m_until{};
+
+#if 0
+      // Consider making this class more compact, e.g.
+      int_least64_t offset_seconds : 18;
+      int_least64_t until_sys_seconds : 46;
+      uint_least32_t save_minutes : 12;
+      uint_least32_t pos : 20;
+      string buf; // abbrev OR "rules format"
+#endif
+    };
+
+    // A RULE record from the tzdata.zi timezone info file.
+    struct Rule
+    {
+      // This allows on_day to reuse padding of at_time.
+      // This keeps the size to 8 bytes and the alignment to 4 bytes.
+      struct datetime : at_time { on_day day; };
+      static_assert(sizeof(datetime) == 8 && alignof(datetime) == 4);
+
+      // TODO combining name+letters into a single string (like in ZoneInfo)
+      // would save sizeof(string) and make Rule fit in a single cacheline.
+      // Or don't store name in the Rule, and replace vector<Rule> with
+      // vector<pair<string,vector<Rule>>> i.e. map-like structure.
+
+      string name;    // the name of the rule set
+      year from{};    // first year in which the rule applies
+      year to{};      // final year in which the rule applies
+      datetime when;  // the day and time on which the rule takes effect
+      sec32_t save{}; // amount of time to be added when the rule is in effect
+      string letters; // variable part of TZ abbreviations when rule in effect
+
+      // Combine y + this->when + offset to give a UTC timestamp.
+      sys_seconds
+      start_time(year y, seconds offset) const
+      {
+	auto time = when.time;
+	if (when.indicator == at_time::Wall
+	      || when.indicator == at_time::Standard)
+	  time -= offset; // Convert local time to sys time.
+	return sys_days(when.day.pin(y)) + time;
+      }
+
+      friend istream& operator>>(istream& in, Rule& rule)
+      {
+	string str;
+
+	// Rule  NAME  FROM  TO  TYPE  IN  ON  AT  SAVE  LETTER/S
+
+	in >> quoted(rule.name)
+	   >> minmax_year{rule.from}
+	   >> minmax_year2{rule.to, rule.from};
+
+	if (char type; in >> type && type != '-')
+	  in.setstate(ios::failbit);
+	in >> rule.when.day >> static_cast<at_time&>(rule.when);
+	at_time save_time;
+	save_time.indicator = at_time::Wall; // not valid for this field
+	in >> save_time;
+	if (save_time.indicator != at_time::Wall)
+	  {
+	    // We don't actually store the save_time.indicator, because we
+	    // assume that it's always deducable from the actual offset value.
+	    auto expected = save_time.time == 0s
+			      ? at_time::Standard
+			      : at_time::Daylight;
+	    __glibcxx_assert(save_time.indicator == expected);
+	  }
+
+	rule.save = save_time.time;
+
+	in >> rule.letters;
+	if (rule.letters == "-")
+	  rule.letters.clear();
+	return in;
+      }
+
+#ifdef _GLIBCXX_ASSERTIONS
+      friend ostream& operator<<(ostream& out, const Rule& r)
+      {
+	out << "Rule " << r.name << ' ' << (int)r.from << ' ' << (int)r.to
+	    << ' ' << (unsigned)r.when.day.get_month() << ' ';
+	switch (r.when.day.kind)
+	{
+	case on_day::DayOfMonth:
+	  out << (unsigned)r.when.day.get_day();
+	  break;
+	case on_day::LastWeekday:
+	  out << "last" << weekday(r.when.day.day_of_week).c_encoding();
+	  break;
+	case on_day::LessEq:
+	  out << weekday(r.when.day.day_of_week).c_encoding() << " <= "
+	    << r.when.day.day_of_month;
+	  break;
+	case on_day::GreaterEq:
+	  out << weekday(r.when.day.day_of_week).c_encoding() << " >= "
+	    << r.when.day.day_of_month;
+	  break;
+	}
+	hh_mm_ss hms(r.when.time);
+	out << ' ' << hms.hours().count() << ':' << hms.minutes().count()
+	    << ':' << hms.seconds().count() << "wusd"[r.when.indicator];
+	out << ' ' << r.save.count();
+	if (!r.letters.empty())
+	  out << ' ' << r.letters;
+	else
+	  out << " -";
+	return out;
+      }
+#endif
+    };
+  } // namespace
+
+  // Private constructor used by reload_tzdb() to create time_zone objects.
+  time_zone::time_zone(unique_ptr<_Impl> __p) : _M_impl(std::move(__p)) { }
+
+  time_zone::~time_zone() = default;
+
+  // The opaque pimpl class stored in a time_zone object.
+  struct time_zone::_Impl
+  {
+    explicit
+    _Impl(weak_ptr<tzdb_list::_Node> node) : node(std::move(node)) { }
+
+    vector<ZoneInfo> infos; // Definitions of the time zone's transitions.
+
+    // Non-owning reference back to the tzdb that owns this time_zone.
+    // Needed to access the list of rules for the time zones.
+    weak_ptr<tzdb_list::_Node> node;
+
+#ifndef __GTHREADS
+    // Don't need synchronization for accessing the infos vector.
+#elif __cpp_lib_atomic_wait
+    atomic<int_least32_t> rules_counter;
+#else
+    mutex infos_mutex;
+#endif
+  };
+
+  namespace
+  {
+    bool
+    select_std_or_dst_abbrev(string& abbrev, minutes save)
+    {
+      if (size_t pos = abbrev.find('/'); pos != string::npos)
+	{
+	  // Select one of "STD/DST" for standard or daylight.
+	  if (save == 0min)
+	    abbrev.erase(pos);
+	  else
+	    abbrev.erase(0, pos + 1);
+	  return true;
+	}
+      return false;
+    }
+
+    // Set the sys_info::abbrev string by expanding any placeholders.
+    void
+    format_abbrev_str(sys_info& info, string_view letters = {})
+    {
+      if (size_t pos = info.abbrev.find("%s"); pos != string::npos)
+	{
+	  // Expand "%s" to the variable part, given by Rule::letters.
+	  info.abbrev.replace(pos, 2, letters);
+	}
+      else if (size_t pos = info.abbrev.find("%z"); pos != string::npos)
+	{
+	  // Expand "%z" to the UT offset as +/-hh, +/-hhmm, or +/-hhmmss.
+	  hh_mm_ss<seconds> t(info.offset);
+	  string z(1, "+-"[t.is_negative()]);
+	  long val = t.hours().count();
+	  if (minutes m = t.minutes(); m != m.zero())
+	    {
+	      val *= 100;
+	      val += m.count();
+	      if (seconds s = t.seconds(); s != s.zero())
+		{
+		  val *= 100;
+		  val += s.count();
+		}
+	    }
+	  z += std::to_string(val);
+	  info.abbrev.replace(pos, 2, z);
+	}
+      else
+	select_std_or_dst_abbrev(info.abbrev, info.save);
+    }
+  }
+
+  // Implementation of std::chrono::time_zone::get_info(const sys_time<D>&)
+  sys_info
+  time_zone::_M_get_sys_info(sys_seconds tp) const
+  {
+    // This gives us access to the node->rules vector, but also ensures
+    // that the tzdb node won't get erased while we're still using it.
+    const auto node = _M_impl->node.lock();
+    auto& infos = _M_impl->infos;
+
+#ifndef __GTHREADS
+#elif __cpp_lib_atomic_wait
+    // Prevent concurrent access to _M_impl->infos if it might need to change.
+    struct Lock
+    {
+      Lock(atomic<int_least32_t>& counter) : counter(counter)
+      {
+	// If counter is non-zero then the contents of _M_impl->info might
+	// need to be changed, so only one thread is allowed to access it.
+	for (auto c = counter.load(memory_order::relaxed); c != 0;)
+	  {
+	    // Setting counter to negative means this thread has the lock.
+	    if (c > 0 && counter.compare_exchange_strong(c, -c))
+	      return;
+
+	    if (c < 0)
+	      {
+		// Counter is negative, another thread already has the lock.
+		counter.wait(c);
+		c = counter.load();
+	      }
+	  }
+      }
+
+      ~Lock()
+      {
+	if (auto c = counter.load(memory_order::relaxed); c < 0)
+	  {
+	    counter.store(-c, memory_order::release);
+	    counter.notify_one();
+	  }
+      }
+
+      atomic<int_least32_t>& counter;
+    };
+    Lock lock{_M_impl->rules_counter};
+#else
+    // Keep it simple, just use a mutex for all access.
+    lock_guard<mutex> lock(_M_impl->infos_mutex);
+#endif
+
+    // Find the transition info for the time point.
+    auto i = ranges::upper_bound(infos, tp, ranges::less{}, &ZoneInfo::until);
+
+    if (i == infos.end())
+      {
+	if (infos.empty())
+	  __throw_runtime_error("std::chrono::time_zone::get_info: invalid data");
+	tp = (--i)->until();
+    }
+
+    sys_info info;
+
+    if (i == infos.begin())
+      info.begin = sys_days(year::min()/January/1);
+    else
+      info.begin = i[-1].until();
+
+    if (i->to(info)) // We already know a sys_info for this time.
+      return info;
+
+    // Otherwise, we have a ZoneInfo object that describes the applicable
+    // transitions in terms of a set of named rules that vary by year.
+    // Replace that rules-based ZoneInfo object with a sequence of one or more
+    // objects that map directly to a sys_info value.
+    const ZoneInfo& ri = *i;
+
+    // Find the rules named by ri.rules()
+    auto rules = ranges::equal_range(node->rules, ri.rules(),
+				     ranges::less{}, &Rule::name);
+
+    if (ranges::empty(rules))
+      __throw_runtime_error("std::chrono::time_zone::get_info: invalid data");
+
+    vector<pair<sys_info, string_view>> new_infos;
+    if (int n = ceil<years>(tp - info.begin).count())
+      new_infos.reserve(std::min(100, n * 2));
+    long result_index = -1;
+    int num_after = 4; // number of sys_info to generate past tp.
+
+    // The following initial values for info.offset, info.save, and letters
+    // are only valid if the first sys_info we are generating uses the time
+    // zone's standard time, because daylight time would need non-zero offset.
+    // This is true by construction, because this function always tries to
+    // finish so that the last ZoneInfo object expanded is for daylight time.
+    // This means that i[-1] is either an expanded ZoneInfo for a DST sys_info
+    // or is an unexpanded (rule-based) ZoneInfo for a different rule, and
+    // rule changes always occur between periods of standard time.
+    info.offset = ri.offset();
+    info.save = 0min;
+    // XXX The ri.until() time point should be
+    // "interpreted using the rules in effect just before the transition"
+    info.end = ri.until();
+    info.abbrev = ri.format();
+
+    string_view letters;
+    if (i != infos.begin())
+      {
+	if (i[-1].expanded())
+	  letters = i[-1].next_letters();
+	// XXX else need to find Rule active before this time and use it
+	// to know the initial offset, save, and letters.
+      }
+
+    const Rule* curr_rule = nullptr;
+
+    while (info.begin < info.end && num_after > 0)
+      {
+	sys_seconds t = info.begin;
+	const year_month_day date(chrono::floor<days>(t));
+	const Rule* next_rule = nullptr;
+
+	// Check every rule to find the next transition after t.
+	for (const auto& rule : rules)
+	  {
+	    if (&rule == curr_rule) // don't bother checking this one again
+	      continue;
+
+	    if (date.year() > rule.to) // rule no longer applies at time t
+	      continue;
+
+	    sys_seconds rule_start;
+
+	    seconds offset{}; // appropriate for at_time::Universal
+	    if (rule.when.indicator == at_time::Wall)
+	      offset = info.offset;
+	    else if (rule.when.indicator == at_time::Standard)
+	      offset = ri.offset();
+
+	    if (date.year() < rule.from) // rule doesn't apply yet at time t
+	      {
+		// Find first transition for this rule:
+		rule_start = rule.start_time(rule.from, offset);
+	      }
+	    else // rule applies in the year that contains time t
+	      {
+		year y = date.year();
+		// Time the rule takes effect this year:
+		rule_start = rule.start_time(y, offset);
+
+		if (rule_start < t && rule.to > y)
+		  {
+		    // Try this rule in the following year.
+		    rule_start = rule.start_time(++y, offset);
+		  }
+	      }
+
+	    if (t < rule_start && rule_start < info.end)
+	      {
+		if (rule_start - t < days(1)) // XXX shouldn't be needed!
+		  continue;
+
+		// Found a closer transition than the previous info.end.
+		info.end = rule_start;
+		next_rule = &rule;
+	      }
+	  }
+
+	format_abbrev_str(info, letters);
+
+	bool merged = false;
+#if 0
+	if (!new_infos.empty())
+	  {
+	    auto& back = new_infos.back();
+	    if (back.offset == info.offset && back.abbrev == info.abbrev
+		  && back.save == info.save)
+	      {
+		// This is a continuation of the previous sys_info.
+		back.end = info.end;
+		merged = true;
+	      }
+	  }
+#endif
+
+	if (next_rule)
+	  letters = next_rule->letters;
+	else
+	  letters = {};
+
+	if (!merged)
+	  new_infos.emplace_back(info, letters);
+
+	if (info.begin <= tp && tp < info.end) // Found the result.
+	  result_index = new_infos.size() - 1;
+	else if (result_index >= 0 && !merged)
+	  {
+	    // Finish on a DST sys_info if possible, so that if we resume
+	    // generating sys_info objects after this time point, save=0
+	    // should be correct for the next sys_info.
+	    if (num_after > 1 || info.save != 0min)
+	      --num_after;
+	  }
+
+	info.begin = info.end;
+	if (next_rule)
+	  {
+	    info.end = ri.until();
+	    info.offset = ri.offset() + next_rule->save;
+	    info.save = duration_cast<minutes>(next_rule->save);
+	    info.abbrev = ri.format();
+	    letters = next_rule->letters;
+	    curr_rule = next_rule;
+	  }
+      }
+
+    if (new_infos.empty() || result_index < 0)
+      __throw_runtime_error("time_zone::get_info");
+
+    info = new_infos[result_index].first;
+
+    if (new_infos.back().first.end < ri.until())
+      {
+	// Insert the new sys_info objects but don't remove the rules_info.
+	infos.insert(i, new_infos.begin(), new_infos.end());
+      }
+    else
+      {
+	// Replace the rules_info at *i with the sys_info objects in new_infos.
+
+	// First note the index of *i because we will invalidate i.
+	result_index = i - infos.begin();
+	// Insert everything except new_infos.front() at the end of infos:
+	i = infos.insert(infos.end(), new_infos.begin() + 1, new_infos.end());
+	// Then rotate those new elements into place:
+	std::rotate(infos.begin() + result_index + 1, i, infos.end());
+	// Then replace the original rules_info object with new_infos.front():
+	infos[result_index] = ZoneInfo(new_infos.front());
+#if defined __GTHREADS && __cpp_lib_atomic_wait
+	if (++_M_impl->rules_counter == 0) // No more unexpanded infos.
+	  _M_impl->rules_counter.notify_all();
+#endif
+      }
+
+    return info;
+  }
+
+  // Implementation of std::chrono::time_zone::get_info(const local_time<D>&)
+  local_info
+  time_zone::_M_get_local_info(local_seconds tp) const
+  {
+    const auto node = _M_impl->node.lock();
+
+    local_info info{};
+    // Get sys_info assuming no offset between local time and UTC:
+    info.first = _M_get_sys_info(sys_seconds(tp.time_since_epoch()));
+
+    // Convert to UTC using the real offset:
+    sys_seconds st(tp.time_since_epoch() - info.first.offset);
+
+    if ((st - info.first.begin) <= days(1))
+      {
+	sys_info prev = _M_get_sys_info(info.first.begin - 1s);
+	sys_seconds prevst(tp.time_since_epoch() - prev.offset);
+	if (st < info.first.begin)
+	  {
+	    if (prevst < info.first.begin)
+	      {
+		// tp is a unique local time, prev is the correct sys_info.
+		info.first = prev;
+	      }
+	    else
+	      {
+		// The local time is nonexistent, falling within a clock change
+		// e.g. there is no 1:30am if DST moves clock from 1am to 2am.
+		__glibcxx_assert(prev.offset < info.first.offset); // start DST
+		info.result = local_info::nonexistent;
+		info.second = info.first;
+		info.first = prev;
+	      }
+	  }
+	else if (prevst < info.first.begin)
+	  {
+	    // The local time is ambiguous, referring to two possible UTC times
+	    // e.g. 1:30am happens twice if clock moves back from 2am to 1am.
+	    __glibcxx_assert(prev.offset > info.first.offset); // DST ended
+	    info.result = local_info::ambiguous;
+	    info.second = info.first;
+	    info.first = prev;
+	  }
+	// else tp is a unique local time, info.first is the correct sys_info.
+      }
+    else if ((info.first.end - st) <= days(1))
+      {
+	sys_info next = _M_get_sys_info(info.first.end);
+	sys_seconds nextst(tp.time_since_epoch() - next.offset);
+	if (st >= info.first.end)
+	  {
+	    if (nextst >= info.first.end)
+	      {
+		// tp is a unique local time, next is the correct sys_info.
+		info.first = next;
+	      }
+	    else
+	      {
+		info.result = local_info::nonexistent;
+		info.second = next;
+	      }
+	  }
+	else if (nextst >= info.first.end)
+	  {
+	    info.result = local_info::ambiguous;
+	    info.second = next;
+	  }
+	// else tp is a unique local time, info.first is the correct sys_info.
+      }
+    return info;
+  }
+
+#ifndef _GLIBCXX_ZONEINFO_DIR
+# define _GLIBCXX_ZONEINFO_DIR "/usr/share/zoneinfo"
+#endif
+ namespace
+ {
+    string
+    zoneinfo_dir()
+    {
+      static const string dir = __gnu_cxx::zoneinfo_dir_override
+				  ? __gnu_cxx::zoneinfo_dir_override()
+				  : _GLIBCXX_ZONEINFO_DIR;
+      return dir;
+    }
+
+    const string tzdata_file = "/tzdata.zi";
+    const string leaps_file = "/leapseconds";
+  }
+
+  // Return leap_second values, and a bool indicating whether the values are
+  // current (true), or potentially out of date (false).
+  pair<vector<leap_second>, bool>
+  tzdb_list::_Node::_S_read_leap_seconds()
+  {
+    const string filename = zoneinfo_dir() + leaps_file;
+
+    // This list is valid until at least 2023-06-28 00:00:00 UTC.
+    auto expires = sys_days{2023y/6/28};
+    vector<leap_second> leaps
+    {
+      (leap_second)  78796800, // 1 Jul 1972
+      (leap_second)  94694400, // 1 Jan 1973
+      (leap_second) 126230400, // 1 Jan 1974
+      (leap_second) 157766400, // 1 Jan 1975
+      (leap_second) 189302400, // 1 Jan 1976
+      (leap_second) 220924800, // 1 Jan 1977
+      (leap_second) 252460800, // 1 Jan 1978
+      (leap_second) 283996800, // 1 Jan 1979
+      (leap_second) 315532800, // 1 Jan 1980
+      (leap_second) 362793600, // 1 Jul 1981
+      (leap_second) 394329600, // 1 Jul 1982
+      (leap_second) 425865600, // 1 Jul 1983
+      (leap_second) 489024000, // 1 Jul 1985
+      (leap_second) 567993600, // 1 Jan 1988
+      (leap_second) 631152000, // 1 Jan 1990
+      (leap_second) 662688000, // 1 Jan 1991
+      (leap_second) 709948800, // 1 Jul 1992
+      (leap_second) 741484800, // 1 Jul 1993
+      (leap_second) 773020800, // 1 Jul 1994
+      (leap_second) 820454400, // 1 Jan 1996
+      (leap_second) 867715200, // 1 Jul 1997
+      (leap_second) 915148800, // 1 Jan 1999
+      (leap_second)1136073600, // 1 Jan 2006
+      (leap_second)1230768000, // 1 Jan 2009
+      (leap_second)1341100800, // 1 Jul 2012
+      (leap_second)1435708800, // 1 Jul 2015
+      (leap_second)1483228800, // 1 Jan 2017
+    };
+
+#if 0
+    // This optimization isn't valid if the file has additional leap seconds
+    // defined since the library was compiled, but the system clock has been
+    // set to a time before the hardcoded expiration date.
+    if (system_clock::now() < expires)
+      return {std::move(leaps), true};
+#endif
+
+    auto exp_year = year_month_day(expires).year();
+
+    if (ifstream ls{filename})
+      {
+	std::string s, w;
+	s.reserve(80); // Avoid later reallocations.
+	while (std::getline(ls, s))
+	  {
+	    // Leap  YEAR  MONTH  DAY  HH:MM:SS  CORR  R/S
+
+	    if (!s.starts_with("Leap"))
+	      continue;
+	    istringstream li(std::move(s));
+	    li.exceptions(ios::failbit);
+	    li.ignore(4);
+	    unsigned yval;
+	    if (li >> yval)
+	      {
+		if (year y(yval); y >= exp_year) // Only process new entries.
+		  {
+		    li >> w;
+		    char m = w[0];
+		    if (m != 'J' && m != 'D')
+		      return {std::move(leaps), false};
+
+		    const int is_december = m == 'D';
+		    year_month_day ymd{y, month(6 + 6 * is_december),
+				       day(30 + is_december)};
+		    sys_seconds secs(sys_days(ymd) + days(1));
+		    li >> w >> w >> m;
+
+		    if (m != '+' && m != '-')
+		      return {std::move(leaps), false};
+
+		    seconds::rep val = secs.time_since_epoch().count();
+		    if (m == '-') [[unlikely]]
+		      val = -(val - 1); // -ve leap second happens at 23:59:59
+
+		    if (leap_second ls{val}; ls > leaps.back())
+		      leaps.push_back(ls);
+		  }
+	      }
+	    s = std::move(li).str(); // return storage to s
+	  }
+	return {std::move(leaps), true};
+      }
+    else
+      return {std::move(leaps), false};
+  }
+
+  namespace
+  {
+    // Read the version number from a tzdata.zi file.
+    string
+    remote_version(istream* zif)
+    {
+#if defined __NetBSD__
+    if (string ver; ifstream(zoneinfo_dir() + "/TZDATA_VERSION") >> ver)
+      return ver;
+#elif defined __APPLE__
+    if (string ver; ifstream(zoneinfo_dir() + "/+VERSION") >> ver)
+      return ver;
+#else
+      ifstream f;
+      if (!zif)
+	{
+	  f.open(zoneinfo_dir() + tzdata_file);
+	  zif = &f;
+	}
+      char hash;
+      string label;
+      string version;
+      if (*zif >> hash >> label >> version)
+	if (hash == '#' && label == "version")
+	  return version;
+#endif
+      __throw_runtime_error("tzdb: no version found in tzdata.zi");
+    }
+  }
+
+  // Definition of std::chrono::remote_version()
+  string remote_version()
+  {
+    return remote_version(nullptr);
+  }
+
+  // Used by chrono::reload_tzdb() to add a new node to the front of the list.
+  const tzdb&
+  tzdb_list::_Node::_S_replace_head(shared_ptr<_Node> curr [[maybe_unused]],
+				    shared_ptr<_Node> new_head)
+  {
+#if USE_ATOMIC_SHARED_PTR
+    new_head->next = curr;
+    while (!_S_head_owner.compare_exchange_strong(curr, new_head))
+      {
+	if (curr->db.version == new_head->db.version)
+	  return curr->db;
+	new_head->next = curr;
+      }
+    // XXX small window here where _S_head still points to previous tzdb.
+    _Node::_S_head = new_head.get();
+    return new_head->db;
+#else
+    lock_guard<mutex> l(list_mutex);
+    if (const _Node* h = _S_head)
+      {
+	if (h->db.version == new_head->db.version)
+	  return h->db;
+	new_head->next = _S_head_owner;
+      }
+    auto* pnode = new_head.get();
+    _S_head_owner = std::move(new_head);
+    _S_head = pnode;
+    return pnode->db;
+#endif
+  }
+
+  // Called to populate the list for the first time. If reload_tzdb() fails,
+  // it creates a tzdb that only contains the UTC and GMT time zones.
+  const tzdb&
+  tzdb_list::_Node::_S_init_tzdb()
+  {
+    try
+      {
+	return reload_tzdb();
+      }
+    catch (const std::exception&)
+      {
+	auto [leaps, ok] = _S_read_leap_seconds();
+
+	using Node = tzdb_list::_Node;
+	auto node = std::make_shared<tzdb_list::_Node>();
+	node->db.version = "ersatz";
+	node->db.leap_seconds = std::move(leaps);
+	node->db.zones.reserve(2);
+	node->db.links.reserve(7);
+
+	time_zone zone(nullptr);
+	time_zone_link link(nullptr);
+	sys_info info{sys_seconds::min(), sys_seconds::max(), 0s, 0min, ""};
+
+	zone._M_impl = std::make_unique<time_zone::_Impl>(node);
+	zone._M_name = "Etc/UTC";
+	info.abbrev = "UTC";
+	zone._M_impl->infos.push_back(std::move(info));
+
+	link._M_target = zone._M_name;
+	link._M_name = "UTC";
+	node->db.links.push_back(std::move(link));
+	for (auto name : {"Etc/UCT", "Etc/Universal", "Etc/Zulu"})
+	  {
+	    link._M_target = zone._M_name;
+	    link._M_name = name;
+	    node->db.links.push_back(std::move(link));
+	    link._M_target = zone._M_name;
+	    link._M_name = name + 4;
+	    node->db.links.push_back(std::move(link));
+	  }
+	node->db.zones.emplace_back(std::move(zone));
+
+	zone._M_impl = std::make_unique<time_zone::_Impl>(node);
+	zone._M_name = "Etc/GMT";
+	info.abbrev = "GMT";
+	zone._M_impl->infos.push_back(std::move(info));
+
+	link._M_target = zone._M_name;
+	link._M_name = "GMT";
+	node->db.links.push_back(std::move(link));
+	for (auto name : {"Etc/GMT+0", "Etc/GMT-0", "Etc/GMT0", "Etc/Greenwich"})
+	  {
+	    link._M_target = zone._M_name;
+	    link._M_name = name;
+	    node->db.links.push_back(std::move(link));
+	    link._M_target = zone._M_name;
+	    link._M_name = name + 4;
+	    node->db.links.push_back(std::move(link));
+	  }
+	node->db.zones.emplace_back(std::move(zone));
+
+	ranges::sort(node->db.zones);
+	ranges::sort(node->db.links);
+	return Node::_S_replace_head(nullptr, std::move(node));
+      }
+  }
+
+  // There are only three ways for users to access the tzdb list.
+  // get_tzdb_list() returns a reference to the list itself.
+  // get_tzdb() returns a reference to the front of the list.
+  // reload_tzdb() returns a reference to the (possibly new) front of the list.
+  // Those are the only functions that need to check whether the list has
+  // been populated already.
+
+  // Implementation of std::chrono::get_tzdb_list()
+  tzdb_list&
+  get_tzdb_list()
+  {
+    using Node = tzdb_list::_Node;
+    if (Node::_S_head.load(memory_order::acquire) == nullptr) [[unlikely]]
+      Node::_S_init_tzdb(); // populates list
+    return Node::_S_the_list;
+  }
+
+  // Implementation of std::chrono::get_tzdb()
+  const tzdb&
+  get_tzdb()
+  {
+    using Node = tzdb_list::_Node;
+    if (auto* __p = Node::_S_head.load(memory_order::acquire)) [[likely]]
+      return __p->db;
+    return Node::_S_init_tzdb(); // populates list
+  }
+
+  // Implementation of std::chrono::reload_tzdb()
+  const tzdb&
+  reload_tzdb()
+  {
+    using Node = tzdb_list::_Node;
+
+    ifstream zif(zoneinfo_dir() + tzdata_file);
+    const string version = remote_version(&zif);
+
+#if USE_ATOMIC_SHARED_PTR
+    auto head = Node::_S_head_owner.load(memory_order::acquire);
+    if (head != nullptr && head->db.version == version)
+      return head->db;
+#else
+    if (Node::_S_head.load(memory_order::relaxed) != nullptr) [[likely]]
+    {
+      lock_guard<mutex> l(list_mutex);
+      const tzdb& current = Node::_S_head_owner->db;
+      if (current.version == version)
+	return current;
+    }
+#endif
+
+    auto [leaps, leaps_ok] = Node::_S_read_leap_seconds();
+    if (!leaps_ok)
+      __throw_runtime_error("tzdb: cannot parse leapseconds file");
+
+    auto node = std::make_shared<Node>();
+    node->db.version = std::move(version);
+    node->db.leap_seconds = std::move(leaps);
+
+    string line, type;
+    line.reserve(80); // Maximum allowed line is 511 but much less in practice.
+    istringstream is;
+    is.exceptions(ios::failbit);
+    int lineno = 0;
+    while (std::getline(zif, line))
+      {
+	++lineno;
+	if (line.empty())
+	  continue;
+	is.str(std::move(line));
+	is.clear();
+	ws(is);
+	int c = is.eof() ? '#' : is.peek();
+	__try
+	  {
+	    switch (c)
+	    {
+	      case '#':
+		break;
+	      case 'R':
+	      {
+		// Rule  NAME  FROM  TO  TYPE  IN  ON  AT  SAVE  LETTER/S
+		is >> type; // extract the "Rule" or "R" marker
+		Rule rule;
+		is >> rule;
+		node->rules.push_back(std::move(rule));
+		break;
+	      }
+	      case 'L':
+	      {
+		// Link  TARGET           LINK-NAME
+		is >> type; // extract the "Link" or "L" marker
+		time_zone_link link(nullptr);
+		is >> quoted(link._M_target) >> quoted(link._M_name);
+		node->db.links.push_back(std::move(link));
+		break;
+	      }
+	      case 'Z':
+	      {
+		// Zone  NAME        STDOFF  RULES   FORMAT  [UNTIL]
+		is >> type; // extract the "Zone" or "Z" marker
+		time_zone tz(std::make_unique<time_zone::_Impl>(node));
+		is >> quoted(tz._M_name);
+		node->db.zones.push_back(time_zone(std::move(tz)));
+		[[fallthrough]]; // Use default case to parse rest of line ...
+	      }
+	      default: // Continuation of the previous Zone line.
+	      {
+		// STDOFF  RULES   FORMAT  [UNTIL]
+		if (type[0] != 'Z')
+		  is.setstate(ios::failbit);
+
+		auto& impl = *node->db.zones.back()._M_impl;
+		ZoneInfo& info = impl.infos.emplace_back();
+		is >> info;
+
+#if defined __GTHREADS && __cpp_lib_atomic_wait
+		// Keep count of ZoneInfo objects that refer to named Rules.
+		if (!info.rules().empty())
+		    impl.rules_counter.fetch_add(1, memory_order::relaxed);
+#endif
+	      }
+	    }
+	  }
+	__catch (const ios::failure&)
+	  {
+	    ostringstream ss;
+	    ss << "std::chrono::reload_tzdb: parse error at line " << lineno
+	       << ": " << std::move(is).str();
+	    __throw_runtime_error(std::move(ss).str().c_str());
+	  }
+
+	line = std::move(is).str(); // return storage to line
+      }
+
+    ranges::sort(node->db.zones, {}, &time_zone::name);
+    ranges::sort(node->db.links, {}, &time_zone_link::name);
+    ranges::stable_sort(node->rules, {}, &Rule::name);
+
+#if ! USE_ATOMIC_SHARED_PTR
+    shared_ptr<Node> head;
+#endif
+    return Node::_S_replace_head(std::move(head), std::move(node));
+  }
+
+  // Any call to tzdb_list::front() or tzdb_list::begin() must follow
+  // a call to get_tzdb_list() so the list has already been populated.
+
+  // Implementation of std::chrono::tzdb_list::front().
+  const tzdb&
+  tzdb_list::front() const noexcept
+  {
+    return _Node::_S_head.load()->db;
+  }
+
+  // Implementation of std::chrono::tzdb_list::begin().
+  auto
+  tzdb_list::begin() const noexcept
+  -> const_iterator
+  {
+#if USE_ATOMIC_SHARED_PTR
+    return const_iterator{_Node::_S_head_owner.load()};
+#else
+    lock_guard<mutex> l(list_mutex);
+    return const_iterator{_Node::_S_head_owner};
+#endif
+  }
+
+  // Implementation of std::chrono::tzdb_list::erase_after(const_iterator).
+  auto
+  tzdb_list::erase_after(const_iterator p)
+  -> const_iterator
+  {
+    if (p._M_node) [[likely]]
+    {
+#if ! USE_ATOMIC_SHARED_PTR
+      lock_guard<mutex> l(list_mutex);
+#endif
+      if (auto next = p._M_node->next) [[likely]]
+	return const_iterator{p._M_node->next = std::move(next->next)};
+    }
+
+    // This is undefined, but let's be kind:
+    std::__throw_logic_error("std::tzdb_list::erase_after: iterator is not "
+			     "dereferenceable");
+  }
+
+  // Private constructor for tzdb_list::const_iterator.
+  // Only used within this file, so can be inline.
+  inline
+  tzdb_list::
+  const_iterator::const_iterator(const shared_ptr<_Node>& __p) noexcept
+  : _M_node(__p)
+  { }
+
+  // Implementation of std::chrono::tzdb_list::const_iterator::operator*().
+  auto
+  tzdb_list::const_iterator::operator*() const noexcept
+  -> reference
+  {
+    return _M_node->db;
+  }
+
+  // Implementation of std::chrono::tzdb_list::const_iterator::operator++().
+  auto
+  tzdb_list::const_iterator::operator++()
+  -> const_iterator&
+  {
+    auto cur = std::move(_M_node);
+    _M_node = cur->next;
+    return *this;
+  }
+
+  // Implementation of std::chrono::tzdb_list::const_iterator::operator++(int).
+  auto
+  tzdb_list::const_iterator::operator++(int)
+  -> const_iterator
+  {
+    auto tmp = std::move(*this);
+    _M_node = tmp._M_node->next;
+    return tmp;
+  }
+
+  namespace
+  {
+    const time_zone*
+    do_locate_zone(const vector<time_zone>& zones,
+		   const vector<time_zone_link>& links,
+		   string_view tz_name) noexcept
+    {
+      // Lambda mangling changed between -fabi-version=2 and -fabi-version=18
+      auto search = []<class Vec>(const Vec& v, string_view name) {
+	auto pos = ranges::lower_bound(v, name, {}, &Vec::value_type::name);
+	auto ptr = pos.base();
+	if (pos == v.end() || pos->name() != name)
+	  ptr = nullptr;
+	return ptr;
+      };
+
+      if (auto tz = search(zones, tz_name))
+	return tz;
+
+      if (auto tz_l = search(links, tz_name))
+	return search(zones, tz_l->target());
+
+      return nullptr;
+    }
+  } // namespace
+
+  // Implementation of std::chrono::tzdb::locate_zone(string_view).
+  const time_zone*
+  tzdb::locate_zone(string_view tz_name) const
+  {
+    if (auto tz = do_locate_zone(zones, links, tz_name))
+      return tz;
+    string_view err = "tzdb: cannot locate zone: ";
+    string str;
+    str.reserve(err.size() + tz_name.size());
+    str += err;
+    str += tz_name;
+    __throw_runtime_error(str.c_str());
+  }
+
+  // Implementation of std::chrono::tzdb::current_zone().
+  const time_zone*
+  tzdb::current_zone() const
+  {
+    // TODO cache this function's result?
+
+    error_code ec;
+    // This should be a symlink to e.g. /usr/share/zoneinfo/Europe/London
+    auto path = filesystem::read_symlink("/etc/localtime", ec);
+    if (!ec)
+      {
+	auto first = path.begin(), last = path.end();
+	if (std::distance(first, last) > 2)
+	  {
+	    --last;
+	    string name = std::prev(last)->string() + '/';
+	    name += last->string();
+	    if (auto tz = do_locate_zone(this->zones, this->links, name))
+	      return tz;
+	  }
+      }
+    // Otherwise, look for a file naming the time zone.
+    string_view files[] {
+      "/etc/timezone",    // Debian derivates
+      "/var/db/zoneinfo", // FreeBSD
+    };
+    for (auto f : files)
+      {
+	std::ifstream tzf{string{f}};
+	if (std::string name; std::getline(tzf, name))
+	  if (auto tz = do_locate_zone(this->zones, this->links, name))
+	    return tz;
+      }
+
+    // TODO AIX stores current zone in $TZ in /etc/environment but the value
+    // is typically a POSIX time zone name, not IANA zone.
+    // https://developer.ibm.com/articles/au-aix-posix/
+    // https://www.ibm.com/support/pages/managing-time-zone-variable-posix
+
+    __throw_runtime_error("tzdb: cannot determine current zone");
+  }
+
+  // Implementation of std::chrono::locate_zone(string_view)
+  // TODO define this inline in the header instead?
+  const time_zone*
+  locate_zone(string_view tz_name)
+  {
+    // Use begin() so the tzdb cannot be erased while this operation runs.
+    return get_tzdb_list().begin()->locate_zone(tz_name);
+  }
+
+  // Implementation of std::chrono::current_zone()
+  // TODO define this inline in the header instead?
+  const time_zone*
+  current_zone()
+  {
+    // Use begin() so the tzdb cannot be erased while this operation runs.
+    return get_tzdb_list().begin()->current_zone();
+  }
+
+  namespace
+  {
+    istream& operator>>(istream& in, abbrev_month& am)
+    {
+      string s;
+      in >> s;
+      switch (s[0])
+      {
+      case 'J':
+	switch (s[1])
+	{
+	case 'a':
+	  am.m = January;
+	  return in;
+	case 'u':
+	  switch (s[2])
+	  {
+	  case 'n':
+	    am.m = June;
+	    return in;
+	  case 'l':
+	    am.m = July;
+	    return in;
+	  }
+	  break;
+	}
+	break;
+      case 'F':
+	am.m = February;
+	return in;
+      case 'M':
+	if (s[1] == 'a') [[likely]]
+	  switch (s[2])
+	  {
+	  case 'r':
+	    am.m = March;
+	    return in;
+	  case 'y':
+	    am.m = May;
+	    return in;
+	  }
+	break;
+      case 'A':
+	switch (s[1])
+	{
+	case 'p':
+	  am.m = April;
+	  return in;
+	case 'u':
+	  am.m = August;
+	  return in;
+	}
+	break;
+      case 'S':
+	am.m = September;
+	return in;
+      case 'O':
+	am.m = October;
+	return in;
+      case 'N':
+	am.m = November;
+	return in;
+      case 'D':
+	am.m = December;
+	return in;
+      }
+      in.setstate(ios::failbit);
+      return in;
+    }
+
+    // Wrapper for chrono::weekday that can be extracted from an istream
+    // as an abbreviated weekday name.
+    // The weekday name can be any unambiguous portion of a weekday name,
+    // e.g. "M" (Monday) or "Su" (Sunday), but not "T" (Tuesday/Thursday).
+    struct abbrev_weekday
+    {
+      weekday wd;
+
+      friend istream& operator>>(istream& in, abbrev_weekday& aw)
+      {
+	// Do not read a whole word from the stream, in some cases
+	// the weekday is only part of a larger word like "Sun<=25".
+	// Just peek at one char at a time.
+	switch (in.peek())
+	{
+	case 'M':
+	  aw.wd = Monday;
+	  break;
+	case 'T':
+	  in.ignore(1); // Discard the 'T'
+	  switch (in.peek())
+	  {
+	  case 'u':
+	    aw.wd = Tuesday;
+	    break;
+	  case 'h':
+	    aw.wd = Thursday;
+	    break;
+	  default:
+	    in.setstate(ios::failbit);
+	  }
+	  break;
+	case 'W':
+	  aw.wd = Wednesday;
+	  break;
+	case 'F':
+	  aw.wd = Friday;
+	  break;
+	case 'S':
+	  in.ignore(1); // Discard the 'S'
+	  switch (in.peek())
+	  {
+	  case 'a':
+	    aw.wd = Saturday;
+	    break;
+	  case 'u':
+	    aw.wd = Sunday;
+	    break;
+	  default:
+	    in.setstate(ios::failbit);
+	  }
+	  break;
+	default:
+	  in.setstate(ios::failbit);
+	}
+	in.ignore(1); // Discard whichever char we just looked at.
+
+	// Discard any remaining chars from weekday, e.g. "onday".
+	string_view day_chars = "ondayesritu";
+	auto is_day_char = [&day_chars](int c) {
+	  return c != char_traits<char>::eof()
+		   && day_chars.find((char)c) != day_chars.npos;
+	};
+	while (is_day_char(in.peek()))
+	  in.ignore(1);
+
+	return in;
+      }
+    };
+
+    istream& operator>>(istream& in, on_day& to)
+    {
+      on_day on{};
+      abbrev_month m{};
+      in >> m;
+      on.month = static_cast<unsigned>(m.m);
+      int c = ws(in).peek();
+      if ('0' <= c && c <= '9')
+	{
+	  on.kind = on_day::DayOfMonth;
+	  unsigned d;
+	  in >> d;
+	  if (d <= 31) [[likely]]
+	    {
+	      on.day_of_month = d;
+	      to = on;
+	      return in;
+	    }
+	}
+      else if (c == 'l') // lastSunday, lastWed, ...
+	{
+	  in.ignore(4);
+	  if (abbrev_weekday w{}; in >> w) [[likely]]
+	    {
+	      on.kind = on_day::LastWeekday;
+	      on.day_of_week = w.wd.c_encoding();
+	      to = on;
+	      return in;
+	    }
+	}
+      else
+	{
+	  abbrev_weekday w;
+	  in >> w;
+	  if (auto c = in.get(); c == '<' || c == '>')
+	    {
+	      if (in.get() == '=')
+		{
+		  on.kind = c == '<' ? on_day::LessEq : on_day::GreaterEq;
+		  on.day_of_week = w.wd.c_encoding();
+		  unsigned d;
+		  in >> d;
+		  if (d <= 31) [[likely]]
+		    {
+		      on.day_of_month = d;
+		      to = on;
+		      return in;
+		    }
+		}
+	    }
+	}
+      in.setstate(ios::failbit);
+      return in;
+    }
+
+    istream& operator>>(istream& in, at_time& at)
+    {
+      int sign = 1;
+      if (in.peek() == '-')
+	{
+	  in.ignore(1);
+	  if (auto [val, yes] = at_time::is_indicator(in.peek()); yes)
+	    {
+	      in.ignore(1);
+	      at.time = 0s;
+	      at.indicator = val;
+	      return in;
+	    }
+	  sign = -1;
+	}
+      int i;
+      in >> i;
+      hours h{i};
+      minutes m{};
+      seconds s{};
+      if (!in.eof() && in.peek() == ':')
+	{
+	  in.ignore(1); // discard the colon.
+	  in >> i;
+	  m = minutes{i};
+	  if (in.peek() == ':')
+	    {
+	      in.ignore(1); // discard the colon.
+	      in >> i;
+	      if (in.peek() == '.')
+		{
+		  double frac;
+		  in >> frac;
+		  // zic(8) rounds to nearest second, rounding ties to even.
+		  s = chrono::round<seconds>(duration<double>(i + frac));
+		}
+	      else
+		s = seconds{i};
+	    }
+	}
+      if (in >> at.indicator)
+	at.time = sign * (h + m + s);
+      return in;
+    }
+
+    istream& operator>>(istream& in, ZoneInfo& inf)
+    {
+      // STDOFF  RULES  FORMAT  [UNTIL]
+      at_time off;
+      string rules;
+      string fmt;
+
+      in >> off >> quoted{rules} >> fmt;
+      inf.m_offset = off.time;
+      if (rules == "-")
+	{
+	  // Standard time always applies, no DST.
+	  inf.set_abbrev(fmt);
+	}
+      else if (string_view("0123456789-+").find(rules[0]) != string_view::npos)
+	{
+	  // rules specifies the difference from standard time.
+	  at_time rules_time;
+	  istringstream in2(std::move(rules));
+	  in2 >> rules_time;
+	  inf.m_save = duration_cast<minutes>(rules_time.time);
+	  select_std_or_dst_abbrev(fmt, inf.m_save);
+	  inf.set_abbrev(fmt);
+	}
+      else
+	{
+	  // rules refers to a named Rule which describes transitions.
+	  inf.set_rules_and_format(rules, fmt);
+	}
+
+      // YEAR [MONTH [DAY [TIME]]]
+      ios::iostate ex = in.exceptions();
+      in.exceptions(ios::goodbit); // Don't throw ios::failure if YEAR absent.
+      if (int y = int(year::max()); in >> y)
+	{
+	  abbrev_month m{January};
+	  int d = 1;
+	  at_time t{};
+	  in >> m >> d >> t;
+	  inf.m_until = sys_days(year(y)/m.m/day(d)) + seconds(t.time);
+	}
+      else
+	inf.m_until = sys_days(year::max()/December/31);
+
+      in.clear(in.rdstate() & ios::eofbit);
+      in.exceptions(ex);
+      if (!in.eof())
+	// Not actually necessary, as we're only parsing a single line:
+	in.ignore(numeric_limits<streamsize>::max(), '\n');
+      return in;
+    }
+  } // namespace
+
+} // namespace std::chrono
diff --git a/libstdc++-v3/testsuite/lib/libstdc++.exp b/libstdc++-v3/testsuite/lib/libstdc++.exp
index 635f16db4e8887163198fd5e45361d9280a294f4..ed5733afb9fa79b00cff9680b350a37d96fe37ce 100644
--- a/libstdc++-v3/testsuite/lib/libstdc++.exp
+++ b/libstdc++-v3/testsuite/lib/libstdc++.exp
@@ -1397,6 +1397,20 @@ proc check_effective_target_hosted { } {
     }]
 }
 
+# Return 1 if std::chrono::tzdb is supported.
+proc check_effective_target_tzdb { } {
+    if {![check_effective_target_cxx11_abi]} {
+	return 0
+    }
+    return [check_v3_target_prop_cached et_tzdb {
+	set cond "defined _GLIBCXX_ZONEINFO_DIR"
+	if {[v3_check_preprocessor_condition tzdb $cond]} {
+	    return 1
+	}
+	return [file exists /usr/share/zoneinfo/tzdata.zi]
+    }]
+}
+
 set additional_prunes ""
 
 if { [info exists env(GCC_RUNTEST_PARALLELIZE_DIR)] \
diff --git a/libstdc++-v3/testsuite/std/time/clock/file/members.cc b/libstdc++-v3/testsuite/std/time/clock/file/members.cc
index 51b89d88f1655f34f763bc9db34395a9342723c1..0d36efcff7002b88b665a9b01e172bd60a8d65b6 100644
--- a/libstdc++-v3/testsuite/std/time/clock/file/members.cc
+++ b/libstdc++-v3/testsuite/std/time/clock/file/members.cc
@@ -32,8 +32,19 @@ test01()
   VERIFY( d2 == d1 );
 }
 
+void
+test02()
+{
+  using namespace std::chrono;
+
+  file_time<file_clock::duration> t = file_clock::now();
+  file_time<seconds> s = floor<seconds>(t);
+  VERIFY( t - s < 1s );
+}
+
 int
 main()
 {
   test01();
+  test02();
 }
diff --git a/libstdc++-v3/testsuite/std/time/clock/gps/1.cc b/libstdc++-v3/testsuite/std/time/clock/gps/1.cc
index 9403ee1eccab6e9cbcd5a258befc36397783e246..f6bfe49207d3ee1b768a7ad74a5c4543ab8e5e88 100644
--- a/libstdc++-v3/testsuite/std/time/clock/gps/1.cc
+++ b/libstdc++-v3/testsuite/std/time/clock/gps/1.cc
@@ -31,8 +31,26 @@ test02()
   VERIFY( clock_cast<gps_clock>(clock_cast<utc_clock>(t)) == t );
 }
 
+void
+test03()
+{
+  using namespace std::chrono;
+
+  gps_time<gps_clock::duration> gps1 = gps_clock::now();
+  utc_time<utc_clock::duration> utc = utc_clock::now();
+  gps_time<gps_clock::duration> gps2 = gps_clock::now();
+
+  auto delta = gps2 - gps1;
+  VERIFY( (utc - clock_cast<utc_clock>(gps1)) <= delta );
+  VERIFY( (clock_cast<utc_clock>(gps2) - utc) <= delta );
+
+  gps_seconds s = time_point_cast<seconds>(gps1);
+  VERIFY( gps1 - s < 1s );
+}
+
 int main()
 {
   test01();
   test02();
+  test03();
 }
diff --git a/libstdc++-v3/testsuite/std/time/clock/tai/1.cc b/libstdc++-v3/testsuite/std/time/clock/tai/1.cc
index 9b36f023c683cde82823e9f14390fa0546738174..08fc972c5503940866959ef002ca017df174bf7d 100644
--- a/libstdc++-v3/testsuite/std/time/clock/tai/1.cc
+++ b/libstdc++-v3/testsuite/std/time/clock/tai/1.cc
@@ -34,8 +34,26 @@ test02()
   VERIFY( clock_cast<tai_clock>(clock_cast<utc_clock>(t)) == t );
 }
 
+void
+test03()
+{
+  using namespace std::chrono;
+
+  tai_time<tai_clock::duration> tai1 = tai_clock::now();
+  utc_time<utc_clock::duration> utc = utc_clock::now();
+  tai_time<tai_clock::duration> tai2 = tai_clock::now();
+
+  auto delta = tai2 - tai1;
+  VERIFY( (utc - clock_cast<utc_clock>(tai1)) <= delta );
+  VERIFY( (clock_cast<utc_clock>(tai2) - utc) <= delta );
+
+  tai_seconds s = time_point_cast<seconds>(tai1);
+  VERIFY( tai1 - s < 1s );
+}
+
 int main()
 {
   test01();
   test02();
+  test03();
 }
diff --git a/libstdc++-v3/testsuite/std/time/clock/utc/leap_second_info.cc b/libstdc++-v3/testsuite/std/time/clock/utc/leap_second_info.cc
new file mode 100644
index 0000000000000000000000000000000000000000..0140c756dabdd6ca9de066d1eb9af2a99421ae63
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/clock/utc/leap_second_info.cc
@@ -0,0 +1,80 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-additional-options "-DHAVE_TZDB" { target tzdb } }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+using namespace std::chrono_literals;
+
+void
+test_before()
+{
+  // No leaps seconds defined before the epoch.
+  auto s = std::chrono::utc_seconds(-1s);
+  auto lsi = get_leap_second_info(s);
+  VERIFY( lsi.is_leap_second == false );
+  VERIFY( lsi.elapsed == 0s );
+
+  auto ms = std::chrono::utc_time<std::chrono::milliseconds>(s - 5500ms);
+  lsi = get_leap_second_info(ms);
+  VERIFY( lsi.is_leap_second == false );
+  VERIFY( lsi.elapsed == 0s );
+}
+
+void
+test_after()
+{
+#ifdef HAVE_TZDB
+  const auto& leaps = std::chrono::get_tzdb().leap_seconds;
+  std::chrono::seconds sum(0);
+  for (auto leap : leaps)
+    sum += leap.value();
+
+  // After the last defined leap second.
+  auto last = leaps.back().date().time_since_epoch();
+  auto ut = std::chrono::utc_time<std::chrono::milliseconds>(last + 72h + 10ms);
+  auto lsi = get_leap_second_info(ut);
+  VERIFY( lsi.is_leap_second == false );
+  VERIFY( lsi.elapsed == sum );
+#endif
+}
+
+void
+test_between()
+{
+  std::chrono::sys_days st(1995y/9/4);
+  auto ut = std::chrono::clock_cast<std::chrono::utc_clock>(st);
+  auto lsi = get_leap_second_info(ut);
+  VERIFY( lsi.is_leap_second == false );
+  VERIFY( lsi.elapsed == 19s );
+}
+
+void
+test_during()
+{
+#ifdef HAVE_TZDB
+  // Verify that leap_second_info::is_leap_second is true for each leap second.
+  const auto& leaps = std::chrono::get_tzdb().leap_seconds;
+  for (const auto& leap : leaps)
+  {
+    // N.B. this assumes all leap seconds are positive:
+    std::chrono::seconds elapsed(&leap - &leaps.front());
+    std::chrono::utc_seconds ut(leap.date().time_since_epoch() + elapsed);
+    auto lsi = get_leap_second_info(ut);
+    VERIFY( lsi.is_leap_second == true );
+    VERIFY( lsi.elapsed == elapsed + 1s );
+    lsi = get_leap_second_info(ut + 999ms);
+    VERIFY( lsi.is_leap_second == true );
+    VERIFY( lsi.elapsed == elapsed + 1s );
+  }
+#endif
+}
+
+int main()
+{
+  test_before();
+  test_after();
+  test_between();
+  test_during();
+}
diff --git a/libstdc++-v3/testsuite/std/time/exceptions.cc b/libstdc++-v3/testsuite/std/time/exceptions.cc
new file mode 100644
index 0000000000000000000000000000000000000000..1b81d5ee27a03069af88ea90cff979b941cf1fb6
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/exceptions.cc
@@ -0,0 +1,49 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target tzdb }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+void
+test_nonexistent()
+{
+    std::string expected
+      = "2016-03-13 02:30:00 is in a gap between\n"
+	"2016-03-13 02:00:00 EST and\n"
+	"2016-03-13 03:00:00 EDT which are both equivalent to\n"
+	"2016-03-13 07:00:00 UTC";
+
+  using namespace std::chrono;
+  try {
+    auto zt = zoned_time{"America/New_York",
+			 local_days{Sunday[2]/March/2016} + 2h + 30min};
+    VERIFY(false);
+  } catch (const nonexistent_local_time& e) {
+    // VERIFY( e.what() == expected );
+  }
+}
+
+void
+test_ambiguous()
+{
+    std::string expected
+      = "2016-11-06 01:30:00 is ambiguous.  It could be\n"
+	"2016-11-06 01:30:00 EDT == 2016-11-06 05:30:00 UTC or\n"
+	"2016-11-06 01:30:00 EST == 2016-11-06 06:30:00 UTC";
+
+  using namespace std::chrono;
+  try {
+    auto zt = zoned_time{"America/New_York",
+			 local_days{Sunday[1]/November/2016} + 1h + 30min};
+    VERIFY(false);
+  } catch (const ambiguous_local_time& e) {
+    // VERIFY( e.what() == expected );
+  }
+}
+
+int main()
+{
+  test_nonexistent();
+  test_ambiguous();
+}
diff --git a/libstdc++-v3/testsuite/std/time/syn_c++20.cc b/libstdc++-v3/testsuite/std/time/syn_c++20.cc
index 4024e0e9205220d35aa7e289d33c676d7d84ccb7..c91723bebd608adba81564112d47557f5e4eaa74 100644
--- a/libstdc++-v3/testsuite/std/time/syn_c++20.cc
+++ b/libstdc++-v3/testsuite/std/time/syn_c++20.cc
@@ -43,8 +43,6 @@ namespace __gnu_test
   using std::chrono::sys_seconds;
   using std::chrono::sys_days;
 
-  // FIXME
-#if 0
   using std::chrono::utc_clock;
   using std::chrono::utc_time;
   using std::chrono::utc_seconds;
@@ -59,7 +57,6 @@ namespace __gnu_test
   using std::chrono::gps_clock;
   using std::chrono::gps_time;
   using std::chrono::gps_seconds;
-#endif
 
   using std::chrono::file_clock;
   using std::chrono::file_time;
@@ -69,13 +66,10 @@ namespace __gnu_test
   using std::chrono::local_seconds;
   using std::chrono::local_days;
 
-  // FIXME
-#if 0
   using std::chrono::clock_time_conversion;
   using std::chrono::clock_cast;
 
   using std::chrono::last_spec;
-#endif
 
   using std::chrono::day;
   using std::chrono::month;
@@ -101,8 +95,7 @@ namespace __gnu_test
   using std::chrono::make12;
   using std::chrono::make24;
 
-  // FIXME
-#if 0
+#if _GLIBCXX_USE_CXX11_ABI
   using std::chrono::tzdb;
   using std::chrono::tzdb_list;
   using std::chrono::get_tzdb;
@@ -129,11 +122,13 @@ namespace __gnu_test
   using std::chrono::leap_second;
 
   using std::chrono::time_zone_link;
+#endif
 
-  using std::chrono::local_time_format;
+  // FIXME
+  // using std::chrono::local_time_format;
 
-  using std::chrono::parse;
-#endif
+  // FIXME
+  // using std::chrono::parse;
 
   using std::chrono::last;
   using std::chrono::Sunday;
diff --git a/libstdc++-v3/testsuite/std/time/time_zone/get_info_local.cc b/libstdc++-v3/testsuite/std/time/time_zone/get_info_local.cc
new file mode 100644
index 0000000000000000000000000000000000000000..d15e1c7036ef673c392cac655750a823b7be5989
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/time_zone/get_info_local.cc
@@ -0,0 +1,222 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target tzdb }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+using namespace std::chrono;
+
+struct empty_tag { } empty;
+
+bool operator==(const sys_info& info, empty_tag)
+{
+  return info.begin == sys_seconds() && info.end == info.begin
+    && info.offset == 0s && info.save == 0min && info.abbrev.empty();
+}
+
+void
+test_utc()
+{
+  auto tz = locate_zone("UTC");
+  auto now = time_point_cast<seconds>(system_clock::now());
+  local_info info = tz->get_info(local_seconds(now.time_since_epoch()));
+  VERIFY( info.result == local_info::unique );
+  VERIFY( info.first.begin < now );
+  VERIFY( info.first.end > now );
+  VERIFY( info.first.offset == 0h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "UTC" );
+  VERIFY( info.second == empty );
+}
+
+auto dst_start = March/Sunday[last];
+auto dst_end = October/Sunday[last];
+
+void
+test_unique()
+{
+  auto tz = locate_zone("Europe/London");
+  local_days feb1(sys_days(2022y/February/1).time_since_epoch());
+  local_info info;
+
+  info = tz->get_info(feb1);
+  VERIFY( info.result == local_info::unique );
+  VERIFY( info.first.begin == sys_days(2021y/dst_end) + 1h );
+  VERIFY( info.first.end == sys_days(2022y/dst_start) + 1h );
+  VERIFY( info.first.offset == 0h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "GMT" );
+  VERIFY( info.second == empty );
+
+  info = tz->get_info(feb1 + months(4));
+  VERIFY( info.result == local_info::unique );
+  VERIFY( info.first.begin == sys_days(2022y/dst_start) + 1h );
+  VERIFY( info.first.end == sys_days(2022y/dst_end) + 1h );
+  VERIFY( info.first.offset == 1h );
+  VERIFY( info.first.save == 1h );
+  VERIFY( info.first.abbrev == "BST" );
+  VERIFY( info.second == empty );
+}
+
+void
+test_nonexistent()
+{
+  auto tz = locate_zone("Europe/Helsinki");
+  sys_time<hours> change = sys_days(2022y/dst_start) + 1h;
+  local_seconds nonesuch(change.time_since_epoch() + 2h + 30min);
+  local_info info;
+
+  info = tz->get_info(nonesuch);
+  VERIFY( info.result == local_info::nonexistent );
+  VERIFY( info.first.end == change );
+  VERIFY( info.first.offset == 2h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "EET" );
+  VERIFY( info.second.begin == info.first.end );
+  VERIFY( info.second.offset == 3h );
+  VERIFY( info.second.save == 1h );
+  VERIFY( info.second.abbrev == "EEST" );
+
+  tz = locate_zone("America/New_York");
+  nonesuch = local_days(Sunday[2]/March/2016) + 2h + 30min;
+  info = tz->get_info(nonesuch);
+  VERIFY( info.result == local_info::nonexistent );
+  VERIFY( info.first.end == sys_days(Sunday[2]/March/2016) + 5h + 2h );
+  VERIFY( info.first.offset == -5h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "EST" );
+  VERIFY( info.second.begin == info.first.end );
+  VERIFY( info.second.offset == -4h );
+  VERIFY( info.second.save == 1h );
+  VERIFY( info.second.abbrev == "EDT" );
+}
+
+void
+test_ambiguous()
+{
+  auto tz = locate_zone("Europe/Helsinki");
+  sys_time<hours> change = sys_days(2022y/dst_end) + 1h;
+  local_seconds twix(change.time_since_epoch() + 2h + 30min);
+  local_info info;
+
+  info = tz->get_info(twix);
+  VERIFY( info.result == local_info::ambiguous );
+  VERIFY( info.first.end == change );
+  VERIFY( info.first.offset == 3h );
+  VERIFY( info.first.save == 1h );
+  VERIFY( info.first.abbrev == "EEST" );
+  VERIFY( info.second.begin == info.first.end );
+  VERIFY( info.second.offset == 2h );
+  VERIFY( info.second.save == 0h );
+  VERIFY( info.second.abbrev == "EET" );
+
+  tz = locate_zone("America/New_York");
+  twix = local_days(Sunday[2]/March/2016) + 2h + 30min;
+  info = tz->get_info(twix);
+  VERIFY( info.result == local_info::nonexistent );
+  VERIFY( info.first.end == sys_days(Sunday[2]/March/2016) + 5h + 2h );
+  VERIFY( info.first.offset == -5h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "EST" );
+  VERIFY( info.second.begin == info.first.end );
+  VERIFY( info.second.offset == -4h );
+  VERIFY( info.second.save == 1h );
+  VERIFY( info.second.abbrev == "EDT" );
+}
+
+void
+test_egypt()
+{
+  local_days d(2010y/May/1);
+  auto tz = locate_zone("Egypt");
+  local_info info = tz->get_info(d);
+  VERIFY( info.result == local_info::unique );
+  VERIFY( info.first.begin == sys_days(2010y/April/29) + 22h );
+  VERIFY( info.first.offset == 3h );
+  VERIFY( info.first.save == 1h );
+  VERIFY( info.first.abbrev == "EEST" );
+
+  info = tz->get_info(d - 24h);
+  VERIFY( info.result == local_info::nonexistent );
+  VERIFY( info.first.begin == sys_days(2009y/August/20) + 21h );
+  VERIFY( info.first.offset == 2h );
+  VERIFY( info.first.save == 0h );
+  VERIFY( info.first.abbrev == "EET" );
+  VERIFY( info.second.begin == sys_days(2010y/April/29) + 22h );
+  VERIFY( info.second.offset == 3h );
+  VERIFY( info.second.save == 1h );
+  VERIFY( info.second.abbrev == "EEST" );
+
+#if 0
+  std::ostringstream out;
+  local_seconds lt(local_days(2001y/January/1));
+  const local_days end(2021y/January/1);
+
+  while (lt < end)
+  {
+    local_info i = tz->get_info(lt);
+
+    out << '\n' << i;
+
+    auto next = i.first.end;
+    if (i.result != local_info::unique)
+      next = i.second.begin + 24h;
+    lt = zoned_time(tz, next).get_local_time();
+  }
+  out << '\n';
+
+  std::string expected = R"(
+[[2000-09-28 21:00:00,2001-04-26 22:00:00,02:00:00,0min,EET]]
+[[2001-04-26 22:00:00,2001-09-27 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2001-04-26 22:00:00,2001-09-27 21:00:00,03:00:00,60min,EEST] and [2001-09-27 21:00:00,2002-04-25 22:00:00,02:00:00,0min,EET]]
+[[2001-09-27 21:00:00,2002-04-25 22:00:00,02:00:00,0min,EET]]
+[[2002-04-25 22:00:00,2002-09-26 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2002-04-25 22:00:00,2002-09-26 21:00:00,03:00:00,60min,EEST] and [2002-09-26 21:00:00,2003-04-24 22:00:00,02:00:00,0min,EET]]
+[[2002-09-26 21:00:00,2003-04-24 22:00:00,02:00:00,0min,EET]]
+[[2003-04-24 22:00:00,2003-09-25 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2003-04-24 22:00:00,2003-09-25 21:00:00,03:00:00,60min,EEST] and [2003-09-25 21:00:00,2004-04-29 22:00:00,02:00:00,0min,EET]]
+[[2003-09-25 21:00:00,2004-04-29 22:00:00,02:00:00,0min,EET]]
+[[2004-04-29 22:00:00,2004-09-30 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2004-04-29 22:00:00,2004-09-30 21:00:00,03:00:00,60min,EEST] and [2004-09-30 21:00:00,2005-04-28 22:00:00,02:00:00,0min,EET]]
+[[2004-09-30 21:00:00,2005-04-28 22:00:00,02:00:00,0min,EET]]
+[[2005-04-28 22:00:00,2005-09-29 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2005-04-28 22:00:00,2005-09-29 21:00:00,03:00:00,60min,EEST] and [2005-09-29 21:00:00,2006-04-27 22:00:00,02:00:00,0min,EET]]
+[[2005-09-29 21:00:00,2006-04-27 22:00:00,02:00:00,0min,EET]]
+[[2006-04-27 22:00:00,2006-09-21 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2006-04-27 22:00:00,2006-09-21 21:00:00,03:00:00,60min,EEST] and [2006-09-21 21:00:00,2007-04-26 22:00:00,02:00:00,0min,EET]]
+[[2006-09-21 21:00:00,2007-04-26 22:00:00,02:00:00,0min,EET]]
+[[2007-04-26 22:00:00,2007-09-06 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2007-04-26 22:00:00,2007-09-06 21:00:00,03:00:00,60min,EEST] and [2007-09-06 21:00:00,2008-04-24 22:00:00,02:00:00,0min,EET]]
+[[2007-09-06 21:00:00,2008-04-24 22:00:00,02:00:00,0min,EET]]
+[[2008-04-24 22:00:00,2008-08-28 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2008-04-24 22:00:00,2008-08-28 21:00:00,03:00:00,60min,EEST] and [2008-08-28 21:00:00,2009-04-23 22:00:00,02:00:00,0min,EET]]
+[[2008-08-28 21:00:00,2009-04-23 22:00:00,02:00:00,0min,EET]]
+[[2009-04-23 22:00:00,2009-08-20 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2009-04-23 22:00:00,2009-08-20 21:00:00,03:00:00,60min,EEST] and [2009-08-20 21:00:00,2010-04-29 22:00:00,02:00:00,0min,EET]]
+[[2009-08-20 21:00:00,2010-04-29 22:00:00,02:00:00,0min,EET]]
+[[2010-04-29 22:00:00,2010-08-10 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2010-04-29 22:00:00,2010-08-10 21:00:00,03:00:00,60min,EEST] and [2010-08-10 21:00:00,2010-09-09 22:00:00,02:00:00,0min,EET]]
+[[2010-08-10 21:00:00,2010-09-09 22:00:00,02:00:00,0min,EET]]
+[[2010-09-09 22:00:00,2010-09-30 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2010-09-09 22:00:00,2010-09-30 21:00:00,03:00:00,60min,EEST] and [2010-09-30 21:00:00,2014-05-15 22:00:00,02:00:00,0min,EET]]
+[[2010-09-30 21:00:00,2014-05-15 22:00:00,02:00:00,0min,EET]]
+[[2014-05-15 22:00:00,2014-06-26 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2014-05-15 22:00:00,2014-06-26 21:00:00,03:00:00,60min,EEST] and [2014-06-26 21:00:00,2014-07-31 22:00:00,02:00:00,0min,EET]]
+[[2014-06-26 21:00:00,2014-07-31 22:00:00,02:00:00,0min,EET]]
+[[2014-07-31 22:00:00,2014-09-25 21:00:00,03:00:00,60min,EEST]]
+[ambiguous local time between [2014-07-31 22:00:00,2014-09-25 21:00:00,03:00:00,60min,EEST] and [2014-09-25 21:00:00,32767-12-31 00:00:00,02:00:00,0min,EET]]
+[[2014-09-25 21:00:00,32767-12-31 00:00:00,02:00:00,0min,EET]]
+)";
+  VERIFY( out.str() == expected );
+#endif
+}
+
+int main()
+{
+  test_utc();
+  test_unique();
+  test_nonexistent();
+  test_ambiguous();
+  test_egypt();
+}
diff --git a/libstdc++-v3/testsuite/std/time/time_zone/get_info_sys.cc b/libstdc++-v3/testsuite/std/time/time_zone/get_info_sys.cc
new file mode 100644
index 0000000000000000000000000000000000000000..a669b68e4401f26508d56e08749c77282ed68bdf
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/time_zone/get_info_sys.cc
@@ -0,0 +1,219 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target tzdb }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+void
+test_zurich()
+{
+  using namespace std::chrono;
+
+  const time_zone* const tz = locate_zone("Europe/Zurich");
+
+  {
+    sys_days d = 1853y/July/16;
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == (34min + 8s) );
+    VERIFY( info.abbrev == "LMT" );
+
+    info = tz->get_info(d);
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    info = tz->get_info(d + 1s);
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    info = tz->get_info(d + 0.001s);
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+  }
+
+  {
+    sys_days d = 1894y/June/1;
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    info = tz->get_info(d);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1941y/May/Monday[1];
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST daylight savings time starts at 1am local time (UTC+1).
+    info = tz->get_info(d);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1941y/October/Monday[1];
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CET standard time starts at 2am local time (UTC+2).
+    info = tz->get_info(d);
+    VERIFY( info.offset == 1h  );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1942y/May/Monday[1];
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST daylight savings time starts at 1am local time (UTC+1).
+    info = tz->get_info(d);
+    VERIFY( info.offset == 2h  );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1942y/October/Monday[1];
+
+    auto info = tz->get_info(d - 1s);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CET standard time starts at 2am local time (UTC+2).
+    info = tz->get_info(d);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1943y/May/Monday[1];
+
+    // No daylight savings from 1943 until 1981.
+    auto info = tz->get_info(d);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    info = tz->get_info(d + days(60));
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    info = tz->get_info(d + years(10));
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    info = tz->get_info(sys_days(1979y/June/3));
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    // Switzerland uses EU rules from 1981
+    sys_days d = 1981y/March/Sunday[last];
+
+    auto info = tz->get_info(d);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    info = tz->get_info(d + 59min + 59s);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST begins at 1am UTC
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1981y/September/Sunday[last];
+
+    auto info = tz->get_info(d + 59min + 59s);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CEST ends at 1am UTC
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1994y/September/Sunday[last];
+
+    auto info = tz->get_info(d + 59min + 59s);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CEST ends at 1am UTC
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    d = 1995y/September/Sunday[last];
+    info = tz->get_info(d + 59min + 59s);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CEST ends at 1am UTC
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    d = 1996y/September/Sunday[last];
+    // CEST ends in October since 1996
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    d = 1996y/October/Sunday[last];
+    // CEST ends at 1am UTC
+    info = tz->get_info(d + 1h);
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+}
+
+void
+test_iterate()
+{
+  using namespace std::chrono;
+  auto tz = locate_zone("Europe/Zurich");
+  sys_seconds start(sys_days(1850y/January/1));
+  const sys_seconds finish(sys_days(1982y/January/1));
+  long count = 0;
+  do
+  {
+    VERIFY(++count < 100); // Fail if we get stuck in a loop.
+    auto info = tz->get_info(start);
+    start = info.end;
+  } while (start < finish);
+
+  VERIFY(count == 10); // Would be 9 if identical adjacent sys_info get merged.
+}
+
+void
+test_shanghai()
+{
+  using namespace std::chrono;
+  auto tz = locate_zone("Asia/Shanghai");
+  sys_info info = tz->get_info(sys_days(1949y/January/1));
+  VERIFY( info.abbrev == "CST" );
+}
+
+int main()
+{
+  test_zurich();
+  test_iterate();
+  test_shanghai();
+}
diff --git a/libstdc++-v3/testsuite/std/time/time_zone/requirements.cc b/libstdc++-v3/testsuite/std/time/time_zone/requirements.cc
new file mode 100644
index 0000000000000000000000000000000000000000..9bbe3193b2d2d4b73e1cca4ac695f98f2ba04081
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/time_zone/requirements.cc
@@ -0,0 +1,25 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do compile { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+
+using std::chrono::time_zone;
+
+static_assert( std::is_move_constructible_v<time_zone> );
+static_assert( std::is_move_assignable_v<time_zone> );
+
+static_assert( ! std::is_default_constructible_v<time_zone> );
+static_assert( ! std::is_copy_constructible_v<time_zone> );
+static_assert( ! std::is_copy_assignable_v<time_zone> );
+
+extern const time_zone* tz;
+
+static_assert( std::is_same_v<decltype(tz->name()), std::string_view> );
+static_assert( noexcept(tz->name()) );
+
+static_assert( std::is_same_v<decltype(*tz == *tz), bool> );
+static_assert( noexcept(*tz == *tz) );
+
+static_assert( std::is_same_v<decltype(*tz <=> *tz), std::strong_ordering> );
+static_assert( noexcept(*tz <=> *tz) );
diff --git a/libstdc++-v3/testsuite/std/time/tzdb/1.cc b/libstdc++-v3/testsuite/std/time/tzdb/1.cc
new file mode 100644
index 0000000000000000000000000000000000000000..64e42701d3b93907867862640a6cb3a226c221e7
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/tzdb/1.cc
@@ -0,0 +1,56 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+// { dg-additional-options "-DHAVE_TZDB" { target tzdb } }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+using namespace std::chrono;
+
+void
+test_version()
+{
+  const tzdb& db = get_tzdb();
+  VERIFY( &db == &get_tzdb_list().front() );
+
+#ifdef HAVE_TZDB
+  VERIFY( db.version == remote_version() );
+  const tzdb& reloaded = reload_tzdb();
+  if (reloaded.version == db.version)
+    VERIFY( &reloaded == &db );
+#endif
+}
+
+void
+test_current()
+{
+#ifdef HAVE_TZDB
+  const tzdb& db = get_tzdb();
+  const time_zone* tz = db.current_zone();
+  VERIFY( tz == std::chrono::current_zone() );
+#endif
+}
+
+void
+test_locate()
+{
+  const tzdb& db = get_tzdb();
+  const time_zone* tz = db.locate_zone("GMT");
+  VERIFY( tz != nullptr );
+  VERIFY( tz->name() == "Etc/GMT" );
+  VERIFY( tz == std::chrono::locate_zone("GMT") );
+  VERIFY( tz == db.locate_zone("Etc/GMT") );
+  VERIFY( tz == db.locate_zone("Etc/GMT+0") );
+
+#ifdef HAVE_TZDB
+  VERIFY( db.locate_zone(db.current_zone()->name()) == db.current_zone() );
+#endif
+}
+
+int main()
+{
+  test_version();
+  test_current();
+  test_locate();
+}
diff --git a/libstdc++-v3/testsuite/std/time/tzdb/leap_seconds.cc b/libstdc++-v3/testsuite/std/time/tzdb/leap_seconds.cc
new file mode 100644
index 0000000000000000000000000000000000000000..82303e8bdf0324af3cef662cc64c2328d73aff30
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/tzdb/leap_seconds.cc
@@ -0,0 +1,76 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+// { dg-xfail-run-if "no weak override on AIX" { powerpc-ibm-aix* } }
+
+#include <chrono>
+#include <fstream>
+#include <testsuite_hooks.h>
+
+static bool override_used = true;
+
+namespace __gnu_cxx
+{
+  const char* zoneinfo_dir_override() {
+    override_used = true;
+    return "./";
+  }
+}
+
+void
+test_load_leapseconds()
+{
+  std::ofstream("leapseconds") << R"(
+# These are all the real leap seconds as of 2022:
+Leap	1972	Jun	30	23:59:60	+	S
+Leap	1972	Dec	31	23:59:60	+	S
+Leap	1973	Dec	31	23:59:60	+	S
+Leap	1974	Dec	31	23:59:60	+	S
+Leap	1975	Dec	31	23:59:60	+	S
+Leap	1976	Dec	31	23:59:60	+	S
+Leap	1977	Dec	31	23:59:60	+	S
+Leap	1978	Dec	31	23:59:60	+	S
+Leap	1979	Dec	31	23:59:60	+	S
+Leap	1981	Jun	30	23:59:60	+	S
+Leap	1982	Jun	30	23:59:60	+	S
+Leap	1983	Jun	30	23:59:60	+	S
+Leap	1985	Jun	30	23:59:60	+	S
+Leap	1987	Dec	31	23:59:60	+	S
+Leap	1989	Dec	31	23:59:60	+	S
+Leap	1990	Dec	31	23:59:60	+	S
+Leap	1992	Jun	30	23:59:60	+	S
+Leap	1993	Jun	30	23:59:60	+	S
+Leap	1994	Jun	30	23:59:60	+	S
+Leap	1995	Dec	31	23:59:60	+	S
+Leap	1997	Jun	30	23:59:60	+	S
+Leap	1998	Dec	31	23:59:60	+	S
+Leap	2005	Dec	31	23:59:60	+	S
+Leap	2008	Dec	31	23:59:60	+	S
+Leap	2012	Jun	30	23:59:60	+	S
+Leap	2015	Jun	30	23:59:60	+	S
+Leap	2016	Dec	31	23:59:60	+	S
+# These are fake leap seconds for testing purposes:
+Leap	2093	Jun	30	23:59:59	-	S
+Leap	2093	Dec	31	23:59:60	+	S
+)";
+
+  const auto& db = std::chrono::get_tzdb();
+  VERIFY( override_used ); // If this fails then XFAIL for the target.
+
+  using namespace std::chrono;
+  // XXX update this value if the number of hardcoded leap seconds changes:
+  VERIFY( db.leap_seconds.size() == 29 );
+
+  auto i = db.leap_seconds.end() - 2;
+
+  VERIFY( i[0].date() == sys_days(2093y/July/1) - 1s );
+  VERIFY( i[0].value() == -1s );
+
+  VERIFY( i[1].date() == sys_days(2094y/January/1) );
+  VERIFY( i[1].value() == 1s );
+}
+
+int main()
+{
+  test_load_leapseconds();
+}
diff --git a/libstdc++-v3/testsuite/std/time/tzdb_list/1.cc b/libstdc++-v3/testsuite/std/time/tzdb_list/1.cc
new file mode 100644
index 0000000000000000000000000000000000000000..4cbd656efbd390e3560ba61eeff4bbed861f88be
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/tzdb_list/1.cc
@@ -0,0 +1,123 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+// { dg-xfail-run-if "no weak override on AIX" { powerpc-ibm-aix* } }
+
+#include <chrono>
+#include <fstream>
+#include <testsuite_hooks.h>
+
+static bool override_used = true;
+
+namespace __gnu_cxx
+{
+  const char* zoneinfo_dir_override() {
+    override_used = true;
+    return "./";
+  }
+}
+
+std::string tzdata_zi = R"(
+ # version test1
+ # Rule  NAME  FROM  TO    TYPE  IN   ON       AT    SAVE  LETTER/S
+ Rule    Swiss 1941  1942  -     May  Mon>=1   1:00  1:00  S
+ Rule    Swiss 1941  1942  -     Oct  Mon>=1   2:00  0     -
+ Rule    EU    1977  1980  -     Apr  Sun>=1   1:00u 1:00  S
+ Rule    EU    1977  only  -     Sep  lastSun  1:00u 0     -
+ Rule    EU    1978  only  -     Oct   1       1:00u 0     -
+ Rule    EU    1979  1995  -     Sep  lastSun  1:00u 0     -
+ Rule    EU    1981  max   -     Mar  lastSun  1:00u 1:00  S
+ Rule    EU    1996  max   -     Oct  lastSun  1:00u 0     -
+
+ # Zone  NAME           STDOFF      RULES  FORMAT  [UNTIL]
+ Zone    Europe/Zurich  0:34:08     -      LMT     1853 Jul 16
+                        0:29:45.50  -      BMT     1894 Jun
+                        1:00        Swiss  CE%sT   1981
+                        1:00        EU     CE%sT
+
+ Link    Europe/Zurich  Europe/Vaduz
+
+)";
+
+using namespace std::chrono;
+
+void
+test_access()
+{
+  tzdb_list& list = get_tzdb_list();
+  tzdb_list::const_iterator first = list.begin();
+  tzdb_list::const_iterator last = list.end();
+  VERIFY( list.cbegin() == first );
+  VERIFY( list.cend() == last );
+  VERIFY( first != last );
+  VERIFY( &*first == &get_tzdb() );
+  VERIFY( &*first == &list.front() );
+  VERIFY( std::next(first) == last );
+  first++;
+  VERIFY( first == last );
+}
+
+void
+test_reload()
+{
+  tzdb_list& list = get_tzdb_list();
+  tzdb_list::const_iterator test1 = list.begin();
+  reload_tzdb();
+  VERIFY( list.begin() == test1 );
+  VERIFY( std::distance(list.begin(), list.end()) == 1 );
+
+  std::string new_tzdata_zi = tzdata_zi;
+  auto pos = new_tzdata_zi.find("test");
+  new_tzdata_zi[pos + 4] = '2';
+  std::ofstream("tzdata.zi") << new_tzdata_zi;
+  VERIFY( remote_version() == "test2" );
+
+  // List doesn't reload until requested to.
+  VERIFY( get_tzdb_list().begin() == test1 );
+  VERIFY( &get_tzdb() == &*test1 );
+  reload_tzdb();
+  VERIFY( list.begin() != test1 );
+  VERIFY( std::distance(list.begin(), list.end()) == 2 );
+  VERIFY( test1 == std::next(list.begin()) );
+  VERIFY( &get_tzdb() == &*list.begin() );
+  VERIFY( list.begin()->version == "test2" );
+  VERIFY( test1->version == "test1" );
+}
+
+void
+test_erase()
+{
+  tzdb_list& list = get_tzdb_list();
+  const int count = std::distance(list.begin(), list.end());
+  tzdb_list::const_iterator test2 = list.begin();
+
+  std::string new_tzdata_zi = tzdata_zi;
+  auto pos = new_tzdata_zi.find("test");
+  new_tzdata_zi[pos + 4] = '3';
+  std::ofstream("tzdata.zi") << new_tzdata_zi;
+
+  reload_tzdb();
+  VERIFY( std::distance(list.begin(), list.end()) == count + 1 );
+  VERIFY( list.begin()->version == "test3" );
+  list.erase_after(list.begin());
+  VERIFY( std::distance(list.begin(), list.end()) == count );
+  VERIFY( list.begin()->version == "test3" );
+  VERIFY( std::next(list.begin())->version == "test1" );
+
+  // As a GCC extension, the erased node is not destroyed
+  // while there are iterators referring to it.
+  VERIFY( test2->version == "test2" );
+  VERIFY( test2->leap_seconds == list.begin()->leap_seconds );
+  // But the iterator points to an unlinked list node now:
+  VERIFY( std::next(test2) == tzdb_list::const_iterator() );
+}
+
+int main()
+{
+  std::ofstream("leapseconds") << '\n';
+  std::ofstream("tzdata.zi") << tzdata_zi;
+
+  test_access();
+  test_reload();
+  test_erase();
+}
diff --git a/libstdc++-v3/testsuite/std/time/tzdb_list/requirements.cc b/libstdc++-v3/testsuite/std/time/tzdb_list/requirements.cc
new file mode 100644
index 0000000000000000000000000000000000000000..a2fd8a4eb575bf97be22989b0f2d7a24e9322327
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/tzdb_list/requirements.cc
@@ -0,0 +1,20 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do compile { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+
+using std::chrono::tzdb_list;
+
+static_assert( ! std::is_default_constructible_v<tzdb_list> );
+static_assert( ! std::is_copy_constructible_v<tzdb_list> );
+static_assert( ! std::is_copy_assignable_v<tzdb_list> );
+static_assert( ! std::is_move_constructible_v<tzdb_list> );
+static_assert( ! std::is_move_assignable_v<tzdb_list> );
+static_assert( std::is_destructible_v<tzdb_list> );
+
+using IterTraits = std::iterator_traits<tzdb_list::const_iterator>;
+
+static_assert( std::is_same_v<IterTraits::iterator_category,
+			      std::forward_iterator_tag> );
+static_assert( std::is_same_v<IterTraits::value_type, std::chrono::tzdb> );
diff --git a/libstdc++-v3/testsuite/std/time/zoned_time/1.cc b/libstdc++-v3/testsuite/std/time/zoned_time/1.cc
new file mode 100644
index 0000000000000000000000000000000000000000..d9083048b5461660e941bb7130c59df98516f90d
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_time/1.cc
@@ -0,0 +1,255 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target tzdb }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+void
+test_members()
+{
+  using namespace std::chrono;
+
+  const time_zone* const zone = locate_zone("Europe/London");
+
+  sys_time<minutes> t = sys_days(2022y/February/1) + 1h + 23min;
+  zoned_time<minutes> zt("Europe/London", t);
+  VERIFY( zt.get_time_zone() == zone );
+  VERIFY( zt.get_sys_time() == t);
+  VERIFY( zt.get_local_time().time_since_epoch() == t.time_since_epoch() );
+  VERIFY( zt.get_info().offset == 0h );
+  VERIFY( zt.get_info().abbrev == "GMT" );
+  VERIFY( static_cast<sys_seconds>(zt) == t );
+  VERIFY( static_cast<local_seconds>(zt) == zt.get_local_time() );
+
+  t = sys_days(2022y/June/1);
+  zt = t;
+  VERIFY( zt.get_time_zone() == zone );
+  VERIFY( zt.get_sys_time() == t);
+  VERIFY( zt.get_local_time().time_since_epoch() == t.time_since_epoch() + 1h );
+  VERIFY( zt.get_info().offset == 1h );
+  VERIFY( zt.get_info().abbrev == "BST" );
+  VERIFY( static_cast<sys_seconds>(zt) == t );
+  VERIFY( static_cast<local_seconds>(zt) == zt.get_local_time() );
+
+  zoned_seconds zs(zt);
+  VERIFY( zs == zt );
+
+  local_time<seconds> local(zt.get_local_time() + days(1) + hours(2));
+  zt = time_point_cast<minutes>(local);
+  VERIFY( zt.get_sys_time() == zs.get_sys_time() + days(1) + hours(2) );
+}
+
+void
+test_zurich()
+{
+  using namespace std::chrono;
+
+  const time_zone* const zurich = locate_zone("Europe/Zurich");
+
+  {
+    sys_days d = 1853y/July/16;
+
+    auto z = zoned_seconds(zurich, sys_seconds(d) - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == (34min + 8s) );
+    VERIFY( info.abbrev == "LMT" );
+
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    z = zoned_seconds(zurich, d + 1s);
+    info = z.get_info();
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    auto z2 = zoned_time(zurich, d + 0.001s);
+    info = z2.get_info();
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+  }
+
+  {
+    sys_days d = 1894y/June/1;
+
+    auto z = zoned_seconds(zurich, sys_seconds(d) - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == (29min + 46s) );
+    VERIFY( info.abbrev == "BMT" );
+
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1941y/May/Monday[1];
+
+    auto z = zoned_seconds(zurich, d - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST daylight savings time starts at 1am local time (UTC+1).
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1941y/October/Monday[1];
+
+    auto z = zoned_seconds(zurich, d - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CET standard time starts at 2am local time (UTC+2).
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == 1h  );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1942y/May/Monday[1];
+
+    auto z = zoned_seconds(zurich, d - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST daylight savings time starts at 1am local time (UTC+1).
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == 2h  );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1942y/October/Monday[1];
+
+    auto z = zoned_seconds(zurich, d - 1s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CET standard time starts at 2am local time (UTC+2).
+    z = zoned_seconds(zurich, d);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1943y/May/Monday[1];
+
+    // No daylight savings from 1943 until 1981.
+    auto z = zoned_seconds(zurich, d);
+    auto info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    z = zoned_seconds(zurich, d + days(60));
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    z = zoned_seconds(zurich, d + years(10));
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    z = zoned_seconds(zurich, sys_days(1979y/June/3));
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    // Switzerland uses EU rules from 1981
+    sys_days d = 1981y/March/Sunday[last];
+
+    auto z = zoned_seconds(zurich, d);
+    auto info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    z = zoned_seconds(zurich, d + 59min + 59s);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    // CEST begins at 1am UTC
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+  }
+
+  {
+    sys_days d = 1981y/September/Sunday[last];
+
+    auto z = zoned_seconds(zurich, d + 59min + 59s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CEST ends at 1am UTC
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+
+  {
+    sys_days d = 1994y/September/Sunday[last];
+
+    auto z = zoned_seconds(zurich, d + 59min + 59s);
+    auto info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    // CEST ends at 1am UTC
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    d = 1995y/September/Sunday[last];
+    z = zoned_seconds(zurich, d + 59min + 59s);
+    info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+    // CEST ends at 1am UTC
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+
+    d = 1996y/September/Sunday[last];
+    // CEST ends in October since 1996
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 2h );
+    VERIFY( info.abbrev == "CEST" );
+
+    d = 1996y/October/Sunday[last];
+    // CEST ends at 1am UTC
+    z = zoned_seconds(zurich, d + 1h);
+    info = z.get_info();
+    VERIFY( info.offset == 1h );
+    VERIFY( info.abbrev == "CET" );
+  }
+}
+
+int main()
+{
+  test_members();
+  test_zurich();
+}
diff --git a/libstdc++-v3/testsuite/std/time/zoned_time/custom.cc b/libstdc++-v3/testsuite/std/time/zoned_time/custom.cc
new file mode 100644
index 0000000000000000000000000000000000000000..dc2d9c00c8d2ad1110adf66aea3193d18cdaa4ba
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_time/custom.cc
@@ -0,0 +1,75 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target tzdb }
+
+#include <chrono>
+#include <set>
+#include <stdexcept>
+#include <testsuite_hooks.h>
+
+struct local_tz
+{
+  local_tz() : name(std::chrono::current_zone()->name()) { }
+
+  explicit local_tz(std::string_view name) : name(name) { }
+
+  template<typename Dur>
+    std::chrono::sys_time<Dur> to_sys(const std::chrono::local_time<Dur>& d)
+    { return std::chrono::locate_zone(name)->to_sys(d); }
+
+  template<typename Dur>
+    std::chrono::sys_time<Dur> to_local(const std::chrono::sys_time<Dur>& d)
+    { return std::chrono::locate_zone(name)->to_sys(d); }
+
+  template<typename Dur>
+    std::chrono::sys_info get_info(const std::chrono::sys_time<Dur>& d)
+    { return std::chrono::locate_zone(name)->get_info(d); }
+
+  struct indirect_cmp
+  {
+    bool operator()(const local_tz* lhs, const local_tz* rhs) const
+    { return lhs->name < rhs->name; }
+  };
+
+  bool eq(const std::chrono::time_zone* tz) const noexcept
+  { return name == tz->name(); }
+
+private:
+  std::string_view name;
+};
+
+template<> struct std::chrono::zoned_traits<const local_tz*>
+{
+  static const local_tz* default_zone()
+  {
+    return locate_zone(std::chrono::current_zone()->name());
+  }
+
+  static const local_tz* locate_zone(std::string_view name)
+  {
+    static std::set<const local_tz*, local_tz::indirect_cmp> zones;
+    local_tz tz(name);
+    if (auto z = zones.find(&tz); z != zones.end())
+      return *z;
+    if (std::chrono::locate_zone(name))
+      return *zones.insert(new local_tz(tz)).first;
+    throw std::runtime_error("zone not found");
+  }
+};
+
+void
+test_custom_tzptr()
+{
+  using namespace std::chrono;
+
+  zoned_time<seconds, const local_tz*> z;
+  VERIFY( z.get_time_zone()->eq(std::chrono::current_zone()) );
+
+  zoned_time<seconds, const local_tz*> z2(std::string_view("Europe/London"));
+  VERIFY( z2.get_time_zone()->eq(std::chrono::locate_zone("Europe/London")) );
+}
+
+int main()
+{
+  test_custom_tzptr();
+}
diff --git a/libstdc++-v3/testsuite/std/time/zoned_time/deduction.cc b/libstdc++-v3/testsuite/std/time/zoned_time/deduction.cc
new file mode 100644
index 0000000000000000000000000000000000000000..a26a6f49d77cb16501a8e4352f73ea0122faa7b9
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_time/deduction.cc
@@ -0,0 +1,79 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do compile { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+
+using namespace std::chrono;
+
+struct local_tz : time_zone { local_tz(); };
+
+template<> struct std::chrono::zoned_traits<const local_tz*>
+{
+  static auto default_zone() { return current_zone(); }
+
+  static auto locate_zone(std::string_view name)
+  { return std::chrono::locate_zone(name); }
+};
+
+void
+test_ctad()
+{
+  zoned_time z1;
+  static_assert( std::is_same_v<decltype(z1), zoned_time<seconds>> );
+  zoned_time z2 = z1;
+  static_assert( std::is_same_v<decltype(z2), decltype(z1)> );
+
+  zoned_time z3 = sys_time<milliseconds>();
+  static_assert( std::is_same_v<decltype(z3), zoned_time<milliseconds>> );
+
+  const local_tz ltz;
+  zoned_time z4(&ltz);
+  static_assert( std::is_same_v<decltype(z4),
+				zoned_time<seconds, const local_tz*>> );
+
+  zoned_time z5("GMT");
+  static_assert( std::is_same_v<decltype(z5), zoned_time<seconds>> );
+
+  zoned_time z6(&ltz, sys_time<minutes>());
+  static_assert( std::is_same_v<decltype(z6),
+				zoned_time<seconds, const local_tz*>> );
+
+  zoned_time z7(&ltz, sys_time<milliseconds>());
+  static_assert( std::is_same_v<decltype(z7),
+				zoned_time<milliseconds, const local_tz*>> );
+
+  zoned_time z8("GMT", sys_time<minutes>());
+  static_assert( std::is_same_v<decltype(z8), zoned_time<seconds>> );
+
+  zoned_time z9("GMT", sys_time<microseconds>());
+  static_assert( std::is_same_v<decltype(z9), zoned_time<microseconds>> );
+
+  zoned_time z10(&ltz, local_time<minutes>());
+  static_assert( std::is_same_v<decltype(z10),
+				zoned_time<seconds, const local_tz*>> );
+
+  zoned_time z11(&ltz, local_time<nanoseconds>(), choose::earliest);
+  static_assert( std::is_same_v<decltype(z11),
+				zoned_time<nanoseconds, const local_tz*>> );
+
+  zoned_time z12("GMT", local_time<minutes>());
+  static_assert( std::is_same_v<decltype(z12), zoned_time<seconds>> );
+
+  zoned_time z13("GMT", local_time<nanoseconds>(), choose::earliest);
+  static_assert( std::is_same_v<decltype(z13), zoned_time<nanoseconds>> );
+
+  zoned_time z14(&ltz, z13);
+  static_assert( std::is_same_v<decltype(z14),
+				zoned_time<nanoseconds, const local_tz*>> );
+
+  zoned_time z15(&ltz, z12, choose::earliest);
+  static_assert( std::is_same_v<decltype(z15),
+				zoned_time<seconds, const local_tz*>> );
+
+  zoned_time z16("GMT", z14);
+  static_assert( std::is_same_v<decltype(z16), zoned_time<nanoseconds>> );
+
+  zoned_time z17("GMT", z12, choose::earliest);
+  static_assert( std::is_same_v<decltype(z17), zoned_time<seconds>> );
+}
diff --git a/libstdc++-v3/testsuite/std/time/zoned_time/req_neg.cc b/libstdc++-v3/testsuite/std/time/zoned_time/req_neg.cc
new file mode 100644
index 0000000000000000000000000000000000000000..ae51a250ee9f7b213a4570e829a60ab07786b48a
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_time/req_neg.cc
@@ -0,0 +1,9 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do compile { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+
+std::chrono::zoned_time<std::chrono::year> z; // { dg-error "here" }
+// { dg-error "static assertion failed" "" { target *-*-* } 0 }
+// { dg-prune-output "common_type" }
diff --git a/libstdc++-v3/testsuite/std/time/zoned_time/requirements.cc b/libstdc++-v3/testsuite/std/time/zoned_time/requirements.cc
new file mode 100644
index 0000000000000000000000000000000000000000..6334e5895439b7561ce11ec70fd5dd6350da2587
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_time/requirements.cc
@@ -0,0 +1,27 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do compile { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+
+using namespace std::chrono;
+
+static_assert( std::is_default_constructible_v<zoned_time<seconds>> );
+static_assert( std::is_copy_constructible_v<zoned_time<seconds>> );
+static_assert( std::is_copy_assignable_v<zoned_time<seconds>> );
+static_assert( std::is_move_constructible_v<zoned_time<seconds>> );
+static_assert( std::is_move_assignable_v<zoned_time<seconds>> );
+static_assert( std::is_destructible_v<zoned_time<seconds>> );
+
+static_assert( std::is_same_v<zoned_time<seconds>::duration, seconds> );
+static_assert( std::is_same_v<zoned_time<nanoseconds>::duration, nanoseconds> );
+static_assert( std::is_same_v<zoned_time<minutes>::duration, seconds> );
+
+extern zoned_time<minutes> z;
+static_assert( std::is_same_v<decltype(z == z), bool> );
+
+// requires zoned_traits<time_zone*>::default_zone().
+static_assert( ! std::is_default_constructible_v<zoned_time<seconds, time_zone*>> );
+// requires zoned_traits<time_zone*>::locate_zone(string_view).
+static_assert( ! std::is_constructible_v<zoned_time<seconds, time_zone*>,
+					 std::string_view> );
diff --git a/libstdc++-v3/testsuite/std/time/zoned_traits.cc b/libstdc++-v3/testsuite/std/time/zoned_traits.cc
new file mode 100644
index 0000000000000000000000000000000000000000..0cab8a2d47f8c78d69ec18707b7c9576350121b1
--- /dev/null
+++ b/libstdc++-v3/testsuite/std/time/zoned_traits.cc
@@ -0,0 +1,39 @@
+// { dg-options "-std=gnu++20" }
+// { dg-do run { target c++20 } }
+// { dg-require-effective-target cxx11_abi }
+
+#include <chrono>
+#include <testsuite_hooks.h>
+
+using namespace std::chrono;
+
+static_assert( std::is_empty_v<zoned_traits<const time_zone*>> );
+static_assert(std::is_default_constructible_v<zoned_traits<const time_zone*>>);
+
+// The primary template is a complete type, it just has no members.
+static_assert( std::is_empty_v<zoned_traits<time_zone*>> );
+static_assert(std::is_default_constructible_v<zoned_traits<time_zone*>>);
+static_assert( std::is_empty_v<zoned_traits<int>> );
+static_assert(std::is_default_constructible_v<zoned_traits<int>>);
+
+void
+test_default_zone()
+{
+  auto p = zoned_traits<const time_zone*>::default_zone();
+  static_assert( std::is_same_v<decltype(p), const time_zone*> );
+  VERIFY( p == locate_zone("UTC") );
+}
+
+void
+test_locate_zone()
+{
+  auto p = zoned_traits<const time_zone*>::locate_zone("GMT");
+  static_assert( std::is_same_v<decltype(p), const time_zone*> );
+  VERIFY( p == locate_zone("GMT") );
+}
+
+int main()
+{
+  test_default_zone();
+  test_locate_zone();
+}