Skip to content

Commit

Permalink
Merge branch 'master' into strip-dogfooding-framework
Browse files Browse the repository at this point in the history
  • Loading branch information
emilypi committed Apr 23, 2021
2 parents 116f613 + 5771a24 commit 825fa86
Show file tree
Hide file tree
Showing 9 changed files with 81 additions and 25 deletions.
22 changes: 16 additions & 6 deletions Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
34 changes: 17 additions & 17 deletions Cabal/src/Distribution/Simple/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -551,13 +551,13 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
createDirectoryIfMissingVerbose verbosity True libTargetDir
-- TODO: do we need to put hs-boot files into place for mutually recursive
-- modules?
let cLikeFiles = fromNubListR $ mconcat
let cLikeSources = fromNubListR $ mconcat
[ toNubListR (cSources libBi)
, toNubListR (cxxSources libBi)
, toNubListR (cmmSources libBi)
, toNubListR (asmSources libBi)
]
cObjs = map (`replaceExtension` objExtension) cLikeFiles
cLikeObjs = map (`replaceExtension` objExtension) cLikeSources
baseOpts = componentGhcOptions verbosity lbi libBi clbi libTargetDir
vanillaOpts = baseOpts `mappend` mempty {
ghcOptMode = toFlag GhcModeMake,
Expand Down Expand Up @@ -598,7 +598,7 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
ghcOptLinkFrameworkDirs = toNubListR $
PD.extraFrameworkDirs libBi,
ghcOptInputFiles = toNubListR
[libTargetDir </> x | x <- cObjs]
[libTargetDir </> x | x <- cLikeObjs]
}
replOpts = vanillaOpts {
ghcOptExtra = Internal.filterGhciFlags
Expand Down Expand Up @@ -779,10 +779,10 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
-- link:
when has_code . unless forRepl $ do
info verbosity "Linking..."
let cProfObjs = map (`replaceExtension` ("p_" ++ objExtension))
cLikeFiles
cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension))
cLikeFiles
let cLikeProfObjs = map (`replaceExtension` ("p_" ++ objExtension))
cLikeSources
cLikeSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension))
cLikeSources
compiler_id = compilerId (compiler lbi)
vanillaLibFilePath = libTargetDir </> mkLibName uid
profileLibFilePath = libTargetDir </> mkProfLibName uid
Expand Down Expand Up @@ -827,20 +827,20 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
libTargetDir ("dyn_" ++ objExtension) False
else return []

unless (null hObjs && null cObjs && null stubObjs) $ do
unless (null hObjs && null cLikeObjs && null stubObjs) $ do
rpaths <- getRPaths lbi clbi

let staticObjectFiles =
hObjs
++ map (libTargetDir </>) cObjs
++ map (libTargetDir </>) cLikeObjs
++ stubObjs
profObjectFiles =
hProfObjs
++ map (libTargetDir </>) cProfObjs
++ map (libTargetDir </>) cLikeProfObjs
++ stubProfObjs
dynamicObjectFiles =
hSharedObjs
++ map (libTargetDir </>) cSharedObjs
++ map (libTargetDir </>) cLikeSharedObjs
++ stubSharedObjs
-- After the relocation lib is created we invoke ghc -shared
-- with the dependencies spelled out as -package arguments
Expand Down Expand Up @@ -1307,7 +1307,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
inputModules = inputSourceModules buildSources
isGhcDynamic = isDynamic comp
dynamicTooSupported = supportsDynamicToo comp
cObjs = map (`replaceExtension` objExtension) cSrcs
cLikeObjs = map (`replaceExtension` objExtension) cSrcs
cxxObjs = map (`replaceExtension` objExtension) cxxSrcs
needDynamic = gbuildNeedDynamic lbi bm
needProfiling = withProfExe lbi
Expand Down Expand Up @@ -1362,12 +1362,12 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
ghcOptLinkFrameworkDirs = toNubListR $
PD.extraFrameworkDirs bnfo,
ghcOptInputFiles = toNubListR
[tmpDir </> x | x <- cObjs ++ cxxObjs]
[tmpDir </> x | x <- cLikeObjs ++ cxxObjs]
}
dynLinkerOpts = mempty {
ghcOptRPaths = rpaths,
ghcOptInputFiles = toNubListR
[tmpDir </> x | x <- cObjs ++ cxxObjs]
[tmpDir </> x | x <- cLikeObjs ++ cxxObjs]
}
replOpts = baseOpts {
ghcOptExtra = Internal.filterGhciFlags
Expand Down
3 changes: 3 additions & 0 deletions Cabal/src/Distribution/Simple/GHC/ImplInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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]
Expand All @@ -79,6 +81,7 @@ ghcjsVersionImplInfo :: Version -- ^ The GHCJS version
-> GhcImplInfo
ghcjsVersionImplInfo _ghcjsver ghcver = GhcImplInfo
{ supportsHaskell2010 = True
, supportsGHC2021 = True
, reportsNoExt = True
, alwaysNondecIndent = False
, flagGhciScript = True
Expand Down
5 changes: 5 additions & 0 deletions Cabal/src/Distribution/Simple/GHC/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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, "")]
Expand Down
16 changes: 15 additions & 1 deletion Cabal/src/Language/Haskell/Extension.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
Expand Down Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion bootstrap/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,9 @@ then the `linux-ghcvec.json` file is available in `bootstrap/` folder:

On a (linux) system you are boostrapping, run

bootstrap.py -d linux-ghcver.json -w /path/to-ghc
./bootstrap/bootstrap.py -d ./bootstrap/linux-ghcver.json -w /path/to-ghc

From the top directory of the source checkout.

To generate the `platform-ghcver` files for other platforms, do:

Expand Down
11 changes: 11 additions & 0 deletions changelog.d/pr-7252
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
synopsis: Include cmm-sources when linking shared objects
packages: Cabal
prs: #7252
issues: #7182

description: {

- Previously `cmm-sources` were not included in the final link when building a library as a shared object. Fix this.

}

4 changes: 4 additions & 0 deletions changelog.d/pr-7349
Original file line number Diff line number Diff line change
@@ -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 }
7 changes: 7 additions & 0 deletions editors/vim/syntax/cabal.vim
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -180,6 +181,7 @@ syn keyword cabalExtension contained
\ ExplicitNamespaces
\ ExtendedDefaultRules
\ ExtensibleRecords
\ FieldSelectors
\ FlexibleContexts
\ FlexibleInstances
\ ForeignFunctionInterface
Expand Down Expand Up @@ -225,6 +227,7 @@ syn keyword cabalExtension contained
\ OverlappingInstances
\ OverloadedLabels
\ OverloadedLists
\ OverloadedRecordDot
\ OverloadedStrings
\ PackageImports
\ ParallelArrays
Expand Down Expand Up @@ -273,6 +276,7 @@ syn keyword cabalExtension contained
\ UndecidableInstances
\ UndecidableSuperClasses
\ UnicodeSyntax
\ UnliftedDatatypes
\ UnliftedFFITypes
\ UnliftedNewtypes
\ ViewPatterns
Expand Down Expand Up @@ -313,6 +317,7 @@ syn keyword cabalExtension contained
\ NoExplicitNamespaces
\ NoExtendedDefaultRules
\ NoExtensibleRecords
\ NoFieldSelectors
\ NoFlexibleContexts
\ NoFlexibleInstances
\ NoForeignFunctionInterface
Expand Down Expand Up @@ -358,6 +363,7 @@ syn keyword cabalExtension contained
\ NoOverlappingInstances
\ NoOverloadedLabels
\ NoOverloadedLists
\ NoOverloadedRecordDot
\ NoOverloadedStrings
\ NoPackageImports
\ NoParallelArrays
Expand Down Expand Up @@ -406,6 +412,7 @@ syn keyword cabalExtension contained
\ NoUndecidableInstances
\ NoUndecidableSuperClasses
\ NoUnicodeSyntax
\ NoUnliftedDatatypes
\ NoUnliftedFFITypes
\ NoUnliftedNewtypes
\ NoViewPatterns
Expand Down

0 comments on commit 825fa86

Please sign in to comment.