diff --git a/.github/mergify.yml b/.github/mergify.yml index 3f6e9f6e078..5864577f608 100644 --- a/.github/mergify.yml +++ b/.github/mergify.yml @@ -97,10 +97,6 @@ pull_request_rules: - label=merge delay passed - '#approved-reviews-by>=2' - '-label~=^blocked:' - # unlike the others, we need to force this one to be up to date - # because it's intended for when Mergify doesn't have permission - # to rebase - - '#commits-behind=0' # merge strategy for release branches - actions: diff --git a/Cabal-syntax/ChangeLog.md b/Cabal-syntax/ChangeLog.md index cbba98a3cc4..205dcdb9cf0 100644 --- a/Cabal-syntax/ChangeLog.md +++ b/Cabal-syntax/ChangeLog.md @@ -1 +1 @@ -Please see https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.14.0.0.md +Please see https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.14.1.0.md diff --git a/Cabal-syntax/src/Distribution/Fields/Lexer.x b/Cabal-syntax/src/Distribution/Fields/Lexer.x index 4fc501d5186..b9b8ad54c4e 100644 --- a/Cabal-syntax/src/Distribution/Fields/Lexer.x +++ b/Cabal-syntax/src/Distribution/Fields/Lexer.x @@ -20,7 +20,7 @@ module Distribution.Fields.Lexer ,mkLexState) where import Prelude () -import qualified Prelude as Prelude +import qualified Prelude import Distribution.Compat.Prelude import Distribution.Fields.LexerMonad diff --git a/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs b/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs index c1c37800f21..a42befd9ccf 100644 --- a/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs +++ b/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs @@ -7,7 +7,7 @@ import Distribution.Types.LibraryName (LibraryName) import Distribution.Types.PackageName (PackageName) import Distribution.Types.Version (Version) --- | A reason for a depency failing to solve. +-- | A reason for a dependency failing to solve. -- -- This helps pinpoint dependencies that are installed with an incorrect -- version vs. dependencies that are not installed at all. diff --git a/Cabal/ChangeLog.md b/Cabal/ChangeLog.md index ea3b88e1082..ba5c56e1705 100644 --- a/Cabal/ChangeLog.md +++ b/Cabal/ChangeLog.md @@ -1,3 +1,6 @@ +# 3.14.1.0 [Hécate](mailto:hecate+github@glitchbra.in) November 2024 +* See https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.14.1.0.md + # 3.14.0.0 [Hécate](mailto:hecate+github@glitchbra.in) September 2024 * See https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.14.0.0.md @@ -5,7 +8,6 @@ * See https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.12.1.0.md # 3.12.0.0 [Francesco Ariis](mailto:fa-ml@ariis.it) May 2024 -# 3.12.0.0 [Francesco Ariis](mailto:fa-ml@ariis.it) March 2024 * See https://github.com/haskell/cabal/blob/master/release-notes/Cabal-3.12.0.0.md # 3.10.3.0 [Hécate](mailto:hecate+github@glitchbra.in) January 2024 diff --git a/Makefile b/Makefile index 5cf1cae4d6f..24d840ce39e 100644 --- a/Makefile +++ b/Makefile @@ -49,12 +49,18 @@ whitespace: ## Run fix-whitespace in check mode fix-whitespace: ## Run fix-whitespace in fix mode fix-whitespace --verbose +.PHONY: lint +lint: ## Run HLint + hlint -j . + +.PHONY: lint-json +lint-json: ## Run HLint in JSON mode + hlint -j --json -- . + # local checks .PHONY: checks -checks: whitespace style - # this should probably be a rule - hlint -j --json -- . +checks: whitespace style lint-json # source generation: SPDX diff --git a/cabal-install-solver/ChangeLog.md b/cabal-install-solver/ChangeLog.md index 978ac0f1b07..64dfd69e966 100644 --- a/cabal-install-solver/ChangeLog.md +++ b/cabal-install-solver/ChangeLog.md @@ -1 +1 @@ -Please see https://github.com/haskell/cabal/blob/master/release-notes/cabal-install-3.14.0.0.md +Please see https://github.com/haskell/cabal/blob/master/release-notes/cabal-install-3.14.1.0.md diff --git a/cabal-install/changelog b/cabal-install/changelog index 67711276c8f..47a798c0be1 100644 --- a/cabal-install/changelog +++ b/cabal-install/changelog @@ -1,5 +1,8 @@ -*-change-log-*- +3.14.1.0 Hécate November 2024 + * See https://github.com/haskell/cabal/blob/master/release-notes/cabal-install-3.14.1.0.md + 3.14.0.0 Hécate September 2024 * See https://github.com/haskell/cabal/blob/master/release-notes/cabal-install-3.14.0.0.md diff --git a/cabal-install/src/Distribution/Client/ParseUtils.hs b/cabal-install/src/Distribution/Client/ParseUtils.hs index 18062b7428f..96c702a2970 100644 --- a/cabal-install/src/Distribution/Client/ParseUtils.hs +++ b/cabal-install/src/Distribution/Client/ParseUtils.hs @@ -1,6 +1,8 @@ {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} ----------------------------------------------------------------------------- @@ -53,6 +55,7 @@ import Distribution.Deprecated.ParseUtils ( Field (..) , FieldDescr (..) , LineNo + , PError (..) , ParseResult (..) , liftField , lineNo @@ -292,13 +295,16 @@ parseFieldsAndSections fieldDescrs sectionDescrs fgSectionDescrs = setField a (F line name value) = case Map.lookup name fieldMap of Just (FieldDescr _ _ set) -> set line value a - Nothing -> do - warning $ - "Unrecognized field '" - ++ name - ++ "' on line " - ++ show line - return a + Nothing -> + case Left <$> Map.lookup name sectionMap <|> Right <$> Map.lookup name fgSectionMap of + Just _ -> ParseFailed $ FieldShouldBeStanza name line + Nothing -> do + warning $ + "Unrecognized field '" + ++ name + ++ "' on line " + ++ show line + return a setField a (Section line name param fields) = case Left <$> Map.lookup name sectionMap <|> Right <$> Map.lookup name fgSectionMap of Just (Left (SectionDescr _ fieldDescrs' sectionDescrs' _ set sectionEmpty)) -> do diff --git a/cabal-install/src/Distribution/Deprecated/ParseUtils.hs b/cabal-install/src/Distribution/Deprecated/ParseUtils.hs index e1d389ac9aa..4743213fde9 100644 --- a/cabal-install/src/Distribution/Deprecated/ParseUtils.hs +++ b/cabal-install/src/Distribution/Deprecated/ParseUtils.hs @@ -91,6 +91,7 @@ data PError = AmbiguousParse String LineNo | NoParse String LineNo | TabsError LineNo + | FieldShouldBeStanza String LineNo | FromString String (Maybe LineNo) deriving (Eq, Show) @@ -186,6 +187,10 @@ locatedErrorMsg (NoParse f n) = , "Parse of field '" ++ f ++ "' failed." ) locatedErrorMsg (TabsError n) = (Just n, "Tab used as indentation.") +locatedErrorMsg (FieldShouldBeStanza name lineNumber) = + ( Just lineNumber + , "'" ++ name ++ "' is a stanza, not a field. Remove the trailing ':' to parse a stanza." + ) locatedErrorMsg (FromString s n) = (n, s) syntaxError :: LineNo -> String -> ParseResult a diff --git a/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs b/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs index a76dd39b082..9b9507d13e9 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs @@ -56,6 +56,12 @@ import UnitTests.Distribution.Client.ArbitraryInstances tests :: MTimeChange -> [TestTree] tests mtimeChange = map + -- Are you tuning performance for these tests? The size of the arbitrary + -- instances involved is very significant, because each element generated + -- corresponds to one or more Git subcommands being run. + -- + -- See [Tuning Arbitrary Instances] below for more information and + -- parameters. (localOption $ QuickCheckTests 10) [ ignoreInWindows "See issue #8048 and #9519" $ testGroup @@ -216,22 +222,27 @@ prop_syncRepos_hg destRepoDirs syncTargetSetIterations seed = testSetup :: VCS Program - -> ( Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver - ) + -> (MkVCSTestDriver -> VCSTestDriver) -> RepoRecipe submodules -> (VCSTestDriver -> FilePath -> RepoState -> IO a) -> IO a testSetup vcs mkVCSTestDriver repoRecipe theTest = do - -- test setup - vcs' <- configureVCS verbosity [] vcs withTestDir verbosity "vcstest" $ \tmpdir -> do + -- test setup + vcs' <- configureVCS verbosity [] vcs + let srcRepoPath = tmpdir "src" submodulesPath = tmpdir "submodules" - vcsDriver = mkVCSTestDriver verbosity vcs' submodulesPath srcRepoPath + vcsDriver = + mkVCSTestDriver + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs' + , mkVcsSubmoduleDir = submodulesPath + , mkVcsRepoRoot = srcRepoPath + , mkVcsTmpDir = tmpdir + } + repoState <- createRepo vcsDriver repoRecipe -- actual test @@ -252,12 +263,7 @@ testSetup vcs mkVCSTestDriver repoRecipe theTest = do -- the working state is the same as the pure representation. prop_framework :: VCS Program - -> ( Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver - ) + -> (MkVCSTestDriver -> VCSTestDriver) -> RepoRecipe submodules -> IO () prop_framework vcs mkVCSTestDriver repoRecipe = @@ -288,12 +294,7 @@ prop_framework vcs mkVCSTestDriver repoRecipe = prop_cloneRepo :: VCS Program - -> ( Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver - ) + -> (MkVCSTestDriver -> VCSTestDriver) -> RepoRecipe submodules -> IO () prop_cloneRepo vcs mkVCSTestDriver repoRecipe = @@ -329,12 +330,7 @@ newtype PrngSeed = PrngSeed Int deriving (Show) prop_syncRepos :: VCS Program - -> ( Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver - ) + -> (MkVCSTestDriver -> VCSTestDriver) -> RepoDirSet -> SyncTargetIterations -> PrngSeed @@ -482,6 +478,7 @@ instance Arbitrary PrngSeed where -- VCS commands to make a repository on-disk. data SubmodulesSupport = SubmodulesSupported | SubmodulesNotSupported + deriving (Show, Eq) class KnownSubmodulesSupport (a :: SubmodulesSupport) where submoduleSupport :: SubmodulesSupport @@ -494,7 +491,11 @@ instance KnownSubmodulesSupport 'SubmodulesNotSupported where data FileUpdate = FileUpdate FilePath String deriving (Show) -data SubmoduleAdd = SubmoduleAdd FilePath FilePath (Commit 'SubmodulesSupported) +data SubmoduleAdd = SubmoduleAdd + { submodulePath :: FilePath + , submoduleSource :: FilePath + , submoduleCommit :: Commit 'SubmodulesSupported + } deriving (Show) newtype Commit (submodules :: SubmodulesSupport) @@ -535,40 +536,71 @@ data RepoRecipe submodules genFileName :: Gen FilePath genFileName = (\c -> "file" [c]) <$> choose ('A', 'E') +-- [Tuning Arbitrary Instances] +-- +-- Arbitrary repo recipes can get quite large due to nesting: +-- +-- - `RepoRecipes` contain a number of groups (`TaggedCommits` or `BranchCommits`). +-- - Groups contain a number of `Commit`s. +-- - Commits contain a number of operations (`FileUpdate` or `SubmoduleAdd`). +-- +-- There's also another wrinkle in that `SubmoduleAdd`s contain a `Commit` +-- themselves, so square the `operationsPerCommit` number! +-- +-- Then, a rough upper bound of the number of `git` calls required for an +-- arbitrary `RepoRecipe` is +-- `groupsPerRecipe * commitsPerGroup * operationsPerCommit^2`. +-- +-- The original implementation of these instances, which chose +-- reasonable-sounding size parameters of 5-15, led to a maximum of 1875 +-- operations per test case! No wonder they took so long! +-- +-- In most cases, we only care about one or many operations, so "two" is a fine +-- stand-in for "many" :) +groupsPerRecipe :: Int +groupsPerRecipe = 3 + +commitsPerGroup :: Int +commitsPerGroup = 3 + +operationsPerCommit :: Int +operationsPerCommit = 3 + instance Arbitrary FileUpdate where - arbitrary = genOnlyFileUpdate + arbitrary = FileUpdate <$> genFileName <*> genFileContent where - genOnlyFileUpdate = FileUpdate <$> genFileName <*> genFileContent genFileContent = vectorOf 10 (choose ('#', '~')) instance Arbitrary SubmoduleAdd where - arbitrary = genOnlySubmoduleAdd + arbitrary = SubmoduleAdd <$> genFileName <*> genSubmoduleSrc <*> arbitrary where - genOnlySubmoduleAdd = SubmoduleAdd <$> genFileName <*> genSubmoduleSrc <*> arbitrary genSubmoduleSrc = vectorOf 20 (choose ('a', 'z')) instance forall submodules. KnownSubmodulesSupport submodules => Arbitrary (Commit submodules) where - arbitrary = Commit <$> shortListOf1 5 fileUpdateOrSubmoduleAdd + arbitrary = Commit <$> shortListOf1 operationsPerCommit (sized fileUpdateOrSubmoduleAdd) where - fileUpdateOrSubmoduleAdd = + fileUpdateOrSubmoduleAdd 0 = Left <$> arbitrary + fileUpdateOrSubmoduleAdd size = case submoduleSupport @submodules of SubmodulesSupported -> frequency [ (10, Left <$> arbitrary) - , (1, Right <$> arbitrary) + , -- A `SubmoduleAdd` contains a `Commit`, so we make sure to scale + -- down the size in the recursive call to avoid unbounded nesting. + (1, Right <$> resize (size `div` 2) arbitrary) ] SubmodulesNotSupported -> Left <$> arbitrary shrink (Commit writes) = Commit <$> filter (not . null) (shrink writes) instance KnownSubmodulesSupport submodules => Arbitrary (TaggedCommits submodules) where - arbitrary = TaggedCommits <$> genTagName <*> shortListOf1 5 arbitrary + arbitrary = TaggedCommits <$> genTagName <*> shortListOf1 commitsPerGroup arbitrary where genTagName = ("tag_" ++) <$> shortListOf1 5 (choose ('A', 'Z')) shrink (TaggedCommits tag commits) = TaggedCommits tag <$> filter (not . null) (shrink commits) instance KnownSubmodulesSupport submodules => Arbitrary (BranchCommits submodules) where - arbitrary = BranchCommits <$> genBranchName <*> shortListOf1 5 arbitrary + arbitrary = BranchCommits <$> genBranchName <*> shortListOf1 commitsPerGroup arbitrary where genBranchName = sized $ \n -> @@ -578,12 +610,12 @@ instance KnownSubmodulesSupport submodules => Arbitrary (BranchCommits submodule BranchCommits branch <$> filter (not . null) (shrink commits) instance KnownSubmodulesSupport submodules => Arbitrary (NonBranchingRepoRecipe submodules) where - arbitrary = NonBranchingRepoRecipe <$> shortListOf1 15 arbitrary + arbitrary = NonBranchingRepoRecipe <$> shortListOf1 groupsPerRecipe arbitrary shrink (NonBranchingRepoRecipe xs) = NonBranchingRepoRecipe <$> filter (not . null) (shrink xs) instance KnownSubmodulesSupport submodules => Arbitrary (BranchingRepoRecipe submodules) where - arbitrary = BranchingRepoRecipe <$> shortListOf1 15 taggedOrBranch + arbitrary = BranchingRepoRecipe <$> shortListOf1 groupsPerRecipe taggedOrBranch where taggedOrBranch = frequency @@ -839,237 +871,271 @@ data VCSTestDriver = VCSTestDriver (TagName -> FilePath -> IO ()) } +data MkVCSTestDriver = MkVCSTestDriver + { mkVcsVerbosity :: Verbosity + , mkVcsVcs :: VCS ConfiguredProgram + , mkVcsSubmoduleDir :: FilePath + , mkVcsRepoRoot :: FilePath + , mkVcsTmpDir :: FilePath + } + +vcsTestDriverGit :: MkVCSTestDriver -> VCSTestDriver vcsTestDriverGit - :: Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver -vcsTestDriverGit verbosity vcs submoduleDir repoRoot = - VCSTestDriver - { vcsVCS = vcs' - , vcsRepoRoot = repoRoot - , vcsIgnoreFiles = Set.empty - , vcsInit = - git $ ["init"] ++ verboseArg - , vcsAddFile = \_ filename -> - git ["add", filename] - , vcsCommitChanges = \_state -> do - git $ - [ "-c" - , "user.name=A" - , "-c" - , "user.email=a@example.com" - , "commit" - , "--all" - , "--message=a patch" - , "--author=A " + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs + , mkVcsSubmoduleDir = submoduleDir + , mkVcsRepoRoot = repoRoot + , mkVcsTmpDir = tmpDir + } = + VCSTestDriver + { vcsVCS = vcs' + , vcsRepoRoot = repoRoot + , vcsIgnoreFiles = Set.empty + , vcsInit = do + createDirectoryIfMissing True home + gitconfigExists <- doesFileExist gitconfigPath + unless gitconfigExists $ do + writeFile gitconfigPath gitconfig + git $ ["init"] ++ verboseArg + , vcsAddFile = \_ filename -> + git ["add", filename] + , vcsCommitChanges = \_state -> do + git $ + [ "commit" + , "--all" + , "--message=a patch" + ] + ++ verboseArg + commit <- git' ["rev-parse", "HEAD"] + let commit' = takeWhile (not . isSpace) commit + return (Just commit') + , vcsTagState = \_ tagname -> + git ["tag", "--force", "--no-sign", tagname] + , vcsSubmoduleDriver = + \newPath -> + pure $ + vcsTestDriverGit + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs' + , mkVcsSubmoduleDir = submoduleDir + , mkVcsRepoRoot = submoduleDir newPath + , mkVcsTmpDir = tmpDir + } + , vcsAddSubmodule = \_ source dest -> do + destExists <- + (||) + <$> doesFileExist (repoRoot dest) + <*> doesDirectoryExist (repoRoot dest) + when destExists $ git ["rm", "-f", dest] + -- If there is an old submodule git dir with the same name, remove it. + -- It most likely has a different URL and `git submodule add` will fai. + submoduleGitDirExists <- doesDirectoryExist $ submoduleGitDir dest + when submoduleGitDirExists $ removeDirectoryRecursive (submoduleGitDir dest) + git ["submodule", "add", source, dest] + git ["submodule", "update", "--init", "--recursive", "--force"] + , vcsSwitchBranch = \RepoState{allBranches} branchname -> do + deinitAndRemoveCachedSubmodules + unless (branchname `Map.member` allBranches) $ + git ["branch", branchname] + git $ ["checkout", branchname] ++ verboseArg + updateSubmodulesAndCleanup + , vcsCheckoutTag = Left $ \tagname -> do + deinitAndRemoveCachedSubmodules + git $ ["checkout", "--detach", "--force", tagname] ++ verboseArg + updateSubmodulesAndCleanup + } + where + home = tmpDir "home" + gitconfigPath = home ".gitconfig" + -- Git 2.38.1 and newer fails to clone from local paths with `fatal: transport 'file' + -- not allowed` unless `protocol.file.allow=always` is set. + -- + -- This is not safe in general, but it's fine in the test suite. + -- + -- See: https://github.blog/open-source/git/git-security-vulnerabilities-announced/#fn-67904-1 + -- See: https://git-scm.com/docs/git-config#Documentation/git-config.txt-protocolallow + gitconfig = + unlines + [ "[protocol.file]" + , " allow = always" + , "[user]" + , " name = Puppy Doggy" + , " email = puppy.doggy@example.com" ] - ++ verboseArg - commit <- git' ["log", "--format=%H", "-1"] - let commit' = takeWhile (not . isSpace) commit - return (Just commit') - , vcsTagState = \_ tagname -> - git ["tag", "--force", "--no-sign", tagname] - , vcsSubmoduleDriver = - pure . vcsTestDriverGit verbosity vcs' submoduleDir . (submoduleDir ) - , vcsAddSubmodule = \_ source dest -> do - destExists <- - (||) - <$> doesFileExist (repoRoot dest) - <*> doesDirectoryExist (repoRoot dest) - when destExists $ git ["rm", "-f", dest] - -- If there is an old submodule git dir with the same name, remove it. - -- It most likely has a different URL and `git submodule add` will fai. - submoduleGitDirExists <- doesDirectoryExist $ submoduleGitDir dest - when submoduleGitDirExists $ removeDirectoryRecursive (submoduleGitDir dest) - git ["submodule", "add", source, dest] - git ["submodule", "update", "--init", "--recursive", "--force"] - , vcsSwitchBranch = \RepoState{allBranches} branchname -> do - deinitAndRemoveCachedSubmodules - unless (branchname `Map.member` allBranches) $ - git ["branch", branchname] - git $ ["checkout", branchname] ++ verboseArg - updateSubmodulesAndCleanup - , vcsCheckoutTag = Left $ \tagname -> do - deinitAndRemoveCachedSubmodules - git $ ["checkout", "--detach", "--force", tagname] ++ verboseArg - updateSubmodulesAndCleanup - } - where - -- Git 2.38.1 and newer fails to clone from local paths with `fatal: transport 'file' - -- not allowed` unless `protocol.file.allow=always` is set. - -- - -- This is not safe in general, but it's fine in the test suite. - -- - -- See: https://github.blog/open-source/git/git-security-vulnerabilities-announced/#fn-67904-1 - -- See: https://git-scm.com/docs/git-config#Documentation/git-config.txt-protocolallow - vcs' = - vcs - { vcsProgram = - (vcsProgram vcs) - { programDefaultArgs = - programDefaultArgs (vcsProgram vcs) - ++ [ "-c" - , "protocol.file.allow=always" - ] - } - } - gitInvocation args = - (programInvocation (vcsProgram vcs') args) - { progInvokeCwd = Just repoRoot - } - git = runProgramInvocation verbosity . gitInvocation - git' = getProgramInvocationOutput verbosity . gitInvocation - verboseArg = ["--quiet" | verbosity < Verbosity.normal] - submoduleGitDir path = repoRoot ".git" "modules" path - deinitAndRemoveCachedSubmodules = do - git $ ["submodule", "deinit", "--force", "--all"] ++ verboseArg - let gitModulesDir = repoRoot ".git" "modules" - gitModulesExists <- doesDirectoryExist gitModulesDir - when gitModulesExists $ removeDirectoryRecursive gitModulesDir - updateSubmodulesAndCleanup = do - git $ ["submodule", "sync", "--recursive"] ++ verboseArg - git $ ["submodule", "update", "--init", "--recursive", "--force"] ++ verboseArg - git $ ["submodule", "foreach", "--recursive"] ++ verboseArg ++ ["git clean -ffxdq"] - git $ ["clean", "-ffxdq"] ++ verboseArg + + vcs' = + vcs + { vcsProgram = + (vcsProgram vcs) + { programOverrideEnv = + programOverrideEnv (vcsProgram vcs) + ++ [ -- > Whether to skip reading settings from the system-wide $(prefix)/etc/gitconfig file. + ("GIT_CONFIG_NOSYSTEM", Just "1") + , ("GIT_CONFIG_GLOBAL", Just gitconfigPath) + , -- Setting the author and committer dates makes commit hashes deterministic between test runs. + ("GIT_AUTHOR_DATE", Just "1998-04-30T18:25:03-0400") + , ("GIT_COMMITTER_DATE", Just "1998-04-30T18:25:00-0400") + , ("HOME", Just home) + ] + } + } + gitInvocation args = + (programInvocation (vcsProgram vcs') args) + { progInvokeCwd = Just repoRoot + } + git = runProgramInvocation verbosity . gitInvocation + git' = getProgramInvocationOutput verbosity . gitInvocation + verboseArg = ["--quiet" | verbosity < Verbosity.normal] + submoduleGitDir path = repoRoot ".git" "modules" path + deinitAndRemoveCachedSubmodules = do + git $ ["submodule", "deinit", "--force", "--all"] ++ verboseArg + let gitModulesDir = repoRoot ".git" "modules" + gitModulesExists <- doesDirectoryExist gitModulesDir + when gitModulesExists $ removeDirectoryRecursive gitModulesDir + updateSubmodulesAndCleanup = do + git $ ["submodule", "sync", "--recursive"] ++ verboseArg + git $ ["submodule", "update", "--init", "--recursive", "--force"] ++ verboseArg + git $ ["submodule", "foreach", "--recursive"] ++ verboseArg ++ ["git clean -ffxdq"] + git $ ["clean", "-ffxdq"] ++ verboseArg type MTimeChange = Int +vcsTestDriverDarcs :: MTimeChange -> MkVCSTestDriver -> VCSTestDriver vcsTestDriverDarcs - :: MTimeChange - -> Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver -vcsTestDriverDarcs mtimeChange verbosity vcs _ repoRoot = - VCSTestDriver - { vcsVCS = vcs - , vcsRepoRoot = repoRoot - , vcsIgnoreFiles = Set.singleton "_darcs" - , vcsInit = - darcs ["initialize"] - , vcsAddFile = \state filename -> do - threadDelay mtimeChange - unless (filename `Map.member` currentWorking state) $ - darcs ["add", filename] - , -- Darcs's file change tracking relies on mtime changes, - -- so we have to be careful with doing stuff too quickly: - - vcsSubmoduleDriver = \_ -> - fail "vcsSubmoduleDriver: darcs does not support submodules" - , vcsAddSubmodule = \_ _ _ -> - fail "vcsAddSubmodule: darcs does not support submodules" - , vcsCommitChanges = \_state -> do - threadDelay mtimeChange - darcs ["record", "--all", "--author=author", "--name=a patch"] - return Nothing - , vcsTagState = \_ tagname -> - darcs ["tag", "--author=author", tagname] - , vcsSwitchBranch = \_ _ -> - fail "vcsSwitchBranch: darcs does not support branches within a repo" - , vcsCheckoutTag = Right $ \tagname dest -> - darcs ["clone", "--lazy", "--tag=^" ++ tagname ++ "$", ".", dest] - } - where - darcsInvocation args = - (programInvocation (vcsProgram vcs) args) - { progInvokeCwd = Just repoRoot - } - darcs = runProgramInvocation verbosity . darcsInvocation + mtimeChange + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs + , mkVcsRepoRoot = repoRoot + } = + VCSTestDriver + { vcsVCS = vcs + , vcsRepoRoot = repoRoot + , vcsIgnoreFiles = Set.singleton "_darcs" + , vcsInit = + darcs ["initialize"] + , vcsAddFile = \state filename -> do + threadDelay mtimeChange + unless (filename `Map.member` currentWorking state) $ + darcs ["add", filename] + , -- Darcs's file change tracking relies on mtime changes, + -- so we have to be careful with doing stuff too quickly: + + vcsSubmoduleDriver = \_ -> + fail "vcsSubmoduleDriver: darcs does not support submodules" + , vcsAddSubmodule = \_ _ _ -> + fail "vcsAddSubmodule: darcs does not support submodules" + , vcsCommitChanges = \_state -> do + threadDelay mtimeChange + darcs ["record", "--all", "--author=author", "--name=a patch"] + return Nothing + , vcsTagState = \_ tagname -> + darcs ["tag", "--author=author", tagname] + , vcsSwitchBranch = \_ _ -> + fail "vcsSwitchBranch: darcs does not support branches within a repo" + , vcsCheckoutTag = Right $ \tagname dest -> + darcs ["clone", "--lazy", "--tag=^" ++ tagname ++ "$", ".", dest] + } + where + darcsInvocation args = + (programInvocation (vcsProgram vcs) args) + { progInvokeCwd = Just repoRoot + } + darcs = runProgramInvocation verbosity . darcsInvocation +vcsTestDriverPijul :: MkVCSTestDriver -> VCSTestDriver vcsTestDriverPijul - :: Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver -vcsTestDriverPijul verbosity vcs _ repoRoot = - VCSTestDriver - { vcsVCS = vcs - , vcsRepoRoot = repoRoot - , vcsIgnoreFiles = Set.empty - , vcsInit = - pijul $ ["init"] - , vcsAddFile = \_ filename -> - pijul ["add", filename] - , vcsSubmoduleDriver = \_ -> - fail "vcsSubmoduleDriver: pijul does not support submodules" - , vcsAddSubmodule = \_ _ _ -> - fail "vcsAddSubmodule: pijul does not support submodules" - , vcsCommitChanges = \_state -> do - pijul $ - [ "record" - , "-a" - , "-m 'a patch'" - , "-A 'A '" - ] - commit <- pijul' ["log"] - let commit' = takeWhile (not . isSpace) commit - return (Just commit') - , -- tags work differently in pijul... - -- so this is wrong - vcsTagState = \_ tagname -> - pijul ["tag", tagname] - , vcsSwitchBranch = \_ branchname -> do - -- unless (branchname `Map.member` allBranches) $ - -- pijul ["from-branch", branchname] - pijul $ ["checkout", branchname] - , vcsCheckoutTag = Left $ \tagname -> - pijul $ ["checkout", tagname] - } - where - gitInvocation args = - (programInvocation (vcsProgram vcs) args) - { progInvokeCwd = Just repoRoot - } - pijul = runProgramInvocation verbosity . gitInvocation - pijul' = getProgramInvocationOutput verbosity . gitInvocation - + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs + , mkVcsRepoRoot = repoRoot + } = + VCSTestDriver + { vcsVCS = vcs + , vcsRepoRoot = repoRoot + , vcsIgnoreFiles = Set.empty + , vcsInit = + pijul $ ["init"] + , vcsAddFile = \_ filename -> + pijul ["add", filename] + , vcsSubmoduleDriver = \_ -> + fail "vcsSubmoduleDriver: pijul does not support submodules" + , vcsAddSubmodule = \_ _ _ -> + fail "vcsAddSubmodule: pijul does not support submodules" + , vcsCommitChanges = \_state -> do + pijul $ + [ "record" + , "-a" + , "-m 'a patch'" + , "-A 'A '" + ] + commit <- pijul' ["log"] + let commit' = takeWhile (not . isSpace) commit + return (Just commit') + , -- tags work differently in pijul... + -- so this is wrong + vcsTagState = \_ tagname -> + pijul ["tag", tagname] + , vcsSwitchBranch = \_ branchname -> do + -- unless (branchname `Map.member` allBranches) $ + -- pijul ["from-branch", branchname] + pijul $ ["checkout", branchname] + , vcsCheckoutTag = Left $ \tagname -> + pijul $ ["checkout", tagname] + } + where + gitInvocation args = + (programInvocation (vcsProgram vcs) args) + { progInvokeCwd = Just repoRoot + } + pijul = runProgramInvocation verbosity . gitInvocation + pijul' = getProgramInvocationOutput verbosity . gitInvocation + +vcsTestDriverHg :: MkVCSTestDriver -> VCSTestDriver vcsTestDriverHg - :: Verbosity - -> VCS ConfiguredProgram - -> FilePath - -> FilePath - -> VCSTestDriver -vcsTestDriverHg verbosity vcs _ repoRoot = - VCSTestDriver - { vcsVCS = vcs - , vcsRepoRoot = repoRoot - , vcsIgnoreFiles = Set.empty - , vcsInit = - hg $ ["init"] ++ verboseArg - , vcsAddFile = \_ filename -> - hg ["add", filename] - , vcsSubmoduleDriver = \_ -> - fail "vcsSubmoduleDriver: hg submodules not supported" - , vcsAddSubmodule = \_ _ _ -> - fail "vcsAddSubmodule: hg submodules not supported" - , vcsCommitChanges = \_state -> do - hg $ - [ "--user='A '" - , "commit" - , "--message=a patch" - ] - ++ verboseArg - commit <- hg' ["log", "--template='{node}\\n' -l1"] - let commit' = takeWhile (not . isSpace) commit - return (Just commit') - , vcsTagState = \_ tagname -> - hg ["tag", "--force", tagname] - , vcsSwitchBranch = \RepoState{allBranches} branchname -> do - unless (branchname `Map.member` allBranches) $ - hg ["branch", branchname] - hg $ ["checkout", branchname] ++ verboseArg - , vcsCheckoutTag = Left $ \tagname -> - hg $ ["checkout", "--rev", tagname] ++ verboseArg - } - where - hgInvocation args = - (programInvocation (vcsProgram vcs) args) - { progInvokeCwd = Just repoRoot - } - hg = runProgramInvocation verbosity . hgInvocation - hg' = getProgramInvocationOutput verbosity . hgInvocation - verboseArg = ["--quiet" | verbosity < Verbosity.normal] + MkVCSTestDriver + { mkVcsVerbosity = verbosity + , mkVcsVcs = vcs + , mkVcsRepoRoot = repoRoot + } = + VCSTestDriver + { vcsVCS = vcs + , vcsRepoRoot = repoRoot + , vcsIgnoreFiles = Set.empty + , vcsInit = + hg $ ["init"] ++ verboseArg + , vcsAddFile = \_ filename -> + hg ["add", filename] + , vcsSubmoduleDriver = \_ -> + fail "vcsSubmoduleDriver: hg submodules not supported" + , vcsAddSubmodule = \_ _ _ -> + fail "vcsAddSubmodule: hg submodules not supported" + , vcsCommitChanges = \_state -> do + hg $ + [ "--user='A '" + , "commit" + , "--message=a patch" + ] + ++ verboseArg + commit <- hg' ["log", "--template='{node}\\n' -l1"] + let commit' = takeWhile (not . isSpace) commit + return (Just commit') + , vcsTagState = \_ tagname -> + hg ["tag", "--force", tagname] + , vcsSwitchBranch = \RepoState{allBranches} branchname -> do + unless (branchname `Map.member` allBranches) $ + hg ["branch", branchname] + hg $ ["checkout", branchname] ++ verboseArg + , vcsCheckoutTag = Left $ \tagname -> + hg $ ["checkout", "--rev", tagname] ++ verboseArg + } + where + hgInvocation args = + (programInvocation (vcsProgram vcs) args) + { progInvokeCwd = Just repoRoot + } + hg = runProgramInvocation verbosity . hgInvocation + hg' = getProgramInvocationOutput verbosity . hgInvocation + verboseArg = ["--quiet" | verbosity < Verbosity.normal] diff --git a/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.out b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.out new file mode 100644 index 00000000000..60680b86db3 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.out @@ -0,0 +1,4 @@ +# cabal build +Error: [Cabal-7090] +Error parsing project file /cabal.project:4: +'source-repository-package' is a stanza, not a field. Remove the trailing ':' to parse a stanza. diff --git a/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.project b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.project new file mode 100644 index 00000000000..518ac39f5fb --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.project @@ -0,0 +1,6 @@ +packages: . + +-- This is an error; a trailing `:` is syntax for a field, not a stanza! +source-repository-package: + type: git + location: https://github.com/haskell-hvr/Only diff --git a/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.test.hs new file mode 100644 index 00000000000..39636819157 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/cabal.test.hs @@ -0,0 +1,6 @@ +import Test.Cabal.Prelude + +main = cabalTest $ do + result <- fails $ cabal' "build" [] + assertOutputContains "Error parsing project file" result + assertOutputContains "'source-repository-package' is a stanza, not a field." result diff --git a/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/src/MyLib.hs b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/src/MyLib.hs new file mode 100644 index 00000000000..e657c4403f6 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/src/MyLib.hs @@ -0,0 +1,4 @@ +module MyLib (someFunc) where + +someFunc :: IO () +someFunc = putStrLn "someFunc" diff --git a/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/test.cabal b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/test.cabal new file mode 100644 index 00000000000..86374a457c7 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectConfig/FieldStanzaConfusion/test.cabal @@ -0,0 +1,13 @@ +cabal-version: 3.0 +name: test +version: 0.1.0.0 +license: NONE +author: rbt@sent.as +maintainer: Rebecca Turner +build-type: Simple + +library + exposed-modules: MyLib + build-depends: base + hs-source-dirs: src + default-language: Haskell2010 diff --git a/cabal-validate/src/Cli.hs b/cabal-validate/src/Cli.hs index 423769cd1d9..482fb2096b1 100644 --- a/cabal-validate/src/Cli.hs +++ b/cabal-validate/src/Cli.hs @@ -233,8 +233,8 @@ resolveOpts opts = do else "cabal.validate.project" tastyArgs' = - "--hide-successes" - : maybe + optional (rawTastyHideSuccesses opts) "--hide-successes" + ++ maybe [] (\tastyPattern -> ["--pattern", tastyPattern]) (rawTastyPattern opts) @@ -282,6 +282,7 @@ data RawOpts = RawOpts , rawExtraCompilers :: [FilePath] , rawTastyPattern :: Maybe String , rawTastyArgs :: [String] + , rawTastyHideSuccesses :: Bool , rawDoctest :: Bool , rawSteps :: [Step] , rawListSteps :: Bool @@ -352,6 +353,11 @@ rawOptsParser = <> help "Extra arguments to pass to Tasty test suites" ) ) + <*> boolOption + True + "hide-successes" + ( help "Do not print tests that passed successfully" + ) <*> boolOption False "doctest" diff --git a/cabal-validate/src/Main.hs b/cabal-validate/src/Main.hs index 428a8a7358d..51472ad34a4 100644 --- a/cabal-validate/src/Main.hs +++ b/cabal-validate/src/Main.hs @@ -325,15 +325,17 @@ libSuiteExtras opts = forM_ (extraCompilers opts) $ \compiler' -> cliTests :: Opts -> IO () cliTests opts = do -- These are sorted in asc time used, quicker tests first. + + -- Only single job, otherwise we fail with "Heap exhausted" timedCabalBin opts "cabal-install" - "test:long-tests" - ( jobsArgs opts + "test:mem-use-tests" + ( ["--num-threads", "1"] ++ tastyArgs opts ) - -- This doesn't work in parallel either. + -- This test-suite doesn't like concurrency timedCabalBin opts "cabal-install" @@ -342,16 +344,15 @@ cliTests opts = do ++ tastyArgs opts ) - -- Only single job, otherwise we fail with "Heap exhausted" timedCabalBin opts "cabal-install" - "test:mem-use-tests" - ( ["--num-threads", "1"] + "test:long-tests" + ( jobsArgs opts ++ tastyArgs opts ) - -- This test-suite doesn't like concurrency + -- This doesn't work in parallel either. timedCabalBin opts "cabal-install" diff --git a/changelog.d/i10418 b/changelog.d/i10418 deleted file mode 100644 index 9a96e47a1e9..00000000000 --- a/changelog.d/i10418 +++ /dev/null @@ -1,13 +0,0 @@ -synopsis: Fix build ways for modules in executables -packages: Cabal -prs: #10419 -issues: #10418 -significance: significant - -description: { - -- Modules belonging to executables were being built in too many ways. For instance, if you -had configured to build profiled library files then your executable modules would also -be built profiled. Which was a regression in behaviour since `Cabal-3.12`. - -} diff --git a/changelog.d/pr-10468 b/changelog.d/pr-10468 deleted file mode 100644 index 2b1511a609c..00000000000 --- a/changelog.d/pr-10468 +++ /dev/null @@ -1,31 +0,0 @@ -synopsis: Add new options from ghc 9.12 -packages: Cabal -prs: #10468 -significance: - -description: { - -- ghc 9.12 adds several new command line options, divided between - `LANGUAGE`s (already added), warnings, new preprocessor control options, - and compilation control options. Two options needed to be added to the - list of options requiring `Int` parameters. - - The new options, excluding warning and language options, are: - - * `-fexpose-overloaded-unfoldings` - * `-fmax-forced-spec-args=N` - * `-fno-expose-overloaded-unfoldings` - * `-fno-object-determinism` - * `-fobject-determinism` - * `-fwrite-if-compression=N` - * `-optCmmP…` - * `-optJSP…` - * `-pgmCmmP` - * `-pgmJSP` - - As they all affect compilation and store hashes, the only necessary - change was to list the two numeric options so they will be parsed - correctly. To the best of our understanding, `-pgm*` and `-opt*` - options are already handled as a group. - -} diff --git a/changelog.d/pr-10486 b/changelog.d/pr-10486 deleted file mode 100644 index 237d2c857b0..00000000000 --- a/changelog.d/pr-10486 +++ /dev/null @@ -1,12 +0,0 @@ -synopsis: Fix a bug that causes `cabal init` to crash if `git` is not installed -packages: cabal-install -prs: #10486 -issues: #10484 #8478 -significance: - -description: { - -- `cabal init` tries to use `git config` to guess the user's name and email. - It no longer crashes if there is no executable named `git` on $PATH. - -} diff --git a/changelog.d/pr-10507 b/changelog.d/pr-10507 deleted file mode 100644 index 02897f71e19..00000000000 --- a/changelog.d/pr-10507 +++ /dev/null @@ -1,16 +0,0 @@ -synopsis: Print out which project file we are using with the default verbosity -packages: cabal-install -prs: #10507 -issues: #8519 - -description: { - -- Many people have been burnt by cabal catching stray project files located up - the directory tree. This change tries to protect them at the expense of - producing more output by default. In particular, before this change, you could - see which project file is in use by supplying `-v` (the verbose mode), and - after the change we print this information with the default verbosity. - Changing the behaviour of cabal is out of scope of this change, and will - hopefully be done in the future versions (see #9353 for a way forward). - -} diff --git a/changelog.d/pr-10525 b/changelog.d/pr-10525 new file mode 100644 index 00000000000..7235d0bec74 --- /dev/null +++ b/changelog.d/pr-10525 @@ -0,0 +1,34 @@ +--- +synopsis: "A trailing colon after a stanza name in `cabal.project` is now an error" +packages: [cabal-install] +prs: 10525 +--- + +It is now a hard error to use a trailing colon after a stanza name in +`cabal.project` or `*.cabal` files: + +``` +packages: . + +source-repository-package: + type: git + location: https://github.com/haskell/cabal + tag: f34aba976a60940295f41b6649674e9568893894 +``` + +``` +$ cabal build +Error parsing project file cabal.project:3: +'source-repository-package' is a stanza, not a field. Remove the trailing ':' to parse a stanza. +``` + +Previously, the warning message was easily ignored and somewhat misleading, as +the difference between a stanza and a field is not immediately obvious to +Haskellers used to config languages like JSON and YAML (which don't distinguish +between fields which have string or list values and stanzas which have nested +fields): + +``` +Warning: cabal.project: Unrecognized field +'source-repository-package' on line 3 +``` diff --git a/changelog.d/t10416 b/changelog.d/t10416 deleted file mode 100644 index 071b9b1ad95..00000000000 --- a/changelog.d/t10416 +++ /dev/null @@ -1,11 +0,0 @@ -synopsis: Fix ./setup install command -packages: Cabal -prs: #10417 -issues: #10416 -significance: significant - -description: { - -- `./setup install` was failing with a `fromFlag NoFlag` error. It is now fixed. - -} diff --git a/doc/cabal-commands.rst b/doc/cabal-commands.rst index d13d13216c4..13f008b13e0 100644 --- a/doc/cabal-commands.rst +++ b/doc/cabal-commands.rst @@ -1297,7 +1297,7 @@ A list of all warnings with their constructor: - ``unsupported-bench``: unsupported benchmark type. - ``bench-unknown-extension``: ``main-is`` for benchmark is neither ``.hs`` nor ``.lhs``. - ``invalid-name-win``: invalid package name on Windows. -- ``reserved-z-prefix``: package with ``z-`` prexif (reseved for Cabal. +- ``reserved-z-prefix``: package with ``z-`` prefix (reserved for Cabal). - ``no-build-type``: missing ``build-type``. - ``undeclared-custom-setup``: ``custom-setup`` section without ``build-type: Custom`` - ``unknown-compiler-tested``: unknown compiler in ``tested-with``. diff --git a/doc/cabal-package-description-file.rst b/doc/cabal-package-description-file.rst index 6ae467b4774..b9b0cb172f3 100644 --- a/doc/cabal-package-description-file.rst +++ b/doc/cabal-package-description-file.rst @@ -2747,22 +2747,28 @@ The :ref:`VCS fields` of ``source-repository`` are: This field is required. + .. include:: vcs/kind.rst + .. pkg-field:: location: VCS location This field is required. -.. pkg-field:: module: token + .. include:: vcs/location.rst - CVS requires a named module, as each CVS server can host multiple - named repositories. +.. pkg-field:: module: token This field is required for the CVS repository type and should not be used otherwise. + CVS requires a named module, as each CVS server can host multiple + named repositories. + .. pkg-field:: branch: VCS branch This field is optional. + .. include:: vcs/branch.rst + .. pkg-field:: tag: VCS tag This field is required for the ``this`` repository kind. @@ -2770,10 +2776,13 @@ The :ref:`VCS fields` of ``source-repository`` are: This might be used to indicate what sources to get if someone needs to fix a bug in an older branch that is no longer an active head branch. + .. include:: vcs/tag.rst + .. pkg-field:: subdir: VCS subdirectory This field is optional but, if given, specifies a single subdirectory. + .. include:: vcs/subdir.rst .. _setup-hooks: diff --git a/doc/cabal-project-description-file.rst b/doc/cabal-project-description-file.rst index f024e540010..929ec642f6f 100644 --- a/doc/cabal-project-description-file.rst +++ b/doc/cabal-project-description-file.rst @@ -1,3 +1,5 @@ +.. _cabal-project-file: + Project Description — cabal.project File ======================================== @@ -269,23 +271,33 @@ The :ref:`VCS fields` of ``source-repository-package`` are: This field is required. + .. include:: vcs/kind.rst + .. cfg-field:: location: VCS location This field is required. + .. include:: vcs/location.rst + .. cfg-field:: branch: VCS branch This field is optional. + .. include:: vcs/branch.rst + .. cfg-field:: tag: VCS tag This field is optional. + .. include:: vcs/tag.rst + .. cfg-field:: subdir: VCS subdirectory list Look in one or more subdirectories of the repository for cabal files, rather than the root. This field is optional. + .. include:: vcs/subdir.rst + .. cfg-field:: post-checkout-command: command Run command in the checked out repository, prior sdisting. @@ -767,6 +779,7 @@ The following settings control the behavior of the dependency solver: explicitly constrained. When set to `none`, the solver will consider all packages. +.. _package-configuration-options: Package configuration options ----------------------------- @@ -1302,6 +1315,8 @@ Foreign function interface options ``--extra-framework-dirs=DIR``, which can be specified multiple times. +.. _profiling-options: + Profiling options ^^^^^^^^^^^^^^^^^ @@ -1328,6 +1343,8 @@ Profiling options The command line variant of this flag is ``--enable-profiling`` and ``--disable-profiling``. +.. _profiling-detail: + .. cfg-field:: profiling-detail: level --profiling-detail=level :synopsis: Profiling detail level. @@ -1367,7 +1384,7 @@ Profiling options late-toplevel Like top-level but costs will be assigned to top level definitions after optimization. This lowers profiling overhead massively while giving similar - levels of detail as toplevle-functions. However it means functions introduced + levels of detail as toplevel-functions. However it means functions introduced by GHC during optimization will show up in profiles as well. Corresponds to ``-fprof-late`` if supported and ``-fprof-auto-top`` otherwise. late diff --git a/doc/how-to-analyze-haskell-code-performance.rst b/doc/how-to-analyze-haskell-code-performance.rst new file mode 100644 index 00000000000..fe117a117bd --- /dev/null +++ b/doc/how-to-analyze-haskell-code-performance.rst @@ -0,0 +1,161 @@ +How to analyze Haskell performance +================================== + +When a Haskell application is slow or uses too much memory, +Cabal and `GHC `__ +can help you understand why. The main steps are: + +1. Configure the project in a way that makes GHC insert performance-measuring code into your application. +2. Run the application with the right + `runtime system (RTS) flags `__ + to produce a performance report. +3. Visualize and analyze that report. + +The process of inserting performance measuring code and collecting performance information +is called "profiling". +This guide describes how to instruct Cabal to pass desired profiling flags to the GHC compiler; +Cabal acts as a convenient build configuration interface while the work is done by GHC. +To get a deeper understanding of the overall profiling process itself in GHC, +it is highly recommended to read in depth the +`Profiling section in GHC's User Guide `__. + +Profiling CPU performance +------------------------- + +First, configure Cabal to build your application, e.g. ``my-app``, with profiling enabled, +with the following command: + +.. code-block:: console + + $ cabal configure --enable-profiling + +This command creates a ``cabal.project.local`` file with the following content: + +.. code-block:: cabal + + profiling: True + +This file stores temporary configuration settings that are passed implicitly to further Cabal commands +like ``cabal build`` and ``cabal run``. +The setting ``profiling: True`` tells GHC to build your application (and its dependencies) with profiling enabled, +and to insert performance measuring code into your application. +Where exactly such code is inserted can be controlled with settings like ``profiling-detail`` +that are presented later. +Further in-depth information on profiling with GHC and its compiler options can be found in the +`GHC profiling guide `__ + +.. note:: + + While a :ref:`cabal.project ` file is intended for long-time settings + that are useful to store in Git, ``cabal.project.local`` is for short-lived, local experiments + (like profiling) that, in general, shouldn't be committed to Git. + +Second, run your application with the right runtime system flags and let it create a profiling report: + +.. code-block:: console + + $ cabal run my-app +RTS -pj -RTS + + +When the application finishes, a profiling JSON report (due to option ``-pj``) +is written to a ``.prof`` file, i.e. ``my-app.prof``, in the current directory. + +.. note:: + + Different report formats can be generated by using different RTS flags. Some useful ones are: + + - ``-p`` for a GHC's own + `standard report `__ + ``.prof``, which can be visualized with `profiteur `__ + or `ghcprofview `__. + - ``-pj`` for a + `JSON report `__ + ``.prof``, which can be visualized with `Speedscope `__. + - ``-l -p`` for a binary + `"eventlog" report `__ + ``.eventlog``, which contains a lot more details and can show you resource usage over time, and can + be converted to JSON with `hs-speedscope `__ + to be visualized with `Speedscope `__. + This will also generate a ``.prof`` file (due to ``-p``), which you can ignore. + We just need the ``-p`` flag for the ``.eventlog`` file to include profiling information. + +Finally, visualize this JSON report ``my-app.prof`` and analyze it for performance bottlenecks. +One popular open-source +`flame graph `__ +visualizer is +`Speedscope `__, +which runs in the browser and can open this JSON file directly. +See the +`Haskell Optimization Handbook `__ +on how to optimize your code based on the profiling results afterwards. + +So far, we’ve only used a single Cabal option to enable profiling in general for your application. +Where and when GHC should insert performance measuring code can be controlled with the ``profiling-detail`` setting +and ``ghc-options``. +Leaving ``profiling-detail`` unspecified as before results in sensible defaults that differ between libraries and executable. +See the docs for :ref:`profiling-detail` to see which options are available. +You can provide ``profiling-detail`` settings and more compiler flags to GHC +(such as ``-fno-prof-count-entries``) via the ``cabal.project.local`` file: + +.. code-block:: cabal + + profiling: True + profiling-detail: late-toplevel + program-options + ghc-options: + + +The setting ``profiling-detail: late-toplevel`` instructs GHC to use so-called +`late-cost-center profiling `__ +and insert measuring code only after important optimisations have been applied to your application code. +This reduces the performance slow-down of profiling itself and gives you more realistic measurements. + +The ``program-options`` section allows you to add more settings like GHC options to the local +packages of your project (See :ref:`Program options`). +The ``ghc-options`` setting allows you to further control which functions and other bindings +the GHC compiler should profile, as well as other aspects of profiling. +You can find more information and further options in the +`GHC "cost-center" guide `__. +and the +`GHC profiling compiler options `__ +section. + +Profiling your dependencies too +------------------------------- + +The profiling setup so far with the ``cabal.project.local`` file only applied to your local packages, +which is usually what you want. +However, bottlenecks may also exist in your dependencies, so you may want to profile those too. + +First, to enable ``late``-cost-center profiling for all packages (including dependencies) concerning your project, +not just the local ones, add the following to your project’s ``cabal.project.local`` file: + +.. code-block:: cabal + + package * + profiling-detail: late-toplevel + +.. note:: + + There are several keywords to specify to which parts of your project some settings should be applied: + + - ``program-options`` to apply to :ref:`all local packages`. + - ``package `` to apply to a :ref:`single package`, be it local or remote. + - ``package *`` to apply to :ref:`all local and remote packages (dependencies)`. + +Second, rerun your application with ``cabal run``, which also automatically rebuilds your application: + +.. code-block:: console + + $ cabal run my-app -- +RTS -pj -RTS + Resolving dependencies... + Build profile: -w ghc-9.10.1 -O1 + In order, the following will be built (use -v for more details): + - base64-bytestring-1.2.1.0 (lib) --enable-profiling (requires build) + - cryptohash-sha256-0.11.102.1 (lib) --enable-profiling (requires build) + ... + + +You can now find profiling data of dependencies in the report ``my-app.prof`` +to analyze. More information on how to configure Cabal options can be found in the +:ref:`Cabal options sections `. diff --git a/doc/how-to-source-packages.rst b/doc/how-to-source-packages.rst index caecf7e90ac..ec26f26f721 100644 --- a/doc/how-to-source-packages.rst +++ b/doc/how-to-source-packages.rst @@ -233,7 +233,7 @@ for the ``tag`` field: .. Warning:: Only a commit hash pins to an exact version of the *source code* for Git - respositories. + repositories. - If the ``tag`` field is omitted then the latest commit on the Git default branch is used. - If the ``tag`` field is a Git branch name then the latest commit on that branch is used. diff --git a/doc/index.rst b/doc/index.rst index 0b5407e8580..c944ed63d09 100644 --- a/doc/index.rst +++ b/doc/index.rst @@ -15,6 +15,7 @@ Welcome to the Cabal User Guide how-to-package-haskell-code how-to-source-packages + how-to-analyze-haskell-code-performance how-to-build-like-nix how-to-run-in-windows how-to-use-backpack diff --git a/doc/setup-commands.rst b/doc/setup-commands.rst index b40b94c95bf..69f9e276cf4 100644 --- a/doc/setup-commands.rst +++ b/doc/setup-commands.rst @@ -713,7 +713,7 @@ Miscellaneous options late-toplevel Like top-level but costs will be assigned to top level definitions after optimization. This lowers profiling overhead massively while giving similar - levels of detail as toplevle-functions. However it means functions introduced + levels of detail as toplevel-functions. However it means functions introduced by GHC during optimization will show up in profiles as well. Corresponds to ``-fprof-late`` if supported and ``-fprof-auto-top`` otherwise. late diff --git a/doc/vcs/branch.rst b/doc/vcs/branch.rst new file mode 100644 index 00000000000..5908367c130 --- /dev/null +++ b/doc/vcs/branch.rst @@ -0,0 +1,8 @@ +.. + VCS branch + +Many source control systems support the notion of a branch, as a distinct +concept from having repositories in separate locations. For example CVS, SVN and +git use branches while darcs uses different locations for different branches. If +you need to specify a branch to identify a your repository then specify it in +this field. diff --git a/doc/vcs/fields.rst b/doc/vcs/fields.rst new file mode 100644 index 00000000000..9ce0d4c840a --- /dev/null +++ b/doc/vcs/fields.rst @@ -0,0 +1,34 @@ +.. + VCS common fields + +Most of the version control system (VCS) fields types are common to both +``source-repository`` and ``source-repository-package`` stanzas. + +.. list-table:: + :header-rows: 1 + :widths: 30 30 40 + + * - Field Name + - source-repository (head|this) + - source-repository-package + * - type + - [x] + - [x] + * - location + - [x] + - [x] + * - branch + - [x] + - [x] + * - tag + - [x] + - [x] + * - subdir + - [x] (0 or 1) + - [x] (0 or 1 for each dependency) + * - module (CVS only) + - [x] + - [_] + * - post-checkout-command + - [_] + - [x] diff --git a/doc/vcs/kind.rst b/doc/vcs/kind.rst new file mode 100644 index 00000000000..e87d55ae49e --- /dev/null +++ b/doc/vcs/kind.rst @@ -0,0 +1,19 @@ +.. + VCS kind + +Cabal supports specifying different information for various common source +control systems. This is the name of the source control system used for a +repository. The currently recognised types are: + +- ``darcs`` +- ``git`` +- ``svn`` +- ``cvs`` +- ``mercurial`` (or alias ``hg``) +- ``bazaar`` (or alias ``bzr``) +- ``arch`` +- ``monotone`` +- ``pijul`` + +The VCS kind will determine what other fields are appropriate to specify for a +particular version control system. diff --git a/doc/vcs/location.rst b/doc/vcs/location.rst new file mode 100644 index 00000000000..df32ffff093 --- /dev/null +++ b/doc/vcs/location.rst @@ -0,0 +1,9 @@ +.. + VCS location + +The location of the repository, usually a URL but the exact form of this field +depends on the repository type. For example: + +- for Darcs: ``http://code.haskell.org/foo/`` +- for Git: ``https://github.com/foo/bar.git`` +- for CVS: ``anoncvs@cvs.foo.org:/cvs`` diff --git a/doc/vcs/subdir.rst b/doc/vcs/subdir.rst new file mode 100644 index 00000000000..33ee731bb86 --- /dev/null +++ b/doc/vcs/subdir.rst @@ -0,0 +1,11 @@ +.. + VCS subdirectory + +A field of this type is always optional because it defaults to empty, which +corresponds to the root directory of the repository and is the same as +specifying ``.`` explicitly. + +Some projects put the sources for multiple packages inside a single VCS +repository. This field lets you specify the relative path from the root of the +repository to the top directory for the package, i.e. the directory containing +the package's ``.cabal`` file. diff --git a/doc/vcs/tag.rst b/doc/vcs/tag.rst new file mode 100644 index 00000000000..4ebdac6781c --- /dev/null +++ b/doc/vcs/tag.rst @@ -0,0 +1,5 @@ +.. + VCS tag + +A tag identifies a particular state of a source repository. The exact form of +the tag depends on the repository type. diff --git a/doc/version-control-fields.rst b/doc/version-control-fields.rst index 739905d4b8a..2298f22ed88 100644 --- a/doc/version-control-fields.rst +++ b/doc/version-control-fields.rst @@ -3,93 +3,31 @@ Version Control System Fields .. _vcs-fields: -Most of the version control system (VCS) fields types are common to both -``source-repository`` and ``source-repository-package`` stanzas. - -.. list-table:: - :header-rows: 1 - :widths: 30 30 40 - - * - Field Name - - source-repository (head|this) - - source-repository-package - * - type - - [x] - - [x] - * - location - - [x] - - [x] - * - branch - - [x] - - [x] - * - tag - - [x] - - [x] - * - subdir - - [x] (0 or 1) - - [x] (0 or 1 for each dependency) - * - module (CVS only) - - [x] - - [_] - * - post-checkout-command - - [_] - - [x] +.. include:: vcs/fields.rst .. _vcs-kind: VCS kind ^^^^^^^^ -Cabal supports specifying different information for various common source -control systems. This is the name of the source control system used for a -repository. The currently recognised types are: - -- ``darcs`` -- ``git`` -- ``svn`` -- ``cvs`` -- ``mercurial`` (or alias ``hg``) -- ``bazaar`` (or alias ``bzr``) -- ``arch`` -- ``monotone`` -- ``pijul`` - -The VCS kind will determine what other fields are appropriate to specify for a -particular version control system. +.. include:: vcs/kind.rst VCS location ^^^^^^^^^^^^ -The location of the repository, usually a URL but the exact form of this field -depends on the repository type. For example: - -- for Darcs: ``http://code.haskell.org/foo/`` -- for Git: ``https://github.com/foo/bar.git`` -- for CVS: ``anoncvs@cvs.foo.org:/cvs`` +.. include:: vcs/location.rst VCS branch ^^^^^^^^^^ -Many source control systems support the notion of a branch, as a distinct -concept from having repositories in separate locations. For example CVS, SVN and -git use branches while darcs uses different locations for different branches. If -you need to specify a branch to identify a your repository then specify it in -this field. +.. include:: vcs/branch.rst VCS tag ^^^^^^^ -A tag identifies a particular state of a source repository. The exact form of -the tag depends on the repository type. +.. include:: vcs/tag.rst VCS subdirectory ^^^^^^^^^^^^^^^^ -A field of this type is always optional because it defaults to empty, which -corresponds to the root directory of the repository and is the same as -specifying ``.`` explicitly. - -Some projects put the sources for multiple packages inside a single VCS -repository. This field lets you specify the relative path from the root of the -repository to the top directory for the package, i.e. the directory containing -the package's ``.cabal`` file. +.. include:: vcs/subdir.rst diff --git a/release-notes/Cabal-3.14.1.0.md b/release-notes/Cabal-3.14.1.0.md new file mode 100644 index 00000000000..d4b32811c5f --- /dev/null +++ b/release-notes/Cabal-3.14.1.0.md @@ -0,0 +1,198 @@ +## Cabal and Cabal-syntax 3.14.0.0 & 3.14.1.0 changelog + +For reasons of discoverability, the changelog of Cabal & Cabal-syntax 3.14.0.0 is also included in this file, since that version had been released for the benefit of GHC 9.12's release process. + +### Significant changes + +- Fix build ways for modules in executables [#10418](https://github.com/haskell/cabal/issues/10418) [#10419](https://github.com/haskell/cabal/pull/10419) + + - Modules belonging to executables were being built in too many ways. For instance, if you + had configured to build profiled library files then your executable modules would also + be built profiled. Which was a regression in behaviour since `Cabal-3.12`. + +- Fix ./setup install command [#10416](https://github.com/haskell/cabal/issues/10416) [#10417](https://github.com/haskell/cabal/pull/10417) + + - `./setup install` was failing with a `fromFlag NoFlag` error. It is now fixed. + +- Neutral field to add files to sdist [#8817](https://github.com/haskell/cabal/issues/8817) [#10107](https://github.com/haskell/cabal/pull/10107) + + Adds the `extra-files` field to the cabal file specification. This is like + the other `extra-*` fields in that it is copied with the `sdist` command, + except there are no other semantics. Compare to: + + * `extra-source-files`: Tracked by `cabal build`. + + * `extra-doc-files`: Copied by Haddock to the html directory. + +### Other changes + +- Add new options from ghc 9.12 [#10468](https://github.com/haskell/cabal/pull/10468) + + - ghc 9.12 adds several new command line options, divided between + `LANGUAGE`s (already added), warnings, new preprocessor control options, + and compilation control options. Two options needed to be added to the + list of options requiring `Int` parameters. + + The new options, excluding warning and language options, are: + + * `-fexpose-overloaded-unfoldings` + * `-fmax-forced-spec-args=N` + * `-fno-expose-overloaded-unfoldings` + * `-fno-object-determinism` + * `-fobject-determinism` + * `-fwrite-if-compression=N` + * `-optCmmP…` + * `-optJSP…` + * `-pgmCmmP` + * `-pgmJSP` + + As they all affect compilation and store hashes, the only necessary + change was to list the two numeric options so they will be parsed + correctly. To the best of our understanding, `-pgm*` and `-opt*` + options are already handled as a group. + +- Include package version when passing `--promised-dependency` flag [#10166](https://github.com/haskell/cabal/issues/10166) [#10248](https://github.com/haskell/cabal/pull/10248) + + The `--promised-dependency` flag now expects an argument in the format + + ``` + NAME-VER[:COMPONENT_NAME]=CID + ``` + + rather than + + ``` + NAME[:COMPONENT_NAME]=CID + ``` + +- Add support for building profiled dynamic way [#4816](https://github.com/haskell/cabal/issues/4816) [#9900](https://github.com/haskell/cabal/pull/9900) + + Add support for profiled dynamic way + + New options for `cabal.project` and `./Setup` interface: + + * `profiling-shared`: Enable building profiling dynamic way + * Passing `--enable-profiling` and `--enable-executable-dynamic` builds + profiled dynamic executables. + + Support for using `profiling-shared` is guarded behind a constraint + which ensures you are using `Cabal >= 3.13`. + + In the cabal file: + + * `ghc-prof-shared-options`, for passing options when building in + profiling dynamic way + +- Working directory support for `Cabal` [#9702](https://github.com/haskell/cabal/issues/9702) [#9718](https://github.com/haskell/cabal/pull/9718) + + The `Cabal` library is now able to handle a passed-in working directory, instead + of always relying on the current working directory of the parent process. + + In order to achieve this, the `SymbolicPath` abstraction was fleshed out, and + all fields of `PackageDescription` that, if relative, should be interpreted + with respect to e.g. the package root, use `SymbolicPath` instead of `FilePath`. + + This means that many library functions in `Cabal` take an extra argument of type + `Maybe (SymbolicPath CWD (Dir "Package"))`, which is an optional (relative or + absolute) path to the package root (if relative, relative to the current working + directory). In addition, many functions that used to manipulate `FilePath`s now + manipulate `SymbolicPath`s, require explicit conversion using e.g. `getSymbolicPath`. + + To illustrate with file searching, the `Cabal` library defines: + + ```haskell + findFileCwd + :: forall dir1 dir2 file + . Verbosity + -> Maybe (SymbolicPath CWD (Dir dir1)) + + -> [SymbolicPath dir1 (Dir dir2)] + + -> RelativePath dir2 File + + -> IO (SymbolicPath dir1 File) + ``` + + See Note [Symbolic paths] in `Distribution.Utils.Path` for further information + on the design of this API. + +- Add `MultilineStrings` extension (GHC proposal #637) [#10245](https://github.com/haskell/cabal/pull/10245) + +- Add `NamedDefaults` extension (GHC proposal #409) [#9740](https://github.com/haskell/cabal/pull/9740) + +- Add `OrPatterns` extension (GHC proposal #958) [#10339](https://github.com/haskell/cabal/pull/10339) + + +### Other changes + +- Add flag `--ignore-build-tools` [#10128](https://github.com/haskell/cabal/pull/10128) + + - Adds flag `--ignore-build-tools` which allows a user to ignore the tool + dependencies declared in `build-tool-depends`. For general use, this flag + should never be needed, but it may be useful for packagers. + +- Do not try to build dynamic executables on Windows [#10217](https://github.com/haskell/cabal/pull/10217) + + - Cabal will now exit with a descriptive error message instead of attempting to + build a dynamic executable on Windows. + +- Always pass `ghc-options` to GHC [#8717](https://github.com/haskell/cabal/pull/8717) + + Previously, options set in the package field `ghc-options` would not be passed + to GHC during the link phase for shared objects (where multiple `.o` or + `.dyn_o` files are merged into a single object file). This made it impossible + to use `ghc-options` to use a different linker by setting (for example) + `ghc-options: -optl-fuse-ld=mold -optlm-fuse-ld=mold`; the options would be + dropped in the link phase, falling back to the default linker. + + It was possible to work around this by duplicating the `ghc-options` to + `ghc-shared-options`, which _are_ passed in the shared link phase, but that had + the undocumented and unfortunate side-effect of disabling the GHC + `-dynamic-too` flag, effectively doubling compilation times when + `ghc-shared-options` are set. + + Now, `ghc-options` are combined with `ghc-shared-options` (to accurately + reflect the documentation on this feature) and the fact that + `ghc-shared-options` disables `-dynamic-too` is documented. + +- Introduce `SetupHooks` [#9551](https://github.com/haskell/cabal/pull/9551) + + Introduction of a new build type: `Hooks`. + This build type, intended to eventually replace the `Custom` build type, integrates + better with the rest of the ecosystem (`cabal-install`, Haskell Language Server). + + The motivation and full design of this new build-type are specified in the + Haskell Foundation Tech Proposal + [Replacing the Cabal Custom build-type](https://github.com/haskellfoundation/tech-proposals/pull/60). + + Package authors willing to use this feature should declare `cabal-version: 3.14` and `build-type: Hooks` + in their `.cabal` file, declare a `custom-setup` stanza with a dependency on the + `Cabal-hooks` package, and define a module `SetupHooks` that exports a value + `setupHooks :: SetupHooks`, using the API exported by `Distribution.Simple.SetupHooks` + from the `Cabal-hooks` package. Refer to the Haddock documentation of + `Distribution.Simple.SetupHooks` for example usage. + +- Redefine `build-type: Configure` in terms of `Hooks` [#9969](https://github.com/haskell/cabal/pull/9969) + + The `build-type: Configure` is now implemented in terms of `build-type: Hooks` + rather than in terms of `build-type: Custom`. This moves the `Configure` + build-type away from the `Custom` issues. Eventually, `build-type: Hooks` will + no longer imply packages are built in legacy-fallback mode. When that + happens, `Configure` will also stop implying `legacy-fallback`. + + The observable aspect of this change is `runConfigureScript` now having a + different type, and `autoconfSetupHooks` being exposed by `Distribution.Simple`. + The former is motivated by internal implementation details, while the latter + provides the `SetupHooks` value for the `Configure` build type, which can be + consumed by other `Hooks` clients (e.g. eventually HLS). + +- Cabal can issue a number of error messages referencing "Setup configure", + but it simply references "configure" which could mean any of three + things (Setup configure, the package's "configure" script, or "cabal + configure"). This has recently caught out even Cabal devs. Clarify these + messages. [#9476](https://github.com/haskell/cabal/pull/9476) + +- Update the SPDX License List to version 3.25 + + The LicenseId and LicenseExceptionId types are updated to reflect the SPDX + License List version 3.25 (2024-08-19). diff --git a/release-notes/cabal-install-3.14.1.0.md b/release-notes/cabal-install-3.14.1.0.md new file mode 100644 index 00000000000..d4ccf28e126 --- /dev/null +++ b/release-notes/cabal-install-3.14.1.0.md @@ -0,0 +1,16 @@ +## cabal-install and cabal-install-solver 3.14.1.0 changelog + +- Fix a bug that causes `cabal init` to crash if `git` is not installed [#8478](https://github.com/haskell/cabal/issues/8478) [#10484](https://github.com/haskell/cabal/issues/10484) [#10486](https://github.com/haskell/cabal/pull/10486) + + - `cabal init` tries to use `git config` to guess the user's name and email. + It no longer crashes if there is no executable named `git` on $PATH. + +- Print out which project file we are using with the default verbosity [#8519](https://github.com/haskell/cabal/issues/8519) [#10507](https://github.com/haskell/cabal/pull/10507) + + - Many people have been burnt by cabal catching stray project files located up + the directory tree. This change tries to protect them at the expense of + producing more output by default. In particular, before this change, you could + see which project file is in use by supplying `-v` (the verbose mode), and + after the change we print this information with the default verbosity. + Changing the behaviour of cabal is out of scope of this change, and will + hopefully be done in the future versions (see #9353 for a way forward).