diff --git a/.github/mergify.yml b/.github/mergify.yml index e8f8e0d43282befe147ef3113e7e926f317843f1..7969fe95c25c68ade0d1dbdd3fc2aafa0426cf5d 100644 --- a/.github/mergify.yml +++ b/.github/mergify.yml @@ -9,7 +9,9 @@ pull_request_rules: name: Wait for 2 days before validating merge conditions: - updated-at<2 days ago - - label=merge me + - or: + - label=merge me + - label=squash+merge me - '#approved-reviews-by>=2' # rebase+merge strategy @@ -57,6 +59,15 @@ pull_request_rules: - body~=backport - '#approved-reviews-by>=1' + # backports should be labeled as such + - actions: + label: + add: + - backport + name: Label backports as such + conditions: + - body~=automatic backport + queue_rules: - name: default conditions: [] diff --git a/.github/workflows/changelogs.yml b/.github/workflows/changelogs.yml index 5d3053c0b75cf9c8278bbd5476b8a7210d1ed6d8..daf2c5c01525b41fb62a4080e85ddb33a0e85a60 100644 --- a/.github/workflows/changelogs.yml +++ b/.github/workflows/changelogs.yml @@ -1,4 +1,4 @@ -name: Changelogs +name: Assorted on: push: @@ -21,6 +21,7 @@ defaults: jobs: build: + name: Changelogs runs-on: ubuntu-latest steps: @@ -35,8 +36,9 @@ jobs: - name: ghcup run: | ghcup config set cache true - ghcup install ghc recommended - ghcup set ghc recommended + ghcup install ghc 8.10.7 + ghcup set ghc 8.10.7 + # GHC 8.10.7 needed due to https://github.com/phadej/changelog-d/pull/2 - name: Update Hackage index run: cabal v2-update # Cannot install it from tarball due to diff --git a/.github/workflows/users-guide.yml b/.github/workflows/users-guide.yml index 29483a564ed921dd3369fdbe205c041052be185c..2d16715b7d75f309cd7ca37635482235cb6ceadd 100644 --- a/.github/workflows/users-guide.yml +++ b/.github/workflows/users-guide.yml @@ -1,6 +1,6 @@ # Adapted from agda/agda/.github/workflows/user-manual.yml by Andreas, 2021-09-11 -name: Users guide +name: Assorted # See: https://docs.github.com/en/actions/reference/workflow-syntax-for-github-actions#concurrency. concurrency: @@ -42,6 +42,7 @@ defaults: jobs: build: + name: Users guide runs-on: ubuntu-latest strategy: matrix: diff --git a/.github/workflows/validate.yml b/.github/workflows/validate.yml index 2a79790a7b6c6e1d39ec034564b034c736987bf9..65a676c528beaa19be11d37d606eb8926274fa12 100644 --- a/.github/workflows/validate.yml +++ b/.github/workflows/validate.yml @@ -74,6 +74,10 @@ jobs: key: ${{ runner.os }}-${{ matrix.ghc }}-20220419-${{ github.sha }} restore-keys: ${{ runner.os }}-${{ matrix.ghc }}-20220419- + - name: Work around git problem https://bugs.launchpad.net/ubuntu/+source/git/+bug/1993586 (cabal PR #8546) + run: | + git config --global protocol.file.allow always + # The '+exe' constraint below is important, otherwise cabal-install # might decide to build the library but not the executable which is # what we need. diff --git a/.github/workflows/whitespace.yml b/.github/workflows/whitespace.yml index 1617d02d18b940e52874781b53d9090b23f6aadb..1c6d884e253d42bafae760f76f3ef30f4768786d 100644 --- a/.github/workflows/whitespace.yml +++ b/.github/workflows/whitespace.yml @@ -1,4 +1,4 @@ -name: Whitespace +name: Assorted on: push: @@ -10,6 +10,7 @@ on: - created jobs: check: + name: Whitespace runs-on: ubuntu-latest env: diff --git a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs index 47eba1ebbe522415d928c194179119cb878caeed..471cf489791613f581bef883d1f960897f8dcd04 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs @@ -6,6 +6,8 @@ module Distribution.PackageDescription.FieldGrammar ( -- * Package description packageDescriptionFieldGrammar, + CompatFilePath(..), + CompatLicenseFile(..), -- * Library libraryFieldGrammar, -- * Foreign library diff --git a/Cabal-syntax/src/Language/Haskell/Extension.hs b/Cabal-syntax/src/Language/Haskell/Extension.hs index 0559e8479dbf622845aed92a7ec3986aa8f4194b..1365398cd1f508043c34c325031c726f8cf2beee 100644 --- a/Cabal-syntax/src/Language/Haskell/Extension.hs +++ b/Cabal-syntax/src/Language/Haskell/Extension.hs @@ -77,7 +77,7 @@ instance Pretty Language where pretty other = Disp.text (show other) instance Parsec Language where - parsec = classifyLanguage <$> P.some P.anyChar + parsec = classifyLanguage <$> P.munch1 isAlphaNum classifyLanguage :: String -> Language classifyLanguage = \str -> case lookup str langTable of @@ -165,6 +165,11 @@ data KnownExtension = -- | Enable the dreaded monomorphism restriction. | MonomorphismRestriction + -- | Enable deep subsumption, relaxing the simple subsumption rules, + -- implicitly inserting eta-expansions when matching up function types + -- with different quantification structures. + | DeepSubsumption + -- | Allow a specification attached to a multi-parameter type class -- which indicates that some parameters are entirely determined by -- others. The implementation will check that this property holds @@ -499,6 +504,9 @@ data KnownExtension = -- | Enable datatype promotion. | DataKinds + -- | Enable @type data@ declarations, defining constructors at the type level. + | TypeData + -- | Enable parallel arrays syntax (@[:@, @:]@) for /Data Parallel Haskell/. | ParallelArrays @@ -655,6 +663,9 @@ data KnownExtension = -- | Enable linear types. | LinearTypes + -- | Allow the use of visible forall in types of terms. + | RequiredTypeArguments + -- | Enable the generation of selector functions corresponding to record fields. | FieldSelectors diff --git a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs index bbf5481da557bb50abd53ab35e32c6cf4f9edc88..2491b1b93c96c301354ff175eb0cd517123068e5 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs @@ -27,9 +27,9 @@ tests = testGroup "Distribution.Utils.Structured" -- The difference is in encoding of newtypes #if MIN_VERSION_base(4,7,0) , testCase "GenericPackageDescription" $ - md5Check (Proxy :: Proxy GenericPackageDescription) 0xaf3d4c667a8f019c98a45451419ad71c + md5Check (Proxy :: Proxy GenericPackageDescription) 0xa3e9433662ecf0c7a3c26f6d75a53ba1 , testCase "LocalBuildInfo" $ - md5Check (Proxy :: Proxy LocalBuildInfo) 0x8ef5a39cb640e4340cf5c43a8300ff94 + md5Check (Proxy :: Proxy LocalBuildInfo) 0x05ef40b1f97c55be526f63ea4cdacae1 #endif ] diff --git a/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs b/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs index 6488ea06101023dd9ca13b0ccdb8a939b0ff171a..9100dc629ec0c9ea62db546bd6805c12f911ff2e 100644 --- a/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs +++ b/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs @@ -41,6 +41,14 @@ render z_root = execWriter $ do return () else do return () + if (zSupportsCpp z_root) + then do + tell "#if __GLASGOW_HASKELL__ >= 810\n" + tell "{-# OPTIONS_GHC -Wno-prepositive-qualified-module #-}\n" + tell "#endif\n" + return () + else do + return () tell "{-# OPTIONS_GHC -fno-warn-missing-import-lists #-}\n" tell "{-# OPTIONS_GHC -w #-}\n" tell "module Paths_" diff --git a/cabal-install/src/Distribution/Client/CmdBuild.hs b/cabal-install/src/Distribution/Client/CmdBuild.hs index 3f2c7589c9a12c60de18e857973c1189d2095d2e..9c8943d939e0cf7fd83556f240486f58c4203a2c 100644 --- a/cabal-install/src/Distribution/Client/CmdBuild.hs +++ b/cabal-install/src/Distribution/Client/CmdBuild.hs @@ -101,7 +101,7 @@ defaultBuildFlags = BuildFlags -- buildAction :: NixStyleFlags BuildFlags -> [String] -> GlobalFlags -> IO () buildAction flags@NixStyleFlags { extraFlags = buildFlags, ..} targetStrings globalFlags - = withContextAndSelectors RejectNoTargets Nothing flags targetStrings globalFlags $ \targetCtx ctx targetSelectors -> do + = withContextAndSelectors RejectNoTargets Nothing flags targetStrings globalFlags BuildCommand $ \targetCtx ctx targetSelectors -> do -- TODO: This flags defaults business is ugly let onlyConfigure = fromFlag (buildOnlyConfigure defaultBuildFlags <> buildOnlyConfigure buildFlags) diff --git a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs index b4cd4fa272c437b02acb29666aee432c995d3407..c9e160ca52eaf9a91402bf28aa14cb4fb2361ff7 100644 --- a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs +++ b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs @@ -19,6 +19,7 @@ import qualified Distribution.Client.NixStyleOptions as NixStyleOptions import Distribution.Client.ProjectOrchestration (AvailableTarget(..) ,AvailableTargetStatus(..) + ,CurrentCommand(..) ,ProjectBaseContext(..) ,ProjectBuildContext(..) ,TargetSelector(..) @@ -141,7 +142,7 @@ haddockProjectAction flags _extraArgs globalFlags = do -- we need. -- - withContextAndSelectors RejectNoTargets Nothing nixFlags ["all"] globalFlags $ \targetCtx ctx targetSelectors -> do + withContextAndSelectors RejectNoTargets Nothing nixFlags ["all"] globalFlags HaddockCommand $ \targetCtx ctx targetSelectors -> do baseCtx <- case targetCtx of ProjectContext -> return ctx GlobalContext -> return ctx diff --git a/cabal-install/src/Distribution/Client/CmdListBin.hs b/cabal-install/src/Distribution/Client/CmdListBin.hs index accf241700aa6d8ee725f6a87ae638d21b1d716d..cde9c8605159a16324b5821cb36f597fcd8d06db 100644 --- a/cabal-install/src/Distribution/Client/CmdListBin.hs +++ b/cabal-install/src/Distribution/Client/CmdListBin.hs @@ -78,7 +78,7 @@ listbinAction flags@NixStyleFlags{..} args globalFlags = do _ -> die' verbosity "One target is required, given multiple" -- configure and elaborate target selectors - withContextAndSelectors RejectNoTargets (Just ExeKind) flags [target] globalFlags $ \targetCtx ctx targetSelectors -> do + withContextAndSelectors RejectNoTargets (Just ExeKind) flags [target] globalFlags OtherCommand $ \targetCtx ctx targetSelectors -> do baseCtx <- case targetCtx of ProjectContext -> return ctx GlobalContext -> return ctx diff --git a/cabal-install/src/Distribution/Client/CmdRepl.hs b/cabal-install/src/Distribution/Client/CmdRepl.hs index bf89e7b10ddadc6a5b7a329763f7abfb36d822fa..be129b042f423e990b39403c66b01cb107750d1c 100644 --- a/cabal-install/src/Distribution/Client/CmdRepl.hs +++ b/cabal-install/src/Distribution/Client/CmdRepl.hs @@ -187,7 +187,7 @@ replCommand = Client.installCommand { -- replAction :: NixStyleFlags (ReplOptions, EnvFlags) -> [String] -> GlobalFlags -> IO () replAction flags@NixStyleFlags { extraFlags = (replOpts, envFlags), ..} targetStrings globalFlags - = withContextAndSelectors AcceptNoTargets (Just LibKind) flags targetStrings globalFlags $ \targetCtx ctx targetSelectors -> do + = withContextAndSelectors AcceptNoTargets (Just LibKind) flags targetStrings globalFlags ReplCommand $ \targetCtx ctx targetSelectors -> do when (buildSettingOnlyDeps (buildSettings ctx)) $ die' verbosity $ "The repl command does not support '--only-dependencies'. " ++ "You may wish to use 'build --only-dependencies' and then " diff --git a/cabal-install/src/Distribution/Client/CmdRun.hs b/cabal-install/src/Distribution/Client/CmdRun.hs index 9bb34b2bfd25511af9e4fa4d94d3269ca8722cd2..64241fd8bbc82a30478dba974382e7a7aff507d4 100644 --- a/cabal-install/src/Distribution/Client/CmdRun.hs +++ b/cabal-install/src/Distribution/Client/CmdRun.hs @@ -122,7 +122,7 @@ runCommand = CommandUI -- runAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () runAction flags@NixStyleFlags {..} targetAndArgs globalFlags - = withContextAndSelectors RejectNoTargets (Just ExeKind) flags targetStr globalFlags $ \targetCtx ctx targetSelectors -> do + = withContextAndSelectors RejectNoTargets (Just ExeKind) flags targetStr globalFlags OtherCommand $ \targetCtx ctx targetSelectors -> do (baseCtx, defaultVerbosity) <- case targetCtx of ProjectContext -> return (ctx, normal) GlobalContext -> return (ctx, normal) diff --git a/cabal-install/src/Distribution/Client/ProjectOrchestration.hs b/cabal-install/src/Distribution/Client/ProjectOrchestration.hs index ccbd84d43c31c71aecc1e5166606350d51d960e9..3d93b0db1153c7bd1eff5b3c1f9a9b655dbc9ab0 100644 --- a/cabal-install/src/Distribution/Client/ProjectOrchestration.hs +++ b/cabal-install/src/Distribution/Client/ProjectOrchestration.hs @@ -186,7 +186,7 @@ import System.Posix.Signals (sigKILL, sigSEGV) -- | Tracks what command is being executed, because we need to hide this somewhere -- for cases that need special handling (usually for error reporting). -data CurrentCommand = InstallCommand | HaddockCommand | OtherCommand +data CurrentCommand = InstallCommand | HaddockCommand | BuildCommand | ReplCommand | OtherCommand deriving (Show, Eq) -- | This holds the context of a project prior to solving: the content of the @@ -859,8 +859,10 @@ printPlan verbosity ProjectBaseContext { buildSettings = BuildTimeSettings{buildSettingDryRun}, projectConfig = ProjectConfig { + projectConfigAllPackages = + PackageConfig {packageConfigOptimization = globalOptimization}, projectConfigLocalPackages = - PackageConfig {packageConfigOptimization} + PackageConfig {packageConfigOptimization = localOptimization} } } ProjectBuildContext { @@ -994,7 +996,7 @@ printPlan verbosity showBuildProfile :: String showBuildProfile = "Build profile: " ++ unwords [ "-w " ++ (showCompilerId . pkgConfigCompiler) elaboratedShared, - "-O" ++ (case packageConfigOptimization of + "-O" ++ (case globalOptimization <> localOptimization of -- if local is not set, read global Setup.Flag NoOptimisation -> "0" Setup.Flag NormalOptimisation -> "1" Setup.Flag MaximumOptimisation -> "2" @@ -1150,7 +1152,7 @@ dieOnBuildFailures verbosity currentCommand plan buildOutcomes , [pkg] <- rootpkgs , installedUnitId pkg == pkgid , isFailureSelfExplanatory (buildFailureReason failure) - , currentCommand /= InstallCommand + , currentCommand `notElem` [InstallCommand, BuildCommand, ReplCommand] = True | otherwise = False diff --git a/cabal-install/src/Distribution/Client/ScriptUtils.hs b/cabal-install/src/Distribution/Client/ScriptUtils.hs index c8372aed263f46e79ae8da7bb2f17f3ce301e5ac..db377c8f10a649d9e0e9fe2f1a7e5bb3516982fc 100644 --- a/cabal-install/src/Distribution/Client/ScriptUtils.hs +++ b/cabal-install/src/Distribution/Client/ScriptUtils.hs @@ -171,10 +171,11 @@ withContextAndSelectors -> NixStyleFlags a -- ^ Command line flags -> [String] -- ^ Target strings or a script and args. -> GlobalFlags -- ^ Global flags. + -> CurrentCommand -- ^ Current Command (usually for error reporting). -> (TargetContext -> ProjectBaseContext -> [TargetSelector] -> IO b) -- ^ The body of your command action. -> IO b -withContextAndSelectors noTargets kind flags@NixStyleFlags {..} targetStrings globalFlags act +withContextAndSelectors noTargets kind flags@NixStyleFlags {..} targetStrings globalFlags cmd act = withTemporaryTempDirectory $ \mkTmpDir -> do (tc, ctx) <- withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag with (without mkTmpDir) @@ -209,11 +210,11 @@ withContextAndSelectors noTargets kind flags@NixStyleFlags {..} targetStrings gl defaultTarget = [TargetPackage TargetExplicitNamed [fakePackageId] Nothing] with = do - ctx <- establishProjectBaseContext verbosity cliConfig OtherCommand + ctx <- establishProjectBaseContext verbosity cliConfig cmd return (ProjectContext, ctx) without mkDir globalConfig = do distDirLayout <- establishDummyDistDirLayout verbosity (globalConfig <> cliConfig) =<< mkDir - ctx <- establishDummyProjectBaseContext verbosity (globalConfig <> cliConfig) distDirLayout [] OtherCommand + ctx <- establishDummyProjectBaseContext verbosity (globalConfig <> cliConfig) distDirLayout [] cmd return (GlobalContext, ctx) scriptOrError script err = do exists <- doesFileExist script diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.out b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.out new file mode 100644 index 0000000000000000000000000000000000000000..bbedd1662c888792db25b4ba773566c0bb36e9e9 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.out @@ -0,0 +1,8 @@ +# cabal build +Resolving dependencies... +Build profile: -w ghc-<GHCVER> -O2 +In order, the following will be built: + - test-0.1.0.0 (lib) (first run) +Configuring library for test-0.1.0.0.. +Preprocessing library for test-0.1.0.0.. +Building library for test-0.1.0.0.. diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.project b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.project new file mode 100644 index 0000000000000000000000000000000000000000..e6fdbadb4398bc0e333947b5fb8021778310d943 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.project @@ -0,0 +1 @@ +packages: . diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.test.hs b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.test.hs new file mode 100644 index 0000000000000000000000000000000000000000..010c47ea4b4734b7c9d0e2632ec0261f9b78bec2 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/cabal.test.hs @@ -0,0 +1,7 @@ +-- 2022-09-20, issue #8487 +-- + +import Test.Cabal.Prelude + +main = cabalTest $ do + cabalG [ "--config-file", "config.file" ] "build" [ "test" ] diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/config.file b/cabal-testsuite/PackageTests/ConfigFile/T8487/config.file new file mode 100644 index 0000000000000000000000000000000000000000..9f3421cdcb2d94ad33db5d9222918f1faace3ee0 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/config.file @@ -0,0 +1 @@ +optimization: 2 diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/src/MyLib.hs b/cabal-testsuite/PackageTests/ConfigFile/T8487/src/MyLib.hs new file mode 100644 index 0000000000000000000000000000000000000000..e657c4403f66f966da13d2027bf595d9673387f6 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/src/MyLib.hs @@ -0,0 +1,4 @@ +module MyLib (someFunc) where + +someFunc :: IO () +someFunc = putStrLn "someFunc" diff --git a/cabal-testsuite/PackageTests/ConfigFile/T8487/test.cabal b/cabal-testsuite/PackageTests/ConfigFile/T8487/test.cabal new file mode 100644 index 0000000000000000000000000000000000000000..f48ee85d0084f95759d9742f3ff91622831ce968 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConfigFile/T8487/test.cabal @@ -0,0 +1,13 @@ +cabal-version: 3.0 +name: test +version: 0.1.0.0 +license: NONE +author: a.pelenitsyn@gmail.com +maintainer: Artem Pelenitsyn +build-type: Simple + +library + exposed-modules: MyLib + build-depends: base + hs-source-dirs: src + default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/CustomWithoutCabal/cabal.out b/cabal-testsuite/PackageTests/CustomWithoutCabal/cabal.out index 84f0d9bf31150852a813c08f7da71a4590a5de05..76b53a860518e0045a019d8ce33771cc9411d0ba 100644 --- a/cabal-testsuite/PackageTests/CustomWithoutCabal/cabal.out +++ b/cabal-testsuite/PackageTests/CustomWithoutCabal/cabal.out @@ -3,3 +3,4 @@ Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: - custom-setup-without-cabal-1.0 (lib:custom-setup-without-cabal) (first run) +Error: cabal: Failed to build custom-setup-without-cabal-1.0-inplace. The failure occurred during the configure step. diff --git a/cabal-testsuite/PackageTests/CustomWithoutCabalDefaultMain/cabal.out b/cabal-testsuite/PackageTests/CustomWithoutCabalDefaultMain/cabal.out index da780d20081348adbd3cda5cff9e2491964eabac..047919ab3c0f3145142da356ac9dfe2bb397bf40 100644 --- a/cabal-testsuite/PackageTests/CustomWithoutCabalDefaultMain/cabal.out +++ b/cabal-testsuite/PackageTests/CustomWithoutCabalDefaultMain/cabal.out @@ -3,3 +3,4 @@ Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: - custom-setup-without-cabal-defaultMain-1.0 (lib:custom-setup-without-cabal-defaultMain) (first run) +Error: cabal: Failed to build custom-setup-without-cabal-defaultMain-1.0-inplace. The failure occurred during the configure step. diff --git a/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.out b/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.out index 8822537f7929b53ba97389e49bf8c16cd2acac24..9ca34b2924c730caa9b1e9e01622727e6653ec75 100644 --- a/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.out +++ b/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.out @@ -6,6 +6,7 @@ In order, the following will be built: Configuring executable 'q' for q-0.1.0.0.. Preprocessing executable 'q' for q-0.1.0.0.. Building executable 'q' for q-0.1.0.0.. +Error: cabal: Failed to build q-0.1.0.0-inplace-q. # cabal v2-build Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 diff --git a/cabal-testsuite/PackageTests/NewHaddock/Fails/cabal.out b/cabal-testsuite/PackageTests/NewHaddock/Fails/cabal.out index 306afff155be08f0876a0476af34a606b35a5a73..e02fc11e31642437a04c01c5f681ed898ba470f4 100644 --- a/cabal-testsuite/PackageTests/NewHaddock/Fails/cabal.out +++ b/cabal-testsuite/PackageTests/NewHaddock/Fails/cabal.out @@ -6,6 +6,7 @@ In order, the following will be built: Configuring library for example-1.0.. Preprocessing library for example-1.0.. Building library for example-1.0.. +Error: cabal: Failed to build example-1.0-inplace. # cabal v2-haddock Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: diff --git a/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/Main.hs b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/Main.hs new file mode 100644 index 0000000000000000000000000000000000000000..d82a4bd93b7e75a6ff9845150450ae0709b93086 --- /dev/null +++ b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/Main.hs @@ -0,0 +1,4 @@ +module Main where + +main :: IO () +main = return () diff --git a/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/my.cabal b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/my.cabal new file mode 100644 index 0000000000000000000000000000000000000000..8ad771ececd78b10ff4819ac1b9f9772b18f4607 --- /dev/null +++ b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/my.cabal @@ -0,0 +1,17 @@ +name: PathsModule +version: 0.1 +license: BSD3 +author: Martijn Bastiaan +category: PackageTests +build-type: Simple +Cabal-version: >= 1.2 + +description: + Check that the generated paths module compiles. + +Executable TestPathsModule + main-is: Main.hs + if impl(ghc >= 8.10.0) + ghc-options: -Werror -fwarn-prepositive-qualified-module + other-modules: Paths_PathsModule + build-depends: base diff --git a/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.cabal.out b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.cabal.out new file mode 100644 index 0000000000000000000000000000000000000000..bead24d62fd344f6bd773e048d3aa2f7334755f2 --- /dev/null +++ b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.cabal.out @@ -0,0 +1,5 @@ +# Setup configure +Configuring PathsModule-0.1... +# Setup build +Preprocessing executable 'TestPathsModule' for PathsModule-0.1.. +Building executable 'TestPathsModule' for PathsModule-0.1.. diff --git a/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.out b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.out new file mode 100644 index 0000000000000000000000000000000000000000..bead24d62fd344f6bd773e048d3aa2f7334755f2 --- /dev/null +++ b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.out @@ -0,0 +1,5 @@ +# Setup configure +Configuring PathsModule-0.1... +# Setup build +Preprocessing executable 'TestPathsModule' for PathsModule-0.1.. +Building executable 'TestPathsModule' for PathsModule-0.1.. diff --git a/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.test.hs b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.test.hs new file mode 100644 index 0000000000000000000000000000000000000000..ac477fa75675666b1cfe51c46c4fde7659fc5bef --- /dev/null +++ b/cabal-testsuite/PackageTests/PathsModule/ImportQualifiedPost/setup.test.hs @@ -0,0 +1,4 @@ +import Test.Cabal.Prelude +-- Test that Paths module is generated and available for executables. +main = setupAndCabalTest $ setup_build [] + diff --git a/cabal-testsuite/PackageTests/Regression/T8507/Foo.hs b/cabal-testsuite/PackageTests/Regression/T8507/Foo.hs new file mode 100644 index 0000000000000000000000000000000000000000..614d2790c839bf2e048440d634069791ebcb123c --- /dev/null +++ b/cabal-testsuite/PackageTests/Regression/T8507/Foo.hs @@ -0,0 +1,4 @@ +module Foo where + +foo :: a +foo = undefined diff --git a/cabal-testsuite/PackageTests/Regression/T8507/cabal.out b/cabal-testsuite/PackageTests/Regression/T8507/cabal.out new file mode 100644 index 0000000000000000000000000000000000000000..0c53c8b3d30b8188da375d2b6ee5f0bde0d1f510 --- /dev/null +++ b/cabal-testsuite/PackageTests/Regression/T8507/cabal.out @@ -0,0 +1,8 @@ +# cabal v2-build +Resolving dependencies... +Build profile: -w ghc-<GHCVER> -O1 +In order, the following will be built: + - pkg-0 (lib) (first run) +Configuring library for pkg-0.. +Preprocessing library for pkg-0.. +Building library for pkg-0.. diff --git a/cabal-testsuite/PackageTests/Regression/T8507/cabal.project b/cabal-testsuite/PackageTests/Regression/T8507/cabal.project new file mode 100644 index 0000000000000000000000000000000000000000..8834d04402a2a77a2fa0c4f718102dc0b450cbce --- /dev/null +++ b/cabal-testsuite/PackageTests/Regression/T8507/cabal.project @@ -0,0 +1,2 @@ +packages: + ./ diff --git a/cabal-testsuite/PackageTests/Regression/T8507/cabal.test.hs b/cabal-testsuite/PackageTests/Regression/T8507/cabal.test.hs new file mode 100644 index 0000000000000000000000000000000000000000..58266256b471e7e002bdec13430571828cadf2cd --- /dev/null +++ b/cabal-testsuite/PackageTests/Regression/T8507/cabal.test.hs @@ -0,0 +1,6 @@ +import Test.Cabal.Prelude + +-- Issue #8507: trailing space in `default-language` should not make +-- `cabal build` complain. +main = cabalTest $ cabal "v2-build" ["all"] + diff --git a/cabal-testsuite/PackageTests/Regression/T8507/pkg.cabal b/cabal-testsuite/PackageTests/Regression/T8507/pkg.cabal new file mode 100644 index 0000000000000000000000000000000000000000..80fb8e284aee035fffe207e6cb6ac69a3b7f6628 --- /dev/null +++ b/cabal-testsuite/PackageTests/Regression/T8507/pkg.cabal @@ -0,0 +1,14 @@ +cabal-version: 3.0 +name: pkg +synopsis: synopsis +description: description +version: 0 +category: example +maintainer: none@example.com +license: GPL-3.0-or-later + +library + exposed-modules: Foo, + build-depends: base == 4.* + default-language: Haskell2010 + -- Note whitespace after “Haskell 2010â€. diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/CompileFail/compile-fail.out b/cabal-testsuite/PackageTests/ShowBuildInfo/CompileFail/compile-fail.out index 444a64e19568cd3d01d1ad3380b845b25c4b146e..4c07cde5ed0fce6f6d86cd37aebc3924021831f8 100644 --- a/cabal-testsuite/PackageTests/ShowBuildInfo/CompileFail/compile-fail.out +++ b/cabal-testsuite/PackageTests/ShowBuildInfo/CompileFail/compile-fail.out @@ -10,6 +10,7 @@ Building library for CompileFail-0.1.0.0.. Configuring test suite 'CompileFail-test' for CompileFail-0.1.0.0.. Preprocessing test suite 'CompileFail-test' for CompileFail-0.1.0.0.. Building test suite 'CompileFail-test' for CompileFail-0.1.0.0.. +Error: cabal: Failed to build CompileFail-0.1.0.0-inplace-CompileFail-test. # cabal build Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: diff --git a/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.negative.project b/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.negative.project index 0100cb0075b08027fbb8fa00a9885e8263af1b56..dfdcf6d3c5b00785f52a38276f324a1649fa094d 100644 --- a/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.negative.project +++ b/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.negative.project @@ -3,6 +3,7 @@ packages: . source-repository-package type: git -- A Sample repo to test post-checkout-command - location: https://github.com/haskell/bytestring + location: https://github.com/haskell/bytestring post-checkout-command: false + tag: 0.10.9.0 -- https://en.wikipedia.org/wiki/True_and_false_(commands) diff --git a/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.positive.project b/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.positive.project index a4f1e08217fd6bd0aab3c0888ad9a871c902e622..3ed5801628cdc78831963e5875eca1845a851df0 100644 --- a/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.positive.project +++ b/cabal-testsuite/PackageTests/postCheckoutCommand/cabal.positive.project @@ -5,4 +5,5 @@ source-repository-package -- A Sample repo to test post-checkout-command location: https://github.com/haskell/bytestring post-checkout-command: true + tag: 0.10.9.0 -- https://en.wikipedia.org/wiki/True_and_false_(commands) diff --git a/cabal.project b/cabal.project index aea54a32efea73d76f5840259114c47b9ae35d65..5f0af8dfa4cc69481f3f655eeab421cabc027d26 100644 --- a/cabal.project +++ b/cabal.project @@ -25,32 +25,5 @@ constraints: these -assoc constraints: text >= 2.0 constraints: time >= 1.12 --- So us hackers get all the assertion failures early: --- --- NOTE: currently commented out, see --- https://github.com/haskell/cabal/issues/3911 --- as a workaround we specify it for each package individually: --- --- program-options --- ghc-options: -fno-ignore-asserts --- -package Cabal - ghc-options: -fno-ignore-asserts - -package cabal-testsuite - ghc-options: -fno-ignore-asserts - -package Cabal-QuickCheck - ghc-options: -fno-ignore-asserts - -package Cabal-tree-diff - ghc-options: -fno-ignore-asserts - -package Cabal-described - ghc-options: -fno-ignore-asserts - -package cabal-install-solver - ghc-options: -fno-ignore-asserts - -package cabal-install +program-options ghc-options: -fno-ignore-asserts diff --git a/cabal.project.coverage b/cabal.project.coverage index 7c39810b88f8a6c178bbe0b319ccbfb8d7df3115..2afe3d10df7eafd8c5aefe5724992e8ad5590033 100644 --- a/cabal.project.coverage +++ b/cabal.project.coverage @@ -28,6 +28,9 @@ allow-newer: windns-0.1.0.1:base constraints: rere -rere-cfg constraints: these +program-options + ghc-options: -fno-ignore-asserts + -- NOTE: for library coverage in multi-project builds, -- see: -- @@ -39,41 +42,33 @@ constraints: these -- the `cabal-install` library -- package Cabal-syntax - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package Cabal - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package cabal-testsuite - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package Cabal-QuickCheck - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package Cabal-tree-diff - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package Cabal-described - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package cabal-install-solver - ghc-options: -fno-ignore-asserts coverage: False library-coverage: False package cabal-install - ghc-options: -fno-ignore-asserts coverage: True library-coverage: True diff --git a/cabal.project.libonly b/cabal.project.libonly index e11d81f5d771411559cce345a35f4c7267f0d0fd..59873fd4ad1026b77e116f29d6a64d60c59f3255 100644 --- a/cabal.project.libonly +++ b/cabal.project.libonly @@ -11,17 +11,4 @@ tests: True --optional-packages: */ program-options - -- So us hackers get all the assertion failures early: - -- - -- NOTE: currently commented out, see - -- https://github.com/haskell/cabal/issues/3911 - -- - -- ghc-options: -fno-ignore-asserts - -- - -- as a workaround we specify it for each package individually: -package Cabal-syntax - ghc-options: -fno-ignore-asserts -package Cabal - ghc-options: -fno-ignore-asserts -package cabal-testsuite ghc-options: -fno-ignore-asserts diff --git a/cabal.project.validate b/cabal.project.validate index 6f9dc0b45d3cf5d7081711ea0e2ed17c049c29dc..66e823f62b172a6a88a8dc0aaba4b36834c2335b 100644 --- a/cabal.project.validate +++ b/cabal.project.validate @@ -19,11 +19,14 @@ constraints: these -assoc write-ghc-environment-files: never +program-options + ghc-options: -fno-ignore-asserts + package Cabal-syntax - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror package Cabal - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror package cabal-testsuite - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror package cabal-install - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror diff --git a/cabal.project.validate.libonly b/cabal.project.validate.libonly index 2566a5cc8d2589c275a6515548839448b24e67a0..3baafa1661aaa8372f44bf2465e5e2eb67531336 100644 --- a/cabal.project.validate.libonly +++ b/cabal.project.validate.libonly @@ -14,12 +14,15 @@ write-ghc-environment-files: never constraints: rere -rere-cfg constraints: these -assoc +program-options + ghc-options: -fno-ignore-asserts + package Cabal-syntax - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror package Cabal - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror package cabal-testsuite - ghc-options: -Werror -fno-ignore-asserts + ghc-options: -Werror -- https://github.com/haskell-hvr/cryptohash-sha256/issues/12 allow-newer: cryptohash-sha256:base diff --git a/changelog.d/issue-8487 b/changelog.d/issue-8487 new file mode 100644 index 0000000000000000000000000000000000000000..432c74d81d6df74b283fcf174cc9d9134f4c66a2 --- /dev/null +++ b/changelog.d/issue-8487 @@ -0,0 +1,12 @@ +synopsis: "Build profile" message now reflects optimization level set in global config +packages: cabal-install +prs: #8488 +issues: #8487 + +description: { + +Imagine you have `optimization: 2` in your `~/.cabal/config`, and you call `cabal build` +in a project that doesn't have optimization level explicitly set in its project file. +You will still see 'Build profile: -w ghc-<VER> -O1'. This is incorrect and was fixed +in this patch: now you'll see '-O2'. +} diff --git a/changelog.d/pr-8493 b/changelog.d/pr-8493 new file mode 100644 index 0000000000000000000000000000000000000000..27344116e271ba68b5de8119701d7fb462a1e678 --- /dev/null +++ b/changelog.d/pr-8493 @@ -0,0 +1,11 @@ +synopsis: Add language extensions DeepSubsumption and TypeData +packages: Cabal-syntax +prs: #8493 +significance: significant + +description: { + +- adds support for the DeepSubsumption language extension (GHC proposal #511) +- adds support for the TypeData language extension (GHC proposal #106) + +} diff --git a/doc/cabal-project.rst b/doc/cabal-project.rst index 4ba2c26f87f90487bd2618f3a9c7f4d95920689d..863ad1bf3cb926fdbd14b5cda53237d3e4b7202f 100644 --- a/doc/cabal-project.rst +++ b/doc/cabal-project.rst @@ -127,8 +127,10 @@ project are: .. cfg-field:: extra-packages: package list with version bounds (comma separated) :synopsis: Adds external packages as local - :strike:`Specifies a list of external packages from Hackage which - should be considered local packages.` (Not implemented) + Specifies a list of external packages from Hackage, which + should be considered local packages. The motivation for + :cfg-field:`extra-packages` is making libraries that are not + dependencies of any package in the project available for use in ghci. There is no command line variant of this field. diff --git a/doc/nix-local-build.rst b/doc/nix-local-build.rst index 19cca22c9f3cae3be9515517cfa91b06b8298e86..3186be8bbf2165b8fa406022ebb9b911c28d6a19 100644 --- a/doc/nix-local-build.rst +++ b/doc/nix-local-build.rst @@ -146,11 +146,10 @@ must be built per-project, versus external packages, which can be cached across projects. To be more precise: 1. A **local package** is one that is listed explicitly in the - ``packages``, ``optional-packages`` or ``extra-packages`` field of a - project. Usually, these refer to packages whose source code lives - directly in a folder in your project. But you can list an - arbitrary Hackage package in :cfg-field:`packages` - to force it to be treated as local. + ``packages``, ``optional-packages`` or ``extra-packages`` fields of a + project. Packages in the former two fields will usually have their + source code stored in a folder in your project, while ``extra-packages`` lists + packages residing on Hackage that are treated as being local anyway. Local packages, as well as the external packages (below) which depend on them, are built **inplace**, meaning that they are always built @@ -159,8 +158,8 @@ packages are not cached and not given unique hashes, which makes them suitable for packages which you want to edit and recompile. 2. An **external package** is any package which is not listed in the - ``packages`` field. The source code for external packages is usually - retrieved from Hackage. + ``packages``, ``optional-packages`` and ``extra-packages`` fields. + The source code for external packages is usually retrieved from Hackage. When an external package does not depend on an inplace package, it can be built and installed to a **global** store, which can be shared across diff --git a/editors/vim/syntax/cabal.vim b/editors/vim/syntax/cabal.vim index 6a6929abe46ecba11533de949589e3ae53c16234..1fc84f4d8af285d21c8e1ae16a9ae19b5c04860e 100644 --- a/editors/vim/syntax/cabal.vim +++ b/editors/vim/syntax/cabal.vim @@ -160,6 +160,7 @@ syn keyword cabalExtension contained \ DataKinds \ DatatypeContexts \ DefaultSignatures + \ DeepSubsumption \ DeriveAnyClass \ DeriveDataTypeable \ DeriveFoldable @@ -207,6 +208,7 @@ syn keyword cabalExtension contained \ LexicalNegation \ LiberalTypeSynonyms \ LinearTypes + \ RequiredTypeArguments \ MagicHash \ MonadComprehensions \ MonadFailDesugaring @@ -266,6 +268,7 @@ syn keyword cabalExtension contained \ TransformListComp \ TupleSections \ TypeApplications + \ TypeData \ TypeFamilies \ TypeFamilyDependencies \ TypeInType @@ -343,6 +346,7 @@ syn keyword cabalExtension contained \ NoLexicalNegation \ NoLiberalTypeSynonyms \ NoLinearTypes + \ NoRequiredTypeArguments \ NoMagicHash \ NoMonadComprehensions \ NoMonadFailDesugaring diff --git a/fix-whitespace.yaml b/fix-whitespace.yaml index bbec61f156f21812ed0c1d292c2b9d1e72350b82..d96e84188b16535ada900573e6602f638daecec4 100644 --- a/fix-whitespace.yaml +++ b/fix-whitespace.yaml @@ -92,6 +92,7 @@ excluded-files: - Cabal-syntax/src/Distribution/Fields/Lexer.hs - Cabal-tests/tests/ParserTests/warnings/tab.cabal - Cabal-tests/tests/ParserTests/warnings/utf8.cabal + - cabal-testsuite/PackageTests/Regression/T8507/pkg.cabal # These also contain tabs that affect the golden value: # Could be removed from exceptions, but then the tab warning diff --git a/templates/Paths_pkg.template.hs b/templates/Paths_pkg.template.hs index 6bc6b7875e6d37ad464cc53a2e6021c2d69084bb..8e1e03d27e425cb0a0114ad6186162dc3da7d69a 100644 --- a/templates/Paths_pkg.template.hs +++ b/templates/Paths_pkg.template.hs @@ -7,6 +7,11 @@ {% if not absolute %} {-# LANGUAGE ForeignFunctionInterface #-} {% endif %} +{% if supportsCpp %} +#if __GLASGOW_HASKELL__ >= 810 +{-# OPTIONS_GHC -Wno-prepositive-qualified-module #-} +#endif +{% endif %} {-# OPTIONS_GHC -fno-warn-missing-import-lists #-} {-# OPTIONS_GHC -w #-} module Paths_{{ manglePkgName packageName }} (