summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2012-05-16 11:14:21 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2012-05-16 11:14:21 +0100
commit7fe110aaf5d464b7934e1429b943d862a6da8c06 (patch)
tree8015bac396d0c821f4501a1ebfefc758dc1505a9
parent969f8b728be0a2fec8263e8866295776c993394b (diff)
parent921530b477867edb5158e4ad5bbbdb5c7c531c97 (diff)
downloadhaskell-7fe110aaf5d464b7934e1429b943d862a6da8c06.tar.gz
Merge branch 'master' of http://darcs.haskell.org/ghc
-rw-r--r--aclocal.m42
-rw-r--r--bindisttest/Makefile4
-rw-r--r--bindisttest/ghc.mk4
-rw-r--r--compiler/main/DynFlags.hs44
-rw-r--r--compiler/main/HscMain.hs8
-rw-r--r--compiler/main/HscTypes.lhs4
-rw-r--r--compiler/main/InteractiveEval.hs17
-rw-r--r--compiler/main/Packages.lhs75
-rw-r--r--compiler/parser/Lexer.x21
-rw-r--r--compiler/typecheck/TcRnDriver.lhs29
-rw-r--r--configure.ac4
-rw-r--r--docs/users_guide/flags.xml32
-rw-r--r--docs/users_guide/packages.xml108
-rw-r--r--docs/users_guide/runghc.xml2
-rw-r--r--ghc.mk2
-rw-r--r--ghc/InteractiveUI.hs2
-rw-r--r--libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs4
-rw-r--r--mk/config.mk.in2
-rw-r--r--rules/distdir-way-opts.mk2
-rw-r--r--rules/package-config.mk8
-rw-r--r--utils/ghc-cabal/Main.hs2
-rw-r--r--utils/ghc-cabal/ghc.mk2
-rw-r--r--utils/ghc-pkg/Main.hs20
-rw-r--r--utils/ghc-pkg/ghc-pkg.wrapper2
-rw-r--r--utils/ghc-pkg/ghc.mk6
25 files changed, 268 insertions, 138 deletions
diff --git a/aclocal.m4 b/aclocal.m4
index c196bdf026..f05dfe96ea 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -1808,7 +1808,7 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd)
dnl except we don't want to have to know what make is called. Sigh.
rm -rf utils/ghc-pwd/dist-boot
mkdir utils/ghc-pwd/dist-boot
- if ! "$WithGhc" -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd
+ if ! "$WithGhc" -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd
then
AC_MSG_ERROR([Building ghc-pwd failed])
fi
diff --git a/bindisttest/Makefile b/bindisttest/Makefile
index 238bce7650..7d20bdbf39 100644
--- a/bindisttest/Makefile
+++ b/bindisttest/Makefile
@@ -48,8 +48,8 @@ endif
$(BIN_DIST_INST_DIR)/bin/ghc --make HelloWorld
./HelloWorld > output
$(CONTEXT_DIFF) output expected_output
-# Without --no-user-package-conf we might pick up random packages from ~/.ghc
- $(BIN_DIST_INST_DIR)/bin/ghc-pkg check --no-user-package-conf
+# Without --no-user-package-db we might pick up random packages from ~/.ghc
+ $(BIN_DIST_INST_DIR)/bin/ghc-pkg check --no-user-package-db
clean distclean:
"$(RM)" $(RM_OPTS_REC) $(BIN_DIST_INST_SUBDIR)
diff --git a/bindisttest/ghc.mk b/bindisttest/ghc.mk
index e051be0ccd..c911da5e8c 100644
--- a/bindisttest/ghc.mk
+++ b/bindisttest/ghc.mk
@@ -48,8 +48,8 @@ endif
$(BIN_DIST_INST_DIR)/bin/ghc --make bindisttest/HelloWorld
bindisttest/HelloWorld > bindisttest/output
$(CONTEXT_DIFF) bindisttest/output bindisttest/expected_output
-# Without --no-user-package-conf we might pick up random packages from ~/.ghc
- $(BIN_DIST_INST_DIR)/bin/ghc-pkg check --no-user-package-conf
+# Without --no-user-package-db we might pick up random packages from ~/.ghc
+ $(BIN_DIST_INST_DIR)/bin/ghc-pkg check --no-user-package-db
$(eval $(call clean-target,bindisttest,all,$(BIN_DIST_INST_DIR) $(wildcard bindisttest/a/b/c/*) bindisttest/HelloWorld bindisttest/HelloWorld.o bindisttest/HelloWorld.hi bindisttest/output))
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index a497dedcda..c26efb2597 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -38,6 +38,7 @@ module DynFlags (
GhcMode(..), isOneShot,
GhcLink(..), isNoLink,
PackageFlag(..),
+ PkgConfRef(..),
Option(..), showOpt,
DynLibLoader(..),
fFlags, fWarningFlags, fLangFlags, xFlags,
@@ -275,7 +276,6 @@ data DynFlag
| Opt_ForceRecomp
| Opt_ExcessPrecision
| Opt_EagerBlackHoling
- | Opt_ReadUserPackageConf
| Opt_NoHsMain
| Opt_SplitObjs
| Opt_StgStats
@@ -548,8 +548,8 @@ data DynFlags = DynFlags {
depSuffixes :: [String],
-- Package flags
- extraPkgConfs :: [FilePath],
- -- ^ The @-package-conf@ flags given on the command line, in the order
+ extraPkgConfs :: [PkgConfRef] -> [PkgConfRef],
+ -- ^ The @-package-db@ flags given on the command line, in the order
-- they appeared.
packageFlags :: [PackageFlag],
@@ -923,7 +923,7 @@ defaultDynFlags mySettings =
hpcDir = ".hpc",
- extraPkgConfs = [],
+ extraPkgConfs = id,
packageFlags = [],
pkgDatabase = Nothing,
pkgState = panic "no package state yet: call GHC.setSessionDynFlags",
@@ -1340,7 +1340,7 @@ parseDynamicFlagsCmdLine :: Monad m =>
parseDynamicFlagsCmdLine dflags args = parseDynamicFlags dflags args True
-- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags
--- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-conf).
+-- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
-- Used to parse flags set in a modules pragma.
parseDynamicFilePragma :: Monad m =>
DynFlags -> [Located String]
@@ -1755,8 +1755,13 @@ dynamic_flags = [
package_flags :: [Flag (CmdLineP DynFlags)]
package_flags = [
------- Packages ----------------------------------------------------
- Flag "package-conf" (HasArg extraPkgConf_)
- , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
+ Flag "package-db" (HasArg (addPkgConfRef . PkgConfFile))
+ , Flag "clear-package-db" (NoArg clearPkgConf)
+ , Flag "no-global-package-db" (NoArg removeGlobalPkgConf)
+ , Flag "no-user-package-db" (NoArg removeUserPkgConf)
+ , Flag "global-package-db" (NoArg (addPkgConfRef GlobalPkgConf))
+ , Flag "user-package-db" (NoArg (addPkgConfRef UserPkgConf))
+
, Flag "package-name" (hasArg setPackageName)
, Flag "package-id" (HasArg exposePackageId)
, Flag "package" (HasArg exposePackage)
@@ -2066,7 +2071,6 @@ xFlags = [
defaultFlags :: [DynFlag]
defaultFlags
= [ Opt_AutoLinkPackages,
- Opt_ReadUserPackageConf,
Opt_SharedImplib,
@@ -2404,8 +2408,28 @@ setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
addCmdlineHCInclude :: String -> DynP ()
addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes = a : cmdlineHcIncludes s})
-extraPkgConf_ :: FilePath -> DynP ()
-extraPkgConf_ p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
+data PkgConfRef
+ = GlobalPkgConf
+ | UserPkgConf
+ | PkgConfFile FilePath
+
+addPkgConfRef :: PkgConfRef -> DynP ()
+addPkgConfRef p = upd $ \s -> s { extraPkgConfs = (p:) . extraPkgConfs s }
+
+removeUserPkgConf :: DynP ()
+removeUserPkgConf = upd $ \s -> s { extraPkgConfs = filter isNotUser . extraPkgConfs s }
+ where
+ isNotUser UserPkgConf = False
+ isNotUser _ = True
+
+removeGlobalPkgConf :: DynP ()
+removeGlobalPkgConf = upd $ \s -> s { extraPkgConfs = filter isNotGlobal . extraPkgConfs s }
+ where
+ isNotGlobal GlobalPkgConf = False
+ isNotGlobal _ = True
+
+clearPkgConf :: DynP ()
+clearPkgConf = upd $ \s -> s { extraPkgConfs = const [] }
exposePackage, exposePackageId, hidePackage, ignorePackage,
trustPackage, distrustPackage :: String -> DynP ()
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index b975a20fd1..4a54c89545 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1403,7 +1403,7 @@ IO monad as explained in Note [Interactively-bound Ids in GHCi] in TcRnDriver
--
-- We return Nothing to indicate an empty statement (or comment only), not a
-- parse error.
-hscStmt :: HscEnv -> String -> IO (Maybe ([Id], IO [HValue]))
+hscStmt :: HscEnv -> String -> IO (Maybe ([Id], IO [HValue], FixityEnv))
hscStmt hsc_env stmt = hscStmtWithLocation hsc_env stmt "<interactive>" 1
-- | Compile a stmt all the way to an HValue, but don't run it
@@ -1414,7 +1414,7 @@ hscStmtWithLocation :: HscEnv
-> String -- ^ The statement
-> String -- ^ The source
-> Int -- ^ Starting line
- -> IO (Maybe ([Id], IO [HValue]))
+ -> IO (Maybe ([Id], IO [HValue], FixityEnv))
hscStmtWithLocation hsc_env0 stmt source linenumber =
runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
@@ -1431,7 +1431,7 @@ hscStmtWithLocation hsc_env0 stmt source linenumber =
-- Rename and typecheck it
-- Here we lift the stmt into the IO monad, see Note
-- [Interactively-bound Ids in GHCi] in TcRnDriver
- (ids, tc_expr) <- ioMsgMaybe $ tcRnStmt hsc_env icntxt parsed_stmt
+ (ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt hsc_env icntxt parsed_stmt
-- Desugar it
ds_expr <- ioMsgMaybe $
@@ -1443,7 +1443,7 @@ hscStmtWithLocation hsc_env0 stmt source linenumber =
hval <- liftIO $ hscCompileCoreExpr hsc_env src_span ds_expr
let hval_io = unsafeCoerce# hval :: IO [HValue]
- return $ Just (ids, hval_io)
+ return $ Just (ids, hval_io, fix_env)
-- | Compile a decls
hscDecls :: HscEnv
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index 82712e2741..1c8276db33 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -942,6 +942,9 @@ data InteractiveContext
-- time we update the context, we just take the results
-- from the instance code that already does that.
+ ic_fix_env :: FixityEnv,
+ -- ^ Fixities declared in let statements
+
#ifdef GHCI
ic_resume :: [Resume],
-- ^ The stack of breakpoint contexts
@@ -983,6 +986,7 @@ emptyInteractiveContext dflags
ic_tythings = [],
ic_sys_vars = [],
ic_instances = ([],[]),
+ ic_fix_env = emptyNameEnv,
#ifdef GHCI
ic_resume = [],
#endif
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index a666220a6e..42147dce94 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -176,6 +176,12 @@ findEnclosingDecls hsc_env inf =
mb = getModBreaks hmi
in modBreaks_decls mb ! breakInfo_number inf
+-- | Update fixity environment in the current interactive context.
+updateFixityEnv :: GhcMonad m => FixityEnv -> m ()
+updateFixityEnv fix_env = do
+ hsc_env <- getSession
+ let ic = hsc_IC hsc_env
+ setSession $ hsc_env { hsc_IC = ic { ic_fix_env = fix_env } }
-- | Run a statement in the current interactive context. Statement
-- may bind multple values.
@@ -206,7 +212,9 @@ runStmtWithLocation source linenumber expr step =
-- empty statement / comment
Nothing -> return (RunOk [])
- Just (tyThings, hval) -> do
+ Just (tyThings, hval, fix_env) -> do
+ updateFixityEnv fix_env
+
status <-
withVirtualCWD $
withBreakAction (isStep step) idflags' breakMVar statusMVar $ do
@@ -947,7 +955,8 @@ typeKind normalise str = withSession $ \hsc_env -> do
compileExpr :: GhcMonad m => String -> m HValue
compileExpr expr = withSession $ \hsc_env -> do
- Just (ids, hval) <- liftIO $ hscStmt hsc_env ("let __cmCompileExpr = "++expr)
+ Just (ids, hval, fix_env) <- liftIO $ hscStmt hsc_env ("let __cmCompileExpr = "++expr)
+ updateFixityEnv fix_env
hvals <- liftIO hval
case (ids,hvals) of
([_],[hv]) -> return hv
@@ -971,9 +980,11 @@ dynCompileExpr expr = do
}
setContext (IIDecl importDecl : iis)
let stmt = "let __dynCompileExpr = Data.Dynamic.toDyn (" ++ expr ++ ")"
- Just (ids, hvals) <- withSession $ \hsc_env ->
+ Just (ids, hvals, fix_env) <- withSession $ \hsc_env ->
liftIO $ hscStmt hsc_env stmt
setContext iis
+ updateFixityEnv fix_env
+
vals <- liftIO (unsafeCoerce# hvals :: IO [Dynamic])
case (ids,vals) of
(_:[], v:[]) -> return v
diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs
index aa5a432762..cdda96193c 100644
--- a/compiler/main/Packages.lhs
+++ b/compiler/main/Packages.lhs
@@ -152,10 +152,10 @@ getPackageDetails :: PackageState -> PackageId -> PackageConfig
getPackageDetails ps pid = expectJust "getPackageDetails" (lookupPackage (pkgIdMap ps) pid)
-- ----------------------------------------------------------------------------
--- Loading the package config files and building up the package state
+-- Loading the package db files and building up the package state
-- | Call this after 'DynFlags.parseDynFlags'. It reads the package
--- configuration files, and sets up various internal tables of package
+-- database files, and sets up various internal tables of package
-- information, according to the package-related flags on the
-- command-line (@-package@, @-hide-package@ etc.)
--
@@ -184,46 +184,37 @@ initPackages dflags = do
readPackageConfigs :: DynFlags -> IO [PackageConfig]
readPackageConfigs dflags = do
- e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH")
- system_pkgconfs <- getSystemPackageConfigs dflags
-
- let pkgconfs = case e_pkg_path of
- Left _ -> system_pkgconfs
- Right path
- | last cs == "" -> init cs ++ system_pkgconfs
- | otherwise -> cs
- where cs = parseSearchPath path
- -- if the path ends in a separator (eg. "/foo/bar:")
- -- the we tack on the system paths.
-
- pkgs <- mapM (readPackageConfig dflags)
- (pkgconfs ++ reverse (extraPkgConfs dflags))
- -- later packages shadow earlier ones. extraPkgConfs
- -- is in the opposite order to the flags on the
- -- command line.
-
- return (concat pkgs)
-
-
-getSystemPackageConfigs :: DynFlags -> IO [FilePath]
-getSystemPackageConfigs dflags = do
- -- System one always comes first
- let system_pkgconf = systemPackageConfig dflags
-
- -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf)
- -- unless the -no-user-package-conf flag was given.
- user_pkgconf <- do
- if not (dopt Opt_ReadUserPackageConf dflags) then return [] else do
- appdir <- getAppUserDataDirectory "ghc"
- let
- dir = appdir </> (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
- pkgconf = dir </> "package.conf.d"
- --
- exist <- doesDirectoryExist pkgconf
- if exist then return [pkgconf] else return []
- `catchIO` (\_ -> return [])
-
- return (system_pkgconf : user_pkgconf)
+ let system_conf_refs = [UserPkgConf, GlobalPkgConf]
+
+ e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH")
+ let base_conf_refs = case e_pkg_path of
+ Left _ -> system_conf_refs
+ Right path
+ | null (last cs)
+ -> map PkgConfFile (init cs) ++ system_conf_refs
+ | otherwise
+ -> map PkgConfFile cs
+ where cs = parseSearchPath path
+ -- if the path ends in a separator (eg. "/foo/bar:")
+ -- then we tack on the system paths.
+
+ let conf_refs = reverse (extraPkgConfs dflags base_conf_refs)
+ -- later packages shadow earlier ones. extraPkgConfs
+ -- is in the opposite order to the flags on the
+ -- command line.
+ confs <- liftM catMaybes $ mapM (resolvePackageConfig dflags) conf_refs
+
+ liftM concat $ mapM (readPackageConfig dflags) confs
+
+resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath)
+resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags)
+resolvePackageConfig _ UserPkgConf = handleIO (\_ -> return Nothing) $ do
+ appdir <- getAppUserDataDirectory "ghc"
+ let dir = appdir </> (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
+ pkgconf = dir </> "package.conf.d"
+ exist <- doesDirectoryExist pkgconf
+ return $ if exist then Just pkgconf else Nothing
+resolvePackageConfig _ (PkgConfFile name) = return $ Just name
readPackageConfig :: DynFlags -> FilePath -> IO [PackageConfig]
readPackageConfig dflags conf_file = do
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 378a25c8e1..e40f7b2f11 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -766,13 +766,17 @@ pop_and act span buf len = do _ <- popLexState
nextCharIs :: StringBuffer -> (Char -> Bool) -> Bool
nextCharIs buf p = not (atEnd buf) && p (currentChar buf)
+{-# INLINE nextCharIsNot #-}
+nextCharIsNot :: StringBuffer -> (Char -> Bool) -> Bool
+nextCharIsNot buf p = not (nextCharIs buf p)
+
notFollowedBy :: Char -> AlexAccPred Int
notFollowedBy char _ _ _ (AI _ buf)
- = nextCharIs buf (/=char)
+ = nextCharIsNot buf (== char)
notFollowedBySymbol :: AlexAccPred Int
notFollowedBySymbol _ _ _ (AI _ buf)
- = nextCharIs buf (`notElem` "!#$%&*+./<=>?@\\^|-~")
+ = nextCharIsNot buf (`elem` "!#$%&*+./<=>?@\\^|-~")
-- We must reject doc comments as being ordinary comments everywhere.
-- In some cases the doc comment will be selected as the lexeme due to
@@ -782,13 +786,16 @@ notFollowedBySymbol _ _ _ (AI _ buf)
isNormalComment :: AlexAccPred Int
isNormalComment bits _ _ (AI _ buf)
| haddockEnabled bits = notFollowedByDocOrPragma
- | otherwise = nextCharIs buf (/='#')
+ | otherwise = nextCharIsNot buf (== '#')
where
notFollowedByDocOrPragma
- = not $ spaceAndP buf (`nextCharIs` (`elem` "|^*$#"))
+ = afterOptionalSpace buf (\b -> nextCharIsNot b (`elem` "|^*$#"))
-spaceAndP :: StringBuffer -> (StringBuffer -> Bool) -> Bool
-spaceAndP buf p = p buf || nextCharIs buf (==' ') && p (snd (nextChar buf))
+afterOptionalSpace :: StringBuffer -> (StringBuffer -> Bool) -> Bool
+afterOptionalSpace buf p
+ = if nextCharIs buf (== ' ')
+ then p (snd (nextChar buf))
+ else p buf
atEOL :: AlexAccPred Int
atEOL _ _ _ (AI _ buf) = atEnd buf || currentChar buf == '\n'
@@ -2341,7 +2348,7 @@ dispatch_pragmas prags span buf len = case Map.lookup (clean_pragma (lexemeToStr
known_pragma :: Map String Action -> AlexAccPred Int
known_pragma prags _ _ len (AI _ buf) = (isJust $ Map.lookup (clean_pragma (lexemeToString (offsetBytes (- len) buf) len)) prags)
- && (nextCharIs buf (\c -> not (isAlphaNum c || c == '_')))
+ && (nextCharIsNot buf (\c -> isAlphaNum c || c == '_'))
clean_pragma :: String -> String
clean_pragma prag = canon_ws (map toLower (unprefix prag))
diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index 2a9f6df3ec..95274f0814 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -1159,6 +1159,7 @@ setInteractiveContext hsc_env icxt thing_inside
(mkNameSet (concatMap snd con_fields))
-- setting tcg_field_env is necessary to make RecordWildCards work
-- (test: ghci049)
+ , tcg_fix_env = ic_fix_env icxt
}) $
tcExtendGhciEnv visible_tmp_ids $ -- Note [GHCi temporary Ids]
@@ -1171,13 +1172,13 @@ setInteractiveContext hsc_env icxt thing_inside
-- The returned TypecheckedHsExpr is of type IO [ () ], a list of the bound
-- values, coerced to ().
tcRnStmt :: HscEnv -> InteractiveContext -> LStmt RdrName
- -> IO (Messages, Maybe ([Id], LHsExpr Id))
+ -> IO (Messages, Maybe ([Id], LHsExpr Id, FixityEnv))
tcRnStmt hsc_env ictxt rdr_stmt
= initTcPrintErrors hsc_env iNTERACTIVE $
setInteractiveContext hsc_env ictxt $ do {
-- The real work is done here
- (bound_ids, tc_expr) <- tcUserStmt rdr_stmt ;
+ ((bound_ids, tc_expr), fix_env) <- tcUserStmt rdr_stmt ;
zonked_expr <- zonkTopLExpr tc_expr ;
zonked_ids <- zonkTopBndrs bound_ids ;
@@ -1212,7 +1213,7 @@ tcRnStmt hsc_env ictxt rdr_stmt
(vcat [text "Bound Ids" <+> pprWithCommas ppr global_ids,
text "Typechecked expr" <+> ppr zonked_expr]) ;
- return (global_ids, zonked_expr)
+ return (global_ids, zonked_expr, fix_env)
}
where
bad_unboxed id = addErr (sep [ptext (sLit "GHCi can't bind a variable of unlifted type:"),
@@ -1281,7 +1282,7 @@ runPlans (p:ps) = tryTcLIE_ (runPlans ps) p
-- for more details. We do this lifting by trying different ways ('plans') of
-- lifting the code into the IO monad and type checking each plan until one
-- succeeds.
-tcUserStmt :: LStmt RdrName -> TcM PlanResult
+tcUserStmt :: LStmt RdrName -> TcM (PlanResult, FixityEnv)
-- An expression typed at the prompt is treated very specially
tcUserStmt (L loc (ExprStmt expr _ _ _))
@@ -1319,7 +1320,7 @@ tcUserStmt (L loc (ExprStmt expr _ _ _))
-- naked expression. Deferring type errors here is unhelpful because the
-- expression gets evaluated right away anyway. It also would potentially
-- emit two redundant type-error warnings, one from each plan.
- ; unsetDOptM Opt_DeferTypeErrors $ runPlans [
+ ; plan <- unsetDOptM Opt_DeferTypeErrors $ runPlans [
-- Plan A
do { stuff@([it_id], _) <- tcGhciStmts [bind_stmt, print_it]
; it_ty <- zonkTcType (idType it_id)
@@ -1336,14 +1337,17 @@ tcUserStmt (L loc (ExprStmt expr _ _ _))
-- This two-step story is very clunky, alas
do { _ <- checkNoErrs (tcGhciStmts [let_stmt])
--- checkNoErrs defeats the error recovery of let-bindings
- ; tcGhciStmts [let_stmt, print_it] }
- ]}
+ ; tcGhciStmts [let_stmt, print_it] } ]
+
+ ; fix_env <- getFixityEnv
+ ; return (plan, fix_env) }
tcUserStmt rdr_stmt@(L loc _)
- = do { (([rn_stmt], _), fvs) <- checkNoErrs $
- rnStmts GhciStmt [rdr_stmt] $ \_ ->
- return ((), emptyFVs) ;
- -- Don't try to typecheck if the renamer fails!
+ = do { (([rn_stmt], fix_env), fvs) <- checkNoErrs $
+ rnStmts GhciStmt [rdr_stmt] $ \_ -> do
+ fix_env <- getFixityEnv
+ return (fix_env, emptyFVs)
+ -- Don't try to typecheck if the renamer fails!
; traceRn (text "tcRnStmt" <+> vcat [ppr rdr_stmt, ppr rn_stmt, ppr fvs])
; rnDump (ppr rn_stmt) ;
@@ -1363,7 +1367,8 @@ tcUserStmt rdr_stmt@(L loc _)
-- The plans are:
-- [stmt; print v] if one binder and not v::()
-- [stmt] otherwise
- ; runPlans (print_result_plan ++ [tcGhciStmts [gi_stmt]]) }
+ ; plan <- runPlans (print_result_plan ++ [tcGhciStmts [gi_stmt]])
+ ; return (plan, fix_env) }
where
mk_print_result_plan stmt v
= do { stuff@([v_id], _) <- tcGhciStmts [stmt, print_v]
diff --git a/configure.ac b/configure.ac
index 8e3d9d2837..aeea6a4d9e 100644
--- a/configure.ac
+++ b/configure.ac
@@ -161,6 +161,10 @@ if test "$BootingFromHc" = "NO"; then
or --with-ghc to specify a different GHC to use.])
fi
fi
+
+ GHC_PACKAGE_DB_FLAG=package-db
+ FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.5],GHC_PACKAGE_DB_FLAG=package-conf)
+ AC_SUBST(GHC_PACKAGE_DB_FLAG)
fi;
# GHC is passed to Cabal, so we need a native path
diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml
index 1d091d7e2f..b501961b4e 100644
--- a/docs/users_guide/flags.xml
+++ b/docs/users_guide/flags.xml
@@ -594,14 +594,38 @@
<entry>-</entry>
</row>
<row>
- <entry><option>-package-conf</option> <replaceable>file</replaceable></entry>
- <entry>Load more packages from <replaceable>file</replaceable></entry>
+ <entry><option>-package-db</option> <replaceable>file</replaceable></entry>
+ <entry>Add <replaceable>file</replaceable> to the package db stack.</entry>
<entry>static</entry>
<entry>-</entry>
</row>
<row>
- <entry><option>-no-user-package-conf</option></entry>
- <entry>Don't load the user's package config file.</entry>
+ <entry><option>-clear-package-db</option></entry>
+ <entry>Clear the package db stack.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-global-package-db</option></entry>
+ <entry>Remove the global package db from the stack.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-global-package-db</option></entry>
+ <entry>Add the global package db to the stack.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-user-package-db</option></entry>
+ <entry>Remove the user's package db from the stack.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-user-package-db</option></entry>
+ <entry>Add the user's package db to the stack.</entry>
<entry>static</entry>
<entry>-</entry>
</row>
diff --git a/docs/users_guide/packages.xml b/docs/users_guide/packages.xml
index 4a3e45f2fb..d1df2d4712 100644
--- a/docs/users_guide/packages.xml
+++ b/docs/users_guide/packages.xml
@@ -408,35 +408,89 @@ _ZCMain_main_closure
see GHC's package table by running GHC with the <option>-v</option>
flag.</para>
- <para>Package databases may overlap: for example, packages in the
- user database will override (<emphasis>shadow</emphasis>) those
- of the same name and version in the global database.</para>
+ <para>Package databases may overlap, and they are arranged in a stack
+ structure. Packages closer to the top of the stack will override
+ (<emphasis>shadow</emphasis>) those below them. By default, the stack
+ contains just the global and the user's package databases, in that
+ order.</para>
- <para>You can control the loading of package databases using the following
- GHC options:</para>
+ <para>You can control GHC's package database stack using the following
+ options:</para>
<variablelist>
<varlistentry>
<term>
- <option>-package-conf <replaceable>file</replaceable></option>
- <indexterm><primary><option>-package-conf</option></primary></indexterm>
+ <option>-package-db <replaceable>file</replaceable></option>
+ <indexterm><primary><option>-package-db</option></primary></indexterm>
</term>
<listitem>
- <para>Read in the package configuration file
- <replaceable>file</replaceable> in addition to the system
- default file and the user's local file. Packages in additional
- files read this way will override those in the global and user
- databases.</para>
+ <para>Add the package database <replaceable>file</replaceable> on top
+ of the current stack. Packages in additional databases read this
+ way will override those in the initial stack and those in
+ previously specified databases.</para>
</listitem>
</varlistentry>
<varlistentry>
- <term><option>-no-user-package-conf</option>
- <indexterm><primary><option>-no-user-package-conf</option></primary>
+ <term><option>-no-global-package-db</option>
+ <indexterm><primary><option>-no-global-package-db</option></primary>
</indexterm>
</term>
<listitem>
- <para>Prevent loading of the user's local package database.</para>
+ <para>Remove the global package database from the package database
+ stack.</para>
+ </listitem>
+ </varlistentry>
+
+ <varlistentry>
+ <term><option>-no-user-package-db</option>
+ <indexterm><primary><option>-no-user-package-db</option></primary>
+ </indexterm>
+ </term>
+ <listitem>
+ <para>Prevent loading of the user's local package database in the
+ initial stack.</para>
+ </listitem>
+ </varlistentry>
+
+ <varlistentry>
+ <term><option>-clear-package-db</option>
+ <indexterm><primary><option>-clear-package-db</option></primary>
+ </indexterm>
+ </term>
+ <listitem>
+ <para>Reset the current package database stack. This option removes
+ every previously specified package database (including those
+ read from the <literal>GHC_PACKAGE_PATH</literal> environment
+ variable) from the package database stack.</para>
+ </listitem>
+ </varlistentry>
+
+ <varlistentry>
+ <term><option>-global-package-db</option>
+ <indexterm><primary><option>-global-package-db</option></primary>
+ </indexterm>
+ </term>
+ <listitem>
+ <para>Add the global package database on top of the current stack.
+ This option can be used after
+ <literal>-no-global-package-db</literal> to specify the position in
+ the stack where the global package database should be
+ loaded.</para>
+ </listitem>
+ </varlistentry>
+
+ <varlistentry>
+ <term><option>-user-package-db</option>
+ <indexterm><primary><option>-user-package-db</option></primary>
+ </indexterm>
+ </term>
+ <listitem>
+ <para>Add the user's package database on top of the current stack.
+ This option can be used after
+ <literal>-no-user-package-db</literal> to specify the position in
+ the stack where the user's package database should be
+ loaded.</para>
</listitem>
</varlistentry>
</variablelist>
@@ -456,11 +510,13 @@ _ZCMain_main_closure
packages.</para>
<para>If <literal>GHC_PACKAGE_PATH</literal> ends in a separator, then
- the default user and system package databases are appended, in that
- order. e.g. to augment the usual set of packages with a database of
- your own, you could say (on Unix):
-<screen>
-$ export GHC_PACKAGE_PATH=$HOME/.my-ghc-packages.conf:</screen>
+ the default package database stack (i.e. the user and global
+ package databases, in that order) is appended. For example, to augment
+ the usual set of packages with a database of your own, you could say
+ (on Unix):
+
+ <screen> $ export GHC_PACKAGE_PATH=$HOME/.my-ghc-packages.conf:</screen>
+
(use <literal>;</literal> instead of <literal>:</literal> on
Windows).</para>
@@ -601,12 +657,12 @@ haskell98-1.0.1.0
<literal>ghc-pkg</literal> knows about can be modified using the
<literal>GHC_PACKAGE_PATH</literal> environment variable (see <xref
linkend="ghc-package-path" />, and using
- <literal>--package-conf</literal> options on the
+ <literal>--package-db</literal> options on the
<literal>ghc-pkg</literal> command line.</para>
<para>When asked to modify a database, <literal>ghc-pkg</literal> modifies
the global database by default. Specifying <option>--user</option>
- causes it to act on the user database, or <option>--package-conf</option>
+ causes it to act on the user database, or <option>--package-db</option>
can be used to act on another database entirely. When multiple of these
options are given, the rightmost one is used as the database to act
upon.</para>
@@ -614,7 +670,7 @@ haskell98-1.0.1.0
<para>Commands that query the package database (list, latest,
describe, field, dot) operate on the list of databases specified by
the flags <option>--user</option>, <option>--global</option>, and
- <option>--package-conf</option>. If none of these flags are
+ <option>--package-db</option>. If none of these flags are
given, the default is <option>--global</option>
<option>--user</option>.</para>
@@ -888,8 +944,8 @@ ghc-pkg dot | tred | dot -Tpdf >pkgs.pdf
</indexterm>
</term>
<term>
- <option>-package-conf</option> <replaceable>file</replaceable>
- <indexterm><primary><option>-package-conf</option></primary>
+ <option>-package-db</option> <replaceable>file</replaceable>
+ <indexterm><primary><option>-package-db</option></primary>
</indexterm>
</term>
<listitem>
@@ -898,7 +954,7 @@ ghc-pkg dot | tred | dot -Tpdf >pkgs.pdf
also be the database modified by a <literal>register</literal>,
<literal>unregister</literal>, <literal>expose</literal> or
<literal>hide</literal> command, unless it is overridden by a later
- <option>--package-conf</option>, <option>--user</option> or
+ <option>--package-db</option>, <option>--user</option> or
<option>--global</option> option.</para>
</listitem>
</varlistentry>
diff --git a/docs/users_guide/runghc.xml b/docs/users_guide/runghc.xml
index 0681f00851..7d61f83ee1 100644
--- a/docs/users_guide/runghc.xml
+++ b/docs/users_guide/runghc.xml
@@ -32,7 +32,7 @@ runghc [runghc flags] [GHC flags] module [program args]
with a dash then you need to prefix it with
<literal>--ghc-arg=</literal> or runghc will think that it is the
program to run, e.g.
- <literal>runghc -package-conf --ghc-arg=foo.conf Main.hs</literal>.
+ <literal>runghc -package-db --ghc-arg=foo.conf Main.hs</literal>.
</para>
</sect1>
diff --git a/ghc.mk b/ghc.mk
index 195310bef6..a23171caa7 100644
--- a/ghc.mk
+++ b/ghc.mk
@@ -899,7 +899,7 @@ install_packages: rts/package.conf.install
$(call INSTALL_DIR,"$(DESTDIR)$(topdir)")
$(call removeTrees,"$(INSTALLED_PACKAGE_CONF)")
$(call INSTALL_DIR,"$(INSTALLED_PACKAGE_CONF)")
- "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install
+ "$(INSTALLED_GHC_PKG_REAL)" --force --global-package-db "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install
$(foreach p, $(INSTALLED_PKG_DIRS), \
$(call make-command, \
CROSS_COMPILE="$(CrossCompilePrefix)" \
diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs
index 1a80b49639..efafd25d23 100644
--- a/ghc/InteractiveUI.hs
+++ b/ghc/InteractiveUI.hs
@@ -993,7 +993,7 @@ pprInfo pefas (thing, fixity, insts)
where
show_fixity fix
| fix == GHC.defaultFixity = empty
- | otherwise = ppr fix <+> ppr (GHC.getName thing)
+ | otherwise = ppr fix <+> pprInfixName (GHC.getName thing)
-----------------------------------------------------------------------------
-- :main
diff --git a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs
index 242b7c02d1..7a254b7ac6 100644
--- a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs
+++ b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs
@@ -136,7 +136,8 @@ instance Binary License where
put PublicDomain = do putWord8 5
put AllRightsReserved = do putWord8 6
put OtherLicense = do putWord8 7
- put (UnknownLicense str) = do putWord8 8; put str
+ put (Apache v) = do putWord8 8; put v
+ put (UnknownLicense str) = do putWord8 9; put str
get = do
n <- getWord8
@@ -149,6 +150,7 @@ instance Binary License where
5 -> return PublicDomain
6 -> return AllRightsReserved
7 -> return OtherLicense
+ 8 -> do v <- get; return (Apache v)
_ -> do str <- get; return (UnknownLicense str)
instance Binary Version where
diff --git a/mk/config.mk.in b/mk/config.mk.in
index b998946239..1cf8685383 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -543,6 +543,8 @@ compiler/cmm/Bitmap_HC_OPTS += -ffull-laziness
# for some unknown reason, so turn full-laziness back on for this module.
endif
+GHC_PACKAGE_DB_FLAG = @GHC_PACKAGE_DB_FLAG@
+
#-----------------------------------------------------------------------------
# C compiler
#
diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk
index dcbd9cb8a6..bbd37d1ee1 100644
--- a/rules/distdir-way-opts.mk
+++ b/rules/distdir-way-opts.mk
@@ -61,7 +61,7 @@ define distdir-way-opts # args: $1 = dir, $2 = distdir, $3 = way, $4 = stage
#
# $1_$2_EXTRA_HC_OPTS GHC options for this dir/distdir mk/build.mk
#
-# $1_$2_HC_PKGCONF -package-conf flag if necessary rules/package-config.mk
+# $1_$2_HC_PKGCONF -package-db flag if necessary rules/package-config.mk
#
# $1_$2_HS_SRC_DIRS dirs relative to $1 containing $1/$2/package-data.mk
# source files
diff --git a/rules/package-config.mk b/rules/package-config.mk
index e0c9757862..1173e5f025 100644
--- a/rules/package-config.mk
+++ b/rules/package-config.mk
@@ -34,10 +34,10 @@ $1_$2_HC_MK_DEPEND = $$($1_$2_HC)
# on cygwin we get a dep on c:/ghc/..., and make gets confused by the :
$1_$2_HC_MK_DEPEND_DEP =
$1_$2_HC_DEP =
-$1_$2_HC_PKGCONF = -package-conf $$(BOOTSTRAPPING_CONF)
-$1_$2_GHC_PKG_OPTS = --package-conf=$$(BOOTSTRAPPING_CONF)
+$1_$2_HC_PKGCONF = -$(GHC_PACKAGE_DB_FLAG) $$(BOOTSTRAPPING_CONF)
+$1_$2_GHC_PKG_OPTS = --$(GHC_PACKAGE_DB_FLAG)=$$(BOOTSTRAPPING_CONF)
$1_$2_CONFIGURE_OPTS += --package-db=$$(TOP)/$$(BOOTSTRAPPING_CONF)
-$1_$2_MORE_HC_OPTS += -no-user-package-conf
+$1_$2_MORE_HC_OPTS += -no-user-$(GHC_PACKAGE_DB_FLAG)
$1_$2_MORE_HC_OPTS += -rtsopts
else
$1_$2_HC_PKGCONF =
@@ -51,7 +51,7 @@ $1_$2_GHC_PKG_OPTS =
$1_$2_HC_MK_DEPEND = $$(GHC_STAGE1)
$1_$2_HC_MK_DEPEND_DEP = $$($1_$2_HC_MK_DEPEND)
$1_$2_HC_DEP = $$($1_$2_HC)
-$1_$2_MORE_HC_OPTS += -no-user-package-conf
+$1_$2_MORE_HC_OPTS += -no-user-package-db
$1_$2_MORE_HC_OPTS += -rtsopts
endif
diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs
index c24f127422..0f11eea497 100644
--- a/utils/ghc-cabal/Main.hs
+++ b/utils/ghc-cabal/Main.hs
@@ -190,7 +190,7 @@ doInstall ghc ghcpkg strip topdir directory distDir
programPostConf = \_ _ -> return ["-B" ++ topdir],
programFindLocation = \_ -> return (Just ghc) }
ghcPkgProgram' = ghcPkgProgram {
- programPostConf = \_ _ -> return $ ["--global-conf", ghcpkgconf]
+ programPostConf = \_ _ -> return $ ["--global-package-db", ghcpkgconf]
++ ["--force" | not (null myDestDir) ],
programFindLocation = \_ -> return (Just ghcpkg) }
stripProgram' = stripProgram {
diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk
index 3ee2b13fa5..0a3e920e7a 100644
--- a/utils/ghc-cabal/ghc.mk
+++ b/utils/ghc-cabal/ghc.mk
@@ -27,7 +27,7 @@ $(GHC_CABAL_DIR)/dist/build/tmp/ghc-cabal$(exeext): $(wildcard libraries/Cabal/C
$(GHC_CABAL_DIR)/dist/build/tmp/ghc-cabal$(exeext): $(GHC_CABAL_DIR)/Main.hs $(TOUCH_DEP) | $$(dir $$@)/. bootstrapping/.
"$(GHC)" $(SRC_HC_OPTS) --make $(GHC_CABAL_DIR)/Main.hs -o $@ \
- -no-user-package-conf \
+ -no-user-$(GHC_PACKAGE_DB_FLAG) \
-Wall \
-DCABAL_VERSION=$(CABAL_VERSION) \
-odir bootstrapping \
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index e29301d933..e63139e997 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -119,11 +119,11 @@ flags = [
"use the current user's package database",
Option [] ["global"] (NoArg FlagGlobal)
"use the global package database",
- Option ['f'] ["package-conf"] (ReqArg FlagConfig "FILE")
+ Option ['f'] ["package-db"] (ReqArg FlagConfig "FILE")
"use the specified package config file",
- Option [] ["global-conf"] (ReqArg FlagGlobalConfig "FILE")
+ Option [] ["global-package-db"] (ReqArg FlagGlobalConfig "FILE")
"location of the global package config",
- Option [] ["no-user-package-conf"] (NoArg FlagNoUserDb)
+ Option [] ["no-user-package-db"] (NoArg FlagNoUserDb)
"never read the user package database",
Option [] ["force"] (NoArg FlagForce)
"ignore missing dependencies, directories, and libraries",
@@ -177,8 +177,8 @@ usageHeader prog = substProg prog $
" $p init {path}\n" ++
" Create and initialise a package database at the location {path}.\n" ++
" Packages can be registered in the new database using the register\n" ++
- " command with --package-conf={path}. To use the new database with GHC,\n" ++
- " use GHC's -package-conf flag.\n" ++
+ " command with --package-db={path}. To use the new database with GHC,\n" ++
+ " use GHC's -package-db flag.\n" ++
"\n" ++
" $p register {filename | -}\n" ++
" Register the package using the specified installed package\n" ++
@@ -247,7 +247,7 @@ usageHeader prog = substProg prog $
" Regenerate the package database cache. This command should only be\n" ++
" necessary if you added a package to the database by dropping a file\n" ++
" into the database directory manually. By default, the global DB\n" ++
- " is recached; to recache a different DB use --user or --package-conf\n" ++
+ " is recached; to recache a different DB use --user or --package-db\n" ++
" as appropriate.\n" ++
"\n" ++
" Substring matching is supported for {module} in find-module and\n" ++
@@ -257,13 +257,13 @@ usageHeader prog = substProg prog $
" When asked to modify a database (register, unregister, update,\n"++
" hide, expose, and also check), ghc-pkg modifies the global database by\n"++
" default. Specifying --user causes it to act on the user database,\n"++
- " or --package-conf can be used to act on another database\n"++
+ " or --package-db can be used to act on another database\n"++
" entirely. When multiple of these options are given, the rightmost\n"++
" one is used as the database to act upon.\n"++
"\n"++
" Commands that query the package database (list, tree, latest, describe,\n"++
" field) operate on the list of databases specified by the flags\n"++
- " --user, --global, and --package-conf. If none of these flags are\n"++
+ " --user, --global, and --package-db. If none of these flags are\n"++
" given, the default is --global --user.\n"++
"\n" ++
" The following optional flags are also accepted:\n"
@@ -471,9 +471,9 @@ getPkgDatabases :: Verbosity
getPkgDatabases verbosity modify use_cache expand_vars my_flags = do
-- first we determine the location of the global package config. On Windows,
-- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
- -- location is passed to the binary using the --global-config flag by the
+ -- location is passed to the binary using the --global-package-db flag by the
-- wrapper script.
- let err_msg = "missing --global-conf option, location of global package.conf unknown\n"
+ let err_msg = "missing --global-package-db option, location of global package database unknown\n"
global_conf <-
case [ f | FlagGlobalConfig f <- my_flags ] of
[] -> do mb_dir <- getLibDir
diff --git a/utils/ghc-pkg/ghc-pkg.wrapper b/utils/ghc-pkg/ghc-pkg.wrapper
index fad4bdfca0..3a14de1e22 100644
--- a/utils/ghc-pkg/ghc-pkg.wrapper
+++ b/utils/ghc-pkg/ghc-pkg.wrapper
@@ -1,5 +1,5 @@
#!/bin/sh
PKGCONF="$topdir/package.conf.d"
-exec "$executablename" --global-conf "$PKGCONF" ${1+"$@"}
+exec "$executablename" --global-package-db "$PKGCONF" ${1+"$@"}
diff --git a/utils/ghc-pkg/ghc.mk b/utils/ghc-pkg/ghc.mk
index 4f4967e07f..8ec3fd0097 100644
--- a/utils/ghc-pkg/ghc.mk
+++ b/utils/ghc-pkg/ghc.mk
@@ -24,7 +24,7 @@ else
$(call removeFiles,$@)
echo "#!/bin/sh" >>$@
echo "PKGCONF=$(TOP)/$(INPLACE_PACKAGE_CONF)" >>$@
- echo '$(TOP)/$< --global-conf $$PKGCONF $${1+"$$@"}' >> $@
+ echo '$(TOP)/$< --global-package-db $$PKGCONF $${1+"$$@"}' >> $@
chmod +x $@
endif
@@ -38,7 +38,7 @@ else
$(call removeFiles,$@)
echo "#!/bin/sh" >>$@
echo "PKGCONF=$(TOP)/$(INPLACE_PACKAGE_CONF)" >>$@
- echo '$(TOP)/$< --global-conf $$PKGCONF $${1+"$$@"}' >> $@
+ echo '$(TOP)/$< --global-package-db $$PKGCONF $${1+"$$@"}' >> $@
chmod +x $@
endif
@@ -53,7 +53,7 @@ endif
#
utils/ghc-pkg/dist/build/tmp/$(utils/ghc-pkg_dist_PROG)$(exeext): utils/ghc-pkg/Main.hs utils/ghc-pkg/Version.hs | bootstrapping/. $$(dir $$@)/. $(GHC_CABAL_INPLACE)
"$(GHC)" $(SRC_HC_OPTS) --make utils/ghc-pkg/Main.hs -o $@ \
- -no-user-package-conf \
+ -no-user-$(GHC_PACKAGE_DB_FLAG) \
-Wall -fno-warn-unused-imports -fno-warn-warnings-deprecations \
$(SRC_HC_WARNING_OPTS) \
-DCABAL_VERSION=$(CABAL_VERSION) \