diff --git a/compiler/GHC/Driver/DynFlags.hs b/compiler/GHC/Driver/DynFlags.hs index 83f7e2ab649c353771ec7548c64ca0c1af8f47b6..6398f29f9a423279e752a3875e4b5fdd1614a09f 100644 --- a/compiler/GHC/Driver/DynFlags.hs +++ b/compiler/GHC/Driver/DynFlags.hs @@ -1339,7 +1339,7 @@ default_PIC platform = languageExtensions :: Maybe Language -> [LangExt.Extension] -- Nothing: the default case -languageExtensions Nothing = languageExtensions (Just GHC2021) +languageExtensions Nothing = languageExtensions (Just defaultLanguage) languageExtensions (Just Haskell98) = [LangExt.ImplicitPrelude, @@ -1427,6 +1427,16 @@ languageExtensions (Just GHC2021) LangExt.TypeOperators, LangExt.TypeSynonymInstances] +languageExtensions (Just GHC2024) + = languageExtensions (Just GHC2021) ++ + [LangExt.DataKinds, + LangExt.DerivingStrategies, + LangExt.DisambiguateRecordFields, + LangExt.ExplicitNamespaces, + LangExt.GADTs, + LangExt.MonoLocalBinds, + LangExt.LambdaCase, + LangExt.RoleAnnotations] ways :: DynFlags -> Ways ways dflags diff --git a/compiler/GHC/Driver/Flags.hs b/compiler/GHC/Driver/Flags.hs index 3b5cfc1a26e4c6a43ce5db3f0eeb4dd270a8d8d6..59647631f45452c905b00887003ced14f5b2b4b5 100644 --- a/compiler/GHC/Driver/Flags.hs +++ b/compiler/GHC/Driver/Flags.hs @@ -4,6 +4,7 @@ module GHC.Driver.Flags , enabledIfVerbose , GeneralFlag(..) , Language(..) + , defaultLanguage , optimisationFlags , codeGenFlags @@ -38,9 +39,14 @@ import Control.Monad (guard) import Data.List.NonEmpty (NonEmpty(..)) import Data.Maybe (fromMaybe,mapMaybe) -data Language = Haskell98 | Haskell2010 | GHC2021 +data Language = Haskell98 | Haskell2010 | GHC2021 | GHC2024 deriving (Eq, Enum, Show, Bounded) +-- | The default Language is used if one is not specified explicitly, by both +-- GHC and GHCi. +defaultLanguage :: Language +defaultLanguage = GHC2021 + instance Outputable Language where ppr = text . show diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index b36a9a7f148855e37d2d00f87c976de22ba83a93..72301f947f8165cf8d822850c9398a81e6ec4ccd 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -2603,7 +2603,8 @@ languageFlagsDeps :: [(Deprecation, FlagSpec Language)] languageFlagsDeps = [ flagSpec "Haskell98" Haskell98, flagSpec "Haskell2010" Haskell2010, - flagSpec "GHC2021" GHC2021 + flagSpec "GHC2021" GHC2021, + flagSpec "GHC2024" GHC2024 ] -- | These -X<blah> flags cannot be reversed with -XNo<blah> diff --git a/docs/users_guide/9.10.1-notes.rst b/docs/users_guide/9.10.1-notes.rst index 2633529325c6b1c7eb729386040452abdd759dd5..b8b43fec159fed4542a0397c56383a3caaab16db 100644 --- a/docs/users_guide/9.10.1-notes.rst +++ b/docs/users_guide/9.10.1-notes.rst @@ -6,6 +6,24 @@ Version 9.10.1 Language ~~~~~~~~ +- The :extension:`GHC2024` language edition is now supported. It builds on top of + :extension:`GHC2021`, adding the following extensions: + + * :extension:`DataKinds` + * :extension:`DerivingStrategies` + * :extension:`DisambiguateRecordFields` + * :extension:`ExplicitNamespaces` + * :extension:`GADTs` + * :extension:`MonoLocalBinds` + * :extension:`LambdaCase` + * :extension:`RoleAnnotations` + + At the moment, :extension:`GHC2021` remains the default langauge edition that + is used when no other language edition is explicitly loaded (e.g. when running + ``ghc`` directly). Because language editions are not necessarily backwards + compatible, and future releases of GHC may change the default, it is highly + recommended to specify the language edition explicitly. + - GHC Proposal `#281 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_ "Visible forall in types of terms" has been partially implemented. The following code is now accepted by GHC:: diff --git a/docs/users_guide/exts/binary_literals.rst b/docs/users_guide/exts/binary_literals.rst index 29c5ad290fb49356cadf6bb75c8a0fee99b0930a..b65f6522f6717c9e9bd4cfdccdec4d206bd751c5 100644 --- a/docs/users_guide/exts/binary_literals.rst +++ b/docs/users_guide/exts/binary_literals.rst @@ -8,7 +8,7 @@ Binary integer literals :since: 7.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of binary notation in integer literals. diff --git a/docs/users_guide/exts/constrained_class_methods.rst b/docs/users_guide/exts/constrained_class_methods.rst index 37ca499c6ceabb7b16ce62fde780df339e434f2d..f28bf0c55dd30d1931e6d218911c108d05e01e58 100644 --- a/docs/users_guide/exts/constrained_class_methods.rst +++ b/docs/users_guide/exts/constrained_class_methods.rst @@ -9,7 +9,7 @@ Constrained class method types :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` :implied by: :extension:`MultiParamTypeClasses` diff --git a/docs/users_guide/exts/constraint_kind.rst b/docs/users_guide/exts/constraint_kind.rst index 7cbe132ff82703724e62e62681b5eac248664cf7..7915b893884e3c90b69acb7cb89fa7f104450ad0 100644 --- a/docs/users_guide/exts/constraint_kind.rst +++ b/docs/users_guide/exts/constraint_kind.rst @@ -8,7 +8,7 @@ The ``Constraint`` kind :since: 7.4.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow types of kind ``Constraint`` to be used in contexts. diff --git a/docs/users_guide/exts/control.rst b/docs/users_guide/exts/control.rst index 60726e9dbabed59a1cf85f6ef84e1a66cc91162b..b5b8383a0792b29aed6896e1db0f3aa778a1c959 100644 --- a/docs/users_guide/exts/control.rst +++ b/docs/users_guide/exts/control.rst @@ -1,49 +1,144 @@ .. _options-language: -Controlling extensions ----------------------- +Controlling editions and extensions +----------------------------------- .. index:: single: language; option single: options; language single: extensions; options controlling + single: editions; language -Language extensions can be controlled (i.e. allowed or not) in two ways: +GHC supports multiple language editions: :extension:`Haskell98`, +:extension:`Haskell2010`, :extension:`GHC2021` and :extension:`GHC2024`. Each +language edition consists of a collection of language extensions, and there are +many other language extensions not currently part of a language edition but that +can be enabled explicitly. -- Every language extension can be switched on by a command-line flag +Currently, :extension:`GHC2021` is used by default if no other language edition +is explicitly requested, for backwards compatibility purposes. Since later +versions of GHC may use a different language edition by default, users are +advised to declare a language edition explicitly. Using :extension:`GHC2024` is +recommended for new code. + +A language edition can be selected: + +- at the package level, e.g. using ``default-language: GHC2024`` in a + ``.cabal`` file; + +- with a command-line flag prefixed by "``-X...``" (e.g. ``-XGHC2024``); or + +- for an individual module using the :pragma:`LANGUAGE` pragma, e.g. + ``{-# LANGUAGE GHC2024 #-}``. + +Selecting a language edition overrides any previous selection. It is not +possible to disable a language edition. + +Similarly, language extensions can be controlled (either enabled or disabled): + +- at the package level, e.g. using ``default-extensions: TemplateHaskell`` in a + ``.cabal`` file; + +- with command-line flags, switched on by a command-line flag "``-X...``" (e.g. ``-XTemplateHaskell``), and switched off by the - flag "``-XNo...``"; (e.g. ``-XNoTemplateHaskell``). + flag "``-XNo...``"; (e.g. ``-XNoTemplateHaskell``); -- Language extensions can also be enabled using the ``LANGUAGE`` pragma, thus - ``{-# LANGUAGE TemplateHaskell #-}`` (see :ref:`language-pragma`). +- for an individual module using the :pragma:`LANGUAGE` pragma, e.g. + ``{-# LANGUAGE TemplateHaskell #-}`` or ``{-# LANGUAGE NoTemplateHaskell #-}``. -.. extension:: GHC2021 - :shortdesc: Use GHC’s set of default language extensions from 2021 +.. extension:: GHC2024 + :shortdesc: Use GHC’s set of default language extensions from 2024 + + :since: 9.10.1 GHC blesses a number of extensions, beyond Haskell 2010, to be suitable to turned on by default. These extensions are considered to be stable and conservative. - ``GHC2021`` is used by GHC if neither ``Haskell98`` nor ``Haskell2010`` is - turned on explicitly. Since later versions of GHC may use a later - ``GHC20xx`` by default, users are advised to declare the language set - explicitly with ``-XGHC2021``. - - Note that, because GHC2021 includes a number of non-standardized + Note that, because GHC2024 includes a number of non-standardized extensions, the stability guarantees it provides are not quite as strong as those provided by, e.g., :extension:`Haskell2010`. While GHC does take pains to avoid changing the semantics of these extensions, changes may still happen (e.g. the simplified subsumption change introduced in GHC 9.0 which caused GHC to reject some programs using :extension:`RankNTypes`). + The ``GHC2024`` language edition includes the following extensions: + + .. hlist:: + + * :extension:`BangPatterns` + * :extension:`BinaryLiterals` + * :extension:`ConstrainedClassMethods` + * :extension:`ConstraintKinds` + * :extension:`DataKinds` + * :extension:`DeriveDataTypeable` + * :extension:`DeriveFoldable` + * :extension:`DeriveFunctor` + * :extension:`DeriveGeneric` + * :extension:`DeriveLift` + * :extension:`DeriveTraversable` + * :extension:`DerivingStrategies` + * :extension:`DisambiguateRecordFields` + * :extension:`DoAndIfThenElse` + * :extension:`EmptyCase` + * :extension:`EmptyDataDecls` + * :extension:`EmptyDataDeriving` + * :extension:`ExistentialQuantification` + * :extension:`ExplicitForAll` + * :extension:`ExplicitNamespaces` + * :extension:`FieldSelectors` + * :extension:`FlexibleContexts` + * :extension:`FlexibleInstances` + * :extension:`ForeignFunctionInterface` + * :extension:`GADTs` + * :extension:`GADTSyntax` + * :extension:`GeneralisedNewtypeDeriving` + * :extension:`HexFloatLiterals` + * :extension:`ImplicitPrelude` + * :extension:`ImportQualifiedPost` + * :extension:`InstanceSigs` + * :extension:`KindSignatures` + * :extension:`LambdaCase` + * :extension:`MonoLocalBinds` + * :extension:`MonomorphismRestriction` + * :extension:`MultiParamTypeClasses` + * :extension:`NamedFieldPuns` + * :extension:`NamedWildCards` + * :extension:`NumericUnderscores` + * :extension:`PatternGuards` + * :extension:`PolyKinds` + * :extension:`PostfixOperators` + * :extension:`RankNTypes` + * :extension:`RelaxedPolyRec` + * :extension:`RoleAnnotations` + * :extension:`ScopedTypeVariables` + * :extension:`StandaloneDeriving` + * :extension:`StandaloneKindSignatures` + * :extension:`StarIsType` + * :extension:`TraditionalRecordSyntax` + * :extension:`TupleSections` + * :extension:`TypeApplications` + * :extension:`TypeOperators` + * :extension:`TypeSynonymInstances` + +.. extension:: GHC2021 + :shortdesc: Use GHC’s set of default language extensions from 2021 + + :since: 9.2.1 + + See :extension:`GHC2024` for general comments about ``GHC20xx`` language + editions. + Also note that due to a `minor oversight - <https://github.com/ghc-proposals/ghc-proposals/issues/551>`_, this - extension set behaves slightly differently than enabling each of its + <https://github.com/ghc-proposals/ghc-proposals/issues/551>`_, enabling + this edition behaves slightly differently than enabling each of its constituent extensions. Specifically, while :extension:`TypeOperators` implies :extension:`ExplicitNamespaces`, :extension:`ExplicitNamespaces` is not included - in :extension:`GHC2021`. + in :extension:`GHC2021`. Moreover, while :extension:`GADTs` is not part of + :extension:`GHC2021`, the combination of :extension:`GADTSyntax` and + :extension:`ExistentialQuantification` is enough to define and use GADTs. - The ``GHC2021`` language set comprises the following extensions: + The ``GHC2021`` language edition includes the following extensions: .. hlist:: @@ -97,10 +192,14 @@ Language extensions can be controlled (i.e. allowed or not) in two ways: .. extension:: Haskell2010 - :shortdesc: Use the Haskell 2010 language variant. + :shortdesc: Use the Haskell 2010 language edition. - Compile Haskell 2010 language variant. Enables the - following language extensions: + Compile using the Haskell 2010 language edition, as specified by the + `Haskell 2010 report <https://www.haskell.org/onlinereport/haskell2010/>`_. + GHC aims to behave mostly as a Haskell 2010 compiler, but there are a few + known deviations from the standard (see :ref:`vs-Haskell-defn`). + + The ``Haskell2010`` language edition includes the following language extensions: .. hlist:: @@ -120,10 +219,14 @@ Language extensions can be controlled (i.e. allowed or not) in two ways: .. extension:: Haskell98 - :shortdesc: Use the Haskell 98 language variant. + :shortdesc: Use the Haskell 98 language edition. + + Compile using the Haskell 98 language edition, as specified by the `Haskell + 98 report <https://www.haskell.org/onlinereport/>`_. GHC aims to behave + mostly as a Haskell 98 compiler, but there are a few known deviations from + the standard (see :ref:`vs-Haskell-defn`). - Compile using Haskell 98 language variant. Enables the - following language extensions: + The ``Haskell98`` language edition includes the following language extensions: .. hlist:: diff --git a/docs/users_guide/exts/data_kinds.rst b/docs/users_guide/exts/data_kinds.rst index 2843819bfecc04922ed1f07dc9548c83c8f32b1c..278e82e6681c0d878402df28223acd0af1593b7e 100644 --- a/docs/users_guide/exts/data_kinds.rst +++ b/docs/users_guide/exts/data_kinds.rst @@ -8,6 +8,8 @@ Datatype promotion :since: 7.4.1 + :status: Included in :extension:`GHC2024` + Allow promotion of data types to kind level. This section describes *data type promotion*, an extension to the kind diff --git a/docs/users_guide/exts/deriving_extra.rst b/docs/users_guide/exts/deriving_extra.rst index 42d684f499c9374c90d3a07483c48c7edc829c91..9f3374e0f1461e59f8cd48c76161939749da7178 100644 --- a/docs/users_guide/exts/deriving_extra.rst +++ b/docs/users_guide/exts/deriving_extra.rst @@ -55,7 +55,7 @@ Deriving ``Functor`` instances :implied by: :extension:`DeriveTraversable` :since: 7.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow automatic deriving of instances for the ``Functor`` typeclass. @@ -251,7 +251,7 @@ Deriving ``Foldable`` instances :implied by: :extension:`DeriveTraversable` :since: 7.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow automatic deriving of instances for the ``Foldable`` typeclass. @@ -472,7 +472,7 @@ Deriving ``Data`` instances :shortdesc: Enable deriving for the ``Data`` class. :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Enable automatic deriving of instances for the ``Data`` typeclass @@ -526,7 +526,7 @@ Deriving ``Lift`` instances :shortdesc: Enable deriving for the Lift class :since: 8.0.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Enable automatic deriving of instances for the ``Lift`` typeclass for Template Haskell. diff --git a/docs/users_guide/exts/deriving_strategies.rst b/docs/users_guide/exts/deriving_strategies.rst index 77e5aa5ffb162c6c9d2acec31588061e1fdb6b89..7a879a9cde3dcd2f3890d3f46169438b40a253a7 100644 --- a/docs/users_guide/exts/deriving_strategies.rst +++ b/docs/users_guide/exts/deriving_strategies.rst @@ -8,6 +8,8 @@ Deriving strategies :since: 8.2.1 + :status: Included in :extension:`GHC2024` + Allow multiple ``deriving``, each optionally qualified with a *strategy*. In most scenarios, every ``deriving`` statement generates a typeclass instance diff --git a/docs/users_guide/exts/disambiguate_record_fields.rst b/docs/users_guide/exts/disambiguate_record_fields.rst index 3c1fbcc4b4b77396347a6bdb62b032526678a083..6e0653d6411360ea875e33037e3815f7bb47d8d7 100644 --- a/docs/users_guide/exts/disambiguate_record_fields.rst +++ b/docs/users_guide/exts/disambiguate_record_fields.rst @@ -9,6 +9,7 @@ Record field disambiguation :since: 6.8.1 :implied by: :extension:`RecordWildCards`, :extension:`DuplicateRecordFields` + :status: Included in :extension:`GHC2024` Allow the compiler to automatically choose between identically-named record fields (if the choice is unambiguous). diff --git a/docs/users_guide/exts/empty_case.rst b/docs/users_guide/exts/empty_case.rst index e69a761bff084015ac1f2645bca6195b8987cfa4..0b4e7ce6deaccbf5bde015f5e7356778d3441fa8 100644 --- a/docs/users_guide/exts/empty_case.rst +++ b/docs/users_guide/exts/empty_case.rst @@ -7,7 +7,7 @@ Empty case alternatives :shortdesc: Allow empty case alternatives. :since: 7.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow empty case expressions. diff --git a/docs/users_guide/exts/empty_data_deriving.rst b/docs/users_guide/exts/empty_data_deriving.rst index e75d9a8e417199834523abfaa3293a65ae03d0eb..0f26ee0f7efac0f4ad1f931486fe4812861b0817 100644 --- a/docs/users_guide/exts/empty_data_deriving.rst +++ b/docs/users_guide/exts/empty_data_deriving.rst @@ -8,7 +8,7 @@ Deriving instances for empty data types empty data types. :since: 8.4.1 - :status: Included in :extension:`Haskell2010`, :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010` Allow deriving instances of standard type classes for empty data types. diff --git a/docs/users_guide/exts/existential_quantification.rst b/docs/users_guide/exts/existential_quantification.rst index 568eb63b7b49ba3a00e39598c4e2a5d1d0dbb922..b71ccf74175b61979a7cac8d5d26fcdff92a71d2 100644 --- a/docs/users_guide/exts/existential_quantification.rst +++ b/docs/users_guide/exts/existential_quantification.rst @@ -8,7 +8,7 @@ Existentially quantified data constructors :implies: :extension:`ExplicitForAll` :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow existentially quantified type variables in types. diff --git a/docs/users_guide/exts/explicit_forall.rst b/docs/users_guide/exts/explicit_forall.rst index 5a6212ee4b3f4ee8bd21d8c52e9ea74e17efb62d..ef470cc22da3bdf0c63e546018bd51495d0ce173 100644 --- a/docs/users_guide/exts/explicit_forall.rst +++ b/docs/users_guide/exts/explicit_forall.rst @@ -11,7 +11,7 @@ Explicit universal quantification (forall) :implied by: :extension:`ScopedTypeVariables`, :extension:`LiberalTypeSynonyms`, :extension:`RankNTypes`, :extension:`ExistentialQuantification` :since: 6.12.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow use of the ``forall`` keyword in places where universal quantification is implicit. diff --git a/docs/users_guide/exts/explicit_namespaces.rst b/docs/users_guide/exts/explicit_namespaces.rst index 74d3a79124af65f84122e37211d2f447fb8bf1c1..0e6509c31bb67cabc1ed22ec1e48c945cb32a04d 100644 --- a/docs/users_guide/exts/explicit_namespaces.rst +++ b/docs/users_guide/exts/explicit_namespaces.rst @@ -10,6 +10,7 @@ Explicit namespaces in import/export :implied by: :extension:`TypeOperators`, :extension:`TypeFamilies` :since: 7.6.1 + :status: Included in :extension:`GHC2024` Enable use of explicit namespaces in module export lists, patterns, and expressions. diff --git a/docs/users_guide/exts/ffi.rst b/docs/users_guide/exts/ffi.rst index 6246ca3b495a57f7dc26541e27069e7b0c1004fa..4000c5cd7399e60d6cf19b1df126bc8b1164ffd2 100644 --- a/docs/users_guide/exts/ffi.rst +++ b/docs/users_guide/exts/ffi.rst @@ -12,7 +12,7 @@ Foreign function interface (FFI) :since: 6.8.1 - :status: Included in :extension:`Haskell2010`, :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010` Allow use of the Haskell foreign function interface. diff --git a/docs/users_guide/exts/field_selectors.rst b/docs/users_guide/exts/field_selectors.rst index 513947fe4f3fd15cf0bf1f7582c9426fad7b2005..e22f920f9801d55b3735956ff06f73fefb3ed453 100644 --- a/docs/users_guide/exts/field_selectors.rst +++ b/docs/users_guide/exts/field_selectors.rst @@ -7,7 +7,7 @@ Field selectors :shortdesc: Control visibility of field selector functions. :since: 9.2.1 - :status: Included in :extension:`Haskell98`, :extension:`Haskell2010`, :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010`, :extension:`Haskell98` Make `record field selector functions <https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-500003.15.1>`_ diff --git a/docs/users_guide/exts/flexible_contexts.rst b/docs/users_guide/exts/flexible_contexts.rst index 532f3f2bb886454076bd71961ed373d1a83f6534..0c4222804c9280104adfcaa08a4271922971ad14 100644 --- a/docs/users_guide/exts/flexible_contexts.rst +++ b/docs/users_guide/exts/flexible_contexts.rst @@ -7,7 +7,7 @@ Loosening restrictions on class contexts :shortdesc: Remove some restrictions on class contexts :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Remove the type-variable restriction on class contexts. diff --git a/docs/users_guide/exts/gadt.rst b/docs/users_guide/exts/gadt.rst index 9190178ec1a1215f8cecca38c8cbcbc6f494c51c..856322077b317f75f410d79ed848b557c1bb12c8 100644 --- a/docs/users_guide/exts/gadt.rst +++ b/docs/users_guide/exts/gadt.rst @@ -9,6 +9,7 @@ Generalised Algebraic Data Types (GADTs) :implies: :extension:`MonoLocalBinds`, :extension:`GADTSyntax` :since: 6.8.1 + :status: Included in :extension:`GHC2024` Allow use of Generalised Algebraic Data Types (GADTs). diff --git a/docs/users_guide/exts/gadt_syntax.rst b/docs/users_guide/exts/gadt_syntax.rst index 40e5086d052a19bcfae2fcafd7eabdf11641e5c0..239dd0326e7cb5565c54bb1b06e5f01b6b79a96f 100644 --- a/docs/users_guide/exts/gadt_syntax.rst +++ b/docs/users_guide/exts/gadt_syntax.rst @@ -9,7 +9,7 @@ Declaring data types with explicit constructor signatures :implied by: :extension:`GADTs` :since: 7.2.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of GADT syntax in data type definitions (but not GADTs themselves; for this see :extension:`GADTs`) diff --git a/docs/users_guide/exts/generics.rst b/docs/users_guide/exts/generics.rst index 1cd47e277656cf33ae04dc2575c681b0e049534f..f7a21bcb0920ea4956eee86d9a4c2de56461ee28 100644 --- a/docs/users_guide/exts/generics.rst +++ b/docs/users_guide/exts/generics.rst @@ -96,7 +96,7 @@ enabled, then it can range of types of kind ``k -> Type``, for any kind ``k``. :since: 7.2.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow automatic deriving of instances for the ``Generic`` typeclass. diff --git a/docs/users_guide/exts/hex_float_literals.rst b/docs/users_guide/exts/hex_float_literals.rst index c8f3708c290a61948d5b151d15c3376f29daf3bf..7ebe6551b4293ac180bf224f641c876b4c5c9b15 100644 --- a/docs/users_guide/exts/hex_float_literals.rst +++ b/docs/users_guide/exts/hex_float_literals.rst @@ -8,7 +8,7 @@ Hexadecimal floating point literals :since: 8.4.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow writing floating point literals using hexadecimal notation. diff --git a/docs/users_guide/exts/import_qualified_post.rst b/docs/users_guide/exts/import_qualified_post.rst index 2719463b5b18f80ac2ff89c15bf6e07c12924981..b89a70d986f4bd5a8dc30da938ee9ffbab645af3 100644 --- a/docs/users_guide/exts/import_qualified_post.rst +++ b/docs/users_guide/exts/import_qualified_post.rst @@ -8,7 +8,7 @@ Writing qualified in postpositive position :since: 8.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` ``ImportQualifiedPost`` allows the syntax ``import M qualified``, that is, to annotate a module as qualified by writing ``qualified`` after the module name. diff --git a/docs/users_guide/exts/instances.rst b/docs/users_guide/exts/instances.rst index ff8f9139fcc9bb31224669090aa5fe96e3cd34ea..75f58ef0661c69f18f0d540e102ba5f57afd486b 100644 --- a/docs/users_guide/exts/instances.rst +++ b/docs/users_guide/exts/instances.rst @@ -48,7 +48,7 @@ Relaxed rules for the instance head :implied by: :extension:`FlexibleInstances` :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow definition of type class instances for type synonyms. @@ -60,7 +60,7 @@ Relaxed rules for the instance head :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow definition of type class instances with arbitrary nested types in the instance head. @@ -671,7 +671,7 @@ Instance signatures: type signatures in instance declarations :since: 7.6.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow type signatures for members in instance definitions. diff --git a/docs/users_guide/exts/intro.rst b/docs/users_guide/exts/intro.rst index 299e756d2e478af08bf66f7d1dc573b2b14d2700..1adf5eb4fb03055d183fe3357a2ae209f5b131b9 100644 --- a/docs/users_guide/exts/intro.rst +++ b/docs/users_guide/exts/intro.rst @@ -1,10 +1,9 @@ Introduction ============ -As with all known Haskell systems, GHC implements some extensions to the -standard Haskell language. They can all be enabled or disabled by command line -flags or language pragmas. By default GHC understands the most recent Haskell -version it supports, plus a handful of extensions. +GHC implements several variants of the Haskell language, along with many +extensions. They can all be enabled or disabled by command line flags or +:pragma:`LANGUAGE` pragmas. Some of the extensions serve to give you access to the underlying facilities with which we implement Haskell. Thus, you can get diff --git a/docs/users_guide/exts/kind_signatures.rst b/docs/users_guide/exts/kind_signatures.rst index a953899be207ec01933039dec81a11f5a05aec95..4b4ced0a37dfd27f8a8ff0d179eaa62de343e34f 100644 --- a/docs/users_guide/exts/kind_signatures.rst +++ b/docs/users_guide/exts/kind_signatures.rst @@ -10,7 +10,7 @@ Explicitly-kinded quantification :implied by: :extension:`TypeFamilies`, :extension:`PolyKinds` :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow explicit kind signatures on type variables. diff --git a/docs/users_guide/exts/lambda_case.rst b/docs/users_guide/exts/lambda_case.rst index 4712da3d744b45c650dcc5180234fc69eb6323c1..b6866f3beec96a88bd457e3990fc9829819c26ac 100644 --- a/docs/users_guide/exts/lambda_case.rst +++ b/docs/users_guide/exts/lambda_case.rst @@ -7,6 +7,7 @@ Lambda-case :shortdesc: Enable lambda-case expressions. :since: 7.6.1 + :status: Included in :extension:`GHC2024` Allow the use of lambda-case syntax. diff --git a/docs/users_guide/exts/let_generalisation.rst b/docs/users_guide/exts/let_generalisation.rst index bdb0c2ef86446d73d061fe9c99cec5bf8a11fb97..259e9b9d3e301c5e84f478bba6cb7ac86fea3e62 100644 --- a/docs/users_guide/exts/let_generalisation.rst +++ b/docs/users_guide/exts/let_generalisation.rst @@ -9,6 +9,7 @@ Let-generalisation :implied by: :extension:`TypeFamilies`, :extension:`GADTs` :since: 6.12.1 + :status: Included in :extension:`GHC2024` Infer less polymorphic types for local bindings by default. diff --git a/docs/users_guide/exts/multi_param_type_classes.rst b/docs/users_guide/exts/multi_param_type_classes.rst index cb2ebdc8af360be89571acc2c42f27e048a05fb3..83a59e5a1995b743346cf2b802a3231570392070 100644 --- a/docs/users_guide/exts/multi_param_type_classes.rst +++ b/docs/users_guide/exts/multi_param_type_classes.rst @@ -12,7 +12,7 @@ Multi-parameter type classes :implied by: :extension:`FunctionalDependencies` :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the definition of typeclasses with more than one parameter. diff --git a/docs/users_guide/exts/newtype_deriving.rst b/docs/users_guide/exts/newtype_deriving.rst index 8856287a916015ffaf63deeab0f8ffd0380418c6..94df2a5ad3d718ca7409f0d539bc4187310b9c5b 100644 --- a/docs/users_guide/exts/newtype_deriving.rst +++ b/docs/users_guide/exts/newtype_deriving.rst @@ -9,7 +9,7 @@ Generalised derived instances for newtypes :since: 6.8.1. British spelling since 8.6.1. - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Enable GHC's cunning generalised deriving mechanism for ``newtype``\s diff --git a/docs/users_guide/exts/nullary_types.rst b/docs/users_guide/exts/nullary_types.rst index 2ce85cb9d95c5ed8aeb254bd69dad78a00055877..f0b70eddc2ef956f73be47eb679fb8b7411e08a4 100644 --- a/docs/users_guide/exts/nullary_types.rst +++ b/docs/users_guide/exts/nullary_types.rst @@ -8,7 +8,7 @@ Data types with no constructors :since: 6.8.1 - :status: Included in :extension:`GHC2021` and :extension:`Haskell2010` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` and :extension:`Haskell2010` Allow definition of empty ``data`` types. diff --git a/docs/users_guide/exts/numeric_underscores.rst b/docs/users_guide/exts/numeric_underscores.rst index 7a96e00d88ac1dc1b74da20bf8c118d070ffca8e..c8a9d708a7b04791fdb0f821239ea05fdb9a0eef 100644 --- a/docs/users_guide/exts/numeric_underscores.rst +++ b/docs/users_guide/exts/numeric_underscores.rst @@ -8,7 +8,7 @@ Numeric underscores :since: 8.6.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of underscores in numeric literals. diff --git a/docs/users_guide/exts/partial_type_signatures.rst b/docs/users_guide/exts/partial_type_signatures.rst index 6b3b88a59cf8f0d0735613aaeca1ba10453eb099..c6e1b30952aea1bb21bcfaa09eb9810e74d51554 100644 --- a/docs/users_guide/exts/partial_type_signatures.rst +++ b/docs/users_guide/exts/partial_type_signatures.rst @@ -125,7 +125,7 @@ Named Wildcards :since: 7.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow naming of wildcards (e.g. ``_x``) in type signatures. diff --git a/docs/users_guide/exts/poly_kinds.rst b/docs/users_guide/exts/poly_kinds.rst index 4b5d609b0ef32c71ce0865c804099d4699901668..06b51d0e1a428c3f42fcf1027e9ee1df5a0ae11e 100644 --- a/docs/users_guide/exts/poly_kinds.rst +++ b/docs/users_guide/exts/poly_kinds.rst @@ -22,7 +22,7 @@ Kind polymorphism :implies: :extension:`KindSignatures` :since: 7.4.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow kind polymorphic types. @@ -389,7 +389,7 @@ Standalone kind signatures and polymorphic recursion :implies: :extension:`NoCUSKs` :since: 8.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Just as in type inference, kind inference for recursive types can only use *monomorphic* recursion. Consider this (contrived) example: :: @@ -922,7 +922,7 @@ The kind ``Type`` :shortdesc: Treat ``*`` as ``Data.Kind.Type``. :since: 8.6.1 - :status: Included in :extension:`Haskell98`, :extension:`Haskell2010`, :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010`, :extension:`Haskell98` Treat the unqualified uses of the ``*`` type operator as nullary and desugar to ``Data.Kind.Type``. diff --git a/docs/users_guide/exts/rank_polymorphism.rst b/docs/users_guide/exts/rank_polymorphism.rst index 9c9e40012b7ebd9e6761800d88ea89ca7380ff5b..1aaab408e3b1871984244c6adeef0a80628f6378 100644 --- a/docs/users_guide/exts/rank_polymorphism.rst +++ b/docs/users_guide/exts/rank_polymorphism.rst @@ -9,7 +9,7 @@ Arbitrary-rank polymorphism :implies: :extension:`ExplicitForAll` :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow types of arbitrary rank. diff --git a/docs/users_guide/exts/rebindable_syntax.rst b/docs/users_guide/exts/rebindable_syntax.rst index 4955e17c1135940c46d0d04ec8e44df68fe7db9a..72445374ef8536958e4cc467645215683ffde3f1 100644 --- a/docs/users_guide/exts/rebindable_syntax.rst +++ b/docs/users_guide/exts/rebindable_syntax.rst @@ -166,7 +166,7 @@ Postfix operators :shortdesc: Enable postfix operators. :since: 7.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of post-fix operators diff --git a/docs/users_guide/exts/record_puns.rst b/docs/users_guide/exts/record_puns.rst index c1bfc6fad8e9990a7fe9964f269dfec57aa1c291..8682d812386769d2ac81b3c20d3cab11deb4cc4e 100644 --- a/docs/users_guide/exts/record_puns.rst +++ b/docs/users_guide/exts/record_puns.rst @@ -8,7 +8,7 @@ Record puns :since: 6.10.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow use of record puns. diff --git a/docs/users_guide/exts/roles.rst b/docs/users_guide/exts/roles.rst index 43c0d1f0d132d5f1bad256542a58e70433444244..16cc84772fc4103ac7a44a0dd5fff87bfb11e169 100644 --- a/docs/users_guide/exts/roles.rst +++ b/docs/users_guide/exts/roles.rst @@ -151,6 +151,7 @@ Role annotations :shortdesc: Enable role annotations. :since: 7.8.1 + :status: Included in :extension:`GHC2024` Allow role annotation syntax. diff --git a/docs/users_guide/exts/scoped_type_variables.rst b/docs/users_guide/exts/scoped_type_variables.rst index feeb65ecb7fefea8b8ca5ab871e72826422f312b..8133e8f81c54c8758afc0a2ad1446eb505442af5 100644 --- a/docs/users_guide/exts/scoped_type_variables.rst +++ b/docs/users_guide/exts/scoped_type_variables.rst @@ -12,7 +12,7 @@ Lexically scoped type variables :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Enable lexical scoping of type variables explicitly introduced with ``forall``. diff --git a/docs/users_guide/exts/standalone_deriving.rst b/docs/users_guide/exts/standalone_deriving.rst index ef2bd86d284424605996a00d924cf6ca8e4ba022..f9c06ee691a0ac57c4f36839d2f673f42fb29b4a 100644 --- a/docs/users_guide/exts/standalone_deriving.rst +++ b/docs/users_guide/exts/standalone_deriving.rst @@ -8,7 +8,7 @@ Stand-alone deriving declarations :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of stand-alone ``deriving`` declarations. diff --git a/docs/users_guide/exts/strict.rst b/docs/users_guide/exts/strict.rst index 1e7bca739bb6f812eef16070a78893455359d156..17e1365092f8f3e416af724d276fc45c65260372 100644 --- a/docs/users_guide/exts/strict.rst +++ b/docs/users_guide/exts/strict.rst @@ -41,7 +41,7 @@ Bang patterns :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow use of bang pattern syntax. diff --git a/docs/users_guide/exts/tuple_sections.rst b/docs/users_guide/exts/tuple_sections.rst index d031535831416a2fa474b7777ce7f462faf8da96..156816120de1ed0b125b7c07d8dd867b24ad80cd 100644 --- a/docs/users_guide/exts/tuple_sections.rst +++ b/docs/users_guide/exts/tuple_sections.rst @@ -8,7 +8,7 @@ Tuple sections :since: 6.12 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of tuple section syntax diff --git a/docs/users_guide/exts/type_applications.rst b/docs/users_guide/exts/type_applications.rst index f37325d9cd6b42eeea794293a64852b124bc3e35..cee3b8c2bf4fcde4680fcc28d8387e223981daaa 100644 --- a/docs/users_guide/exts/type_applications.rst +++ b/docs/users_guide/exts/type_applications.rst @@ -8,7 +8,7 @@ Visible type application :since: 8.0.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use of type application syntax. diff --git a/docs/users_guide/exts/type_operators.rst b/docs/users_guide/exts/type_operators.rst index 30886913d5ada2d2ba0cad1df713224e5e27364f..f3a6abdb02b93aa94b4412b48b18f141176a273f 100644 --- a/docs/users_guide/exts/type_operators.rst +++ b/docs/users_guide/exts/type_operators.rst @@ -11,7 +11,7 @@ Type operators :since: 6.8.1 - :status: Included in :extension:`GHC2021` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021` Allow the use and definition of types with operator names. diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index d0e39e2cc78d8ee080c1a7aeb9c04758f54f3883..3a9dfd92d6a34513e3de0e80c5688fadcf2f1e94 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -45,6 +45,7 @@ import GHC.ByteCode.Types import GHC.Core.DataCon import GHC.Core.ConLike import GHC.Core.PatSyn +import GHC.Driver.Flags import GHC.Driver.Errors import GHC.Driver.Errors.Types import GHC.Driver.Phases @@ -3488,6 +3489,7 @@ showLanguages' show_all dflags = Haskell98 -> text "Haskell98" Haskell2010 -> text "Haskell2010" GHC2021 -> text "GHC2021" + GHC2024 -> text "GHC2024" , (if show_all then text "all active language options:" else text "with the following modifiers:") $$ nest 2 (vcat (map (setting xopt) DynFlags.xFlags)) @@ -3504,7 +3506,7 @@ showLanguages' show_all dflags = default_dflags = defaultDynFlags (settings dflags) `lang_set` Just lang - lang = fromMaybe GHC2021 (language dflags) + lang = fromMaybe defaultLanguage (language dflags) showTargets :: GHC.GhcMonad m => m () diff --git a/testsuite/tests/roles/should_compile/Roles1.hs b/testsuite/tests/roles/should_compile/Roles1.hs index 8488665fc613cd8a4154023cbd2d19d243754fd9..036149b7c1a73d3bb92676407ddd17b13aed3efb 100644 --- a/testsuite/tests/roles/should_compile/Roles1.hs +++ b/testsuite/tests/roles/should_compile/Roles1.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE RoleAnnotations, PolyKinds #-} +{-# LANGUAGE GHC2024 #-} module Roles1 where