diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index 6957a691264a8503148ebccd97b797b7a2ad5739..4d3ab6cdfaccc5fbb1fdf4d0c74381918a1c210b 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -595,9 +595,10 @@ test-suite unit-tests Test.Laws Test.QuickCheck.Utils UnitTests.Distribution.Compat.CreatePipe - UnitTests.Distribution.Compat.Time UnitTests.Distribution.Compat.Graph + UnitTests.Distribution.Compat.Time UnitTests.Distribution.Simple.Glob + UnitTests.Distribution.Simple.Program.GHC UnitTests.Distribution.Simple.Program.Internal UnitTests.Distribution.Simple.Utils UnitTests.Distribution.SPDX @@ -625,6 +626,7 @@ test-suite unit-tests temporary, text, pretty, + Diff >=0.4 && <0.5, QuickCheck >= 2.13.2 && < 2.14, Cabal ghc-options: -Wall diff --git a/Cabal/ChangeLog.md b/Cabal/ChangeLog.md index 88dfab78b263c27628b6162059aa53470f549bc1..04c23ef7a35808a5bc729e79830ca8c875ef7073 100644 --- a/Cabal/ChangeLog.md +++ b/Cabal/ChangeLog.md @@ -224,7 +224,7 @@ types (#4701). * Support for building with Win32 version 2.6 (#4835). * Change `compilerExtensions` and `ghcOptExtensionMap` to contain - `Maybe Flag`s, since a supported extention can lack a flag (#4443). + `Maybe Flag`s, since a supported extension can lack a flag (#4443). * Pretty-printing of `.cabal` files is slightly different due to parser changes. For an example, see https://mail.haskell.org/pipermail/cabal-devel/2017-December/010414.html. @@ -470,7 +470,7 @@ * Support GHC 7.10. * Experimental support for emitting DWARF debug info. * Preliminary support for relocatable packages. - * Allow cabal to be used inside cabal exec enviroments. + * Allow cabal to be used inside cabal exec environments. * hpc: support multiple "ways" (e.g. profiling and vanilla). * Support GHCJS. * Improved command line documentation. @@ -806,7 +806,7 @@ * It is no longer necessary to run `configure` before `clean` or `sdist` * Added support for ghc's `-split-objs` * Initial support for JHC - * Ignore extension fields in `.cabal` files (fields begining with "`x-`") + * Ignore extension fields in `.cabal` files (fields beginning with "`x-`") * Some changes to command hooks API to improve consistency * Hugs support improvements * Added GeneralisedNewtypeDeriving language extension diff --git a/Cabal/Distribution/Compat/Lens.hs b/Cabal/Distribution/Compat/Lens.hs index e353d9f258cb830367dfca0e63e553333a875847..f9d9605c002348be6a2a0b817760d88993206708 100644 --- a/Cabal/Distribution/Compat/Lens.hs +++ b/Cabal/Distribution/Compat/Lens.hs @@ -72,7 +72,7 @@ type Traversal' s a = Traversal s s a a type Getting r s a = LensLike (Const r) s s a a -type AGetter s a = LensLike (Const a) s s a a -- this doens't exist in 'lens' +type AGetter s a = LensLike (Const a) s s a a -- this doesn't exist in 'lens' type ASetter s t a b = LensLike Identity s t a b type ALens s t a b = LensLike (Pretext a b) s t a b diff --git a/Cabal/Distribution/FieldGrammar/Parsec.hs b/Cabal/Distribution/FieldGrammar/Parsec.hs index 7b712e33448af6dbe9ec2567c05e1b1d58c594d7..c6b5b32914532512d862a3e7a9cbc6d2d9e2cfc1 100644 --- a/Cabal/Distribution/FieldGrammar/Parsec.hs +++ b/Cabal/Distribution/FieldGrammar/Parsec.hs @@ -47,7 +47,7 @@ -- is obviously invalid specification. -- -- We can parse 'Fields' like we parse @aeson@ objects, yet we use --- slighly higher-level API, so we can process unspecified fields, +-- slightly higher-level API, so we can process unspecified fields, -- to report unknown fields and save custom @x-fields@. -- module Distribution.FieldGrammar.Parsec ( diff --git a/Cabal/Distribution/Fields/Field.hs b/Cabal/Distribution/Fields/Field.hs index 5e49d176757e07b5a19e66734a329303fc092a7d..c2b97ff7120dc062f37f88ffe7ea62a4158adcee 100644 --- a/Cabal/Distribution/Fields/Field.hs +++ b/Cabal/Distribution/Fields/Field.hs @@ -47,7 +47,7 @@ fieldName (Section n _ _) = n fieldAnn :: Field ann -> ann fieldAnn = nameAnn . fieldName --- | All transitive descendands of 'Field', including itself. +-- | All transitive descendants of 'Field', including itself. -- -- /Note:/ the resulting list is never empty. -- diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index 0d6659ece19e1f7fc501a58351b122d428ef6a79..6be2157fd781087424aba23e00958e12f8d3a968 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -1116,7 +1116,7 @@ gbuildModDefFiles (GReplFLib _ flib) = foreignLibModDefFile flib -- In case of 'Nothing', 'Distribution.ModuleName.main' can be assumed. exeMainModuleName :: Executable -> Maybe ModuleName exeMainModuleName Executable{buildInfo = bnfo} = - -- GHC honors the last occurence of a module name updated via -main-is + -- GHC honors the last occurrence of a module name updated via -main-is -- -- Moreover, -main-is when parsed left-to-right can update either -- the "Main" module name, or the "main" function name, or both, @@ -1528,7 +1528,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do } ForeignLibNativeStatic -> -- this should be caught by buildFLib - -- (and if we do implement tihs, we probably don't even want to call + -- (and if we do implement this, we probably don't even want to call -- ghc here, but rather Ar.createArLibArchive or something) cabalBug "static libraries not yet implemented" ForeignLibTypeUnknown -> diff --git a/Cabal/Distribution/Simple/GHCJS.hs b/Cabal/Distribution/Simple/GHCJS.hs index 46896c3a0320e1c3fab4312b6c2417b8e7642777..1eb798bc901ad41e507606d681e024ba1b309f23 100644 --- a/Cabal/Distribution/Simple/GHCJS.hs +++ b/Cabal/Distribution/Simple/GHCJS.hs @@ -903,7 +903,7 @@ gbuildModDefFiles (GReplFLib _ flib) = foreignLibModDefFile flib -- In case of 'Nothing', 'Distribution.ModuleName.main' can be assumed. exeMainModuleName :: Executable -> Maybe ModuleName exeMainModuleName Executable{buildInfo = bnfo} = - -- GHC honors the last occurence of a module name updated via -main-is + -- GHC honors the last occurrence of a module name updated via -main-is -- -- Moreover, -main-is when parsed left-to-right can update either -- the "Main" module name, or the "main" function name, or both, @@ -1308,7 +1308,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do } ForeignLibNativeStatic -> -- this should be caught by buildFLib - -- (and if we do implement tihs, we probably don't even want to call + -- (and if we do implement this, we probably don't even want to call -- ghc here, but rather Ar.createArLibArchive or something) cabalBug "static libraries not yet implemented" ForeignLibTypeUnknown -> diff --git a/Cabal/Distribution/Simple/Program/GHC.hs b/Cabal/Distribution/Simple/Program/GHC.hs index bc7868828549041d596da6e8601c10dedf9b1d7e..dff628de62cfd384081058d1f322abbda0cac315 100644 --- a/Cabal/Distribution/Simple/Program/GHC.hs +++ b/Cabal/Distribution/Simple/Program/GHC.hs @@ -56,7 +56,7 @@ normaliseGhcArgs (Just ghcVersion) PackageDescription{..} ghcArgs supportedGHCVersions :: VersionRange supportedGHCVersions = intersectVersionRanges (orLaterVersion (mkVersion [8,0])) - (earlierVersion (mkVersion [8,7])) + (earlierVersion (mkVersion [8,9])) from :: Monoid m => [Int] -> m -> m from version flags @@ -219,6 +219,7 @@ normaliseGhcArgs (Just ghcVersion) PackageDescription{..} ghcArgs , from [8,4] [ "-ddebug-output" ] , from [8,4] $ to [8,6] [ "-fno-max-valid-substitutions" ] , from [8,6] [ "-dhex-word-literals" ] + , from [8,8] [ "-fshow-docs-of-hole-fits", "-fno-show-docs-of-hole-fits" ] ] isOptIntFlag :: String -> Any diff --git a/Cabal/Distribution/Types/BuildInfo.hs b/Cabal/Distribution/Types/BuildInfo.hs index 06b69bf4db4e1a16f06ca48cf39a96d8ae9b4bea..cb68f436882784e10c3ce0f9d1ef4bf35f8b41fc 100644 --- a/Cabal/Distribution/Types/BuildInfo.hs +++ b/Cabal/Distribution/Types/BuildInfo.hs @@ -83,7 +83,7 @@ data BuildInfo = BuildInfo { -- and copied and registered together with this library. The -- logic on how this library is built will have to be encoded in a -- custom Setup for now. Oherwise cabal would need to lear how to - -- call arbitary library builders. + -- call arbitrary library builders. extraLibFlavours :: [String], -- ^ Hidden Flag. This set of strings, will be appended to all libraries when -- copying. E.g. [libHS<name>_<flavour> | flavour <- extraLibFlavours]. This -- should only be needed in very specific cases, e.g. the `rts` package, where diff --git a/Cabal/Distribution/Types/LocalBuildInfo.hs b/Cabal/Distribution/Types/LocalBuildInfo.hs index 31ad96ef89adc86695bb7879117bdd8e2c0cf420..c11649e59707deff3c6d9a8fc86653215afe741f 100644 --- a/Cabal/Distribution/Types/LocalBuildInfo.hs +++ b/Cabal/Distribution/Types/LocalBuildInfo.hs @@ -129,7 +129,7 @@ data LocalBuildInfo = LocalBuildInfo { -- In principle, this is supposed to contain the -- resolved package description, that does not contain -- any conditionals. However, it MAY NOT contain - -- the description wtih a 'HookedBuildInfo' applied + -- the description with a 'HookedBuildInfo' applied -- to it; see 'HookedBuildInfo' for the whole sordid saga. -- As much as possible, Cabal library should avoid using -- this parameter. diff --git a/Cabal/Distribution/Types/PkgconfigVersionRange.hs b/Cabal/Distribution/Types/PkgconfigVersionRange.hs index 6b1bc94939d1d4ec93532c3817ab9177d95ed5cb..60e88e49d783b5cd86dc7a8cf938f7a618acb6d2 100644 --- a/Cabal/Distribution/Types/PkgconfigVersionRange.hs +++ b/Cabal/Distribution/Types/PkgconfigVersionRange.hs @@ -61,7 +61,7 @@ instance Parsec PkgconfigVersionRange where -- note: the wildcard is used in some places, e.g -- http://hackage.haskell.org/package/bindings-libzip-0.10.1/bindings-libzip.cabal -- - -- however, in the presense of alphanumerics etc. lax version parser, + -- however, in the presence of alphanumerics etc. lax version parser, -- wildcard is ill-specified parsec = do diff --git a/Cabal/Distribution/Utils/NubList.hs b/Cabal/Distribution/Utils/NubList.hs index ab23a2a54cb859aab59e632679f69a7f2d2a8866..c6ad2d95b391619e20a97619d83e922ab74b3cc3 100644 --- a/Cabal/Distribution/Utils/NubList.hs +++ b/Cabal/Distribution/Utils/NubList.hs @@ -25,7 +25,7 @@ newtype NubList a = deriving (Eq, Generic, Typeable) -- NubList assumes that nub retains the list order while removing duplicate --- elements (keeping the first occurence). Documentation for "Data.List.nub" +-- elements (keeping the first occurrence). Documentation for "Data.List.nub" -- does not specifically state that ordering is maintained so we will add a test -- for that to the test suite. diff --git a/Cabal/Language/Haskell/Extension.hs b/Cabal/Language/Haskell/Extension.hs index b279abafe1d99c69fd66ec08d865bb00fc628b78..bbbdc41e68f716150714da2ec27bca8545e6cd70 100644 --- a/Cabal/Language/Haskell/Extension.hs +++ b/Cabal/Language/Haskell/Extension.hs @@ -777,7 +777,7 @@ data KnownExtension = -- to the type-level. | TypeInType - -- | Allow recursive (and therefore undecideable) super-class relationships. + -- | Allow recursive (and therefore undecidable) super-class relationships. | UndecidableSuperClasses -- | A temporary extension to help library authors check if their diff --git a/Cabal/doc/developing-packages.rst b/Cabal/doc/developing-packages.rst index d29722266e803ea64396d31a14c848a25a95eb88..6575c45c9caea2cae57c6958b7fc57147d3ba403 100644 --- a/Cabal/doc/developing-packages.rst +++ b/Cabal/doc/developing-packages.rst @@ -1340,7 +1340,7 @@ look something like this: build-depends: foo-internal, base Internal libraries are also useful for packages that define multiple -executables, but do not define a publically accessible library. Internal +executables, but do not define a publicly accessible library. Internal libraries are only visible internally in the package (so they can only be added to the :pkg-field:`build-depends` of same-package libraries, executables, test suites, etc.) Internal libraries locally shadow any @@ -2013,7 +2013,7 @@ system-dependent values for these fields. **Library Names** External libraries are identified by the package's name they're - provided by (currently a package can only publically expose its + provided by (currently a package can only publicly expose its main library compeonent; in future, packages with multiple exposed public library components will be supported and a syntax for referring to public sub-libraries will be provided). diff --git a/Cabal/doc/nix-local-build.rst b/Cabal/doc/nix-local-build.rst index a4733b28830c3ff7bebf60a70e630cd6221faac5..1b0ecc7afe40d78f1c75e916112d6cb391e823a9 100644 --- a/Cabal/doc/nix-local-build.rst +++ b/Cabal/doc/nix-local-build.rst @@ -961,7 +961,7 @@ The following settings control the behavior of the dependency solver: .. cfg-field:: allow-newer: none, all or list of scoped package names (space or comma separated) --allow-newer, --allow-newer=[none,all,[scope:][^]pkg] - :synopsis: Lift dependencies upper bound constaints. + :synopsis: Lift dependencies upper bound constraints. :default: ``none`` @@ -1054,7 +1054,7 @@ The following settings control the behavior of the dependency solver: .. cfg-field:: allow-older: none, all, list of scoped package names (space or comma separated) --allow-older, --allow-older=[none,all,[scope:][^]pkg] - :synopsis: Lift dependency lower bound constaints. + :synopsis: Lift dependency lower bound constraints. :since: 2.0 :default: ``none`` diff --git a/Cabal/tests/UnitTests.hs b/Cabal/tests/UnitTests.hs index 6615ade2396ca63c933d824201bf1a5cdb3960a5..b892e2739b1f500745f7778617601a60d5d8458d 100644 --- a/Cabal/tests/UnitTests.hs +++ b/Cabal/tests/UnitTests.hs @@ -17,6 +17,7 @@ import qualified UnitTests.Distribution.Compat.CreatePipe import qualified UnitTests.Distribution.Compat.Time import qualified UnitTests.Distribution.Compat.Graph import qualified UnitTests.Distribution.Simple.Glob +import qualified UnitTests.Distribution.Simple.Program.GHC import qualified UnitTests.Distribution.Simple.Program.Internal import qualified UnitTests.Distribution.Simple.Utils import qualified UnitTests.Distribution.System @@ -45,6 +46,7 @@ tests mtimeChangeCalibrated = UnitTests.Distribution.Compat.Graph.tests , testGroup "Distribution.Simple.Glob" UnitTests.Distribution.Simple.Glob.tests + , UnitTests.Distribution.Simple.Program.GHC.tests , testGroup "Distribution.Simple.Program.Internal" UnitTests.Distribution.Simple.Program.Internal.tests , testGroup "Distribution.Simple.Utils" $ diff --git a/Cabal/tests/UnitTests/Distribution/Simple/Program/GHC.hs b/Cabal/tests/UnitTests/Distribution/Simple/Program/GHC.hs new file mode 100644 index 0000000000000000000000000000000000000000..f24045203acb7ccd7960a19c9bd388caf1cca19a --- /dev/null +++ b/Cabal/tests/UnitTests/Distribution/Simple/Program/GHC.hs @@ -0,0 +1,93 @@ +module UnitTests.Distribution.Simple.Program.GHC (tests) where + +import Test.Tasty (TestTree, testGroup) +import Test.Tasty.HUnit +import Data.Algorithm.Diff (PolyDiff (..), getDiff) + +import Distribution.Simple.Program.GHC (normaliseGhcArgs) +import Distribution.PackageDescription (emptyPackageDescription) +import Distribution.Version (mkVersion) + +tests :: TestTree +tests = testGroup "Distribution.Simple.Program.GHC" + [ testGroup "normaliseGhcArgs" + [ testCase "options added in GHC-8.8" $ do + let flags :: [String] + flags = normaliseGhcArgs + (Just $ mkVersion [8,8,1]) + emptyPackageDescription + options_8_8_all + + assertListEquals flags options_8_8_affects + ] + ] + +assertListEquals :: (Eq a, Show a) => [a] -> [a] -> Assertion +assertListEquals xs ys + | xs == ys = return () + | otherwise = assertFailure $ unlines $ + "Lists are not equal" : + [ case d of + First x -> "- " ++ show x + Second y -> "+ " ++ show y + Both x _ -> " " ++ show x + | d <- getDiff xs ys + ] + +------------------------------------------------------------------------------- +-- Options +------------------------------------------------------------------------------- + +-- | Options added in GHC-8.8, to generate: +-- +-- @ +-- ghc-8.6.5 --show-options | sort > 8.6.5.txt +-- ghc-8.8.1 --show-options | sort > 8.8.1.txt +-- diff -u 8.6.5 8.8.1 +-- @ +-- +-- - remove -W(no-)error=, -W(no-)warn flags. +-- - split into all and flags which may affect artifacts +options_8_8_all :: [String] +options_8_8_all = + [ "-ddump-cfg-weights" + , "-dno-suppress-stg-exts" + , "-dsuppress-stg-exts" + , "-Wmissed-extra-shared-lib" + , "-Wmissing-deriving-strategies" + , "-Wmissing-space-after-bang" + , "-Wno-missed-extra-shared-lib" + , "-Wno-missing-deriving-strategies" + , "-Wno-missing-space-after-bang" + , "-fno-show-docs-of-hole-fits" + , "-fshow-docs-of-hole-fits" + ] ++ options_8_8_affects + +options_8_8_affects :: [String] +options_8_8_affects = + [ "-fblock-layout-cfg" + , "-fblock-layout-weightless" + , "-fblock-layout-weights" + , "-fclear-plugins" + , "-fkeep-cafs" + , "-fno-block-layout-cfg" + , "-fno-block-layout-weightless" + , "-fno-keep-cafs" + , "-fno-safe-haskell" + , "-fno-stg-lift-lams" + , "-fno-stg-lift-lams-known" + , "-fno-validate-ide-info" + , "-fno-write-ide-info" + , "-fstg-lift-lams" + , "-fstg-lift-lams-known" + , "-fstg-lift-lams-non-rec-args" + , "-fstg-lift-lams-non-rec-args-any" + , "-fstg-lift-lams-rec-args" + , "-fstg-lift-lams-rec-args-any" + , "-fvalidate-ide-info" + , "-fwrite-ide-info" + , "-hiedir" + , "-hiesuf" + , "-keep-hscpp-file" + , "-keep-hscpp-files" + ] diff --git a/cabal-install/Distribution/Client/FetchUtils.hs b/cabal-install/Distribution/Client/FetchUtils.hs index ae2e2717966214ead720529870dbadaaeada29e6..992eb0f3fc7443a2f47410a1a1ea13bcf7fade39 100644 --- a/cabal-install/Distribution/Client/FetchUtils.hs +++ b/cabal-install/Distribution/Client/FetchUtils.hs @@ -162,7 +162,7 @@ fetchPackage verbosity repoCtxt loc = case loc of -- | Fetch a repo package if we don't have it already. -- fetchRepoTarball :: Verbosity -> RepoContext -> Repo -> PackageId -> IO FilePath -fetchRepoTarball verbosity repoCtxt repo pkgid = do +fetchRepoTarball verbosity' repoCtxt repo pkgid = do fetched <- doesFileExist (packageFile repo pkgid) if fetched then do info verbosity $ display pkgid ++ " has already been downloaded." @@ -171,9 +171,10 @@ fetchRepoTarball verbosity repoCtxt repo pkgid = do res <- downloadRepoPackage progressMessage verbosity ProgressDownloaded (display pkgid) return res - - where + -- whether we download or not is non-deterministic + verbosity = verboseUnmarkOutput verbosity' + downloadRepoPackage = case repo of RepoLocal{..} -> return (packageFile repo pkgid) diff --git a/cabal-install/Distribution/Client/ProjectBuilding.hs b/cabal-install/Distribution/Client/ProjectBuilding.hs index cce62595bd65a58ba036a2f271fba45cfcdf10e3..b2232bdc33d77bf95c5d3d28479dc5642e4433fa 100644 --- a/cabal-install/Distribution/Client/ProjectBuilding.hs +++ b/cabal-install/Distribution/Client/ProjectBuilding.hs @@ -272,7 +272,7 @@ rebuildTargetsDryRun distDirLayout@DistDirLayout{..} shared = -- -- The packages are visited in dependency order, starting with packages with no -- dependencies. The result for each package is accumulated into a 'Map' and --- returned as the final result. In addition, when visting a package, the +-- returned as the final result. In addition, when visiting a package, the -- visiting function is passed the results for all the immediate package -- dependencies. This can be used to propagate information from dependencies. -- @@ -983,6 +983,12 @@ buildAndInstallUnpackedPackage verbosity let prefix = normalise $ dropDrive (InstallDirs.prefix (elabInstallDirs pkg)) entryDir = tmpDirNormalised </> prefix + + -- if there weren't anything to build, it might be that directory is not created + -- the @setup Cabal.copyCommand@ above might do nothing. + -- https://github.com/haskell/cabal/issues/4130 + createDirectoryIfMissingVerbose verbosity True entryDir + LBS.writeFile (entryDir </> "cabal-hash.txt") (renderPackageHashInputs (packageHashInputs pkgshared pkg)) diff --git a/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs index 77f3a3f2896c1cd0a07d16069ca11d52faff4cc0..ea30084c338d07666337f177fca8e59793b04324 100644 --- a/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs @@ -1393,7 +1393,7 @@ remoteRepoSectionDescr = -- -- | Parser combinator for simple fields which uses the field type's --- 'Monoid' instance for combining multiple occurences of the field. +-- 'Monoid' instance for combining multiple occurrences of the field. monoidField :: Monoid a => String -> (a -> Doc) -> ReadP a a -> (b -> a) -> (a -> b -> b) -> FieldDescr b monoidField name showF readF get' set = diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs index a0a6b1835476aa1bc10feb2d73704fa9d32564fc..6ee19d4a9da56fa1b7e4b0ca7b6579f523134efe 100644 --- a/cabal-install/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/Distribution/Client/ProjectPlanning.hs @@ -1077,6 +1077,7 @@ planPackages verbosity comp platform solver SolverSettings{..} -- respective major Cabal version bundled with the respective GHC -- release). -- + -- GHC 8.8 needs Cabal >= 3.0 -- GHC 8.6 needs Cabal >= 2.4 -- GHC 8.4 needs Cabal >= 2.2 -- GHC 8.2 needs Cabal >= 2.0 @@ -1089,11 +1090,8 @@ planPackages verbosity comp platform solver SolverSettings{..} -- TODO: long-term, this compatibility matrix should be -- stored as a field inside 'Distribution.Compiler.Compiler' setupMinCabalVersionConstraint - | isGHC, compVer >= mkVersion [8,6,1] = mkVersion [2,4] - -- GHC 8.6alpha2 (GHC 8.6.0.20180714) still shipped with a - -- devel snapshot of Cabal-2.3.0.0; the rule below can be - -- dropped at some point - | isGHC, compVer >= mkVersion [8,6] = mkVersion [2,3] + | isGHC, compVer >= mkVersion [8,8] = mkVersion [3,0] + | isGHC, compVer >= mkVersion [8,6] = mkVersion [2,4] | isGHC, compVer >= mkVersion [8,4] = mkVersion [2,2] | isGHC, compVer >= mkVersion [8,2] = mkVersion [2,0] | isGHC, compVer >= mkVersion [8,0] = mkVersion [1,24] diff --git a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs index 377e935869918e77ead9220aea0c0a5ef97cfe59..c9565c80dba2462c0b5bc6b7b67d961f5a5a7c82 100644 --- a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs +++ b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs @@ -341,7 +341,7 @@ filterIPNs ipns d@(Dependency pn _ _) -- | Convert condition trees to flagged dependencies. Mutually -- recursive with 'convBranch'. See 'convBranch' for an explanation --- of all arguments preceeding the input 'CondTree'. +-- of all arguments preceding the input 'CondTree'. convCondTree :: Map FlagName Bool -> DependencyReason PN -> PackageDescription -> OS -> Arch -> CompilerInfo -> PN -> FlagInfo -> Component -> (a -> BuildInfo) -> diff --git a/cabal-install/changelog b/cabal-install/changelog index 407dfd3bee22f0f4298ec2e7e3229a6ee733c3f2..be79e309227c8e7acc015f8184c04be0b8d4beae 100644 --- a/cabal-install/changelog +++ b/cabal-install/changelog @@ -504,7 +504,7 @@ 0.6.2 Duncan Coutts <duncan@haskell.org> Feb 2009 * The upgrade command has been disabled in this release * The configure and install commands now have consistent behaviour - * Reduce the tendancy to re-install already existing packages + * Reduce the tendency to re-install already existing packages * The --constraint= flag now works for the install command * New --preference= flag for soft constraints / version preferences * Improved bootstrap.sh script, smarter and better error checking diff --git a/cabal-install/tests/IntegrationTests2.hs b/cabal-install/tests/IntegrationTests2.hs index 836920408f1d74c3b33bb4ebc973e5f3500a85da..cd9e22b8a5c272e4129076faebde2b7780707f0f 100644 --- a/cabal-install/tests/IntegrationTests2.hs +++ b/cabal-install/tests/IntegrationTests2.hs @@ -1410,7 +1410,7 @@ testBuildKeepGoing config = do expectBuildFailed failure1 _ <- expectPackageConfigured plan1 res1 "q-0.1" - -- With keep-going then we should go on to sucessfully build Q + -- With keep-going then we should go on to successfully build Q (plan2, res2) <- executePlan =<< planProject testdir (config `mappend` keepGoing True) (_, failure2) <- expectPackageFailed plan2 res2 "p-0.1" diff --git a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs index d6c1a1db2aec8c743b7acb81f280fd9b373c70d9..3e725c16acfa9ac8c99be9c7534972c1e2ef1173 100644 --- a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs +++ b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs @@ -478,7 +478,7 @@ db1 = ] -- In this example, we _can_ install C and D as independent goals, but we have --- to pick two diferent versions for B (arbitrarily) +-- to pick two different versions for B (arbitrarily) db2 :: ExampleDb db2 = [ Right $ exAv "A" 1 [] @@ -874,7 +874,7 @@ db14 = [ -- has a setup dependency on D, and D has a regular dependency on C-*. However, -- version C-1.0 is already available (perhaps it didn't have this setup dep). -- Thus, we should be able to break this cycle even if we are installing package --- E, which explictly depends on C-2.0. +-- E, which explicitly depends on C-2.0. db15 :: ExampleDb db15 = [ -- First example (real cycle, no solution) @@ -1211,7 +1211,7 @@ testIndepGoals4 name = -- | Test the trace messages that we get when a package refers to an unknown pkg -- -- TODO: Currently we don't actually test the trace messages, and this particular --- test still suceeds. The trace can only be verified by hand. +-- test still succeeds. The trace can only be verified by hand. db21 :: ExampleDb db21 = [ Right $ exAv "A" 1 [ExAny "B"] diff --git a/cabal-testsuite/PackageTests/AutogenModules/SrcDist/setup.test.hs b/cabal-testsuite/PackageTests/AutogenModules/SrcDist/setup.test.hs index c5fbcf26bf8b1aeb8ab4b1b8b6bcbe6e3badfdcf..16c5e75f38912c4c4846cb62ff62c6ee50e4840d 100644 --- a/cabal-testsuite/PackageTests/AutogenModules/SrcDist/setup.test.hs +++ b/cabal-testsuite/PackageTests/AutogenModules/SrcDist/setup.test.hs @@ -13,7 +13,7 @@ main = setupAndCabalTest $ do -- Calling sdist without running configure first makes test fail with: -- "Exception: Run the 'configure' command first." - -- This is becuase we are calling getPersistBuildConfig + -- This is because we are calling getPersistBuildConfig configureResult <- setup' "configure" [] sdistResult <- setup' "sdist" [] diff --git a/cabal-testsuite/PackageTests/Regression/T5309/memoized-tcm/costMatrixWrapper.h b/cabal-testsuite/PackageTests/Regression/T5309/memoized-tcm/costMatrixWrapper.h index f592347dd6e3a8f300a58b73f722eb4bd4503513..e158143e6ff1ab9b62f27782a163e08aa2ce42d0 100644 --- a/cabal-testsuite/PackageTests/Regression/T5309/memoized-tcm/costMatrixWrapper.h +++ b/cabal-testsuite/PackageTests/Regression/T5309/memoized-tcm/costMatrixWrapper.h @@ -5,7 +5,7 @@ #include "dynamicCharacterOperations.h" -/** Initialize a matrix (fill in all values for non-ambiguous chracter transition costs) using a TCM sent in from an outside source. */ +/** Initialize a matrix (fill in all values for non-ambiguous character transition costs) using a TCM sent in from an outside source. */ costMatrix_p matrixInit(size_t alphSize, int *tcm); /** C wrapper for cpp destructor */