From bd20f1b2f09f3dfe735afd66c4779491479670ce Mon Sep 17 00:00:00 2001 From: Emily Pillmore <emilypi@cohomolo.gy> Date: Tue, 20 Apr 2021 15:01:08 -0400 Subject: [PATCH] Add new language extensions for 9.2 (#7349) * Add language and extensions for 9.2 * Add changelog entry for extensions * Add vim editor entry for 9.2 extensions Co-authored-by: Ben Gamari <ben@smart-cactus.org> --- .../Distribution/Utils/Structured.hs | 22 ++++++++++++++----- Cabal/src/Distribution/Simple/GHC.hs | 6 ++--- Cabal/src/Distribution/Simple/GHC/ImplInfo.hs | 3 +++ Cabal/src/Distribution/Simple/GHC/Internal.hs | 5 +++++ Cabal/src/Language/Haskell/Extension.hs | 16 +++++++++++++- changelog.d/pr-7349 | 4 ++++ editors/vim/syntax/cabal.vim | 7 ++++++ 7 files changed, 53 insertions(+), 10 deletions(-) create mode 100644 changelog.d/pr-7349 diff --git a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs index fd984b1a78..cf24426217 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs @@ -3,9 +3,9 @@ module UnitTests.Distribution.Utils.Structured (tests) where import Data.Proxy (Proxy (..)) import Distribution.Utils.MD5 (md5FromInteger) -import Distribution.Utils.Structured (structureHash) +import Distribution.Utils.Structured (structureHash, Structured) import Test.Tasty (TestTree, testGroup) -import Test.Tasty.HUnit (testCase, (@?=)) +import Test.Tasty.HUnit (testCase, (@?=), Assertion) import Distribution.SPDX.License (License) import Distribution.Types.VersionRange (VersionRange) @@ -20,11 +20,21 @@ import UnitTests.Orphans () tests :: TestTree tests = testGroup "Distribution.Utils.Structured" -- This test also verifies that structureHash doesn't loop. - [ testCase "VersionRange" $ structureHash (Proxy :: Proxy VersionRange) @?= md5FromInteger 0x39396fc4f2d751aaa1f94e6d843f03bd - , testCase "SPDX.License" $ structureHash (Proxy :: Proxy License) @?= md5FromInteger 0xd3d4a09f517f9f75bc3d16370d5a853a + [ testCase "VersionRange" $ + md5Check (Proxy :: Proxy VersionRange) 0x39396fc4f2d751aaa1f94e6d843f03bd + , testCase "SPDX.License" $ + md5Check (Proxy :: Proxy License) 0xd3d4a09f517f9f75bc3d16370d5a853a -- The difference is in encoding of newtypes #if MIN_VERSION_base(4,7,0) - , testCase "GenericPackageDescription" $ structureHash (Proxy :: Proxy GenericPackageDescription) @?= md5FromInteger 0x1e02ad776ad91e10d644d1ead8927205 - , testCase "LocalBuildInfo" $ structureHash (Proxy :: Proxy LocalBuildInfo) @?= md5FromInteger 0x06bf760ed08809b56b165f72d485b9c5 + , testCase "GenericPackageDescription" $ + md5Check (Proxy :: Proxy GenericPackageDescription) 0x9b7d0415b1d2522d72ac9e9739c97574 + , testCase "LocalBuildInfo" $ + md5Check (Proxy :: Proxy LocalBuildInfo) 0x0ca1dc5da4c4695a9da40e080bf4f536 #endif ] + +-- -------------------------------------------------------------------- -- +-- utils + +md5Check :: Structured a => Proxy a -> Integer -> Assertion +md5Check proxy md5Int = structureHash proxy @?= md5FromInteger md5Int diff --git a/Cabal/src/Distribution/Simple/GHC.hs b/Cabal/src/Distribution/Simple/GHC.hs index e506ab4218..3c9ef3b440 100644 --- a/Cabal/src/Distribution/Simple/GHC.hs +++ b/Cabal/src/Distribution/Simple/GHC.hs @@ -137,12 +137,12 @@ configure verbosity hcPath hcPkgPath conf0 = do (userMaybeSpecifyPath "ghc" hcPath conf0) let implInfo = ghcVersionImplInfo ghcVersion - -- Cabal currently supports ghc >= 7.0.1 && < 9.1 + -- Cabal currently supports ghc >= 7.0.1 && < 9.4 -- ... and the following odd development version - unless (ghcVersion < mkVersion [9,2]) $ + unless (ghcVersion < mkVersion [9,4]) $ warn verbosity $ "Unknown/unsupported 'ghc' version detected " - ++ "(Cabal " ++ prettyShow cabalVersion ++ " supports 'ghc' version < 9.1): " + ++ "(Cabal " ++ prettyShow cabalVersion ++ " supports 'ghc' version < 9.4): " ++ programPath ghcProg ++ " is version " ++ prettyShow ghcVersion -- This is slightly tricky, we have to configure ghc first, then we use the diff --git a/Cabal/src/Distribution/Simple/GHC/ImplInfo.hs b/Cabal/src/Distribution/Simple/GHC/ImplInfo.hs index ce4df928d8..7132398d14 100644 --- a/Cabal/src/Distribution/Simple/GHC/ImplInfo.hs +++ b/Cabal/src/Distribution/Simple/GHC/ImplInfo.hs @@ -35,6 +35,7 @@ import Distribution.Version data GhcImplInfo = GhcImplInfo { supportsHaskell2010 :: Bool -- ^ -XHaskell2010 and -XHaskell98 flags + , supportsGHC2021 :: Bool -- ^ -XGHC2021 flag , reportsNoExt :: Bool -- ^ --supported-languages gives Ext and NoExt , alwaysNondecIndent :: Bool -- ^ NondecreasingIndentation is always on , flagGhciScript :: Bool -- ^ -ghci-script flag supported @@ -61,6 +62,7 @@ getImplInfo comp = ghcVersionImplInfo :: Version -> GhcImplInfo ghcVersionImplInfo ver = GhcImplInfo { supportsHaskell2010 = v >= [7] + , supportsGHC2021 = v >= [9,1] , reportsNoExt = v >= [7] , alwaysNondecIndent = v < [7,1] , flagGhciScript = v >= [7,2] @@ -79,6 +81,7 @@ ghcjsVersionImplInfo :: Version -- ^ The GHCJS version -> GhcImplInfo ghcjsVersionImplInfo _ghcjsver ghcver = GhcImplInfo { supportsHaskell2010 = True + , supportsGHC2021 = True , reportsNoExt = True , alwaysNondecIndent = False , flagGhciScript = True diff --git a/Cabal/src/Distribution/Simple/GHC/Internal.hs b/Cabal/src/Distribution/Simple/GHC/Internal.hs index bdf72c79c6..8ff5f24091 100644 --- a/Cabal/src/Distribution/Simple/GHC/Internal.hs +++ b/Cabal/src/Distribution/Simple/GHC/Internal.hs @@ -218,6 +218,11 @@ getLanguages :: Verbosity -> GhcImplInfo -> ConfiguredProgram -> IO [(Language, String)] getLanguages _ implInfo _ -- TODO: should be using --supported-languages rather than hard coding + | supportsGHC2021 implInfo = return + [ (GHC2021, "-XGHC2021") + , (Haskell2010, "-XHaskell2010") + , (Haskell98, "-XHaskell98") + ] | supportsHaskell2010 implInfo = return [(Haskell98, "-XHaskell98") ,(Haskell2010, "-XHaskell2010")] | otherwise = return [(Haskell98, "")] diff --git a/Cabal/src/Language/Haskell/Extension.hs b/Cabal/src/Language/Haskell/Extension.hs index e091e9b68a..ca83516be8 100644 --- a/Cabal/src/Language/Haskell/Extension.hs +++ b/Cabal/src/Language/Haskell/Extension.hs @@ -54,6 +54,10 @@ data Language = -- <http://www.haskell.org/onlinereport/haskell2010> | Haskell2010 + -- | The GHC2021 collection of language extensions. + -- <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0380-ghc2021.rst> + | GHC2021 + -- | An unknown language, identified by its name. | UnknownLanguage String deriving (Generic, Show, Read, Eq, Typeable, Data) @@ -63,8 +67,9 @@ instance Structured Language instance NFData Language where rnf = genericRnf +-- | List of known (supported) languages for GHC knownLanguages :: [Language] -knownLanguages = [Haskell98, Haskell2010] +knownLanguages = [Haskell98, Haskell2010, GHC2021] instance Pretty Language where pretty (UnknownLanguage other) = Disp.text other @@ -849,6 +854,15 @@ data KnownExtension = -- | Enable linear types. | LinearTypes + -- | Enable the generation of selector functions corresponding to record fields. + | FieldSelectors + + -- | Enable the use of record dot-accessor and updater syntax + | OverloadedRecordDot + + -- | Enable data types for which an unlifted or levity-polymorphic result kind is inferred. + | UnliftedDatatypes + deriving (Generic, Show, Read, Eq, Ord, Enum, Bounded, Typeable, Data) instance Binary KnownExtension diff --git a/changelog.d/pr-7349 b/changelog.d/pr-7349 new file mode 100644 index 0000000000..d7ad857bdc --- /dev/null +++ b/changelog.d/pr-7349 @@ -0,0 +1,4 @@ +synopsis: Add language extensions for GHC 9.2 +pr: #7349 +issues: #7312 +decription: { Add support for new language extensions added in 9.2 } \ No newline at end of file diff --git a/editors/vim/syntax/cabal.vim b/editors/vim/syntax/cabal.vim index 44941f01f2..6a6929abe4 100644 --- a/editors/vim/syntax/cabal.vim +++ b/editors/vim/syntax/cabal.vim @@ -38,6 +38,7 @@ syn keyword cabalCompType contained syn keyword cabalLanguage contained \ Haskell98 \ Haskell2010 + \ GHC2021 " To update this in Cabal, `cabal repl Cabal` and: " >>> :m *Distribution.PackageDescription.FieldGrammar @@ -180,6 +181,7 @@ syn keyword cabalExtension contained \ ExplicitNamespaces \ ExtendedDefaultRules \ ExtensibleRecords + \ FieldSelectors \ FlexibleContexts \ FlexibleInstances \ ForeignFunctionInterface @@ -225,6 +227,7 @@ syn keyword cabalExtension contained \ OverlappingInstances \ OverloadedLabels \ OverloadedLists + \ OverloadedRecordDot \ OverloadedStrings \ PackageImports \ ParallelArrays @@ -273,6 +276,7 @@ syn keyword cabalExtension contained \ UndecidableInstances \ UndecidableSuperClasses \ UnicodeSyntax + \ UnliftedDatatypes \ UnliftedFFITypes \ UnliftedNewtypes \ ViewPatterns @@ -313,6 +317,7 @@ syn keyword cabalExtension contained \ NoExplicitNamespaces \ NoExtendedDefaultRules \ NoExtensibleRecords + \ NoFieldSelectors \ NoFlexibleContexts \ NoFlexibleInstances \ NoForeignFunctionInterface @@ -358,6 +363,7 @@ syn keyword cabalExtension contained \ NoOverlappingInstances \ NoOverloadedLabels \ NoOverloadedLists + \ NoOverloadedRecordDot \ NoOverloadedStrings \ NoPackageImports \ NoParallelArrays @@ -406,6 +412,7 @@ syn keyword cabalExtension contained \ NoUndecidableInstances \ NoUndecidableSuperClasses \ NoUnicodeSyntax + \ NoUnliftedDatatypes \ NoUnliftedFFITypes \ NoUnliftedNewtypes \ NoViewPatterns -- GitLab