Torsten Schmits pushed to branch wip/torsten.schmits/mercury-ghc910-mhu-transitive-th-deps_ospath at Glasgow Haskell Compiler / GHC
Commits:
-
4d6ffa22
by Torsten Schmits at 2025-11-06T16:10:01+01:00
-
75206a24
by Georgios Karachalias at 2025-11-19T13:58:58+01:00
8 changed files:
- + compiler/GHC/Data/OsPath.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Unit/State.hs
- compiler/ghc.cabal.in
Changes:
| 1 | +module GHC.Data.OsPath
|
|
| 2 | + (
|
|
| 3 | + -- * OsPath initialisation and transformation
|
|
| 4 | + OsPath
|
|
| 5 | + , OsString
|
|
| 6 | + , encodeUtf
|
|
| 7 | + , decodeUtf
|
|
| 8 | + , unsafeDecodeUtf
|
|
| 9 | + , unsafeEncodeUtf
|
|
| 10 | + , os
|
|
| 11 | + -- * Common utility functions
|
|
| 12 | + , (</>)
|
|
| 13 | + , (<.>)
|
|
| 14 | + , splitSearchPath
|
|
| 15 | + , isRelative
|
|
| 16 | + , dropTrailingPathSeparator
|
|
| 17 | + , takeDirectory
|
|
| 18 | + , isSuffixOf
|
|
| 19 | + , doesDirectoryExist
|
|
| 20 | + , doesFileExist
|
|
| 21 | + , getDirectoryContents
|
|
| 22 | + , createDirectoryIfMissing
|
|
| 23 | + , pprOsPath
|
|
| 24 | + )
|
|
| 25 | + where
|
|
| 26 | + |
|
| 27 | +import GHC.Prelude
|
|
| 28 | + |
|
| 29 | +import GHC.Utils.Misc (HasCallStack)
|
|
| 30 | +import GHC.Utils.Outputable qualified as Outputable
|
|
| 31 | +import GHC.Utils.Panic (panic)
|
|
| 32 | + |
|
| 33 | +import System.OsPath
|
|
| 34 | +import System.OsString (isSuffixOf)
|
|
| 35 | +import System.Directory.OsPath (doesDirectoryExist, doesFileExist, getDirectoryContents, createDirectoryIfMissing)
|
|
| 36 | +import System.Directory.Internal (os)
|
|
| 37 | + |
|
| 38 | +-- | Decode an 'OsPath' to 'FilePath', throwing an 'error' if decoding failed.
|
|
| 39 | +-- Prefer 'decodeUtf' and gracious error handling.
|
|
| 40 | +unsafeDecodeUtf :: HasCallStack => OsPath -> FilePath
|
|
| 41 | +unsafeDecodeUtf p =
|
|
| 42 | + either (\err -> panic $ "Failed to decodeUtf \"" ++ show p ++ "\", because: " ++ show err) id (decodeUtf p)
|
|
| 43 | + |
|
| 44 | +pprOsPath :: HasCallStack => OsPath -> Outputable.SDoc
|
|
| 45 | +pprOsPath = Outputable.text . unsafeDecodeUtf |
| ... | ... | @@ -76,6 +76,7 @@ import qualified GHC.LanguageExtensions as LangExt |
| 76 | 76 | import GHC.Data.Maybe
|
| 77 | 77 | import GHC.Data.StringBuffer
|
| 78 | 78 | import GHC.Data.FastString
|
| 79 | +import qualified GHC.Data.OsPath as OsPath
|
|
| 79 | 80 | import qualified GHC.Data.EnumSet as EnumSet
|
| 80 | 81 | import qualified GHC.Data.ShortText as ST
|
| 81 | 82 | |
| ... | ... | @@ -433,7 +434,7 @@ addUnit u = do |
| 433 | 434 | Nothing -> panic "addUnit: called too early"
|
| 434 | 435 | Just dbs ->
|
| 435 | 436 | let newdb = UnitDatabase
|
| 436 | - { unitDatabasePath = "(in memory " ++ showSDoc dflags0 (ppr (unitId u)) ++ ")"
|
|
| 437 | + { unitDatabasePath = OsPath.unsafeEncodeUtf $ "(in memory " ++ showSDoc dflags0 (ppr (unitId u)) ++ ")"
|
|
| 437 | 438 | , unitDatabaseUnits = [u]
|
| 438 | 439 | }
|
| 439 | 440 | in return (dbs ++ [newdb]) -- added at the end because ordering matters
|
| ... | ... | @@ -96,6 +96,7 @@ import GHC.Core.Unfold |
| 96 | 96 | import GHC.Data.Bool
|
| 97 | 97 | import GHC.Data.EnumSet (EnumSet)
|
| 98 | 98 | import GHC.Data.Maybe
|
| 99 | +import GHC.Data.OsPath (OsPath)
|
|
| 99 | 100 | import GHC.Builtin.Names ( mAIN_NAME )
|
| 100 | 101 | import GHC.Driver.Backend
|
| 101 | 102 | import GHC.Driver.Flags
|
| ... | ... | @@ -948,7 +949,7 @@ setDynamicNow dflags0 = |
| 948 | 949 | data PkgDbRef
|
| 949 | 950 | = GlobalPkgDb
|
| 950 | 951 | | UserPkgDb
|
| 951 | - | PkgDbPath FilePath
|
|
| 952 | + | PkgDbPath OsPath
|
|
| 952 | 953 | deriving Eq
|
| 953 | 954 | |
| 954 | 955 | -- | Used to differentiate the scope an include needs to apply to.
|
| ... | ... | @@ -1009,11 +1009,6 @@ initWholeCoreBindings hsc_env mod_iface details (LM utc_time this_mod uls) = do |
| 1009 | 1009 | types_var <- newIORef (md_types details)
|
| 1010 | 1010 | let kv = knotVarsFromModuleEnv (mkModuleEnv [(this_mod, types_var)])
|
| 1011 | 1011 | let hsc_env' = hscUpdateHPT act hsc_env { hsc_type_env_vars = kv }
|
| 1012 | - core_binds <- initIfaceCheck (text "l") hsc_env' $ typecheckWholeCoreBindings types_var fi
|
|
| 1013 | - -- MP: The NoStubs here is only from (I think) the TH `qAddForeignFilePath` feature but it's a bit unclear what to do
|
|
| 1014 | - -- with these files, do we have to read and serialise the foreign file? I will leave it for now until someone
|
|
| 1015 | - -- reports a bug.
|
|
| 1016 | - let cgi_guts = CgInteractiveGuts this_mod core_binds (typeEnvTyCons (md_types details)) NoStubs Nothing []
|
|
| 1017 | 1012 | -- The bytecode generation itself is lazy because otherwise even when doing
|
| 1018 | 1013 | -- recompilation checking the bytecode will be generated (which slows things down a lot)
|
| 1019 | 1014 | -- the laziness is OK because generateByteCode just depends on things already loaded
|
| ... | ... | @@ -255,6 +255,7 @@ import GHC.Types.SrcLoc |
| 255 | 255 | import GHC.Types.SafeHaskell
|
| 256 | 256 | import GHC.Types.Basic ( treatZeroAsInf )
|
| 257 | 257 | import GHC.Data.FastString
|
| 258 | +import qualified GHC.Data.OsPath as OsPath
|
|
| 258 | 259 | import GHC.Utils.TmpFs
|
| 259 | 260 | import GHC.Utils.Fingerprint
|
| 260 | 261 | import GHC.Utils.Outputable
|
| ... | ... | @@ -1962,7 +1963,7 @@ package_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))] |
| 1962 | 1963 | package_flags_deps = [
|
| 1963 | 1964 | ------- Packages ----------------------------------------------------
|
| 1964 | 1965 | make_ord_flag defFlag "package-db"
|
| 1965 | - (HasArg (addPkgDbRef . PkgDbPath))
|
|
| 1966 | + (HasArg (addPkgDbRef . PkgDbPath . OsPath.unsafeEncodeUtf))
|
|
| 1966 | 1967 | , make_ord_flag defFlag "clear-package-db" (NoArg clearPkgDb)
|
| 1967 | 1968 | , make_ord_flag defFlag "no-global-package-db" (NoArg removeGlobalPkgDb)
|
| 1968 | 1969 | , make_ord_flag defFlag "no-user-package-db" (NoArg removeUserPkgDb)
|
| ... | ... | @@ -1972,7 +1973,7 @@ package_flags_deps = [ |
| 1972 | 1973 | (NoArg (addPkgDbRef UserPkgDb))
|
| 1973 | 1974 | -- backwards compat with GHC<=7.4 :
|
| 1974 | 1975 | , make_dep_flag defFlag "package-conf"
|
| 1975 | - (HasArg $ addPkgDbRef . PkgDbPath) "Use -package-db instead"
|
|
| 1976 | + (HasArg $ addPkgDbRef . PkgDbPath . OsPath.unsafeEncodeUtf) "Use -package-db instead"
|
|
| 1976 | 1977 | , make_dep_flag defFlag "no-user-package-conf"
|
| 1977 | 1978 | (NoArg removeUserPkgDb) "Use -no-user-package-db instead"
|
| 1978 | 1979 | , make_ord_flag defGhcFlag "package-name" (HasArg $ \name ->
|
| ... | ... | @@ -3377,7 +3378,7 @@ parseEnvFile :: FilePath -> String -> DynP () |
| 3377 | 3378 | parseEnvFile envfile = mapM_ parseEntry . lines
|
| 3378 | 3379 | where
|
| 3379 | 3380 | parseEntry str = case words str of
|
| 3380 | - ("package-db": _) -> addPkgDbRef (PkgDbPath (envdir </> db))
|
|
| 3381 | + ("package-db": _) -> addPkgDbRef (PkgDbPath (OsPath.unsafeEncodeUtf (envdir </> db)))
|
|
| 3381 | 3382 | -- relative package dbs are interpreted relative to the env file
|
| 3382 | 3383 | where envdir = takeDirectory envfile
|
| 3383 | 3384 | db = drop 11 str
|
| ... | ... | @@ -54,8 +54,6 @@ import Control.Monad.IO.Class (MonadIO (liftIO)) |
| 54 | 54 | import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
|
| 55 | 55 | |
| 56 | 56 | import qualified Data.Set as Set
|
| 57 | -import qualified Data.Map as M
|
|
| 58 | -import Data.List (isSuffixOf)
|
|
| 59 | 57 | |
| 60 | 58 | import System.FilePath
|
| 61 | 59 | import System.Directory
|
| ... | ... | @@ -103,6 +103,8 @@ import GHC.Data.Maybe |
| 103 | 103 | import System.Environment ( getEnv )
|
| 104 | 104 | import GHC.Data.FastString
|
| 105 | 105 | import qualified GHC.Data.ShortText as ST
|
| 106 | +import GHC.Data.OsPath (OsPath)
|
|
| 107 | +import qualified GHC.Data.OsPath as OsPath
|
|
| 106 | 108 | import GHC.Utils.Logger
|
| 107 | 109 | import GHC.Utils.Error
|
| 108 | 110 | import GHC.Utils.Exception
|
| ... | ... | @@ -112,7 +114,7 @@ import System.FilePath as FilePath |
| 112 | 114 | import Control.Monad
|
| 113 | 115 | import Data.Graph (stronglyConnComp, SCC(..))
|
| 114 | 116 | import Data.Char ( toUpper )
|
| 115 | -import Data.List ( intersperse, partition, sortBy, isSuffixOf, sortOn )
|
|
| 117 | +import Data.List ( intersperse, partition, sortBy, sortOn )
|
|
| 116 | 118 | import Data.Set (Set)
|
| 117 | 119 | import Data.Monoid (First(..))
|
| 118 | 120 | import qualified Data.Semigroup as Semigroup
|
| ... | ... | @@ -405,7 +407,7 @@ initUnitConfig dflags cached_dbs home_units = |
| 405 | 407 | |
| 406 | 408 | where
|
| 407 | 409 | offsetPackageDb :: Maybe FilePath -> PackageDBFlag -> PackageDBFlag
|
| 408 | - offsetPackageDb (Just offset) (PackageDB (PkgDbPath p)) | isRelative p = PackageDB (PkgDbPath (offset </> p))
|
|
| 410 | + offsetPackageDb (Just offset) (PackageDB (PkgDbPath p)) | OsPath.isRelative p = PackageDB (PkgDbPath (OsPath.unsafeEncodeUtf offset OsPath.</> p))
|
|
| 409 | 411 | offsetPackageDb _ p = p
|
| 410 | 412 | |
| 411 | 413 | |
| ... | ... | @@ -500,12 +502,12 @@ emptyUnitState = UnitState { |
| 500 | 502 | |
| 501 | 503 | -- | Unit database
|
| 502 | 504 | data UnitDatabase unit = UnitDatabase
|
| 503 | - { unitDatabasePath :: FilePath
|
|
| 505 | + { unitDatabasePath :: OsPath
|
|
| 504 | 506 | , unitDatabaseUnits :: [GenUnitInfo unit]
|
| 505 | 507 | }
|
| 506 | 508 | |
| 507 | 509 | instance Outputable u => Outputable (UnitDatabase u) where
|
| 508 | - ppr (UnitDatabase fp _u) = text "DB:" <+> text fp
|
|
| 510 | + ppr (UnitDatabase fp _u) = text "DB:" <+> OsPath.pprOsPath fp
|
|
| 509 | 511 | |
| 510 | 512 | type UnitInfoMap = UniqMap UnitId UnitInfo
|
| 511 | 513 | |
| ... | ... | @@ -720,9 +722,9 @@ getUnitDbRefs cfg = do |
| 720 | 722 | Left _ -> system_conf_refs
|
| 721 | 723 | Right path
|
| 722 | 724 | | Just (xs, x) <- snocView path, isSearchPathSeparator x
|
| 723 | - -> map PkgDbPath (splitSearchPath xs) ++ system_conf_refs
|
|
| 725 | + -> map PkgDbPath (OsPath.splitSearchPath (OsPath.unsafeEncodeUtf xs)) ++ system_conf_refs
|
|
| 724 | 726 | | otherwise
|
| 725 | - -> map PkgDbPath (splitSearchPath path)
|
|
| 727 | + -> map PkgDbPath (OsPath.splitSearchPath (OsPath.unsafeEncodeUtf path))
|
|
| 726 | 728 | |
| 727 | 729 | -- Apply the package DB-related flags from the command line to get the
|
| 728 | 730 | -- final list of package DBs.
|
| ... | ... | @@ -751,24 +753,24 @@ getUnitDbRefs cfg = do |
| 751 | 753 | -- NB: This logic is reimplemented in Cabal, so if you change it,
|
| 752 | 754 | -- make sure you update Cabal. (Or, better yet, dump it in the
|
| 753 | 755 | -- compiler info so Cabal can use the info.)
|
| 754 | -resolveUnitDatabase :: UnitConfig -> PkgDbRef -> IO (Maybe FilePath)
|
|
| 755 | -resolveUnitDatabase cfg GlobalPkgDb = return $ Just (unitConfigGlobalDB cfg)
|
|
| 756 | +resolveUnitDatabase :: UnitConfig -> PkgDbRef -> IO (Maybe OsPath)
|
|
| 757 | +resolveUnitDatabase cfg GlobalPkgDb = return $ Just $ OsPath.unsafeEncodeUtf $ unitConfigGlobalDB cfg
|
|
| 756 | 758 | resolveUnitDatabase cfg UserPkgDb = runMaybeT $ do
|
| 757 | 759 | dir <- versionedAppDir (unitConfigProgramName cfg) (unitConfigPlatformArchOS cfg)
|
| 758 | 760 | let pkgconf = dir </> unitConfigDBName cfg
|
| 759 | 761 | exist <- tryMaybeT $ doesDirectoryExist pkgconf
|
| 760 | - if exist then return pkgconf else mzero
|
|
| 762 | + if exist then return (OsPath.unsafeEncodeUtf pkgconf) else mzero
|
|
| 761 | 763 | resolveUnitDatabase _ (PkgDbPath name) = return $ Just name
|
| 762 | 764 | |
| 763 | -readUnitDatabase :: Logger -> UnitConfig -> FilePath -> IO (UnitDatabase UnitId)
|
|
| 765 | +readUnitDatabase :: Logger -> UnitConfig -> OsPath -> IO (UnitDatabase UnitId)
|
|
| 764 | 766 | readUnitDatabase logger cfg conf_file = do
|
| 765 | - isdir <- doesDirectoryExist conf_file
|
|
| 767 | + isdir <- OsPath.doesDirectoryExist conf_file
|
|
| 766 | 768 | |
| 767 | 769 | proto_pkg_configs <-
|
| 768 | 770 | if isdir
|
| 769 | 771 | then readDirStyleUnitInfo conf_file
|
| 770 | 772 | else do
|
| 771 | - isfile <- doesFileExist conf_file
|
|
| 773 | + isfile <- OsPath.doesFileExist conf_file
|
|
| 772 | 774 | if isfile
|
| 773 | 775 | then do
|
| 774 | 776 | mpkgs <- tryReadOldFileStyleUnitInfo
|
| ... | ... | @@ -776,48 +778,49 @@ readUnitDatabase logger cfg conf_file = do |
| 776 | 778 | Just pkgs -> return pkgs
|
| 777 | 779 | Nothing -> throwGhcExceptionIO $ InstallationError $
|
| 778 | 780 | "ghc no longer supports single-file style package " ++
|
| 779 | - "databases (" ++ conf_file ++
|
|
| 781 | + "databases (" ++ show conf_file ++
|
|
| 780 | 782 | ") use 'ghc-pkg init' to create the database with " ++
|
| 781 | 783 | "the correct format."
|
| 782 | 784 | else throwGhcExceptionIO $ InstallationError $
|
| 783 | - "can't find a package database at " ++ conf_file
|
|
| 785 | + "can't find a package database at " ++ show conf_file
|
|
| 784 | 786 | |
| 785 | 787 | let
|
| 786 | 788 | -- Fix #16360: remove trailing slash from conf_file before calculating pkgroot
|
| 787 | - conf_file' = dropTrailingPathSeparator conf_file
|
|
| 788 | - top_dir = unitConfigGHCDir cfg
|
|
| 789 | - pkgroot = takeDirectory conf_file'
|
|
| 789 | + conf_file' = OsPath.dropTrailingPathSeparator conf_file
|
|
| 790 | + top_dir = OsPath.unsafeEncodeUtf (unitConfigGHCDir cfg) -- TODO: hm.
|
|
| 791 | + pkgroot = OsPath.takeDirectory conf_file'
|
|
| 790 | 792 | pkg_configs1 = map (mungeUnitInfo top_dir pkgroot . mapUnitInfo (\(UnitKey x) -> UnitId x) . mkUnitKeyInfo)
|
| 791 | 793 | proto_pkg_configs
|
| 792 | 794 | --
|
| 793 | 795 | return $ UnitDatabase conf_file' pkg_configs1
|
| 794 | 796 | where
|
| 797 | + readDirStyleUnitInfo :: OsPath -> IO [DbUnitInfo]
|
|
| 795 | 798 | readDirStyleUnitInfo conf_dir = do
|
| 796 | - let filename = conf_dir </> "package.cache"
|
|
| 797 | - cache_exists <- doesFileExist filename
|
|
| 799 | + let filename = conf_dir OsPath.</> (OsPath.unsafeEncodeUtf "package.cache")
|
|
| 800 | + cache_exists <- OsPath.doesFileExist filename
|
|
| 798 | 801 | if cache_exists
|
| 799 | 802 | then do
|
| 800 | - debugTraceMsg logger 2 $ text "Using binary package database:" <+> text filename
|
|
| 801 | - readPackageDbForGhc filename
|
|
| 803 | + debugTraceMsg logger 2 $ text "Using binary package database:" <+> OsPath.pprOsPath filename
|
|
| 804 | + readPackageDbForGhc (OsPath.unsafeDecodeUtf filename) -- TODO: Can we help it with this one? it comes from the ghc-boot package
|
|
| 802 | 805 | else do
|
| 803 | 806 | -- If there is no package.cache file, we check if the database is not
|
| 804 | 807 | -- empty by inspecting if the directory contains any .conf file. If it
|
| 805 | 808 | -- does, something is wrong and we fail. Otherwise we assume that the
|
| 806 | 809 | -- database is empty.
|
| 807 | 810 | debugTraceMsg logger 2 $ text "There is no package.cache in"
|
| 808 | - <+> text conf_dir
|
|
| 811 | + <+> OsPath.pprOsPath conf_dir
|
|
| 809 | 812 | <> text ", checking if the database is empty"
|
| 810 | - db_empty <- all (not . isSuffixOf ".conf")
|
|
| 811 | - <$> getDirectoryContents conf_dir
|
|
| 813 | + db_empty <- all (not . OsPath.isSuffixOf (OsPath.unsafeEncodeUtf ".conf"))
|
|
| 814 | + <$> OsPath.getDirectoryContents conf_dir
|
|
| 812 | 815 | if db_empty
|
| 813 | 816 | then do
|
| 814 | 817 | debugTraceMsg logger 3 $ text "There are no .conf files in"
|
| 815 | - <+> text conf_dir <> text ", treating"
|
|
| 818 | + <+> OsPath.pprOsPath conf_dir <> text ", treating"
|
|
| 816 | 819 | <+> text "package database as empty"
|
| 817 | 820 | return []
|
| 818 | 821 | else
|
| 819 | 822 | throwGhcExceptionIO $ InstallationError $
|
| 820 | - "there is no package.cache in " ++ conf_dir ++
|
|
| 823 | + "there is no package.cache in " ++ show conf_dir ++
|
|
| 821 | 824 | " even though package database is not empty"
|
| 822 | 825 | |
| 823 | 826 | |
| ... | ... | @@ -830,13 +833,13 @@ readUnitDatabase logger cfg conf_file = do |
| 830 | 833 | -- assumes it's a file and tries to overwrite with 'writeFile'.
|
| 831 | 834 | -- ghc-pkg also cooperates with this workaround.
|
| 832 | 835 | tryReadOldFileStyleUnitInfo = do
|
| 833 | - content <- readFile conf_file `catchIO` \_ -> return ""
|
|
| 836 | + content <- readFile (OsPath.unsafeDecodeUtf conf_file) `catchIO` \_ -> return ""
|
|
| 834 | 837 | if take 2 content == "[]"
|
| 835 | 838 | then do
|
| 836 | - let conf_dir = conf_file <.> "d"
|
|
| 837 | - direxists <- doesDirectoryExist conf_dir
|
|
| 839 | + let conf_dir = conf_file OsPath.<.> OsPath.unsafeEncodeUtf "d"
|
|
| 840 | + direxists <- OsPath.doesDirectoryExist conf_dir
|
|
| 838 | 841 | if direxists
|
| 839 | - then do debugTraceMsg logger 2 (text "Ignoring old file-style db and trying:" <+> text conf_dir)
|
|
| 842 | + then do debugTraceMsg logger 2 (text "Ignoring old file-style db and trying:" <+> OsPath.pprOsPath conf_dir)
|
|
| 840 | 843 | liftM Just (readDirStyleUnitInfo conf_dir)
|
| 841 | 844 | else return (Just []) -- ghc-pkg will create it when it's updated
|
| 842 | 845 | else return Nothing
|
| ... | ... | @@ -846,11 +849,12 @@ distrustAllUnits pkgs = map distrust pkgs |
| 846 | 849 | where
|
| 847 | 850 | distrust pkg = pkg{ unitIsTrusted = False }
|
| 848 | 851 | |
| 849 | -mungeUnitInfo :: FilePath -> FilePath
|
|
| 852 | +-- TODO: Can we help it with this one? it comes from the ghc-boot package
|
|
| 853 | +mungeUnitInfo :: OsPath -> OsPath
|
|
| 850 | 854 | -> UnitInfo -> UnitInfo
|
| 851 | 855 | mungeUnitInfo top_dir pkgroot =
|
| 852 | 856 | mungeDynLibFields
|
| 853 | - . mungeUnitInfoPaths (ST.pack top_dir) (ST.pack pkgroot)
|
|
| 857 | + . mungeUnitInfoPaths (ST.pack (OsPath.unsafeDecodeUtf top_dir)) (ST.pack (OsPath.unsafeDecodeUtf pkgroot))
|
|
| 854 | 858 | |
| 855 | 859 | mungeDynLibFields :: UnitInfo -> UnitInfo
|
| 856 | 860 | mungeDynLibFields pkg =
|
| ... | ... | @@ -1388,7 +1392,7 @@ mergeDatabases logger = foldM merge (emptyUniqMap, emptyUniqMap) . zip [1..] |
| 1388 | 1392 | where
|
| 1389 | 1393 | merge (pkg_map, prec_map) (i, UnitDatabase db_path db) = do
|
| 1390 | 1394 | debugTraceMsg logger 2 $
|
| 1391 | - text "loading package database" <+> text db_path
|
|
| 1395 | + text "loading package database" <+> OsPath.pprOsPath db_path
|
|
| 1392 | 1396 | forM_ (Set.toList override_set) $ \pkg ->
|
| 1393 | 1397 | debugTraceMsg logger 2 $
|
| 1394 | 1398 | text "package" <+> ppr pkg <+>
|
| ... | ... | @@ -115,6 +115,7 @@ Library |
| 115 | 115 | containers >= 0.6.2.1 && < 0.8,
|
| 116 | 116 | array >= 0.1 && < 0.6,
|
| 117 | 117 | filepath >= 1 && < 1.6,
|
| 118 | + os-string >= 2.0.1 && < 2.1,
|
|
| 118 | 119 | template-haskell == 2.22.*,
|
| 119 | 120 | hpc >= 0.6 && < 0.8,
|
| 120 | 121 | transformers >= 0.5 && < 0.7,
|
| ... | ... | @@ -430,6 +431,7 @@ Library |
| 430 | 431 | GHC.Data.List.SetOps
|
| 431 | 432 | GHC.Data.Maybe
|
| 432 | 433 | GHC.Data.OrdList
|
| 434 | + GHC.Data.OsPath
|
|
| 433 | 435 | GHC.Data.Pair
|
| 434 | 436 | GHC.Data.SmallArray
|
| 435 | 437 | GHC.Data.Stream
|