diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 2ecbd6efb5a60c64d8c980f5e8641aca28fa0db4..3957879436775a5bf374bf082301358d1051cfa4 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -4115,7 +4115,10 @@ xFlagsDeps = [ flagSpec "AlternativeLayoutRuleTransitional" LangExt.AlternativeLayoutRuleTransitional, flagSpec "Arrows" LangExt.Arrows, - flagSpec "AutoDeriveTypeable" LangExt.AutoDeriveTypeable, + depFlagSpecCond "AutoDeriveTypeable" LangExt.AutoDeriveTypeable + id + ("Typeable instances are created automatically " ++ + "for all types since GHC 8.2."), flagSpec "BangPatterns" LangExt.BangPatterns, flagSpec "BinaryLiterals" LangExt.BinaryLiterals, flagSpec "CApiFFI" LangExt.CApiFFI, diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4a860acfb142183e56958f39a368fd75e87341d1..2a98522e837b49b119c3975c48d8904d385c911b 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -4453,7 +4453,7 @@ Deriving ``Data`` instances .. extension:: DeriveDataTypeable :shortdesc: Enable deriving for the Data class. - Implied by :extension:`AutoDeriveTypeable`. + Implied by (deprecated) :extension:`AutoDeriveTypeable`. :since: 6.8.1 diff --git a/testsuite/tests/dependent/should_compile/dynamic-paper.hs b/testsuite/tests/dependent/should_compile/dynamic-paper.hs index 2c284cfeea2cdd8d53c3db473d1b06f3cb084151..c998f0967c2fa649f1cb65912d0432ac516c625f 100644 --- a/testsuite/tests/dependent/should_compile/dynamic-paper.hs +++ b/testsuite/tests/dependent/should_compile/dynamic-paper.hs @@ -7,7 +7,7 @@ Stephanie Weirich, Richard Eisenberg, and Dimitrios Vytiniotis, 2016. -} {-# LANGUAGE RankNTypes, PolyKinds, TypeOperators, ScopedTypeVariables, GADTs, FlexibleInstances, UndecidableInstances, RebindableSyntax, - DataKinds, MagicHash, AutoDeriveTypeable #-} + DataKinds, MagicHash #-} {-# OPTIONS_GHC -Wno-missing-methods -Wno-redundant-constraints #-} {-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-} -- Because we define a local Typeable class and have diff --git a/testsuite/tests/deriving/should_compile/AutoDeriveTypeable.hs b/testsuite/tests/deriving/should_compile/AutoDeriveTypeable.hs index 52e6c3823c57db71f9a94b975e48c610ef77f950..281b33033778946632e46eedbd58ed7c2990004c 100644 --- a/testsuite/tests/deriving/should_compile/AutoDeriveTypeable.hs +++ b/testsuite/tests/deriving/should_compile/AutoDeriveTypeable.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE AutoDeriveTypeable #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} diff --git a/testsuite/tests/deriving/should_compile/T7710.hs b/testsuite/tests/deriving/should_compile/T7710.hs index 5375c2c0ebd533e2a19c3284cbad38df1c58a159..9a5af946ac27f3855368692ad8eecad2c758783d 100644 --- a/testsuite/tests/deriving/should_compile/T7710.hs +++ b/testsuite/tests/deriving/should_compile/T7710.hs @@ -1,6 +1,5 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE AutoDeriveTypeable #-} {-# LANGUAGE TypeFamilies #-} module T7710 where diff --git a/testsuite/tests/deriving/should_compile/T8950.hs b/testsuite/tests/deriving/should_compile/T8950.hs index b913b27aa88f6812c2f01ace74ed957cd3e882e4..58c6590b0e6627d0a075a2d7ae25e355d02a3126 100644 --- a/testsuite/tests/deriving/should_compile/T8950.hs +++ b/testsuite/tests/deriving/should_compile/T8950.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE AutoDeriveTypeable, DataKinds, StandaloneDeriving #-} +{-# LANGUAGE DataKinds, StandaloneDeriving #-} module T8950 where diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs index dadb8aa7cfeab90b94ab0c31bce99b6e367d699e..d79e66b93685c9ee15f5a11b8487d365c06f081d 100644 --- a/testsuite/tests/typecheck/should_compile/T10348.hs +++ b/testsuite/tests/typecheck/should_compile/T10348.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving, TypeOperators #-} +{-# LANGUAGE GADTs, DataKinds, KindSignatures, StandaloneDeriving, TypeOperators #-} module T10348 where diff --git a/testsuite/tests/typecheck/should_fail/T9999.hs b/testsuite/tests/typecheck/should_fail/T9999.hs index 656e913043c239c1609e395b0f2ece9c3b2b1ca5..8422df2b03b3b708b950f07080aa3ad0af785ce9 100644 --- a/testsuite/tests/typecheck/should_fail/T9999.hs +++ b/testsuite/tests/typecheck/should_fail/T9999.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE AutoDeriveTypeable, PolyKinds, TypeFamilies, StandaloneDeriving #-} +{-# LANGUAGE PolyKinds, TypeFamilies, StandaloneDeriving #-} module T9999 where