diff --git a/Cabal-syntax/Cabal-syntax.cabal b/Cabal-syntax/Cabal-syntax.cabal index ab9170e1811..a915c48db94 100644 --- a/Cabal-syntax/Cabal-syntax.cabal +++ b/Cabal-syntax/Cabal-syntax.cabal @@ -58,6 +58,8 @@ library if impl(ghc >= 8.0) && impl(ghc < 8.8) ghc-options: -Wnoncanonical-monadfail-instances + build-tool-depends: alex:alex + exposed-modules: Distribution.Backpack Distribution.CabalSpecVersion diff --git a/templates/Lexer.x b/Cabal-syntax/src/Distribution/Fields/Lexer.x similarity index 95% rename from templates/Lexer.x rename to Cabal-syntax/src/Distribution/Fields/Lexer.x index da6a029f97e..4fc501d5186 100644 --- a/templates/Lexer.x +++ b/Cabal-syntax/src/Distribution/Fields/Lexer.x @@ -19,18 +19,6 @@ module Distribution.Fields.Lexer ,bol_section, in_section, in_field_layout, in_field_braces ,mkLexState) where --- [Note: bootstrapping parsec parser] --- --- We manually produce the `Lexer.hs` file from `boot/Lexer.x` (make lexer) --- because bootstrapping cabal-install would be otherwise tricky. --- Alex is (atm) tricky package to build, cabal-install has some magic --- to move bundled generated files in place, so rather we don't depend --- on it before we can build it ourselves. --- Therefore there is one thing less to worry in bootstrap.sh, which is a win. --- --- See also https://github.com/haskell/cabal/issues/4633 --- - import Prelude () import qualified Prelude as Prelude import Distribution.Compat.Prelude @@ -53,6 +41,8 @@ import qualified Data.Text.Encoding.Error as T } -- Various character classes +%encoding "latin1" + $space = \ -- single space char $ctlchar = [\x0-\x1f \x7f] $printable = \x0-\xff # $ctlchar -- so no \n \r diff --git a/Cabal/src/Distribution/PackageDescription/Check.hs b/Cabal/src/Distribution/PackageDescription/Check.hs index 4c2701d95c3..2c9806a1ae5 100644 --- a/Cabal/src/Distribution/PackageDescription/Check.hs +++ b/Cabal/src/Distribution/PackageDescription/Check.hs @@ -309,7 +309,7 @@ ppExplanation SignaturesCabal2 = "To use the 'signatures' field the package needs to specify " ++ "at least 'cabal-version: 2.0'." ppExplanation AutogenNotExposed = - "An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'." + "An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'." ppExplanation AutogenIncludesNotIncluded = "An include in 'autogen-includes' is neither in 'includes' or " ++ "'install-includes'." diff --git a/Cabal/src/Distribution/Simple.hs b/Cabal/src/Distribution/Simple.hs index 10b1c9fb50e..d6f50d0af90 100644 --- a/Cabal/src/Distribution/Simple.hs +++ b/Cabal/src/Distribution/Simple.hs @@ -92,6 +92,7 @@ import Distribution.Pretty import Distribution.Simple.Bench import Distribution.Simple.BuildPaths import Distribution.Simple.ConfigureScript +import Distribution.Simple.Errors import Distribution.Simple.Haddock import Distribution.Simple.Install import Distribution.Simple.LocalBuildInfo @@ -601,16 +602,10 @@ sanityCheckHookedBuildInfo verbosity (PackageDescription{library = Nothing}) (Just _, _) = - die' verbosity $ - "The buildinfo contains info for a library, " - ++ "but the package does not have a library." + dieWithException verbosity $ NoLibraryForPackage sanityCheckHookedBuildInfo verbosity pkg_descr (_, hookExes) | exe1 : _ <- nonExistant = - die' verbosity $ - "The buildinfo contains info for an executable called '" - ++ prettyShow exe1 - ++ "' but the package does not have a " - ++ "executable with that name." + dieWithException verbosity $ SanityCheckHookedBuildInfo exe1 where pkgExeNames = nub (map exeName (executables pkg_descr)) hookExeNames = nub (map fst hookExes) @@ -777,7 +772,7 @@ autoconfUserHooks = verbosity flags lbi - else die' verbosity "configure script not found." + else dieWithException verbosity ConfigureScriptNotFound pbi <- getHookedBuildInfo verbosity (buildDir lbi) sanityCheckHookedBuildInfo verbosity pkg_descr pbi diff --git a/Cabal/src/Distribution/Simple/Build.hs b/Cabal/src/Distribution/Simple/Build.hs index 6d9aa5b3486..893ca24e187 100644 --- a/Cabal/src/Distribution/Simple/Build.hs +++ b/Cabal/src/Distribution/Simple/Build.hs @@ -181,9 +181,7 @@ checkSemaphoreSupport :: Verbosity -> Compiler -> BuildFlags -> IO () checkSemaphoreSupport verbosity comp flags = do unless (jsemSupported comp || (isNothing (flagToMaybe (buildUseSemaphore flags)))) $ - die' verbosity $ - "Your compiler does not support the -jsem flag. " - ++ "To use this feature you must use GHC 9.8 or later." + dieWithException verbosity CheckSemaphoreSupport -- | Write available build information for 'LocalBuildInfo' to disk. -- diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 9298ab0d763..f35f98f4fcb 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -150,14 +150,9 @@ import qualified System.Info import Text.PrettyPrint ( Doc , char - , comma , hsep - , nest - , punctuate , quotes - , render , renderStyle - , sep , text , ($+$) ) @@ -165,6 +160,7 @@ import Text.PrettyPrint import qualified Data.Maybe as M import qualified Data.Set as Set import qualified Distribution.Compat.NonEmptySet as NES +import Distribution.Simple.Errors import Distribution.Types.AnnotatedId type UseExternalInternalDeps = Bool @@ -425,11 +421,8 @@ configure (pkg_descr0, pbi) cfg = do case targets' of _ | null (configArgs cfg) -> return Nothing [cname] -> return (Just cname) - [] -> die' verbosity "No valid component targets found" - _ -> - die' - verbosity - "Can only configure either single component or all of them" + [] -> dieWithException verbosity NoValidComponent + _ -> dieWithException verbosity ConfigureEitherSingleOrAll let use_external_internal_deps = isJust mb_cname case mb_cname of @@ -444,7 +437,7 @@ configure (pkg_descr0, pbi) cfg = do -- configCID is only valid for per-component configure when (isJust (flagToMaybe (configCID cfg)) && isNothing mb_cname) $ - die' verbosity "--cid is only supported for per-component configure" + dieWithException verbosity ConfigCIDValidForPreComponent checkDeprecatedFlags verbosity cfg checkExactConfiguration verbosity pkg_descr0 cfg @@ -513,15 +506,11 @@ configure (pkg_descr0, pbi) cfg = do ( isJust mb_cname && (fromFlag (configTests cfg) || fromFlag (configBenchmarks cfg)) ) - $ die' verbosity - $ "--enable-tests/--enable-benchmarks are incompatible with" - ++ " explicitly specifying a component to configure." + $ dieWithException verbosity SanityCheckForEnableComponents -- Some sanity checks related to dynamic/static linking. when (fromFlag (configDynExe cfg) && fromFlag (configFullyStaticExe cfg)) $ - die' verbosity $ - "--enable-executable-dynamic and --enable-executable-static" - ++ " are incompatible with each other." + dieWithException verbosity SanityCheckForDynamicStaticLinking -- allConstraints: The set of all 'Dependency's we have. Used ONLY -- to 'configureFinalizedPackage'. @@ -539,7 +528,7 @@ configure (pkg_descr0, pbi) cfg = do ( allConstraints :: [PackageVersionConstraint] , requiredDepsMap :: Map (PackageName, ComponentName) InstalledPackageInfo ) <- - either (die' verbosity) return $ + either (dieWithException verbosity) return $ combinedConstraints (configConstraints cfg) (configDependencies cfg) @@ -657,14 +646,8 @@ configure (pkg_descr0, pbi) cfg = do (enabledBuildInfos pkg_descr enabled) let langs = unsupportedLanguages comp langlist when (not (null langs)) $ - die' verbosity $ - "The package " - ++ prettyShow (packageId pkg_descr0) - ++ " requires the following languages which are not " - ++ "supported by " - ++ prettyShow (compilerId comp) - ++ ": " - ++ intercalate ", " (map prettyShow langs) + dieWithException verbosity $ + UnsupportedLanguages (packageId pkg_descr0) (compilerId comp) (map prettyShow langs) let extlist = nub $ concatMap @@ -672,22 +655,15 @@ configure (pkg_descr0, pbi) cfg = do (enabledBuildInfos pkg_descr enabled) let exts = unsupportedExtensions comp extlist when (not (null exts)) $ - die' verbosity $ - "The package " - ++ prettyShow (packageId pkg_descr0) - ++ " requires the following language extensions which are not " - ++ "supported by " - ++ prettyShow (compilerId comp) - ++ ": " - ++ intercalate ", " (map prettyShow exts) + dieWithException verbosity $ + UnsupportedLanguageExtension (packageId pkg_descr0) (compilerId comp) (map prettyShow exts) -- Check foreign library build requirements let flibs = [flib | CFLib flib <- enabledComponents pkg_descr enabled] let unsupportedFLibs = unsupportedForeignLibs comp compPlatform flibs when (not (null unsupportedFLibs)) $ - die' verbosity $ - "Cannot build some foreign libraries: " - ++ intercalate "," unsupportedFLibs + dieWithException verbosity $ + CantFindForeignLibraries unsupportedFLibs -- Configure certain external build tools, see below for which ones. let requiredBuildTools = do @@ -968,8 +944,8 @@ configure (pkg_descr0, pbi) cfg = do ( isAbsolute (prefix dirs) || "${pkgroot}" `isPrefixOf` prefix dirs ) - $ die' verbosity - $ "expected an absolute directory name for --prefix: " ++ prefix dirs + $ dieWithException verbosity + $ ExpectedAbsoluteDirectory (prefix dirs) when ("${pkgroot}" `isPrefixOf` prefix dirs) $ warn verbosity $ @@ -1084,10 +1060,8 @@ checkExactConfiguration verbosity pkg_descr0 cfg = allFlags = map flagName . genPackageFlags $ pkg_descr0 diffFlags = allFlags \\ cmdlineFlags when (not . null $ diffFlags) $ - die' verbosity $ - "'--exact-configuration' was given, " - ++ "but the following flags were not specified: " - ++ intercalate ", " (map show diffFlags) + dieWithException verbosity $ + FlagsNotSpecified diffFlags -- | Create a PackageIndex that makes *any libraries that might be* -- defined internally to this package look like installed packages, in @@ -1246,15 +1220,7 @@ configureFinalizedPackage pkg_descr0 of Right r -> return r Left missing -> - die' verbosity $ - "Encountered missing or private dependencies:\n" - ++ ( render - . nest 4 - . sep - . punctuate comma - . map (pretty . simplifyDependency) - $ missing - ) + dieWithException verbosity $ EncounteredMissingDependency missing -- add extra include/lib dirs as specified in cfg -- we do it here so that those get checked too @@ -1328,26 +1294,17 @@ checkCompilerProblems verbosity comp pkg_descr enabled = do (all (isDefaultIncludeRenaming . mixinIncludeRenaming) . mixins) (enabledBuildInfos pkg_descr enabled) ) - $ die' verbosity - $ "Your compiler does not support thinning and renaming on " - ++ "package flags. To use this feature you must use " - ++ "GHC 7.9 or later." - + $ dieWithException verbosity CompilerDoesn'tSupportThinning when ( any (not . null . reexportedModules) (allLibraries pkg_descr) && not (reexportedModulesSupported comp) ) - $ die' verbosity - $ "Your compiler does not support module re-exports. To use " - ++ "this feature you must use GHC 7.9 or later." - + $ dieWithException verbosity CompilerDoesn'tSupportReexports when ( any (not . null . signatures) (allLibraries pkg_descr) && not (backpackSupported comp) ) - $ die' verbosity - $ "Your compiler does not support Backpack. To use " - ++ "this feature you must use GHC 8.1 or later." + $ dieWithException verbosity CompilerDoesn'tSupportBackpack -- | Select dependencies for the package. configureDependencies @@ -1410,13 +1367,8 @@ configureDependencies ( not (null internalPkgDeps) && not (newPackageDepsBehaviour pkg_descr) ) - $ die' verbosity - $ "The field 'build-depends: " - ++ intercalate ", " (map (prettyShow . packageName) internalPkgDeps) - ++ "' refers to a library which is defined within the same " - ++ "package. To use this feature the package must specify at " - ++ "least 'cabal-version: >= 1.8'." - + $ dieWithException verbosity + $ LibraryWithinSamePackage internalPkgDeps reportFailedDependencies verbosity failedDeps reportSelectedDependencies verbosity allPkgDeps @@ -1605,11 +1557,6 @@ data DependencyResolution -- polymorphism out of the 'Package' typeclass.) InternalDependency PackageId -data FailedDependency - = DependencyNotExists PackageName - | DependencyMissingInternal PackageName LibraryName - | DependencyNoVersion Dependency - -- | Test for a package dependency and record the version we have installed. selectDependency :: PackageId @@ -1718,26 +1665,7 @@ reportSelectedDependencies verbosity deps = reportFailedDependencies :: Verbosity -> [FailedDependency] -> IO () reportFailedDependencies _ [] = return () reportFailedDependencies verbosity failed = - die' verbosity (intercalate "\n\n" (map reportFailedDependency failed)) - where - reportFailedDependency (DependencyNotExists pkgname) = - "there is no version of " - ++ prettyShow pkgname - ++ " installed.\n" - ++ "Perhaps you need to download and install it from\n" - ++ hackageUrl - ++ prettyShow pkgname - ++ "?" - reportFailedDependency (DependencyMissingInternal pkgname lib) = - "internal dependency " - ++ prettyShow (prettyLibraryNameComponent lib) - ++ " not installed.\n" - ++ "Perhaps you need to configure and install it first?\n" - ++ "(This library was defined by " - ++ prettyShow pkgname - ++ ")" - reportFailedDependency (DependencyNoVersion dep) = - "cannot satisfy dependency " ++ prettyShow (simplifyDependency dep) ++ "\n" + dieWithException verbosity $ ReportFailedDependencies failed hackageUrl -- | List all installed packages in the given package databases. -- Non-existent package databases do not cause errors, they just get skipped @@ -1752,10 +1680,7 @@ getInstalledPackages -> IO InstalledPackageIndex getInstalledPackages verbosity comp packageDBs progdb = do when (null packageDBs) $ - die' verbosity $ - "No package databases have been specified. If you use " - ++ "--package-db=clear, you must follow it with --package-db= " - ++ "with 'global', 'user' or a specific file." + dieWithException verbosity NoPackageDatabaseSpecified info verbosity "Reading installed packages..." -- do not check empty packagedbs (ghc-pkg would error out) @@ -1767,9 +1692,7 @@ getInstalledPackages verbosity comp packageDBs progdb = do HaskellSuite{} -> HaskellSuite.getInstalledPackages verbosity packageDBs' progdb flv -> - die' verbosity $ - "don't know how to find the installed packages for " - ++ prettyShow flv + dieWithException verbosity $ HowToFindInstalledPackages flv where packageDBExists (SpecificPackageDB path) = do exists <- doesPathExist path @@ -1859,17 +1782,14 @@ combinedConstraints -- ^ installed dependencies -> InstalledPackageIndex -> Either - String + CabalException ( [PackageVersionConstraint] , Map (PackageName, ComponentName) InstalledPackageInfo ) combinedConstraints constraints dependencies installedPackages = do when (not (null badComponentIds)) $ Left $ - render $ - text "The following package dependencies were requested" - $+$ nest 4 (dispDependencies badComponentIds) - $+$ text "however the given installed package instance does not exist." + CombinedConstraints (dispDependencies badComponentIds) -- TODO: we don't check that all dependencies are used! @@ -2045,28 +1965,14 @@ configurePkgconfigPackages verbosity pkg_descr progdb enabled requirePkg dep@(PkgconfigDependency pkgn range) = do version <- pkgconfig ["--modversion", pkg] - `catchIO` (\_ -> die' verbosity notFound) - `catchExit` (\_ -> die' verbosity notFound) + `catchIO` (\_ -> dieWithException verbosity $ PkgConfigNotFound pkg versionRequirement) + `catchExit` (\_ -> dieWithException verbosity $ PkgConfigNotFound pkg versionRequirement) let trim = dropWhile isSpace . dropWhileEnd isSpace let v = PkgconfigVersion (toUTF8BS $ trim version) if not (withinPkgconfigVersionRange v range) - then die' verbosity (badVersion v) + then dieWithException verbosity $ BadVersion pkg versionRequirement v else info verbosity (depSatisfied v) where - notFound = - "The pkg-config package '" - ++ pkg - ++ "'" - ++ versionRequirement - ++ " is required but it could not be found." - badVersion v = - "The pkg-config package '" - ++ pkg - ++ "'" - ++ versionRequirement - ++ " is required but the version installed on the" - ++ " system is version " - ++ prettyShow v depSatisfied v = "Dependency " ++ prettyShow dep @@ -2159,14 +2065,14 @@ configCompilerEx -> ProgramDb -> Verbosity -> IO (Compiler, Platform, ProgramDb) -configCompilerEx Nothing _ _ _ verbosity = die' verbosity "Unknown compiler" +configCompilerEx Nothing _ _ _ verbosity = dieWithException verbosity UnknownCompilerException configCompilerEx (Just hcFlavor) hcPath hcPkg progdb verbosity = do (comp, maybePlatform, programDb) <- case hcFlavor of GHC -> GHC.configure verbosity hcPath hcPkg progdb GHCJS -> GHCJS.configure verbosity hcPath hcPkg progdb UHC -> UHC.configure verbosity hcPath hcPkg progdb HaskellSuite{} -> HaskellSuite.configure verbosity hcPath hcPkg progdb - _ -> die' verbosity "Unknown compiler" + _ -> dieWithException verbosity UnknownCompilerException return (comp, fromMaybe buildPlatform maybePlatform, programDb) -- ----------------------------------------------------------------------------- @@ -2370,80 +2276,9 @@ checkForeignDeps pkg lbi verbosity = explainErrors Nothing [] = return () -- should be impossible! explainErrors _ _ | isNothing . lookupProgram gccProgram . withPrograms $ lbi = - die' verbosity $ - unlines - [ "No working gcc" - , "This package depends on foreign library but we cannot " - ++ "find a working C compiler. If you have it in a " - ++ "non-standard location you can use the --with-gcc " - ++ "flag to specify it." - ] + dieWithException verbosity NoWorkingGcc explainErrors hdr libs = - die' verbosity $ - unlines $ - [ if plural - then "Missing dependencies on foreign libraries:" - else "Missing dependency on a foreign library:" - | missing - ] - ++ case hdr of - Just (Left h) -> ["* Missing (or bad) header file: " ++ h] - _ -> [] - ++ case libs of - [] -> [] - [lib] -> ["* Missing (or bad) C library: " ++ lib] - _ -> - [ "* Missing (or bad) C libraries: " - ++ intercalate ", " libs - ] - ++ [if plural then messagePlural else messageSingular | missing] - ++ case hdr of - Just (Left _) -> [headerCppMessage] - Just (Right h) -> - [ (if missing then "* " else "") - ++ "Bad header file: " - ++ h - , headerCcMessage - ] - _ -> [] - where - plural = length libs >= 2 - -- Is there something missing? (as opposed to broken) - missing = - not (null libs) - || case hdr of Just (Left _) -> True; _ -> False - - messageSingular = - "This problem can usually be solved by installing the system " - ++ "package that provides this library (you may need the " - ++ "\"-dev\" version). If the library is already installed " - ++ "but in a non-standard location then you can use the flags " - ++ "--extra-include-dirs= and --extra-lib-dirs= to specify " - ++ "where it is." - ++ "If the library file does exist, it may contain errors that " - ++ "are caught by the C compiler at the preprocessing stage. " - ++ "In this case you can re-run configure with the verbosity " - ++ "flag -v3 to see the error messages." - messagePlural = - "This problem can usually be solved by installing the system " - ++ "packages that provide these libraries (you may need the " - ++ "\"-dev\" versions). If the libraries are already installed " - ++ "but in a non-standard location then you can use the flags " - ++ "--extra-include-dirs= and --extra-lib-dirs= to specify " - ++ "where they are." - ++ "If the library files do exist, it may contain errors that " - ++ "are caught by the C compiler at the preprocessing stage. " - ++ "In this case you can re-run configure with the verbosity " - ++ "flag -v3 to see the error messages." - headerCppMessage = - "If the header file does exist, it may contain errors that " - ++ "are caught by the C compiler at the preprocessing stage. " - ++ "In this case you can re-run configure with the verbosity " - ++ "flag -v3 to see the error messages." - headerCcMessage = - "The header file contains a compile error. " - ++ "You can re-run configure with the verbosity flag " - ++ "-v3 to see the error messages from the C compiler." + dieWithException verbosity $ ExplainErrors hdr libs -- | Output package check warnings and errors. Exit if any errors. checkPackageProblems @@ -2460,7 +2295,7 @@ checkPackageProblems verbosity dir gpkg pkg = do partitionEithers (M.mapMaybe classEW $ pureChecks ++ ioChecks) if null errors then traverse_ (warn verbosity) (map ppPackageCheck warnings) - else die' verbosity (intercalate "\n\n" $ map ppPackageCheck errors) + else dieWithException verbosity $ CheckPackageProblems (map ppPackageCheck errors) where -- Classify error/warnings. Left: error, Right: warning. classEW :: PackageCheck -> Maybe (Either PackageCheck PackageCheck) @@ -2491,29 +2326,24 @@ checkRelocatable verbosity pkg lbi = -- Distribution.Simple.GHC.getRPaths checkOS = unless (os `elem` [OSX, Linux]) $ - die' verbosity $ - "Operating system: " - ++ prettyShow os - ++ ", does not support relocatable builds" + dieWithException verbosity $ + NoOSSupport os where (Platform _ os) = hostPlatform lbi -- Check if the Compiler support relocatable builds checkCompiler = unless (compilerFlavor comp `elem` [GHC]) $ - die' verbosity $ - "Compiler: " - ++ show comp - ++ ", does not support relocatable builds" + dieWithException verbosity $ + NoCompilerSupport (show comp) where comp = compiler lbi -- Check if all the install dirs are relative to same prefix packagePrefixRelative = unless (relativeInstallDirs installDirs) $ - die' verbosity $ - "Installation directories are not prefix_relative:\n" - ++ show installDirs + dieWithException verbosity $ + InstallDirsNotPrefixRelative (installDirs) where -- NB: should be good enough to check this against the default -- component ID, but if we wanted to be strictly correct we'd @@ -2554,8 +2384,8 @@ checkRelocatable verbosity pkg lbi = -- @..@s and following check will fail without @canonicalizePath@. canonicalized <- canonicalizePath libdir unless (p `isPrefixOf` canonicalized) $ - die' verbosity $ - msg libdir + dieWithException verbosity $ + LibDirDepsPrefixNotRelative libdir p | otherwise = return () -- NB: should be good enough to check this against the default @@ -2564,11 +2394,6 @@ checkRelocatable verbosity pkg lbi = installDirs = absoluteInstallDirs pkg lbi NoCopyDest p = prefix installDirs ipkgs = PackageIndex.allPackages (installedPkgs lbi) - msg l = - "Library directory of a dependency: " - ++ show l - ++ "\nis not relative to the installation prefix:\n" - ++ show p -- ----------------------------------------------------------------------------- -- Testing foreign library requirements diff --git a/Cabal/src/Distribution/Simple/Errors.hs b/Cabal/src/Distribution/Simple/Errors.hs index e086bf04cc3..fb1c2875f1c 100644 --- a/Cabal/src/Distribution/Simple/Errors.hs +++ b/Cabal/src/Distribution/Simple/Errors.hs @@ -11,6 +11,7 @@ module Distribution.Simple.Errors ( CabalException (..) + , FailedDependency (..) , exceptionCode , exceptionMessage ) where @@ -19,14 +20,26 @@ import Distribution.Compat.Prelude import Distribution.Compiler import Distribution.InstalledPackageInfo import Distribution.ModuleName +import Distribution.Package +import Distribution.PackageDescription (FlagName, UnqualComponentName) import Distribution.Pretty - ( prettyShow + ( Pretty (pretty) + , prettyShow ) +import Distribution.Simple.InstallDirs +import Distribution.System (OS) import Distribution.Types.BenchmarkType -import Distribution.Types.PackageId +import Distribution.Types.LibraryName +import Distribution.Types.PkgconfigVersion import Distribution.Types.TestType -import Distribution.Types.UnitId import Distribution.Version +import Text.PrettyPrint + +data FailedDependency + = DependencyNotExists PackageName + | DependencyMissingInternal PackageName LibraryName + | DependencyNoVersion Dependency + deriving (Show) -- Types representing exceptions thrown by functions in all the modules of Cabal Package data CabalException @@ -95,6 +108,42 @@ data CabalException | NoSupportPreProcessingTestExtras TestType | NoSupportPreProcessingBenchmarkExtras BenchmarkType | UnlitException String + | RunProgramInvocationException FilePath String + | GetProgramInvocationException FilePath String + | GetProgramInvocationLBSException FilePath String + | CheckSemaphoreSupport + | NoLibraryForPackage + | SanityCheckHookedBuildInfo UnqualComponentName + | ConfigureScriptNotFound + | NoValidComponent + | ConfigureEitherSingleOrAll + | ConfigCIDValidForPreComponent + | SanityCheckForEnableComponents + | SanityCheckForDynamicStaticLinking + | UnsupportedLanguages PackageIdentifier CompilerId [String] + | UnsupportedLanguageExtension PackageIdentifier CompilerId [String] + | CantFindForeignLibraries [String] + | ExpectedAbsoluteDirectory FilePath + | FlagsNotSpecified [FlagName] + | EncounteredMissingDependency [Dependency] + | CompilerDoesn'tSupportThinning + | CompilerDoesn'tSupportReexports + | CompilerDoesn'tSupportBackpack + | LibraryWithinSamePackage [PackageId] + | ReportFailedDependencies [FailedDependency] String + | NoPackageDatabaseSpecified + | HowToFindInstalledPackages CompilerFlavor + | PkgConfigNotFound String String + | BadVersion String String PkgconfigVersion + | UnknownCompilerException + | NoWorkingGcc + | NoOSSupport OS + | NoCompilerSupport String + | InstallDirsNotPrefixRelative (InstallDirs FilePath) + | ExplainErrors (Maybe (Either [Char] [Char])) [String] + | CheckPackageProblems [String] + | LibDirDepsPrefixNotRelative FilePath FilePath + | CombinedConstraints Doc deriving (Show, Typeable) exceptionCode :: CabalException -> Int @@ -126,7 +175,7 @@ exceptionCode e = case e of NoGHCVersionFromCompiler -> 4098 HaddockAndGHCVersionDoesntMatch{} -> 1998 MustHaveSharedLibraries{} -> 6032 - HaddockPackageFlags{} -> 4567 + HaddockPackageFlags{} -> 4569 UnknownCompilerFlavor{} -> 3102 FailedToDetermineTarget{} -> 5049 NoMultipleTargets{} -> 6091 @@ -136,7 +185,7 @@ exceptionCode e = case e of BuildingNotSupportedWithCompiler{} -> 7077 ProvideHaskellSuiteTool{} -> 7509 CannotDetermineCompilerVersion{} -> 4519 - PkgDumpFailed{} -> 2290 + PkgDumpFailed{} -> 2291 FailedToParseOutput{} -> 5500 CantFindSourceModule{} -> 8870 VersionMismatchJS{} -> 9001 @@ -164,6 +213,42 @@ exceptionCode e = case e of NoSupportPreProcessingTestExtras{} -> 7886 NoSupportPreProcessingBenchmarkExtras{} -> 9999 UnlitException{} -> 5454 + RunProgramInvocationException{} -> 8012 + GetProgramInvocationException{} -> 7300 + GetProgramInvocationLBSException{} -> 6578 + CheckSemaphoreSupport{} -> 2002 + NoLibraryForPackage{} -> 8004 + SanityCheckHookedBuildInfo{} -> 6007 + ConfigureScriptNotFound{} -> 4567 + NoValidComponent{} -> 5680 + ConfigureEitherSingleOrAll{} -> 2001 + ConfigCIDValidForPreComponent{} -> 7006 + SanityCheckForEnableComponents{} -> 5004 + SanityCheckForDynamicStaticLinking{} -> 4007 + UnsupportedLanguages{} -> 8074 + UnsupportedLanguageExtension{} -> 5656 + CantFindForeignLibraries{} -> 4574 + ExpectedAbsoluteDirectory{} -> 6662 + FlagsNotSpecified{} -> 9080 + EncounteredMissingDependency{} -> 8010 + CompilerDoesn'tSupportThinning{} -> 4003 + CompilerDoesn'tSupportReexports{} -> 3456 + CompilerDoesn'tSupportBackpack{} -> 5446 + LibraryWithinSamePackage{} -> 7007 + ReportFailedDependencies{} -> 4321 + NoPackageDatabaseSpecified{} -> 2300 + HowToFindInstalledPackages{} -> 3003 + PkgConfigNotFound{} -> 7123 + BadVersion{} -> 7600 + UnknownCompilerException{} -> 3022 + NoWorkingGcc{} -> 1088 + NoOSSupport{} -> 3339 + NoCompilerSupport{} -> 2290 + InstallDirsNotPrefixRelative{} -> 6000 + ExplainErrors{} -> 4345 + CheckPackageProblems{} -> 5559 + LibDirDepsPrefixNotRelative{} -> 6667 + CombinedConstraints{} -> 5000 exceptionMessage :: CabalException -> String exceptionMessage e = case e of @@ -189,7 +274,7 @@ exceptionMessage e = case e of SuppressingChecksOnFile -> "HcPkg.register: the compiler does not support ,suppressing checks on files." NoSupportDirStylePackageDb -> "HcPkg.writeRegistrationFileDirectly: compiler does not support dir style package dbs" OnlySupportSpecificPackageDb -> "HcPkg.writeRegistrationFileDirectly: only supports SpecificPackageDB for now" - FailedToParseOutputDescribe programId packageId -> "failed to parse output of '" ++ programId ++ " describe " ++ prettyShow packageId ++ "'" + FailedToParseOutputDescribe programId pkgId -> "failed to parse output of '" ++ programId ++ " describe " ++ prettyShow pkgId ++ "'" DumpFailed programId exception -> programId ++ " dump failed: " ++ exception FailedToParseOutputDump programId -> "failed to parse output of '" ++ programId ++ " dump'" ListFailed programId -> programId ++ " list failed" @@ -353,3 +438,210 @@ exceptionMessage e = case e of ++ "type " ++ prettyShow tt UnlitException str -> str + RunProgramInvocationException path errors -> "'" ++ path ++ "' exited with an error:\n" ++ errors + GetProgramInvocationException path errors -> "'" ++ path ++ "' exited with an error:\n" ++ errors + GetProgramInvocationLBSException path errors -> "'" ++ path ++ "' exited with an error:\n" ++ errors + CheckSemaphoreSupport -> + "Your compiler does not support the -jsem flag. " + ++ "To use this feature you must use GHC 9.8 or later." + NoLibraryForPackage -> + "The buildinfo contains info for a library, " + ++ "but the package does not have a library." + SanityCheckHookedBuildInfo exe1 -> + "The buildinfo contains info for an executable called '" + ++ prettyShow exe1 + ++ "' but the package does not have a " + ++ "executable with that name." + ConfigureScriptNotFound -> "configure script not found." + NoValidComponent -> "No valid component targets found" + ConfigureEitherSingleOrAll -> "Can only configure either single component or all of them" + ConfigCIDValidForPreComponent -> "--cid is only supported for per-component configure" + SanityCheckForEnableComponents -> + "--enable-tests/--enable-benchmarks are incompatible with" + ++ " explicitly specifying a component to configure." + SanityCheckForDynamicStaticLinking -> + "--enable-executable-dynamic and --enable-executable-static" + ++ " are incompatible with each other." + UnsupportedLanguages pkgId compilerId langs -> + "The package " + ++ prettyShow (pkgId) + ++ " requires the following languages which are not " + ++ "supported by " + ++ prettyShow (compilerId) + ++ ": " + ++ intercalate ", " langs + UnsupportedLanguageExtension pkgId compilerId exts -> + "The package " + ++ prettyShow (pkgId) + ++ " requires the following language extensions which are not " + ++ "supported by " + ++ prettyShow (compilerId) + ++ ": " + ++ intercalate ", " exts + CantFindForeignLibraries unsupportedFLibs -> + "Cannot build some foreign libraries: " + ++ intercalate "," unsupportedFLibs + ExpectedAbsoluteDirectory fPath -> "expected an absolute directory name for --prefix: " ++ fPath + FlagsNotSpecified diffFlags -> + "'--exact-configuration' was given, " + ++ "but the following flags were not specified: " + ++ intercalate ", " (map show diffFlags) + EncounteredMissingDependency missing -> + "Encountered missing or private dependencies:\n" + ++ ( render + . nest 4 + . sep + . punctuate comma + . map (pretty . simplifyDependency) + $ missing + ) + CompilerDoesn'tSupportThinning -> + "Your compiler does not support thinning and renaming on " + ++ "package flags. To use this feature you must use " + ++ "GHC 7.9 or later." + CompilerDoesn'tSupportReexports -> + "Your compiler does not support module re-exports. To use " + ++ "this feature you must use GHC 7.9 or later." + CompilerDoesn'tSupportBackpack -> + "Your compiler does not support Backpack. To use " + ++ "this feature you must use GHC 8.1 or later." + LibraryWithinSamePackage internalPkgDeps -> + "The field 'build-depends: " + ++ intercalate ", " (map (prettyShow . packageName) internalPkgDeps) + ++ "' refers to a library which is defined within the same " + ++ "package. To use this feature the package must specify at " + ++ "least 'cabal-version: >= 1.8'." + ReportFailedDependencies failed hackageUrl -> (intercalate "\n\n" (map reportFailedDependency failed)) + where + reportFailedDependency (DependencyNotExists pkgname) = + "there is no version of " + ++ prettyShow pkgname + ++ " installed.\n" + ++ "Perhaps you need to download and install it from\n" + ++ hackageUrl + ++ prettyShow pkgname + ++ "?" + reportFailedDependency (DependencyMissingInternal pkgname lib) = + "internal dependency " + ++ prettyShow (prettyLibraryNameComponent lib) + ++ " not installed.\n" + ++ "Perhaps you need to configure and install it first?\n" + ++ "(This library was defined by " + ++ prettyShow pkgname + ++ ")" + reportFailedDependency (DependencyNoVersion dep) = + "cannot satisfy dependency " ++ prettyShow (simplifyDependency dep) ++ "\n" + NoPackageDatabaseSpecified -> + "No package databases have been specified. If you use " + ++ "--package-db=clear, you must follow it with --package-db= " + ++ "with 'global', 'user' or a specific file." + HowToFindInstalledPackages flv -> + "don't know how to find the installed packages for " + ++ prettyShow flv + PkgConfigNotFound pkg versionRequirement -> + "The pkg-config package '" + ++ pkg + ++ "'" + ++ versionRequirement + ++ " is required but it could not be found." + BadVersion pkg versionRequirement v -> + "The pkg-config package '" + ++ pkg + ++ "'" + ++ versionRequirement + ++ " is required but the version installed on the" + ++ " system is version " + ++ prettyShow v + UnknownCompilerException -> "Unknown compiler" + NoWorkingGcc -> + unlines + [ "No working gcc" + , "This package depends on foreign library but we cannot " + ++ "find a working C compiler. If you have it in a " + ++ "non-standard location you can use the --with-gcc " + ++ "flag to specify it." + ] + NoOSSupport os -> + "Operating system: " + ++ prettyShow os + ++ ", does not support relocatable builds" + NoCompilerSupport comp -> + "Compiler: " + ++ comp + ++ ", does not support relocatable builds" + InstallDirsNotPrefixRelative installDirs -> "Installation directories are not prefix_relative:\n" ++ show installDirs + ExplainErrors hdr libs -> + unlines $ + [ if plural + then "Missing dependencies on foreign libraries:" + else "Missing dependency on a foreign library:" + | missing + ] + ++ case hdr of + Just (Left h) -> ["* Missing (or bad) header file: " ++ h] + _ -> [] + ++ case libs of + [] -> [] + [lib] -> ["* Missing (or bad) C library: " ++ lib] + _ -> + [ "* Missing (or bad) C libraries: " + ++ intercalate ", " libs + ] + ++ [if plural then messagePlural else messageSingular | missing] + ++ case hdr of + Just (Left _) -> [headerCppMessage] + Just (Right h) -> + [ (if missing then "* " else "") + ++ "Bad header file: " + ++ h + , headerCcMessage + ] + _ -> [] + where + plural = length libs >= 2 + -- Is there something missing? (as opposed to broken) + missing = + not (null libs) + || case hdr of Just (Left _) -> True; _ -> False + messageSingular = + "This problem can usually be solved by installing the system " + ++ "package that provides this library (you may need the " + ++ "\"-dev\" version). If the library is already installed " + ++ "but in a non-standard location then you can use the flags " + ++ "--extra-include-dirs= and --extra-lib-dirs= to specify " + ++ "where it is." + ++ "If the library file does exist, it may contain errors that " + ++ "are caught by the C compiler at the preprocessing stage. " + ++ "In this case you can re-run configure with the verbosity " + ++ "flag -v3 to see the error messages." + messagePlural = + "This problem can usually be solved by installing the system " + ++ "packages that provide these libraries (you may need the " + ++ "\"-dev\" versions). If the libraries are already installed " + ++ "but in a non-standard location then you can use the flags " + ++ "--extra-include-dirs= and --extra-lib-dirs= to specify " + ++ "where they are." + ++ "If the library files do exist, it may contain errors that " + ++ "are caught by the C compiler at the preprocessing stage. " + ++ "In this case you can re-run configure with the verbosity " + ++ "flag -v3 to see the error messages." + headerCppMessage = + "If the header file does exist, it may contain errors that " + ++ "are caught by the C compiler at the preprocessing stage. " + ++ "In this case you can re-run configure with the verbosity " + ++ "flag -v3 to see the error messages." + headerCcMessage = + "The header file contains a compile error. " + ++ "You can re-run configure with the verbosity flag " + ++ "-v3 to see the error messages from the C compiler." + CheckPackageProblems errors -> (intercalate "\n\n" $ errors) + LibDirDepsPrefixNotRelative l p -> + "Library directory of a dependency: " + ++ show l + ++ "\nis not relative to the installation prefix:\n" + ++ show p + CombinedConstraints dispDepend -> + render $ + text "The following package dependencies were requested" + $+$ nest 4 dispDepend + $+$ text "however the given installed package instance does not exist." diff --git a/Cabal/src/Distribution/Simple/GHC.hs b/Cabal/src/Distribution/Simple/GHC.hs index 3f1ede31b16..3c380a41a86 100644 --- a/Cabal/src/Distribution/Simple/GHC.hs +++ b/Cabal/src/Distribution/Simple/GHC.hs @@ -1879,13 +1879,6 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do , ghcOptFPic = toFlag True , ghcOptLinkModDefFiles = toNubListR $ gbuildModDefFiles bm } - -- See Note [RPATH] - `mappend` ifNeedsRPathWorkaround - lbi - mempty - { ghcOptLinkOptions = ["-Wl,--no-as-needed"] - , ghcOptLinkLibs = ["ffi"] - } ForeignLibNativeStatic -> -- this should be caught by buildFLib -- (and if we do implement this, we probably don't even want to call @@ -1901,82 +1894,6 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do runGhcProg linkOpts{ghcOptOutputFile = toFlag (targetDir buildName)} renameFile (targetDir buildName) (targetDir targetName) -{- -Note [RPATH] -~~~~~~~~~~~~ - -Suppose that the dynamic library depends on `base`, but not (directly) on -`integer-gmp` (which, however, is a dependency of `base`). We will link the -library as - - gcc ... -lHSbase-4.7.0.2-ghc7.8.4 -lHSinteger-gmp-0.5.1.0-ghc7.8.4 ... - -However, on systems (like Ubuntu) where the linker gets called with `-as-needed` -by default, the linker will notice that `integer-gmp` isn't actually a direct -dependency and hence omit the link. - -Then when we attempt to link a C program against this dynamic library, the -_static_ linker will attempt to verify that all symbols can be resolved. The -dynamic library itself does not require any symbols from `integer-gmp`, but -`base` does. In order to verify that the symbols used by `base` can be -resolved, the static linker needs to be able to _find_ integer-gmp. - -Finding the `base` dependency is simple, because the dynamic elf header -(`readelf -d`) for the library that we have created looks something like - - (NEEDED) Shared library: [libHSbase-4.7.0.2-ghc7.8.4.so] - (RPATH) Library rpath: [/path/to/base-4.7.0.2:...] - -However, when it comes to resolving the dependency on `integer-gmp`, it needs -to look at the dynamic header for `base`. On modern ghc (7.8 and higher) this -looks something like - - (NEEDED) Shared library: [libHSinteger-gmp-0.5.1.0-ghc7.8.4.so] - (RPATH) Library rpath: [$ORIGIN/../integer-gmp-0.5.1.0:...] - -This specifies the location of `integer-gmp` _in terms of_ the location of base -(using the `$ORIGIN`) variable. But here's the crux: when the static linker -attempts to verify that all symbols can be resolved, [**IT DOES NOT RESOLVE -`$ORIGIN`**](http://stackoverflow.com/questions/6323603/ld-using-rpath-origin-inside-a-shared-library-recursive). -As a consequence, it will not be able to resolve the symbols and report the -missing symbols as errors, _even though the dynamic linker **would** be able to -resolve these symbols_. We can tell the static linker not to report these -errors by using `--unresolved-symbols=ignore-all` and all will be fine when we -run the program ([(indeed, this is what the gold linker -does)](https://sourceware.org/ml/binutils/2013-05/msg00038.html), but it makes -the resulting library more difficult to use. - -Instead what we can do is make sure that the generated dynamic library has -explicit top-level dependencies on these libraries. This means that the static -linker knows where to find them, and when we have transitive dependencies on -the same libraries the linker will only load them once, so we avoid needing to -look at the `RPATH` of our dependencies. We can do this by passing -`--no-as-needed` to the linker, so that it doesn't omit any libraries. - -Note that on older ghc (7.6 and before) the Haskell libraries don't have an -RPATH set at all, which makes it even more important that we make these -top-level dependencies. - -Finally, we have to explicitly link against `libffi` for the same reason. For -newer ghc this _happens_ to be unnecessary on many systems because `libffi` is -a library which is not specific to GHC, and when the static linker verifies -that all symbols can be resolved it will find the `libffi` that is globally -installed (completely independent from ghc). Of course, this may well be the -_wrong_ version of `libffi`, but it's quite possible that symbol resolution -happens to work. This is of course the wrong approach, which is why we link -explicitly against `libffi` so that we will find the _right_ version of -`libffi`. --} - --- | Do we need the RPATH workaround? --- --- See Note [RPATH]. -ifNeedsRPathWorkaround :: Monoid a => LocalBuildInfo -> a -> a -ifNeedsRPathWorkaround lbi a = - case hostPlatform lbi of - Platform _ Linux -> a - _otherwise -> mempty - data DynamicRtsInfo = DynamicRtsInfo { dynRtsVanillaLib :: FilePath , dynRtsThreadedLib :: FilePath diff --git a/Cabal/src/Distribution/Simple/GHCJS.hs b/Cabal/src/Distribution/Simple/GHCJS.hs index ad27c97d3d9..58194f5ffa3 100644 --- a/Cabal/src/Distribution/Simple/GHCJS.hs +++ b/Cabal/src/Distribution/Simple/GHCJS.hs @@ -1556,13 +1556,6 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do , ghcOptFPic = toFlag True , ghcOptLinkModDefFiles = toNubListR $ gbuildModDefFiles bm } - -- See Note [RPATH] - `mappend` ifNeedsRPathWorkaround - lbi - mempty - { ghcOptLinkOptions = ["-Wl,--no-as-needed"] - , ghcOptLinkLibs = ["ffi"] - } ForeignLibNativeStatic -> -- this should be caught by buildFLib -- (and if we do implement this, we probably don't even want to call @@ -1578,82 +1571,6 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do runGhcProg linkOpts{ghcOptOutputFile = toFlag (targetDir buildName)} renameFile (targetDir buildName) (targetDir targetName) -{- -Note [RPATH] -~~~~~~~~~~~~ - -Suppose that the dynamic library depends on `base`, but not (directly) on -`integer-gmp` (which, however, is a dependency of `base`). We will link the -library as - - gcc ... -lHSbase-4.7.0.2-ghc7.8.4 -lHSinteger-gmp-0.5.1.0-ghc7.8.4 ... - -However, on systems (like Ubuntu) where the linker gets called with `-as-needed` -by default, the linker will notice that `integer-gmp` isn't actually a direct -dependency and hence omit the link. - -Then when we attempt to link a C program against this dynamic library, the -_static_ linker will attempt to verify that all symbols can be resolved. The -dynamic library itself does not require any symbols from `integer-gmp`, but -`base` does. In order to verify that the symbols used by `base` can be -resolved, the static linker needs to be able to _find_ integer-gmp. - -Finding the `base` dependency is simple, because the dynamic elf header -(`readelf -d`) for the library that we have created looks something like - - (NEEDED) Shared library: [libHSbase-4.7.0.2-ghc7.8.4.so] - (RPATH) Library rpath: [/path/to/base-4.7.0.2:...] - -However, when it comes to resolving the dependency on `integer-gmp`, it needs -to look at the dynamic header for `base`. On modern ghc (7.8 and higher) this -looks something like - - (NEEDED) Shared library: [libHSinteger-gmp-0.5.1.0-ghc7.8.4.so] - (RPATH) Library rpath: [$ORIGIN/../integer-gmp-0.5.1.0:...] - -This specifies the location of `integer-gmp` _in terms of_ the location of base -(using the `$ORIGIN`) variable. But here's the crux: when the static linker -attempts to verify that all symbols can be resolved, [**IT DOES NOT RESOLVE -`$ORIGIN`**](http://stackoverflow.com/questions/6323603/ld-using-rpath-origin-inside-a-shared-library-recursive). -As a consequence, it will not be able to resolve the symbols and report the -missing symbols as errors, _even though the dynamic linker **would** be able to -resolve these symbols_. We can tell the static linker not to report these -errors by using `--unresolved-symbols=ignore-all` and all will be fine when we -run the program ([(indeed, this is what the gold linker -does)](https://sourceware.org/ml/binutils/2013-05/msg00038.html), but it makes -the resulting library more difficult to use. - -Instead what we can do is make sure that the generated dynamic library has -explicit top-level dependencies on these libraries. This means that the static -linker knows where to find them, and when we have transitive dependencies on -the same libraries the linker will only load them once, so we avoid needing to -look at the `RPATH` of our dependencies. We can do this by passing -`--no-as-needed` to the linker, so that it doesn't omit any libraries. - -Note that on older ghc (7.6 and before) the Haskell libraries don't have an -RPATH set at all, which makes it even more important that we make these -top-level dependencies. - -Finally, we have to explicitly link against `libffi` for the same reason. For -newer ghc this _happens_ to be unnecessary on many systems because `libffi` is -a library which is not specific to GHC, and when the static linker verifies -that all symbols can be resolved it will find the `libffi` that is globally -installed (completely independent from ghc). Of course, this may well be the -_wrong_ version of `libffi`, but it's quite possible that symbol resolution -happens to work. This is of course the wrong approach, which is why we link -explicitly against `libffi` so that we will find the _right_ version of -`libffi`. --} - --- | Do we need the RPATH workaround? --- --- See Note [RPATH]. -ifNeedsRPathWorkaround :: Monoid a => LocalBuildInfo -> a -> a -ifNeedsRPathWorkaround lbi a = - case hostPlatform lbi of - Platform _ Linux -> a - _otherwise -> mempty - data DynamicRtsInfo = DynamicRtsInfo { dynRtsVanillaLib :: FilePath , dynRtsThreadedLib :: FilePath diff --git a/Cabal/src/Distribution/Simple/Program/Run.hs b/Cabal/src/Distribution/Simple/Program/Run.hs index bfc62896d91..27ff33dce01 100644 --- a/Cabal/src/Distribution/Simple/Program/Run.hs +++ b/Cabal/src/Distribution/Simple/Program/Run.hs @@ -31,11 +31,11 @@ import Distribution.Compat.Prelude import Prelude () import Distribution.Compat.Environment +import Distribution.Simple.Errors import Distribution.Simple.Program.Types import Distribution.Simple.Utils import Distribution.Utils.Generic import Distribution.Verbosity - import System.FilePath (searchPathSeparator) import qualified Data.ByteString.Lazy as LBS @@ -157,8 +157,8 @@ runProgramInvocation (Just input) IODataModeBinary when (exitCode /= ExitSuccess) $ - die' verbosity $ - "'" ++ path ++ "' exited with an error:\n" ++ errors + dieWithException verbosity $ + RunProgramInvocationException path errors where input = encodeToIOData encoding inputStr @@ -174,8 +174,8 @@ getProgramInvocationLBS :: Verbosity -> ProgramInvocation -> IO LBS.ByteString getProgramInvocationLBS verbosity inv = do (output, errors, exitCode) <- getProgramInvocationIODataAndErrors verbosity inv IODataModeBinary when (exitCode /= ExitSuccess) $ - die' verbosity $ - "'" ++ progInvokePath inv ++ "' exited with an error:\n" ++ errors + dieWithException verbosity $ + GetProgramInvocationLBSException (progInvokePath inv) errors return output getProgramInvocationOutputAndErrors diff --git a/Makefile b/Makefile index 8f35c847af6..6d8394aa64e 100644 --- a/Makefile +++ b/Makefile @@ -25,19 +25,6 @@ style-modified: ## Run the code styler on modified files @git ls-files --modified Cabal Cabal-syntax cabal-install \ | grep '.hs$$' | xargs -P $(PROCS) -I {} fourmolu -q -i {} -# source generation: Lexer - -LEXER_HS:=Cabal-syntax/src/Distribution/Fields/Lexer.hs - -lexer : $(LEXER_HS) - -$(LEXER_HS) : templates/Lexer.x - alex --latin1 --ghc -o $@ $^ - @rm -f Lexer.tmp - echo '{- FOURMOLU_DISABLE -}' >> Lexer.tmp - cat -s $@ >> Lexer.tmp - mv Lexer.tmp $@ - # source generation: SPDX SPDX_LICENSE_HS:=Cabal-syntax/src/Distribution/SPDX/LicenseId.hs @@ -213,33 +200,13 @@ bootstrap-jsons: $(BOOTSTRAP_GHC_VERSIONS:%=bootstrap-json-%) # documentation ############################################################################## -# TODO: when we have sphinx-build2 ? -SPHINXCMD:=sphinx-build -# Flag -n ("nitpick") warns about broken references -# Flag -W turns warnings into errors -# Flag --keep-going continues after errors -SPHINX_FLAGS:=-n -W --keep-going -E -SPHINX_HTML_OUTDIR:=dist-newstyle/doc/users-guide -USERGUIDE_STAMP:=$(SPHINX_HTML_OUTDIR)/index.html - -# do pip install every time so we have up to date requirements when we build -users-guide: .python-sphinx-virtualenv $(USERGUIDE_STAMP) -$(USERGUIDE_STAMP) : doc/*.rst - mkdir -p $(SPHINX_HTML_OUTDIR) - (. ./.python-sphinx-virtualenv/bin/activate && pip install -r doc/requirements.txt && $(SPHINXCMD) $(SPHINX_FLAGS) doc $(SPHINX_HTML_OUTDIR)) - -.python-sphinx-virtualenv: - python3 -m venv .python-sphinx-virtualenv - (. ./.python-sphinx-virtualenv/bin/activate) - -# This goal is intended for manual invocation, always rebuilds. -.PHONY: users-guide-requirements -users-guide-requirements: doc/requirements.txt +.PHONY: users-guide +users-guide: + $(MAKE) -C doc users-guide -.PHONY: doc/requirements.txt -doc/requirements.txt: .python-sphinx-virtualenv - . .python-sphinx-virtualenv/bin/activate \ - && make -C doc build-and-check-requirements +.PHONY: users-guide-requirements +users-guide-requirements: + $(MAKE) -C doc users-guide-requirements ifeq ($(shell uname), Darwin) PROCS := $(shell sysctl -n hw.logicalcpu) diff --git a/bootstrap/bootstrap.py b/bootstrap/bootstrap.py index 10d8dfe5717..cf2ee03b442 100755 --- a/bootstrap/bootstrap.py +++ b/bootstrap/bootstrap.py @@ -64,6 +64,7 @@ class PackageSource(Enum): ('revision', Optional[int]), ('cabal_sha256', Optional[SHA256Hash]), ('flags', List[str]), + ('component', Optional[str]) ]) BootstrapInfo = NamedTuple('BootstrapInfo', [ @@ -189,9 +190,9 @@ def install_dep(dep: BootstrapDep, ghc: Compiler) -> None: sdist_dir = resolve_dep(dep) - install_sdist(dist_dir, sdist_dir, ghc, dep.flags) + install_sdist(dist_dir, sdist_dir, ghc, dep.flags, dep.component) -def install_sdist(dist_dir: Path, sdist_dir: Path, ghc: Compiler, flags: List[str]): +def install_sdist(dist_dir: Path, sdist_dir: Path, ghc: Compiler, flags: List[str], component): prefix = PSEUDOSTORE.resolve() flags_option = ' '.join(flags) setup_dist_dir = dist_dir / 'setup' @@ -205,10 +206,12 @@ def install_sdist(dist_dir: Path, sdist_dir: Path, ghc: Compiler, flags: List[st f'--package-db={PKG_DB.resolve()}', f'--prefix={prefix}', f'--bindir={BINDIR.resolve()}', + f'--extra-prog-path={BINDIR.resolve()}', f'--with-compiler={ghc.ghc_path}', f'--with-hc-pkg={ghc.ghc_pkg_path}', f'--with-hsc2hs={ghc.hsc2hs_path}', f'--flags={flags_option}', + f'{component or ""}' ] def check_call(args: List[str]) -> None: diff --git a/bootstrap/cabal.project b/bootstrap/cabal.project index 8d1ac11b28e..d1eb5750c9d 100644 --- a/bootstrap/cabal.project +++ b/bootstrap/cabal.project @@ -3,6 +3,3 @@ packages: . optimization: False - -allow-newer: - cabal-install-parsers:Cabal-syntax diff --git a/bootstrap/linux-8.10.7.json b/bootstrap/linux-8.10.7.json index 24dc7fcf5e6..4ef250fd0c2 100644 --- a/bootstrap/linux-8.10.7.json +++ b/bootstrap/linux-8.10.7.json @@ -24,6 +24,10 @@ "package": "deepseq", "version": "1.4.4.0" }, + { + "package": "containers", + "version": "0.6.5.1" + }, { "package": "ghc-boot-th", "version": "8.10.7" @@ -36,10 +40,6 @@ "package": "template-haskell", "version": "2.16.0.0" }, - { - "package": "containers", - "version": "0.6.5.1" - }, { "package": "transformers", "version": "0.5.6.2" @@ -63,45 +63,40 @@ ], "dependencies": [ { - "cabal_sha256": "55390b63bbd7846aab6b16b7b255cf5108a3a422798a1e9a3b674eb0c68ac20c", + "cabal_sha256": "458d4794a5ced371a844e325fe539dd5fee8fe41f78b6f00e6c70920b7dd18e3", + "component": "lib:bytestring", "flags": [], "package": "bytestring", "revision": 0, "source": "hackage", - "src_sha256": "491aaef7625c693a06c26ae7f097caf23d9e3f9cae14af5ab17e71abb39576d3", - "version": "0.11.4.0" + "src_sha256": "76193d39b66197107f452184597a4e458194c64731efbba1e9605550c732f7f4", + "version": "0.11.5.0" }, { - "cabal_sha256": "81f468c1c75fd6535152ab69b2d32ac6cfcc03e345267b069abe4da56ec95801", - "flags": [], - "package": "binary", - "revision": 0, - "source": "hackage", - "src_sha256": "ac21ca63452dfc9b0bcab87c57699c531d87f7a9bcb6230ca46fba1b7faeebc0", - "version": "0.8.9.1" - }, - { - "cabal_sha256": "ab6e3330c42817b0effb14cae9c60d5cdc41d61f7354d04bc529ed031113f27c", + "cabal_sha256": "2de84756d3907308230e34fcc7c1917a73f218f6d53838618b7d5b95dd33e2c3", + "component": "lib:filepath", "flags": [ "-cpphs" ], "package": "filepath", "revision": 0, "source": "hackage", - "src_sha256": "ed1d11173f5052461cd1df58b5ef4abbfa1803ad2b237da7ddb7c7d64e017de2", - "version": "1.4.100.3" + "src_sha256": "82876250347c2fdf0f9de5448ce44f02539f37951b671d9a30719a6c4f96e9ad", + "version": "1.4.100.4" }, { - "cabal_sha256": "26eeda14432a2fcc6049045068ecf59525ffff9196616a642b5ab2326a003692", + "cabal_sha256": "91cbc951a742fc2c95d5902be38fcf1b859c2891241bc353ff16154a8f7c35ae", + "component": "lib:unix", "flags": [], "package": "unix", "revision": 0, "source": "hackage", - "src_sha256": "5e59d9ca0f8e505d2203af7dba17c67275621fbcd4ed8fcbdd59e80df4d79a7d", - "version": "2.8.1.0" + "src_sha256": "cc287659427c80f3598c199387ba7eb7d4cc3270cbb31f75e2f677e879f26384", + "version": "2.8.1.1" }, { "cabal_sha256": "e384a4831b0ac0f8908a1d99d14ce44bf9c5fe2092eec5b2c47ea072d477a493", + "component": "lib:directory", "flags": [], "package": "directory", "revision": 0, @@ -110,19 +105,41 @@ "version": "1.3.8.1" }, { - "cabal_sha256": "d495b2a2a53da7e66163477a5837d2109074f8818fc938739b9ecf27d506050a", + "cabal_sha256": "3c9e1e6b4f2f956623375dd15b904144dd3183b28f1ce1afcce11192f6d868dd", + "component": "exe:alex", + "flags": [], + "package": "alex", + "revision": 0, + "source": "hackage", + "src_sha256": "7a1cd4e21399c40ea9372d1c03bf38698944b8437ce95cf27d1a7c262babe38e", + "version": "3.4.0.0" + }, + { + "cabal_sha256": "81f468c1c75fd6535152ab69b2d32ac6cfcc03e345267b069abe4da56ec95801", + "component": "lib:binary", + "flags": [], + "package": "binary", + "revision": 0, + "source": "hackage", + "src_sha256": "ac21ca63452dfc9b0bcab87c57699c531d87f7a9bcb6230ca46fba1b7faeebc0", + "version": "0.8.9.1" + }, + { + "cabal_sha256": "71b5fa8c64d3c1fd0a08f993463220867b08290a2256e94b0952bf0e8f5a45cc", + "component": "lib:text", "flags": [ "-developer", "+simdutf" ], "package": "text", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "c735be650a898606ce9f2c8642bc6ac6123eea82871d5e90f92797801f59efad", "version": "2.0.2" }, { "cabal_sha256": "5769242043b01bf759b07b7efedcb19607837ee79015fcddde34645664136aed", + "component": "lib:parsec", "flags": [], "package": "parsec", "revision": 0, @@ -132,6 +149,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal-syntax", "flags": [], "package": "Cabal-syntax", "revision": null, @@ -141,6 +159,7 @@ }, { "cabal_sha256": "49d8a7f372d35363011591b253cae4c8db8b9ec594590448e20b7bed7acaee98", + "component": "lib:process", "flags": [], "package": "process", "revision": 0, @@ -150,6 +169,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal", "flags": [], "package": "Cabal", "revision": null, @@ -158,18 +178,32 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "29b28d2e19ae9f5ff92cea4ab8d2e185408ee5de73b4127f7b485a904c9a8b15", + "cabal_sha256": "115b8c34b9f83603cfd9eb8b1e2d7ac520da0a4a43d96be435f06ce01a7bc95e", + "component": "exe:hsc2hs", + "flags": [ + "-in-ghc-tree" + ], + "package": "hsc2hs", + "revision": 0, + "source": "hackage", + "src_sha256": "c95b10ce0b2c881480e35118d738dcc9cefc435ec72baa0031af81d0d4d3bc0a", + "version": "0.68.9" + }, + { + "cabal_sha256": "e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def", + "component": "lib:network", "flags": [ "-devel" ], "package": "network", - "revision": 0, + "revision": 1, "source": "hackage", - "src_sha256": "fde2d4b065f1984c76755004c64a29ae9ec52c8bf74f2485d805ef577e7c7822", - "version": "3.1.2.8" + "src_sha256": "b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e", + "version": "3.1.4.0" }, { "cabal_sha256": "e5ae7c083ef3a22248558f8451669bb1c55ea8090f5908b86b9033743c161730", + "component": "lib:th-compat", "flags": [], "package": "th-compat", "revision": 2, @@ -179,6 +213,7 @@ }, { "cabal_sha256": "1fde59abf5d82a9666b4415bc2b2e9e33f6c1309074fda12d50410c7dbd95f3b", + "component": "lib:network-uri", "flags": [], "package": "network-uri", "revision": 0, @@ -187,7 +222,8 @@ "version": "2.6.4.2" }, { - "cabal_sha256": "b878d575c470bd1f72d37af6654d924ab2b9489d88de8a71bd74d9d5d726c013", + "cabal_sha256": "d9220cc1b8c1f287248d650910710b96e62e54530772e3bcd19dbdec6547f8ae", + "component": "lib:HTTP", "flags": [ "-conduit10", "+network-uri", @@ -195,13 +231,14 @@ "-warp-tests" ], "package": "HTTP", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "df31d8efec775124dab856d7177ddcba31be9f9e0836ebdab03d94392f2dd453", "version": "4000.4.1" }, { "cabal_sha256": "0bdd3486d3a1bcbed0513b46af4a13ca74b395313fa5b6e0068d6b7413b76a04", + "component": "lib:base-orphans", "flags": [], "package": "base-orphans", "revision": 0, @@ -211,6 +248,7 @@ }, { "cabal_sha256": "2ef1bd3511e82ba56f7f23cd793dd2da84338a1e7c2cbea5b151417afe3baada", + "component": "lib:data-array-byte", "flags": [], "package": "data-array-byte", "revision": 1, @@ -220,6 +258,7 @@ }, { "cabal_sha256": "585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a", + "component": "lib:hashable", "flags": [ "+integer-gmp", "-random-initial-seed" @@ -232,6 +271,7 @@ }, { "cabal_sha256": "46367dc0c8326dcbeb7b93f200b567491c2f6029bccf822b8bb26ee660397e08", + "component": "lib:async", "flags": [ "-bench" ], @@ -243,6 +283,7 @@ }, { "cabal_sha256": "64abad7816ab8cabed8489e29f807b3a6f828e0b2cec0eae404323d69d36df9a", + "component": "lib:base16-bytestring", "flags": [], "package": "base16-bytestring", "revision": 0, @@ -251,16 +292,18 @@ "version": "1.0.2.0" }, { - "cabal_sha256": "50ec0e229255d4c45cbdd568da011311b8887f304b931564886016f4984334d8", + "cabal_sha256": "45305ccf8914c66d385b518721472c7b8c858f1986945377f74f85c1e0d49803", + "component": "lib:base64-bytestring", "flags": [], "package": "base64-bytestring", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "fbf8ed30edde271eb605352021431d8f1b055f95a56af31fe2eacf6bdfdc49c9", "version": "1.2.1.0" }, { "cabal_sha256": "db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e", + "component": "lib:splitmix", "flags": [ "-optimised-mixer" ], @@ -272,6 +315,7 @@ }, { "cabal_sha256": "dea1f11e5569332dc6c8efaad1cb301016a5587b6754943a49f9de08ae0e56d9", + "component": "lib:random", "flags": [], "package": "random", "revision": 0, @@ -281,6 +325,7 @@ }, { "cabal_sha256": "4d33a49cd383d50af090f1b888642d10116e43809f9da6023d9fc6f67d2656ee", + "component": "lib:edit-distance", "flags": [], "package": "edit-distance", "revision": 1, @@ -290,6 +335,7 @@ }, { "cabal_sha256": null, + "component": "lib:cabal-install-solver", "flags": [ "-debug-conflict-sets", "-debug-expensive-assertions", @@ -302,19 +348,21 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "facd0c04925ef925ec05243471fd16055229fdf51f64db1a1049de0cc6c6dfc3", + "cabal_sha256": "72ce9095872eae653addca5f412ac8070d6282d8e1c8578c2237c33f2cbbf4bc", + "component": "lib:cryptohash-sha256", "flags": [ "-exe", "+use-cbits" ], "package": "cryptohash-sha256", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "73a7dc7163871a80837495039a099967b11f5c4fe70a118277842f7a713c6bf6", "version": "0.11.102.1" }, { "cabal_sha256": "ccce771562c49a2b29a52046ca68c62179e97e8fbeacdae32ca84a85445e8f42", + "component": "lib:echo", "flags": [ "-example" ], @@ -325,7 +373,8 @@ "version": "0.1.4" }, { - "cabal_sha256": "885c9e2410e5d91a08b199897df0867fecedf818216d7329a2d43a512833dd63", + "cabal_sha256": "3db04d7c18b9e68ba5eef3fa7eeca05e1e248958dd182290c8e6b010c81ef73e", + "component": "lib:ed25519", "flags": [ "+no-donna", "+test-doctests", @@ -333,49 +382,53 @@ "+test-properties" ], "package": "ed25519", - "revision": 6, + "revision": 7, "source": "hackage", "src_sha256": "d8a5958ebfa9309790efade64275dc5c441b568645c45ceed1b0c6ff36d6156d", "version": "0.0.5.0" }, { - "cabal_sha256": "efd4c08c4df1ac3f423858a834c0e3b5b4909febda66a901d12a8e1d57bddaa8", + "cabal_sha256": "9ab54ee4f80bbd8a3fddd639ea142b7039ee2deb27f7df031a93de1819e34146", + "component": "lib:lukko", "flags": [ "+ofd-locking" ], "package": "lukko", - "revision": 3, + "revision": 4, "source": "hackage", "src_sha256": "a80efb60cfa3dae18682c01980d76d5f7e413e191cd186992e1bf7388d48ab1f", "version": "0.1.1.3" }, { - "cabal_sha256": "bc14969ea4adfec6eee20264decf4a07c4002b38b2aa802d58d86b1a2cf7b895", + "cabal_sha256": "63dbcb0f507273a8331363e4c13a1fe91f4ea0c495883cf65f314629582a2630", + "component": "lib:tar", "flags": [ "-old-bytestring", "-old-time" ], "package": "tar", - "revision": 5, + "revision": 6, "source": "hackage", "src_sha256": "b384449f62b2b0aa3e6d2cb1004b8060b01f21ec93e7b63e7af6d8fad8a9f1de", "version": "0.5.1.1" }, { - "cabal_sha256": "9adce39e4ca0b7a87d45df0a243134816c57059a08e28cff5469c98ae1f54dfc", + "cabal_sha256": "386dd93bc0352bf6ad5c6bca4dee0442b52d95b4c34e85901064f3eb05c81731", + "component": "lib:zlib", "flags": [ "-bundled-c-zlib", "-non-blocking-ffi", "-pkg-config" ], "package": "zlib", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da", "version": "0.6.3.0" }, { - "cabal_sha256": "18405474813b37ddfc27778c88c549f444661432224999068417dfab3471281e", + "cabal_sha256": "2e5893334ee8967a990349a04953331b28e83bebd64d4f7cb46b71603d183d0c", + "component": "lib:hackage-security", "flags": [ "+base48", "+cabal-syntax", @@ -385,60 +438,79 @@ "+use-network-uri" ], "package": "hackage-security", - "revision": 2, + "revision": 5, "source": "hackage", "src_sha256": "52ee0576971955571d846b8e6c09638f89f4f7881f4a95173e44ccc0d856a066", "version": "0.6.2.3" }, { - "cabal_sha256": "4ff4425c710cddf440dfbac6cd52310bb6b23e17902390ff71c9fc7eaafc4fcc", + "cabal_sha256": "3a76c313f9f75e8e0b3c103c1bff5bbaf754da30cbddedc1d5b7061d001030e0", + "component": "lib:regex-base", "flags": [], "package": "regex-base", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "7b99408f580f5bb67a1c413e0bc735886608251331ad36322020f2169aea2ef1", "version": "0.94.0.2" }, { - "cabal_sha256": "9dbba4b65a3bb6975d9740814be5593c6b2d2d6a0b3febc8ec940edb9a9bbdf4", + "cabal_sha256": "d479ca2cc6274c15801169f83dae883c9b62b78af3c7b30ed3fbd4b4612156b8", + "component": "lib:regex-posix", "flags": [ "-_regex-posix-clib" ], "package": "regex-posix", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "c7827c391919227711e1cff0a762b1678fd8739f9c902fc183041ff34f59259c", "version": "0.96.0.1" }, { - "cabal_sha256": "61e2d98ff634b8b4b3db467772420c0f9c79c2da9ddf3d2daeb2af2417f2c535", + "cabal_sha256": "a42b4a473478db92f4728f755403db232b55445e3091a957be073fc8e84e5d46", + "component": "lib:resolv", "flags": [], "package": "resolv", - "revision": 5, + "revision": 1, "source": "hackage", - "src_sha256": "81a2bafad484db123cf8d17a02d98bb388a127fd0f822fa022589468a0e64671", - "version": "0.1.2.0" + "src_sha256": "880d283df9132a7375fa28670f71e86480a4f49972256dc2a204c648274ae74b", + "version": "0.2.0.2" }, { - "cabal_sha256": "6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2", + "cabal_sha256": "f4aad0eca90044cb1eba53b84f75d5fa142d25d695117730bf31178d409c4fe0", + "component": "lib:safe-exceptions", "flags": [], "package": "safe-exceptions", "revision": 0, "source": "hackage", - "src_sha256": "91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf", - "version": "0.1.7.3" + "src_sha256": "3c51d8d50c9b60ff8bf94f942fd92e3bea9e62c5afa778dfc9f707b79da41ef6", + "version": "0.1.7.4" }, { - "cabal_sha256": "868694b09361e7c6756542bcdcfba68a9b8b93410c6798709e475abd3751afe7", + "cabal_sha256": "8ed6242cab5b0e1a8c654424275ac178035d108dfe4d651053947790fcf83017", + "component": "lib:semaphore-compat", "flags": [], "package": "semaphore-compat", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "1c6e6fab021c2ccee5d86112fb1c0bd016d15e0cf70c489dae5fb5ec156ed9e2", "version": "1.0.0" }, { "cabal_sha256": null, + "component": "lib:cabal-install", + "flags": [ + "+lukko", + "+native-dns" + ], + "package": "cabal-install", + "revision": null, + "source": "local", + "src_sha256": null, + "version": "3.11.0.0" + }, + { + "cabal_sha256": null, + "component": "exe:cabal", "flags": [ "+lukko", "+native-dns" diff --git a/bootstrap/linux-9.0.2.json b/bootstrap/linux-9.0.2.json index 5700325f05c..36613ac64ea 100644 --- a/bootstrap/linux-9.0.2.json +++ b/bootstrap/linux-9.0.2.json @@ -24,6 +24,10 @@ "package": "deepseq", "version": "1.4.5.0" }, + { + "package": "containers", + "version": "0.6.4.1" + }, { "package": "ghc-boot-th", "version": "9.0.2" @@ -36,10 +40,6 @@ "package": "template-haskell", "version": "2.17.0.0" }, - { - "package": "containers", - "version": "0.6.4.1" - }, { "package": "transformers", "version": "0.5.6.2" @@ -63,45 +63,40 @@ ], "dependencies": [ { - "cabal_sha256": "55390b63bbd7846aab6b16b7b255cf5108a3a422798a1e9a3b674eb0c68ac20c", + "cabal_sha256": "458d4794a5ced371a844e325fe539dd5fee8fe41f78b6f00e6c70920b7dd18e3", + "component": "lib:bytestring", "flags": [], "package": "bytestring", "revision": 0, "source": "hackage", - "src_sha256": "491aaef7625c693a06c26ae7f097caf23d9e3f9cae14af5ab17e71abb39576d3", - "version": "0.11.4.0" + "src_sha256": "76193d39b66197107f452184597a4e458194c64731efbba1e9605550c732f7f4", + "version": "0.11.5.0" }, { - "cabal_sha256": "81f468c1c75fd6535152ab69b2d32ac6cfcc03e345267b069abe4da56ec95801", - "flags": [], - "package": "binary", - "revision": 0, - "source": "hackage", - "src_sha256": "ac21ca63452dfc9b0bcab87c57699c531d87f7a9bcb6230ca46fba1b7faeebc0", - "version": "0.8.9.1" - }, - { - "cabal_sha256": "ab6e3330c42817b0effb14cae9c60d5cdc41d61f7354d04bc529ed031113f27c", + "cabal_sha256": "2de84756d3907308230e34fcc7c1917a73f218f6d53838618b7d5b95dd33e2c3", + "component": "lib:filepath", "flags": [ "-cpphs" ], "package": "filepath", "revision": 0, "source": "hackage", - "src_sha256": "ed1d11173f5052461cd1df58b5ef4abbfa1803ad2b237da7ddb7c7d64e017de2", - "version": "1.4.100.3" + "src_sha256": "82876250347c2fdf0f9de5448ce44f02539f37951b671d9a30719a6c4f96e9ad", + "version": "1.4.100.4" }, { - "cabal_sha256": "26eeda14432a2fcc6049045068ecf59525ffff9196616a642b5ab2326a003692", + "cabal_sha256": "91cbc951a742fc2c95d5902be38fcf1b859c2891241bc353ff16154a8f7c35ae", + "component": "lib:unix", "flags": [], "package": "unix", "revision": 0, "source": "hackage", - "src_sha256": "5e59d9ca0f8e505d2203af7dba17c67275621fbcd4ed8fcbdd59e80df4d79a7d", - "version": "2.8.1.0" + "src_sha256": "cc287659427c80f3598c199387ba7eb7d4cc3270cbb31f75e2f677e879f26384", + "version": "2.8.1.1" }, { "cabal_sha256": "e384a4831b0ac0f8908a1d99d14ce44bf9c5fe2092eec5b2c47ea072d477a493", + "component": "lib:directory", "flags": [], "package": "directory", "revision": 0, @@ -110,19 +105,41 @@ "version": "1.3.8.1" }, { - "cabal_sha256": "d495b2a2a53da7e66163477a5837d2109074f8818fc938739b9ecf27d506050a", + "cabal_sha256": "3c9e1e6b4f2f956623375dd15b904144dd3183b28f1ce1afcce11192f6d868dd", + "component": "exe:alex", + "flags": [], + "package": "alex", + "revision": 0, + "source": "hackage", + "src_sha256": "7a1cd4e21399c40ea9372d1c03bf38698944b8437ce95cf27d1a7c262babe38e", + "version": "3.4.0.0" + }, + { + "cabal_sha256": "81f468c1c75fd6535152ab69b2d32ac6cfcc03e345267b069abe4da56ec95801", + "component": "lib:binary", + "flags": [], + "package": "binary", + "revision": 0, + "source": "hackage", + "src_sha256": "ac21ca63452dfc9b0bcab87c57699c531d87f7a9bcb6230ca46fba1b7faeebc0", + "version": "0.8.9.1" + }, + { + "cabal_sha256": "71b5fa8c64d3c1fd0a08f993463220867b08290a2256e94b0952bf0e8f5a45cc", + "component": "lib:text", "flags": [ "-developer", "+simdutf" ], "package": "text", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "c735be650a898606ce9f2c8642bc6ac6123eea82871d5e90f92797801f59efad", "version": "2.0.2" }, { "cabal_sha256": "5769242043b01bf759b07b7efedcb19607837ee79015fcddde34645664136aed", + "component": "lib:parsec", "flags": [], "package": "parsec", "revision": 0, @@ -132,6 +149,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal-syntax", "flags": [], "package": "Cabal-syntax", "revision": null, @@ -141,6 +159,7 @@ }, { "cabal_sha256": "49d8a7f372d35363011591b253cae4c8db8b9ec594590448e20b7bed7acaee98", + "component": "lib:process", "flags": [], "package": "process", "revision": 0, @@ -150,6 +169,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal", "flags": [], "package": "Cabal", "revision": null, @@ -158,18 +178,32 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "29b28d2e19ae9f5ff92cea4ab8d2e185408ee5de73b4127f7b485a904c9a8b15", + "cabal_sha256": "115b8c34b9f83603cfd9eb8b1e2d7ac520da0a4a43d96be435f06ce01a7bc95e", + "component": "exe:hsc2hs", + "flags": [ + "-in-ghc-tree" + ], + "package": "hsc2hs", + "revision": 0, + "source": "hackage", + "src_sha256": "c95b10ce0b2c881480e35118d738dcc9cefc435ec72baa0031af81d0d4d3bc0a", + "version": "0.68.9" + }, + { + "cabal_sha256": "e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def", + "component": "lib:network", "flags": [ "-devel" ], "package": "network", - "revision": 0, + "revision": 1, "source": "hackage", - "src_sha256": "fde2d4b065f1984c76755004c64a29ae9ec52c8bf74f2485d805ef577e7c7822", - "version": "3.1.2.8" + "src_sha256": "b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e", + "version": "3.1.4.0" }, { "cabal_sha256": "e5ae7c083ef3a22248558f8451669bb1c55ea8090f5908b86b9033743c161730", + "component": "lib:th-compat", "flags": [], "package": "th-compat", "revision": 2, @@ -179,6 +213,7 @@ }, { "cabal_sha256": "1fde59abf5d82a9666b4415bc2b2e9e33f6c1309074fda12d50410c7dbd95f3b", + "component": "lib:network-uri", "flags": [], "package": "network-uri", "revision": 0, @@ -187,7 +222,8 @@ "version": "2.6.4.2" }, { - "cabal_sha256": "b878d575c470bd1f72d37af6654d924ab2b9489d88de8a71bd74d9d5d726c013", + "cabal_sha256": "d9220cc1b8c1f287248d650910710b96e62e54530772e3bcd19dbdec6547f8ae", + "component": "lib:HTTP", "flags": [ "-conduit10", "+network-uri", @@ -195,13 +231,14 @@ "-warp-tests" ], "package": "HTTP", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "df31d8efec775124dab856d7177ddcba31be9f9e0836ebdab03d94392f2dd453", "version": "4000.4.1" }, { "cabal_sha256": "0bdd3486d3a1bcbed0513b46af4a13ca74b395313fa5b6e0068d6b7413b76a04", + "component": "lib:base-orphans", "flags": [], "package": "base-orphans", "revision": 0, @@ -211,6 +248,7 @@ }, { "cabal_sha256": "2ef1bd3511e82ba56f7f23cd793dd2da84338a1e7c2cbea5b151417afe3baada", + "component": "lib:data-array-byte", "flags": [], "package": "data-array-byte", "revision": 1, @@ -220,6 +258,7 @@ }, { "cabal_sha256": "585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a", + "component": "lib:hashable", "flags": [ "+integer-gmp", "-random-initial-seed" @@ -232,6 +271,7 @@ }, { "cabal_sha256": "46367dc0c8326dcbeb7b93f200b567491c2f6029bccf822b8bb26ee660397e08", + "component": "lib:async", "flags": [ "-bench" ], @@ -243,6 +283,7 @@ }, { "cabal_sha256": "64abad7816ab8cabed8489e29f807b3a6f828e0b2cec0eae404323d69d36df9a", + "component": "lib:base16-bytestring", "flags": [], "package": "base16-bytestring", "revision": 0, @@ -251,16 +292,18 @@ "version": "1.0.2.0" }, { - "cabal_sha256": "50ec0e229255d4c45cbdd568da011311b8887f304b931564886016f4984334d8", + "cabal_sha256": "45305ccf8914c66d385b518721472c7b8c858f1986945377f74f85c1e0d49803", + "component": "lib:base64-bytestring", "flags": [], "package": "base64-bytestring", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "fbf8ed30edde271eb605352021431d8f1b055f95a56af31fe2eacf6bdfdc49c9", "version": "1.2.1.0" }, { "cabal_sha256": "db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e", + "component": "lib:splitmix", "flags": [ "-optimised-mixer" ], @@ -272,6 +315,7 @@ }, { "cabal_sha256": "dea1f11e5569332dc6c8efaad1cb301016a5587b6754943a49f9de08ae0e56d9", + "component": "lib:random", "flags": [], "package": "random", "revision": 0, @@ -281,6 +325,7 @@ }, { "cabal_sha256": "4d33a49cd383d50af090f1b888642d10116e43809f9da6023d9fc6f67d2656ee", + "component": "lib:edit-distance", "flags": [], "package": "edit-distance", "revision": 1, @@ -290,6 +335,7 @@ }, { "cabal_sha256": null, + "component": "lib:cabal-install-solver", "flags": [ "-debug-conflict-sets", "-debug-expensive-assertions", @@ -302,19 +348,21 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "facd0c04925ef925ec05243471fd16055229fdf51f64db1a1049de0cc6c6dfc3", + "cabal_sha256": "72ce9095872eae653addca5f412ac8070d6282d8e1c8578c2237c33f2cbbf4bc", + "component": "lib:cryptohash-sha256", "flags": [ "-exe", "+use-cbits" ], "package": "cryptohash-sha256", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "73a7dc7163871a80837495039a099967b11f5c4fe70a118277842f7a713c6bf6", "version": "0.11.102.1" }, { "cabal_sha256": "ccce771562c49a2b29a52046ca68c62179e97e8fbeacdae32ca84a85445e8f42", + "component": "lib:echo", "flags": [ "-example" ], @@ -325,7 +373,8 @@ "version": "0.1.4" }, { - "cabal_sha256": "885c9e2410e5d91a08b199897df0867fecedf818216d7329a2d43a512833dd63", + "cabal_sha256": "3db04d7c18b9e68ba5eef3fa7eeca05e1e248958dd182290c8e6b010c81ef73e", + "component": "lib:ed25519", "flags": [ "+no-donna", "+test-doctests", @@ -333,49 +382,53 @@ "+test-properties" ], "package": "ed25519", - "revision": 6, + "revision": 7, "source": "hackage", "src_sha256": "d8a5958ebfa9309790efade64275dc5c441b568645c45ceed1b0c6ff36d6156d", "version": "0.0.5.0" }, { - "cabal_sha256": "efd4c08c4df1ac3f423858a834c0e3b5b4909febda66a901d12a8e1d57bddaa8", + "cabal_sha256": "9ab54ee4f80bbd8a3fddd639ea142b7039ee2deb27f7df031a93de1819e34146", + "component": "lib:lukko", "flags": [ "+ofd-locking" ], "package": "lukko", - "revision": 3, + "revision": 4, "source": "hackage", "src_sha256": "a80efb60cfa3dae18682c01980d76d5f7e413e191cd186992e1bf7388d48ab1f", "version": "0.1.1.3" }, { - "cabal_sha256": "bc14969ea4adfec6eee20264decf4a07c4002b38b2aa802d58d86b1a2cf7b895", + "cabal_sha256": "63dbcb0f507273a8331363e4c13a1fe91f4ea0c495883cf65f314629582a2630", + "component": "lib:tar", "flags": [ "-old-bytestring", "-old-time" ], "package": "tar", - "revision": 5, + "revision": 6, "source": "hackage", "src_sha256": "b384449f62b2b0aa3e6d2cb1004b8060b01f21ec93e7b63e7af6d8fad8a9f1de", "version": "0.5.1.1" }, { - "cabal_sha256": "9adce39e4ca0b7a87d45df0a243134816c57059a08e28cff5469c98ae1f54dfc", + "cabal_sha256": "386dd93bc0352bf6ad5c6bca4dee0442b52d95b4c34e85901064f3eb05c81731", + "component": "lib:zlib", "flags": [ "-bundled-c-zlib", "-non-blocking-ffi", "-pkg-config" ], "package": "zlib", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da", "version": "0.6.3.0" }, { - "cabal_sha256": "18405474813b37ddfc27778c88c549f444661432224999068417dfab3471281e", + "cabal_sha256": "2e5893334ee8967a990349a04953331b28e83bebd64d4f7cb46b71603d183d0c", + "component": "lib:hackage-security", "flags": [ "+base48", "+cabal-syntax", @@ -385,60 +438,79 @@ "+use-network-uri" ], "package": "hackage-security", - "revision": 2, + "revision": 5, "source": "hackage", "src_sha256": "52ee0576971955571d846b8e6c09638f89f4f7881f4a95173e44ccc0d856a066", "version": "0.6.2.3" }, { - "cabal_sha256": "4ff4425c710cddf440dfbac6cd52310bb6b23e17902390ff71c9fc7eaafc4fcc", + "cabal_sha256": "3a76c313f9f75e8e0b3c103c1bff5bbaf754da30cbddedc1d5b7061d001030e0", + "component": "lib:regex-base", "flags": [], "package": "regex-base", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "7b99408f580f5bb67a1c413e0bc735886608251331ad36322020f2169aea2ef1", "version": "0.94.0.2" }, { - "cabal_sha256": "9dbba4b65a3bb6975d9740814be5593c6b2d2d6a0b3febc8ec940edb9a9bbdf4", + "cabal_sha256": "d479ca2cc6274c15801169f83dae883c9b62b78af3c7b30ed3fbd4b4612156b8", + "component": "lib:regex-posix", "flags": [ "-_regex-posix-clib" ], "package": "regex-posix", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "c7827c391919227711e1cff0a762b1678fd8739f9c902fc183041ff34f59259c", "version": "0.96.0.1" }, { - "cabal_sha256": "61e2d98ff634b8b4b3db467772420c0f9c79c2da9ddf3d2daeb2af2417f2c535", + "cabal_sha256": "a42b4a473478db92f4728f755403db232b55445e3091a957be073fc8e84e5d46", + "component": "lib:resolv", "flags": [], "package": "resolv", - "revision": 5, + "revision": 1, "source": "hackage", - "src_sha256": "81a2bafad484db123cf8d17a02d98bb388a127fd0f822fa022589468a0e64671", - "version": "0.1.2.0" + "src_sha256": "880d283df9132a7375fa28670f71e86480a4f49972256dc2a204c648274ae74b", + "version": "0.2.0.2" }, { - "cabal_sha256": "6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2", + "cabal_sha256": "f4aad0eca90044cb1eba53b84f75d5fa142d25d695117730bf31178d409c4fe0", + "component": "lib:safe-exceptions", "flags": [], "package": "safe-exceptions", "revision": 0, "source": "hackage", - "src_sha256": "91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf", - "version": "0.1.7.3" + "src_sha256": "3c51d8d50c9b60ff8bf94f942fd92e3bea9e62c5afa778dfc9f707b79da41ef6", + "version": "0.1.7.4" }, { - "cabal_sha256": "868694b09361e7c6756542bcdcfba68a9b8b93410c6798709e475abd3751afe7", + "cabal_sha256": "8ed6242cab5b0e1a8c654424275ac178035d108dfe4d651053947790fcf83017", + "component": "lib:semaphore-compat", "flags": [], "package": "semaphore-compat", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "1c6e6fab021c2ccee5d86112fb1c0bd016d15e0cf70c489dae5fb5ec156ed9e2", "version": "1.0.0" }, { "cabal_sha256": null, + "component": "lib:cabal-install", + "flags": [ + "+lukko", + "+native-dns" + ], + "package": "cabal-install", + "revision": null, + "source": "local", + "src_sha256": null, + "version": "3.11.0.0" + }, + { + "cabal_sha256": null, + "component": "exe:cabal", "flags": [ "+lukko", "+native-dns" diff --git a/bootstrap/linux-9.2.7.json b/bootstrap/linux-9.2.7.json index 3b8fda58d69..4cc8973f751 100644 --- a/bootstrap/linux-9.2.7.json +++ b/bootstrap/linux-9.2.7.json @@ -24,6 +24,10 @@ "package": "deepseq", "version": "1.4.6.1" }, + { + "package": "containers", + "version": "0.6.5.1" + }, { "package": "ghc-boot-th", "version": "9.2.7" @@ -40,14 +44,6 @@ "package": "bytestring", "version": "0.11.4.0" }, - { - "package": "containers", - "version": "0.6.5.1" - }, - { - "package": "binary", - "version": "0.8.9.0" - }, { "package": "transformers", "version": "0.5.6.2" @@ -68,6 +64,10 @@ "package": "time", "version": "1.11.1.1" }, + { + "package": "binary", + "version": "0.8.9.0" + }, { "package": "text", "version": "1.2.5.0" @@ -79,27 +79,30 @@ ], "dependencies": [ { - "cabal_sha256": "ab6e3330c42817b0effb14cae9c60d5cdc41d61f7354d04bc529ed031113f27c", + "cabal_sha256": "2de84756d3907308230e34fcc7c1917a73f218f6d53838618b7d5b95dd33e2c3", + "component": "lib:filepath", "flags": [ "-cpphs" ], "package": "filepath", "revision": 0, "source": "hackage", - "src_sha256": "ed1d11173f5052461cd1df58b5ef4abbfa1803ad2b237da7ddb7c7d64e017de2", - "version": "1.4.100.3" + "src_sha256": "82876250347c2fdf0f9de5448ce44f02539f37951b671d9a30719a6c4f96e9ad", + "version": "1.4.100.4" }, { - "cabal_sha256": "26eeda14432a2fcc6049045068ecf59525ffff9196616a642b5ab2326a003692", + "cabal_sha256": "91cbc951a742fc2c95d5902be38fcf1b859c2891241bc353ff16154a8f7c35ae", + "component": "lib:unix", "flags": [], "package": "unix", "revision": 0, "source": "hackage", - "src_sha256": "5e59d9ca0f8e505d2203af7dba17c67275621fbcd4ed8fcbdd59e80df4d79a7d", - "version": "2.8.1.0" + "src_sha256": "cc287659427c80f3598c199387ba7eb7d4cc3270cbb31f75e2f677e879f26384", + "version": "2.8.1.1" }, { "cabal_sha256": "e384a4831b0ac0f8908a1d99d14ce44bf9c5fe2092eec5b2c47ea072d477a493", + "component": "lib:directory", "flags": [], "package": "directory", "revision": 0, @@ -107,8 +110,19 @@ "src_sha256": "bd8253197587d32d4553070d2de89d3817176860932b0e9ab7bb7ba3759d8e9c", "version": "1.3.8.1" }, + { + "cabal_sha256": "3c9e1e6b4f2f956623375dd15b904144dd3183b28f1ce1afcce11192f6d868dd", + "component": "exe:alex", + "flags": [], + "package": "alex", + "revision": 0, + "source": "hackage", + "src_sha256": "7a1cd4e21399c40ea9372d1c03bf38698944b8437ce95cf27d1a7c262babe38e", + "version": "3.4.0.0" + }, { "cabal_sha256": null, + "component": "lib:Cabal-syntax", "flags": [], "package": "Cabal-syntax", "revision": null, @@ -118,6 +132,7 @@ }, { "cabal_sha256": "49d8a7f372d35363011591b253cae4c8db8b9ec594590448e20b7bed7acaee98", + "component": "lib:process", "flags": [], "package": "process", "revision": 0, @@ -127,6 +142,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal", "flags": [], "package": "Cabal", "revision": null, @@ -135,18 +151,32 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "29b28d2e19ae9f5ff92cea4ab8d2e185408ee5de73b4127f7b485a904c9a8b15", + "cabal_sha256": "115b8c34b9f83603cfd9eb8b1e2d7ac520da0a4a43d96be435f06ce01a7bc95e", + "component": "exe:hsc2hs", + "flags": [ + "-in-ghc-tree" + ], + "package": "hsc2hs", + "revision": 0, + "source": "hackage", + "src_sha256": "c95b10ce0b2c881480e35118d738dcc9cefc435ec72baa0031af81d0d4d3bc0a", + "version": "0.68.9" + }, + { + "cabal_sha256": "e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def", + "component": "lib:network", "flags": [ "-devel" ], "package": "network", - "revision": 0, + "revision": 1, "source": "hackage", - "src_sha256": "fde2d4b065f1984c76755004c64a29ae9ec52c8bf74f2485d805ef577e7c7822", - "version": "3.1.2.8" + "src_sha256": "b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e", + "version": "3.1.4.0" }, { "cabal_sha256": "e5ae7c083ef3a22248558f8451669bb1c55ea8090f5908b86b9033743c161730", + "component": "lib:th-compat", "flags": [], "package": "th-compat", "revision": 2, @@ -156,6 +186,7 @@ }, { "cabal_sha256": "1fde59abf5d82a9666b4415bc2b2e9e33f6c1309074fda12d50410c7dbd95f3b", + "component": "lib:network-uri", "flags": [], "package": "network-uri", "revision": 0, @@ -164,7 +195,8 @@ "version": "2.6.4.2" }, { - "cabal_sha256": "b878d575c470bd1f72d37af6654d924ab2b9489d88de8a71bd74d9d5d726c013", + "cabal_sha256": "d9220cc1b8c1f287248d650910710b96e62e54530772e3bcd19dbdec6547f8ae", + "component": "lib:HTTP", "flags": [ "-conduit10", "+network-uri", @@ -172,13 +204,14 @@ "-warp-tests" ], "package": "HTTP", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "df31d8efec775124dab856d7177ddcba31be9f9e0836ebdab03d94392f2dd453", "version": "4000.4.1" }, { "cabal_sha256": "2ef1bd3511e82ba56f7f23cd793dd2da84338a1e7c2cbea5b151417afe3baada", + "component": "lib:data-array-byte", "flags": [], "package": "data-array-byte", "revision": 1, @@ -188,6 +221,7 @@ }, { "cabal_sha256": "585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a", + "component": "lib:hashable", "flags": [ "+integer-gmp", "-random-initial-seed" @@ -200,6 +234,7 @@ }, { "cabal_sha256": "46367dc0c8326dcbeb7b93f200b567491c2f6029bccf822b8bb26ee660397e08", + "component": "lib:async", "flags": [ "-bench" ], @@ -211,6 +246,7 @@ }, { "cabal_sha256": "64abad7816ab8cabed8489e29f807b3a6f828e0b2cec0eae404323d69d36df9a", + "component": "lib:base16-bytestring", "flags": [], "package": "base16-bytestring", "revision": 0, @@ -219,16 +255,18 @@ "version": "1.0.2.0" }, { - "cabal_sha256": "50ec0e229255d4c45cbdd568da011311b8887f304b931564886016f4984334d8", + "cabal_sha256": "45305ccf8914c66d385b518721472c7b8c858f1986945377f74f85c1e0d49803", + "component": "lib:base64-bytestring", "flags": [], "package": "base64-bytestring", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "fbf8ed30edde271eb605352021431d8f1b055f95a56af31fe2eacf6bdfdc49c9", "version": "1.2.1.0" }, { "cabal_sha256": "db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e", + "component": "lib:splitmix", "flags": [ "-optimised-mixer" ], @@ -240,6 +278,7 @@ }, { "cabal_sha256": "dea1f11e5569332dc6c8efaad1cb301016a5587b6754943a49f9de08ae0e56d9", + "component": "lib:random", "flags": [], "package": "random", "revision": 0, @@ -249,6 +288,7 @@ }, { "cabal_sha256": "4d33a49cd383d50af090f1b888642d10116e43809f9da6023d9fc6f67d2656ee", + "component": "lib:edit-distance", "flags": [], "package": "edit-distance", "revision": 1, @@ -258,6 +298,7 @@ }, { "cabal_sha256": null, + "component": "lib:cabal-install-solver", "flags": [ "-debug-conflict-sets", "-debug-expensive-assertions", @@ -270,19 +311,21 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "facd0c04925ef925ec05243471fd16055229fdf51f64db1a1049de0cc6c6dfc3", + "cabal_sha256": "72ce9095872eae653addca5f412ac8070d6282d8e1c8578c2237c33f2cbbf4bc", + "component": "lib:cryptohash-sha256", "flags": [ "-exe", "+use-cbits" ], "package": "cryptohash-sha256", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "73a7dc7163871a80837495039a099967b11f5c4fe70a118277842f7a713c6bf6", "version": "0.11.102.1" }, { "cabal_sha256": "ccce771562c49a2b29a52046ca68c62179e97e8fbeacdae32ca84a85445e8f42", + "component": "lib:echo", "flags": [ "-example" ], @@ -293,7 +336,8 @@ "version": "0.1.4" }, { - "cabal_sha256": "885c9e2410e5d91a08b199897df0867fecedf818216d7329a2d43a512833dd63", + "cabal_sha256": "3db04d7c18b9e68ba5eef3fa7eeca05e1e248958dd182290c8e6b010c81ef73e", + "component": "lib:ed25519", "flags": [ "+no-donna", "+test-doctests", @@ -301,49 +345,53 @@ "+test-properties" ], "package": "ed25519", - "revision": 6, + "revision": 7, "source": "hackage", "src_sha256": "d8a5958ebfa9309790efade64275dc5c441b568645c45ceed1b0c6ff36d6156d", "version": "0.0.5.0" }, { - "cabal_sha256": "efd4c08c4df1ac3f423858a834c0e3b5b4909febda66a901d12a8e1d57bddaa8", + "cabal_sha256": "9ab54ee4f80bbd8a3fddd639ea142b7039ee2deb27f7df031a93de1819e34146", + "component": "lib:lukko", "flags": [ "+ofd-locking" ], "package": "lukko", - "revision": 3, + "revision": 4, "source": "hackage", "src_sha256": "a80efb60cfa3dae18682c01980d76d5f7e413e191cd186992e1bf7388d48ab1f", "version": "0.1.1.3" }, { - "cabal_sha256": "bc14969ea4adfec6eee20264decf4a07c4002b38b2aa802d58d86b1a2cf7b895", + "cabal_sha256": "63dbcb0f507273a8331363e4c13a1fe91f4ea0c495883cf65f314629582a2630", + "component": "lib:tar", "flags": [ "-old-bytestring", "-old-time" ], "package": "tar", - "revision": 5, + "revision": 6, "source": "hackage", "src_sha256": "b384449f62b2b0aa3e6d2cb1004b8060b01f21ec93e7b63e7af6d8fad8a9f1de", "version": "0.5.1.1" }, { - "cabal_sha256": "9adce39e4ca0b7a87d45df0a243134816c57059a08e28cff5469c98ae1f54dfc", + "cabal_sha256": "386dd93bc0352bf6ad5c6bca4dee0442b52d95b4c34e85901064f3eb05c81731", + "component": "lib:zlib", "flags": [ "-bundled-c-zlib", "-non-blocking-ffi", "-pkg-config" ], "package": "zlib", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da", "version": "0.6.3.0" }, { - "cabal_sha256": "18405474813b37ddfc27778c88c549f444661432224999068417dfab3471281e", + "cabal_sha256": "2e5893334ee8967a990349a04953331b28e83bebd64d4f7cb46b71603d183d0c", + "component": "lib:hackage-security", "flags": [ "+base48", "+cabal-syntax", @@ -353,60 +401,79 @@ "+use-network-uri" ], "package": "hackage-security", - "revision": 2, + "revision": 5, "source": "hackage", "src_sha256": "52ee0576971955571d846b8e6c09638f89f4f7881f4a95173e44ccc0d856a066", "version": "0.6.2.3" }, { - "cabal_sha256": "4ff4425c710cddf440dfbac6cd52310bb6b23e17902390ff71c9fc7eaafc4fcc", + "cabal_sha256": "3a76c313f9f75e8e0b3c103c1bff5bbaf754da30cbddedc1d5b7061d001030e0", + "component": "lib:regex-base", "flags": [], "package": "regex-base", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "7b99408f580f5bb67a1c413e0bc735886608251331ad36322020f2169aea2ef1", "version": "0.94.0.2" }, { - "cabal_sha256": "9dbba4b65a3bb6975d9740814be5593c6b2d2d6a0b3febc8ec940edb9a9bbdf4", + "cabal_sha256": "d479ca2cc6274c15801169f83dae883c9b62b78af3c7b30ed3fbd4b4612156b8", + "component": "lib:regex-posix", "flags": [ "-_regex-posix-clib" ], "package": "regex-posix", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "c7827c391919227711e1cff0a762b1678fd8739f9c902fc183041ff34f59259c", "version": "0.96.0.1" }, { - "cabal_sha256": "61e2d98ff634b8b4b3db467772420c0f9c79c2da9ddf3d2daeb2af2417f2c535", + "cabal_sha256": "a42b4a473478db92f4728f755403db232b55445e3091a957be073fc8e84e5d46", + "component": "lib:resolv", "flags": [], "package": "resolv", - "revision": 5, + "revision": 1, "source": "hackage", - "src_sha256": "81a2bafad484db123cf8d17a02d98bb388a127fd0f822fa022589468a0e64671", - "version": "0.1.2.0" + "src_sha256": "880d283df9132a7375fa28670f71e86480a4f49972256dc2a204c648274ae74b", + "version": "0.2.0.2" }, { - "cabal_sha256": "6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2", + "cabal_sha256": "f4aad0eca90044cb1eba53b84f75d5fa142d25d695117730bf31178d409c4fe0", + "component": "lib:safe-exceptions", "flags": [], "package": "safe-exceptions", "revision": 0, "source": "hackage", - "src_sha256": "91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf", - "version": "0.1.7.3" + "src_sha256": "3c51d8d50c9b60ff8bf94f942fd92e3bea9e62c5afa778dfc9f707b79da41ef6", + "version": "0.1.7.4" }, { - "cabal_sha256": "868694b09361e7c6756542bcdcfba68a9b8b93410c6798709e475abd3751afe7", + "cabal_sha256": "8ed6242cab5b0e1a8c654424275ac178035d108dfe4d651053947790fcf83017", + "component": "lib:semaphore-compat", "flags": [], "package": "semaphore-compat", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "1c6e6fab021c2ccee5d86112fb1c0bd016d15e0cf70c489dae5fb5ec156ed9e2", "version": "1.0.0" }, { "cabal_sha256": null, + "component": "lib:cabal-install", + "flags": [ + "+lukko", + "+native-dns" + ], + "package": "cabal-install", + "revision": null, + "source": "local", + "src_sha256": null, + "version": "3.11.0.0" + }, + { + "cabal_sha256": null, + "component": "exe:cabal", "flags": [ "+lukko", "+native-dns" diff --git a/bootstrap/linux-9.4.4.json b/bootstrap/linux-9.4.4.json index bcb80b9104a..af00acf12af 100644 --- a/bootstrap/linux-9.4.4.json +++ b/bootstrap/linux-9.4.4.json @@ -36,17 +36,13 @@ "package": "template-haskell", "version": "2.19.0.0" }, - { - "package": "bytestring", - "version": "0.11.3.1" - }, { "package": "containers", "version": "0.6.6" }, { - "package": "binary", - "version": "0.8.9.1" + "package": "bytestring", + "version": "0.11.3.1" }, { "package": "transformers", @@ -68,6 +64,10 @@ "package": "time", "version": "1.12.2" }, + { + "package": "binary", + "version": "0.8.9.1" + }, { "package": "text", "version": "2.0.1" @@ -79,27 +79,30 @@ ], "dependencies": [ { - "cabal_sha256": "ab6e3330c42817b0effb14cae9c60d5cdc41d61f7354d04bc529ed031113f27c", + "cabal_sha256": "2de84756d3907308230e34fcc7c1917a73f218f6d53838618b7d5b95dd33e2c3", + "component": "lib:filepath", "flags": [ "-cpphs" ], "package": "filepath", "revision": 0, "source": "hackage", - "src_sha256": "ed1d11173f5052461cd1df58b5ef4abbfa1803ad2b237da7ddb7c7d64e017de2", - "version": "1.4.100.3" + "src_sha256": "82876250347c2fdf0f9de5448ce44f02539f37951b671d9a30719a6c4f96e9ad", + "version": "1.4.100.4" }, { - "cabal_sha256": "26eeda14432a2fcc6049045068ecf59525ffff9196616a642b5ab2326a003692", + "cabal_sha256": "91cbc951a742fc2c95d5902be38fcf1b859c2891241bc353ff16154a8f7c35ae", + "component": "lib:unix", "flags": [], "package": "unix", "revision": 0, "source": "hackage", - "src_sha256": "5e59d9ca0f8e505d2203af7dba17c67275621fbcd4ed8fcbdd59e80df4d79a7d", - "version": "2.8.1.0" + "src_sha256": "cc287659427c80f3598c199387ba7eb7d4cc3270cbb31f75e2f677e879f26384", + "version": "2.8.1.1" }, { "cabal_sha256": "e384a4831b0ac0f8908a1d99d14ce44bf9c5fe2092eec5b2c47ea072d477a493", + "component": "lib:directory", "flags": [], "package": "directory", "revision": 0, @@ -107,8 +110,19 @@ "src_sha256": "bd8253197587d32d4553070d2de89d3817176860932b0e9ab7bb7ba3759d8e9c", "version": "1.3.8.1" }, + { + "cabal_sha256": "3c9e1e6b4f2f956623375dd15b904144dd3183b28f1ce1afcce11192f6d868dd", + "component": "exe:alex", + "flags": [], + "package": "alex", + "revision": 0, + "source": "hackage", + "src_sha256": "7a1cd4e21399c40ea9372d1c03bf38698944b8437ce95cf27d1a7c262babe38e", + "version": "3.4.0.0" + }, { "cabal_sha256": null, + "component": "lib:Cabal-syntax", "flags": [], "package": "Cabal-syntax", "revision": null, @@ -118,6 +132,7 @@ }, { "cabal_sha256": "49d8a7f372d35363011591b253cae4c8db8b9ec594590448e20b7bed7acaee98", + "component": "lib:process", "flags": [], "package": "process", "revision": 0, @@ -127,6 +142,7 @@ }, { "cabal_sha256": null, + "component": "lib:Cabal", "flags": [], "package": "Cabal", "revision": null, @@ -135,18 +151,32 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "29b28d2e19ae9f5ff92cea4ab8d2e185408ee5de73b4127f7b485a904c9a8b15", + "cabal_sha256": "115b8c34b9f83603cfd9eb8b1e2d7ac520da0a4a43d96be435f06ce01a7bc95e", + "component": "exe:hsc2hs", + "flags": [ + "-in-ghc-tree" + ], + "package": "hsc2hs", + "revision": 0, + "source": "hackage", + "src_sha256": "c95b10ce0b2c881480e35118d738dcc9cefc435ec72baa0031af81d0d4d3bc0a", + "version": "0.68.9" + }, + { + "cabal_sha256": "e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def", + "component": "lib:network", "flags": [ "-devel" ], "package": "network", - "revision": 0, + "revision": 1, "source": "hackage", - "src_sha256": "fde2d4b065f1984c76755004c64a29ae9ec52c8bf74f2485d805ef577e7c7822", - "version": "3.1.2.8" + "src_sha256": "b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e", + "version": "3.1.4.0" }, { "cabal_sha256": "e5ae7c083ef3a22248558f8451669bb1c55ea8090f5908b86b9033743c161730", + "component": "lib:th-compat", "flags": [], "package": "th-compat", "revision": 2, @@ -156,6 +186,7 @@ }, { "cabal_sha256": "1fde59abf5d82a9666b4415bc2b2e9e33f6c1309074fda12d50410c7dbd95f3b", + "component": "lib:network-uri", "flags": [], "package": "network-uri", "revision": 0, @@ -164,7 +195,8 @@ "version": "2.6.4.2" }, { - "cabal_sha256": "b878d575c470bd1f72d37af6654d924ab2b9489d88de8a71bd74d9d5d726c013", + "cabal_sha256": "d9220cc1b8c1f287248d650910710b96e62e54530772e3bcd19dbdec6547f8ae", + "component": "lib:HTTP", "flags": [ "-conduit10", "+network-uri", @@ -172,13 +204,14 @@ "-warp-tests" ], "package": "HTTP", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "df31d8efec775124dab856d7177ddcba31be9f9e0836ebdab03d94392f2dd453", "version": "4000.4.1" }, { "cabal_sha256": "585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a", + "component": "lib:hashable", "flags": [ "+integer-gmp", "-random-initial-seed" @@ -191,6 +224,7 @@ }, { "cabal_sha256": "46367dc0c8326dcbeb7b93f200b567491c2f6029bccf822b8bb26ee660397e08", + "component": "lib:async", "flags": [ "-bench" ], @@ -202,6 +236,7 @@ }, { "cabal_sha256": "64abad7816ab8cabed8489e29f807b3a6f828e0b2cec0eae404323d69d36df9a", + "component": "lib:base16-bytestring", "flags": [], "package": "base16-bytestring", "revision": 0, @@ -210,16 +245,18 @@ "version": "1.0.2.0" }, { - "cabal_sha256": "50ec0e229255d4c45cbdd568da011311b8887f304b931564886016f4984334d8", + "cabal_sha256": "45305ccf8914c66d385b518721472c7b8c858f1986945377f74f85c1e0d49803", + "component": "lib:base64-bytestring", "flags": [], "package": "base64-bytestring", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "fbf8ed30edde271eb605352021431d8f1b055f95a56af31fe2eacf6bdfdc49c9", "version": "1.2.1.0" }, { "cabal_sha256": "db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e", + "component": "lib:splitmix", "flags": [ "-optimised-mixer" ], @@ -231,6 +268,7 @@ }, { "cabal_sha256": "dea1f11e5569332dc6c8efaad1cb301016a5587b6754943a49f9de08ae0e56d9", + "component": "lib:random", "flags": [], "package": "random", "revision": 0, @@ -240,6 +278,7 @@ }, { "cabal_sha256": "4d33a49cd383d50af090f1b888642d10116e43809f9da6023d9fc6f67d2656ee", + "component": "lib:edit-distance", "flags": [], "package": "edit-distance", "revision": 1, @@ -249,6 +288,7 @@ }, { "cabal_sha256": null, + "component": "lib:cabal-install-solver", "flags": [ "-debug-conflict-sets", "-debug-expensive-assertions", @@ -261,19 +301,21 @@ "version": "3.11.0.0" }, { - "cabal_sha256": "facd0c04925ef925ec05243471fd16055229fdf51f64db1a1049de0cc6c6dfc3", + "cabal_sha256": "72ce9095872eae653addca5f412ac8070d6282d8e1c8578c2237c33f2cbbf4bc", + "component": "lib:cryptohash-sha256", "flags": [ "-exe", "+use-cbits" ], "package": "cryptohash-sha256", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "73a7dc7163871a80837495039a099967b11f5c4fe70a118277842f7a713c6bf6", "version": "0.11.102.1" }, { "cabal_sha256": "ccce771562c49a2b29a52046ca68c62179e97e8fbeacdae32ca84a85445e8f42", + "component": "lib:echo", "flags": [ "-example" ], @@ -284,7 +326,8 @@ "version": "0.1.4" }, { - "cabal_sha256": "885c9e2410e5d91a08b199897df0867fecedf818216d7329a2d43a512833dd63", + "cabal_sha256": "3db04d7c18b9e68ba5eef3fa7eeca05e1e248958dd182290c8e6b010c81ef73e", + "component": "lib:ed25519", "flags": [ "+no-donna", "+test-doctests", @@ -292,49 +335,53 @@ "+test-properties" ], "package": "ed25519", - "revision": 6, + "revision": 7, "source": "hackage", "src_sha256": "d8a5958ebfa9309790efade64275dc5c441b568645c45ceed1b0c6ff36d6156d", "version": "0.0.5.0" }, { - "cabal_sha256": "efd4c08c4df1ac3f423858a834c0e3b5b4909febda66a901d12a8e1d57bddaa8", + "cabal_sha256": "9ab54ee4f80bbd8a3fddd639ea142b7039ee2deb27f7df031a93de1819e34146", + "component": "lib:lukko", "flags": [ "+ofd-locking" ], "package": "lukko", - "revision": 3, + "revision": 4, "source": "hackage", "src_sha256": "a80efb60cfa3dae18682c01980d76d5f7e413e191cd186992e1bf7388d48ab1f", "version": "0.1.1.3" }, { - "cabal_sha256": "bc14969ea4adfec6eee20264decf4a07c4002b38b2aa802d58d86b1a2cf7b895", + "cabal_sha256": "63dbcb0f507273a8331363e4c13a1fe91f4ea0c495883cf65f314629582a2630", + "component": "lib:tar", "flags": [ "-old-bytestring", "-old-time" ], "package": "tar", - "revision": 5, + "revision": 6, "source": "hackage", "src_sha256": "b384449f62b2b0aa3e6d2cb1004b8060b01f21ec93e7b63e7af6d8fad8a9f1de", "version": "0.5.1.1" }, { - "cabal_sha256": "9adce39e4ca0b7a87d45df0a243134816c57059a08e28cff5469c98ae1f54dfc", + "cabal_sha256": "386dd93bc0352bf6ad5c6bca4dee0442b52d95b4c34e85901064f3eb05c81731", + "component": "lib:zlib", "flags": [ "-bundled-c-zlib", "-non-blocking-ffi", "-pkg-config" ], "package": "zlib", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da", "version": "0.6.3.0" }, { - "cabal_sha256": "18405474813b37ddfc27778c88c549f444661432224999068417dfab3471281e", + "cabal_sha256": "2e5893334ee8967a990349a04953331b28e83bebd64d4f7cb46b71603d183d0c", + "component": "lib:hackage-security", "flags": [ "+base48", "+cabal-syntax", @@ -344,60 +391,79 @@ "+use-network-uri" ], "package": "hackage-security", - "revision": 2, + "revision": 5, "source": "hackage", "src_sha256": "52ee0576971955571d846b8e6c09638f89f4f7881f4a95173e44ccc0d856a066", "version": "0.6.2.3" }, { - "cabal_sha256": "4ff4425c710cddf440dfbac6cd52310bb6b23e17902390ff71c9fc7eaafc4fcc", + "cabal_sha256": "3a76c313f9f75e8e0b3c103c1bff5bbaf754da30cbddedc1d5b7061d001030e0", + "component": "lib:regex-base", "flags": [], "package": "regex-base", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "7b99408f580f5bb67a1c413e0bc735886608251331ad36322020f2169aea2ef1", "version": "0.94.0.2" }, { - "cabal_sha256": "9dbba4b65a3bb6975d9740814be5593c6b2d2d6a0b3febc8ec940edb9a9bbdf4", + "cabal_sha256": "d479ca2cc6274c15801169f83dae883c9b62b78af3c7b30ed3fbd4b4612156b8", + "component": "lib:regex-posix", "flags": [ "-_regex-posix-clib" ], "package": "regex-posix", - "revision": 1, + "revision": 2, "source": "hackage", "src_sha256": "c7827c391919227711e1cff0a762b1678fd8739f9c902fc183041ff34f59259c", "version": "0.96.0.1" }, { - "cabal_sha256": "61e2d98ff634b8b4b3db467772420c0f9c79c2da9ddf3d2daeb2af2417f2c535", + "cabal_sha256": "a42b4a473478db92f4728f755403db232b55445e3091a957be073fc8e84e5d46", + "component": "lib:resolv", "flags": [], "package": "resolv", - "revision": 5, + "revision": 1, "source": "hackage", - "src_sha256": "81a2bafad484db123cf8d17a02d98bb388a127fd0f822fa022589468a0e64671", - "version": "0.1.2.0" + "src_sha256": "880d283df9132a7375fa28670f71e86480a4f49972256dc2a204c648274ae74b", + "version": "0.2.0.2" }, { - "cabal_sha256": "6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2", + "cabal_sha256": "f4aad0eca90044cb1eba53b84f75d5fa142d25d695117730bf31178d409c4fe0", + "component": "lib:safe-exceptions", "flags": [], "package": "safe-exceptions", "revision": 0, "source": "hackage", - "src_sha256": "91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf", - "version": "0.1.7.3" + "src_sha256": "3c51d8d50c9b60ff8bf94f942fd92e3bea9e62c5afa778dfc9f707b79da41ef6", + "version": "0.1.7.4" }, { - "cabal_sha256": "868694b09361e7c6756542bcdcfba68a9b8b93410c6798709e475abd3751afe7", + "cabal_sha256": "8ed6242cab5b0e1a8c654424275ac178035d108dfe4d651053947790fcf83017", + "component": "lib:semaphore-compat", "flags": [], "package": "semaphore-compat", - "revision": 0, + "revision": 1, "source": "hackage", "src_sha256": "1c6e6fab021c2ccee5d86112fb1c0bd016d15e0cf70c489dae5fb5ec156ed9e2", "version": "1.0.0" }, { "cabal_sha256": null, + "component": "lib:cabal-install", + "flags": [ + "+lukko", + "+native-dns" + ], + "package": "cabal-install", + "revision": null, + "source": "local", + "src_sha256": null, + "version": "3.11.0.0" + }, + { + "cabal_sha256": null, + "component": "exe:cabal", "flags": [ "+lukko", "+native-dns" diff --git a/bootstrap/src/Main.hs b/bootstrap/src/Main.hs index 0ca636ea020..8f06acba2ce 100644 --- a/bootstrap/src/Main.hs +++ b/bootstrap/src/Main.hs @@ -1,11 +1,12 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE LambdaCase #-} +{-# OPTIONS_GHC -Wno-deferred-out-of-scope-variables #-} module Main (main) where -import Control.Monad (when) import Data.Either (partitionEithers) -import Data.Foldable (for_, traverse_) -import Data.Maybe (listToMaybe) +import Data.Foldable (for_) import Data.String (fromString) import Data.Traversable (for) import System.Environment (getArgs) @@ -18,10 +19,11 @@ import qualified Cabal.Plan as P import qualified Data.Aeson as A import qualified Data.ByteString.Lazy as LBS import qualified Data.Map.Strict as Map -import qualified Data.Set as Set import qualified Distribution.Types.PackageName as C import qualified Distribution.Types.Version as C import qualified Topograph as TG +import Control.Exception +import System.IO.Error (isDoesNotExistError) ------------------------------------------------------------------------------- -- Main @@ -31,8 +33,30 @@ main :: IO () main = do args <- getArgs case args of - [fp] -> main1 fp - _ -> die "Usage: cabal-bootstrap-gen plan.json" + [fp] -> + handleJust + (\e -> if isDoesNotExistError e then Just e else Nothing) + (\e -> die $ unlines ["~~~ ERROR ~~~", "", displayException e, "", cabalDirWarning]) + (main1 fp) + _ -> die "Usage: cabal-bootstrap-gen plan.json" + +cabalDirWarning :: String +cabalDirWarning = + unlines [ + "~~~ NOTE ~~~", + "", + "This script will look for cabal global config file in the following locations", + " - $CABAL_CONFIG", + " - $CABAL_DIR/config", + " - $HOME/.cabal/config (on Unix-like systems)", + " - %APPDATA%/cabal (on Windows)", + "", + "If you are using XDG paths or a entirely different location, you can set either", + "CABAL_CONFIG or CABAL_DIR to guide the script to the correct location.", + "", + "E.g.", + " $ CABAL_DIR=$HOME/.config/cabal cabal-bootstrap-gen" + ] main1 :: FilePath -> IO () main1 planPath = do @@ -50,69 +74,60 @@ main2 :: Map.Map C.PackageName I.PackageInfo -> P.PlanJson -> IO () main2 meta plan = do info $ show $ Map.keys $ P.pjUnits plan - -- find cabal-install:exe:cabal unit - (cabalUid, cabalUnit) <- case findCabalExe plan of - Just x -> return x - Nothing -> die "Cannot find cabal-install:exe:cabal unit" - - info $ "cabal-install:exe:cabal unit " ++ show cabalUid + let res = TG.runG (P.planJsonIdGraph plan) $ \g -> + map (TG.gFromVertex g) (reverse $ TG.gVertices g) - -- BFS from cabal unit, getting all dependencies - units <- bfs plan cabalUnit + units <- case res of + Left loop -> die $ "Loop in install-plan: " ++ show loop + Right uids -> for uids $ lookupUnit (P.pjUnits plan) - info $ "Unit order:" + info "Unit order:" for_ units $ \unit -> do info $ " - " ++ show (P.uId unit) (builtin, deps) <- fmap partitionEithers $ for units $ \unit -> do let P.PkgId pkgname@(P.PkgName tpkgname) ver@(P.Ver verdigits) = P.uPId unit - let uid = P.uId unit - let cpkgname :: C.PackageName cpkgname = C.mkPackageName (T.unpack tpkgname) let cversion :: C.Version cversion = C.mkVersion verdigits + let flags = [ (if fval then "+" else "-") ++ T.unpack fname + | (P.FlagName fname, fval) <- Map.toList (P.uFlags unit) + ] + let relInfo = Map.lookup cpkgname meta >>= \pkgInfo -> Map.lookup cversion $ I.piVersions pkgInfo case P.uType unit of P.UnitTypeBuiltin -> return $ Left Builtin { builtinPackageName = pkgname , builtinVersion = ver } - _ -> do - (src, rev, revhash) <- case P.uSha256 unit of - Just _ -> do - pkgInfo <- maybe (die $ "Cannot find " ++ show uid ++ " package metadata") return $ - Map.lookup cpkgname meta - relInfo <- maybe (die $ "Cannot find " ++ show uid ++ " version metadata") return $ - Map.lookup cversion $ I.piVersions pkgInfo - - return - ( Hackage - , Just $ fromIntegral (I.riRevision relInfo) - , P.sha256FromByteString $ I.getSHA256 $ getHash relInfo - ) - - Nothing -> case P.uType unit of - P.UnitTypeLocal -> return (Local, Nothing, Nothing) - t -> die $ "Unit of wrong type " ++ show uid ++ " " ++ show t - - return $ Right Dep - { depPackageName = pkgname - , depVersion = ver - , depSource = src - , depSrcHash = P.uSha256 unit - , depRevision = rev - , depRevHash = revhash - , depFlags = - [ (if fval then "+" else "-") ++ T.unpack fname - | (P.FlagName fname, fval) <- Map.toList (P.uFlags unit) - ] - } - + let component = case Map.keys (P.uComps unit) of + [c] -> Just (P.dispCompNameTarget pkgname c) + _ -> Nothing + + source <- + case P.uPkgSrc unit of + Just (P.RepoTarballPackage (P.RepoSecure _uri)) -> + return Hackage + Just (P.LocalUnpackedPackage _path) -> + return Local + pkgsrc -> + die $ "package source not supported: " ++ show pkgsrc + + return $ Right Dep + { depPackageName = pkgname + , depVersion = ver + , depSource = source + , depSrcHash = P.uSha256 unit + , depRevision = fromIntegral . I.riRevision <$> relInfo + , depRevHash = relInfo >>= P.sha256FromByteString . I.getSHA256 . getHash + , depFlags = flags + , depComponent = component + } LBS.putStr $ A.encode Result { resBuiltin = builtin , resDependencies = deps @@ -124,42 +139,6 @@ main2 meta plan = do getHash = I.riCabal #endif -bfs :: P.PlanJson -> P.Unit -> IO [P.Unit] -bfs plan unit0 = do - uids <- either (\loop -> die $ "Loop in install-plan " ++ show loop) id $ TG.runG am $ \g -> do - v <- maybe (die "Cannot find cabal-install unit in topograph") return $ - TG.gToVertex g $ P.uId unit0 - - let t = TG.dfs g v - - return $ map (TG.gFromVertex g) $ - -- nub and sort - reverse $ Set.toList $ Set.fromList $ concat t - - units <- for uids $ \uid -> do - unit <- lookupUnit (P.pjUnits plan) uid - case Map.toList (P.uComps unit) of - [(_, compinfo)] -> checkExeDeps uid (P.pjUnits plan) (P.ciExeDeps compinfo) - _ -> die $ "Unit with multiple components " ++ show uid - return unit - - -- Remove non-exe copies of cabal-install. Otherwise, cabal-install - -- may appear as cabal-install:lib before dependencies of - -- cabal-install:exe:cabal, and the bootstrap build tries to build - -- all of cabal-install before those dependencies. - return $ filter (\u -> P.uId u == P.uId unit0 || P.uPId u /= P.uPId unit0) units - where - am :: Map.Map P.UnitId (Set.Set P.UnitId) - am = fmap (foldMap P.ciLibDeps . P.uComps) (P.pjUnits plan) - -checkExeDeps :: P.UnitId -> Map.Map P.UnitId P.Unit -> Set.Set P.UnitId -> IO () -checkExeDeps pkgUid units = traverse_ check . Set.toList where - check uid = do - unit <- lookupUnit units uid - let P.PkgId pkgname _ = P.uPId unit - when (pkgname /= P.PkgName (fromString "hsc2hs")) $ do - die $ "unit " ++ show pkgUid ++ " depends on executable " ++ show uid - lookupUnit :: Map.Map P.UnitId P.Unit -> P.UnitId -> IO P.Unit lookupUnit units uid = maybe (die $ "Cannot find unit " ++ show uid) return @@ -189,6 +168,7 @@ data Dep = Dep , depRevision :: Maybe Int , depRevHash :: Maybe P.Sha256 , depFlags :: [String] + , depComponent :: Maybe T.Text } deriving (Show) @@ -218,6 +198,7 @@ instance A.ToJSON Dep where , fromString "revision" A..= depRevision dep , fromString "cabal_sha256" A..= depRevHash dep , fromString "flags" A..= depFlags dep + , fromString "component" A..= depComponent dep ] instance A.ToJSON SrcType where @@ -241,16 +222,3 @@ die :: String -> IO a die msg = do hPutStrLn stderr msg exitFailure - -------------------------------------------------------------------------------- --- Pure bits -------------------------------------------------------------------------------- - -findCabalExe :: P.PlanJson -> Maybe (P.UnitId, P.Unit) -findCabalExe plan = listToMaybe - [ (uid, unit) - | (uid, unit) <- Map.toList (P.pjUnits plan) - , let P.PkgId pkgname _ = P.uPId unit - , pkgname == P.PkgName (fromString "cabal-install") - , Map.keys (P.uComps unit) == [P.CompNameExe (fromString "cabal")] - ] diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs index 680d4175c09..6a96fb54640 100644 --- a/cabal-install/src/Distribution/Client/Setup.hs +++ b/cabal-install/src/Distribution/Client/Setup.hs @@ -1670,6 +1670,7 @@ reportCommand = , commandDescription = Nothing , commandNotes = Just $ \_ -> "You can store your Hackage login in the ~/.config/cabal/config file\n" + ++ "(the %APPDATA%\\cabal\\config file on Windows)\n" , commandUsage = usageAlternatives "report" ["[FLAGS]"] , commandDefaultFlags = defaultReportFlags , commandOptions = \_ -> @@ -2690,6 +2691,7 @@ uploadCommand = , commandDescription = Nothing , commandNotes = Just $ \_ -> "You can store your Hackage login in the ~/.config/cabal/config file\n" + ++ "(the %APPDATA%\\cabal\\config file on Windows)\n" ++ relevantConfigValuesText ["username", "password", "password-command"] , commandUsage = \pname -> "Usage: " ++ pname ++ " upload [FLAGS] TARFILES\n" diff --git a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.cabal.out b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.cabal.out index 0e0ba47ae67..dd76b493185 100644 --- a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.cabal.out +++ b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.cabal.out @@ -1,6 +1,7 @@ # Setup configure Configuring AutogenModules-0.1... -Error: cabal: An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'. +Error: [Cabal-5559] +An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'. On executable 'Exe' an 'autogen-module' is not on 'other-modules' @@ -9,7 +10,7 @@ On test suite 'Test' an 'autogen-module' is not on 'other-modules' On benchmark 'Bench' an 'autogen-module' is not on 'other-modules' # Setup sdist Distribution quality errors: -An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'. +An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'. On executable 'Exe' an 'autogen-module' is not on 'other-modules' On test suite 'Test' an 'autogen-module' is not on 'other-modules' On benchmark 'Bench' an 'autogen-module' is not on 'other-modules' diff --git a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.out b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.out index b19916e9329..dd76b493185 100644 --- a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.out +++ b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.out @@ -1,6 +1,7 @@ # Setup configure Configuring AutogenModules-0.1... -Error: setup: An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'. +Error: [Cabal-5559] +An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'. On executable 'Exe' an 'autogen-module' is not on 'other-modules' @@ -9,7 +10,7 @@ On test suite 'Test' an 'autogen-module' is not on 'other-modules' On benchmark 'Bench' an 'autogen-module' is not on 'other-modules' # Setup sdist Distribution quality errors: -An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'. +An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'. On executable 'Exe' an 'autogen-module' is not on 'other-modules' On test suite 'Test' an 'autogen-module' is not on 'other-modules' On benchmark 'Bench' an 'autogen-module' is not on 'other-modules' diff --git a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.test.hs b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.test.hs index 2b52b469e22..12fb9823309 100644 --- a/cabal-testsuite/PackageTests/AutogenModules/Package/setup.test.hs +++ b/cabal-testsuite/PackageTests/AutogenModules/Package/setup.test.hs @@ -8,7 +8,7 @@ main = setupAndCabalTest $ do -- Package check messages. let libAutogenMsg = - "An 'autogen-module' is neither on 'exposed-modules' or " + "An 'autogen-module' is neither on 'exposed-modules' nor " ++ "'other-modules'" let exeAutogenMsg = "On executable 'Exe' an 'autogen-module' is not on " diff --git a/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.cabal.out b/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.cabal.out index 2f94ecbb228..75bc0f494a7 100644 --- a/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.cabal.out +++ b/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring Reexport2-1.0... -Error: cabal: Duplicate modules in library: Asdf +Error: [Cabal-5559] +Duplicate modules in library: Asdf diff --git a/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.out b/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.out index 58f2330e0d3..75bc0f494a7 100644 --- a/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.out +++ b/cabal-testsuite/PackageTests/Backpack/Reexport2/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring Reexport2-1.0... -Error: setup: Duplicate modules in library: Asdf +Error: [Cabal-5559] +Duplicate modules in library: Asdf diff --git a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.cabal.out b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.cabal.out index 14aba5dcbbb..391531a89e2 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.cabal.out +++ b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring InternalLibrary0-0.1... -Error: cabal: The field 'build-depends: InternalLibrary0' refers to a library which is defined within the same package. To use this feature the package must specify at least 'cabal-version: >= 1.8'. +Error: [Cabal-7007] +The field 'build-depends: InternalLibrary0' refers to a library which is defined within the same package. To use this feature the package must specify at least 'cabal-version: >= 1.8'. diff --git a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.out b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.out index 0a464192dc9..391531a89e2 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.out +++ b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary0/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring InternalLibrary0-0.1... -Error: setup: The field 'build-depends: InternalLibrary0' refers to a library which is defined within the same package. To use this feature the package must specify at least 'cabal-version: >= 1.8'. +Error: [Cabal-7007] +The field 'build-depends: InternalLibrary0' refers to a library which is defined within the same package. To use this feature the package must specify at least 'cabal-version: >= 1.8'. diff --git a/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.cabal.out b/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.cabal.out index fce5331e560..da5c074772e 100644 --- a/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.cabal.out +++ b/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tool-depends-missing-0.1.0.0... -Error: cabal: The package depends on a missing internal executable: build-tool-depends-missing:hello-world +Error: [Cabal-5559] +The package depends on a missing internal executable: build-tool-depends-missing:hello-world diff --git a/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.out b/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.out index 861f95ddeb8..da5c074772e 100644 --- a/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.out +++ b/cabal-testsuite/PackageTests/BuildToolDependsInternalMissing/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tool-depends-missing-0.1.0.0... -Error: setup: The package depends on a missing internal executable: build-tool-depends-missing:hello-world +Error: [Cabal-5559] +The package depends on a missing internal executable: build-tool-depends-missing:hello-world diff --git a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Sanity/AutogenExposedOther/cabal.out b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Sanity/AutogenExposedOther/cabal.out index 1d74420d541..94c22120311 100644 --- a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Sanity/AutogenExposedOther/cabal.out +++ b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Sanity/AutogenExposedOther/cabal.out @@ -1,4 +1,4 @@ # cabal check The package will not build sanely due to these errors: -Error: An 'autogen-module' is neither on 'exposed-modules' or 'other-modules'. +Error: An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'. Error: Hackage would reject this package. diff --git a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out index 3726ef6fb23..fec347864e5 100644 --- a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out +++ b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out @@ -9,5 +9,6 @@ Installing internal library sublib in Registering library 'sublib' for Lib-0.1.0.0... # Setup configure Configuring executable 'exe' for Lib-0.1.0.0... -Error: setup: Encountered missing or private dependencies: +Error: [Cabal-8010] +Encountered missing or private dependencies: Lib:sublib diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.cabal.out b/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.cabal.out index 843f2e7808a..b03e6765cb0 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.cabal.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-depends-bad-version-0.1.0.0... -Error: cabal: The package has an impossible version range for a dependency on an internal library: build-depends-bad-version >=2. This version range does not include the current package, and must be removed as the current package's library will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal library: build-depends-bad-version >=2. This version range does not include the current package, and must be removed as the current package's library will always be used. diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.out b/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.out index e0b6883000a..b03e6765cb0 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildDependsBad/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-depends-bad-version-0.1.0.0... -Error: setup: The package has an impossible version range for a dependency on an internal library: build-depends-bad-version >=2. This version range does not include the current package, and must be removed as the current package's library will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal library: build-depends-bad-version >=2. This version range does not include the current package, and must be removed as the current package's library will always be used. diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.cabal.out b/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.cabal.out index d92e9e784e5..077f750b066 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.cabal.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tool-depends-bad-version-0.1.0.0... -Error: cabal: The package has an impossible version range for a dependency on an internal executable: build-tool-depends-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal executable: build-tool-depends-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.out b/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.out index eeb1226a74f..077f750b066 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildToolDependsBad/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tool-depends-bad-version-0.1.0.0... -Error: setup: The package has an impossible version range for a dependency on an internal executable: build-tool-depends-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal executable: build-tool-depends-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.cabal.out b/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.cabal.out index 44f43d8b30b..68a45e22992 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.cabal.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.cabal.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tools-bad-version-0.1.0.0... -Error: cabal: The package has an impossible version range for a dependency on an internal executable: build-tools-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal executable: build-tools-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. diff --git a/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.out b/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.out index 06aaa652bce..68a45e22992 100644 --- a/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.out +++ b/cabal-testsuite/PackageTests/InternalVersions/BuildToolsBad/setup.out @@ -1,3 +1,4 @@ # Setup configure Configuring build-tools-bad-version-0.1.0.0... -Error: setup: The package has an impossible version range for a dependency on an internal executable: build-tools-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. +Error: [Cabal-5559] +The package has an impossible version range for a dependency on an internal executable: build-tools-bad-version:hello-world >=2. This version range does not include the current package, and must be removed as the current package's executable will always be used. diff --git a/cabal-testsuite/PackageTests/PackageDB/cabal-fail-no-packagedbs.out b/cabal-testsuite/PackageTests/PackageDB/cabal-fail-no-packagedbs.out index dabae31b77d..5697c77102c 100644 --- a/cabal-testsuite/PackageTests/PackageDB/cabal-fail-no-packagedbs.out +++ b/cabal-testsuite/PackageTests/PackageDB/cabal-fail-no-packagedbs.out @@ -1,2 +1,3 @@ # cabal v2-build -Error: cabal: No package databases have been specified. If you use --package-db=clear, you must follow it with --package-db= with 'global', 'user' or a specific file. +Error: [Cabal-2300] +No package databases have been specified. If you use --package-db=clear, you must follow it with --package-db= with 'global', 'user' or a specific file. diff --git a/doc/Makefile b/doc/Makefile index 5ef45877223..58c2e4f4656 100644 --- a/doc/Makefile +++ b/doc/Makefile @@ -12,6 +12,40 @@ # # SKJOLD_GITHUB_API_TOKEN ?= ${GITHUB_TOKEN} +# TODO: when we have sphinx-build2 ? +SPHINXCMD:=sphinx-build +# Flag -n ("nitpick") warns about broken references +# Flag -W turns warnings into errors +# Flag --keep-going continues after errors +SPHINX_FLAGS:=-n -W --keep-going -E +SPHINX_HTML_OUTDIR:=../dist-newstyle/doc/users-guide +USERGUIDE_STAMP:=$(SPHINX_HTML_OUTDIR)/index.html +PYTHON_VIRTUALENV_ACTIVATE:=../.python-sphinx-virtualenv/bin/activate + +# Python virtual environment +############################################################################## + +# Create a python virtual environment in the root of the cabal repository. +$(PYTHON_VIRTUALENV_ACTIVATE): + python3 -m venv ../.python-sphinx-virtualenv + (. $(PYTHON_VIRTUALENV_ACTIVATE)) + +# Users guide +############################################################################## + +# do pip install every time so we have up to date requirements when we build +users-guide: $(PYTHON_VIRTUALENV_ACTIVATE) $(USERGUIDE_STAMP) +$(USERGUIDE_STAMP) : *.rst + mkdir -p $(SPHINX_HTML_OUTDIR) + (. $(PYTHON_VIRTUALENV_ACTIVATE) && pip install -r requirements.txt && $(SPHINXCMD) $(SPHINX_FLAGS) . $(SPHINX_HTML_OUTDIR)) + +# Requirements +############################################################################## + +## +# This goal is intended for manual invocation, always rebuilds. +.PHONY: users-guide-requirements +users-guide-requirements: requirements.txt .PHONY: build-and-check-requirements build-and-check-requirements: requirements.txt check-requirements @@ -21,8 +55,8 @@ build-and-check-requirements: requirements.txt check-requirements # requirements.txt is generated from requirements.in # via pip-compile included in the pip-tools package. # See https://modelpredict.com/wht-requirements-txt-is-not-enough -requirements.txt: requirements.in - . ../.python-sphinx-virtualenv/bin/activate \ +requirements.txt: requirements.in $(PYTHON_VIRTUALENV_ACTIVATE) + . $(PYTHON_VIRTUALENV_ACTIVATE) \ && pip install --upgrade pip \ && pip install pip-tools \ && pip-compile requirements.in @@ -37,7 +71,7 @@ check-requirements: echo "WARNING: Neither SKJOLD_GITHUB_API_TOKEN nor GITHUB_TOKEN is set." \ ; echo "Vulnerability check via skjold might fail when using the GitHub GraphQL API." \ ; fi - . ../.python-sphinx-virtualenv/bin/activate \ + . $(PYTHON_VIRTUALENV_ACTIVATE) \ && pip install skjold \ && skjold audit # NB: For portability, we use '.' (sh etc.) instead of 'source' (bash). diff --git a/doc/README.md b/doc/README.md index 219b177c87f..c3b25787ce6 100644 --- a/doc/README.md +++ b/doc/README.md @@ -11,8 +11,7 @@ http://cabal.readthedocs.io/ ### How to build it -Building the documentation requires Python 3 and PIP. From the root of cabal -repository run: +Building the documentation requires Python 3 and PIP. Run the following command either from the root of the cabal repository or from the `docs/` subdirectory: ``` console make users-guide @@ -33,7 +32,7 @@ generation step run > make users-guide-requirements ``` -in the root of the repository. +either from the root of the cabal repository or from the `docs/` subdirectory. Note that generating `requirements.txt` is sensitive to the Python version. The version currently used is stamped at the top of `requirements.txt`. diff --git a/doc/cabal-package.rst b/doc/cabal-package.rst index 774e9b13a00..71340330526 100644 --- a/doc/cabal-package.rst +++ b/doc/cabal-package.rst @@ -419,7 +419,7 @@ describe the package as a whole: The type of build used by this package. Build types are the constructors of the - `BuildType `__ + `BuildType `__ type. This field is optional and when missing, its default value is inferred according to the following rules: @@ -1825,7 +1825,7 @@ system-dependent values for these fields. A list of Haskell extensions used by every module. These determine corresponding compiler options enabled for all files. Extension names are the constructors of the - `Extension `__ + `Extension `__ type. For example, ``CPP`` specifies that Haskell source files are to be preprocessed with a C preprocessor. @@ -2568,7 +2568,7 @@ Configuration Flags Conditional Blocks ^^^^^^^^^^^^^^^^^^ -Conditional blocks may appear anywhere inside a library or executable +Conditional blocks may appear anywhere inside a component or common section. They have to follow rather strict formatting rules. Conditional blocks must always be of the shape diff --git a/doc/requirements.in b/doc/requirements.in index df0b2f34d80..b022abd00a4 100644 --- a/doc/requirements.in +++ b/doc/requirements.in @@ -4,5 +4,5 @@ sphinx-jsonschema sphinxnotes-strike # Pygments>=2.7.4 suggested by CVE-2021-20270 CVE-2021-27291 Pygments >= 2.7.4 -# Suggested by dependabot in https://github.com/haskell/cabal/pull/8807 -certifi >= 2022.12.7 +# CVE-2023-37920 +certifi >= 2023.07.22 diff --git a/doc/requirements.txt b/doc/requirements.txt index 5e0da823db0..af23e5d28ec 100644 --- a/doc/requirements.txt +++ b/doc/requirements.txt @@ -1,5 +1,5 @@ # -# This file is autogenerated by pip-compile with Python 3.10 +# This file is autogenerated by pip-compile with Python 3.11 # by the following command: # # pip-compile requirements.in @@ -8,7 +8,7 @@ alabaster==0.7.13 # via sphinx babel==2.12.1 # via sphinx -certifi==2023.5.7 +certifi==2023.7.22 # via # -r requirements.in # requests