X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=utils%2Fghc-pkg%2FMain.hs;h=936b3098b88631bb433e16e53a53dd74152b8c48;hp=a89be047a2ad9c00f106f6490f5c831d267a1935;hb=21c9699eb5175355db4c44643a58b3c532238400;hpb=8789db32595b2f9de24fc6a51dd9c35ea197a7d5 diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index a89be04..936b309 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -fglasgow-exts #-} +{-# OPTIONS -fglasgow-exts -cpp #-} ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow 2004. @@ -41,20 +41,37 @@ import qualified Control.Exception as Exception import Data.Maybe import Data.Char ( isSpace, toLower ) -import Monad -import Directory -import System ( getArgs, getProgName, getEnv, exitWith, ExitCode(..) ) +import Control.Monad +import System.Directory ( doesDirectoryExist, getDirectoryContents, + doesFileExist, renameFile, removeFile ) +import System.Exit ( exitWith, ExitCode(..) ) +import System.Environment ( getArgs, getProgName, getEnv ) import System.IO import System.IO.Error (try) -import Data.List ( isPrefixOf, isSuffixOf, intersperse, sortBy ) +import Data.List ( isPrefixOf, isSuffixOf, intersperse, sortBy, nub, + unfoldr, break ) +#if __GLASGOW_HASKELL__ > 604 +import Data.List ( isInfixOf ) +#else +import Data.List ( tails ) +#endif +import Control.Concurrent #ifdef mingw32_HOST_OS import Foreign import Foreign.C.String +import GHC.ConsoleHandler +#else +import System.Posix #endif import IO ( isPermissionError, isDoesNotExistError ) +#if defined(GLOB) +import System.Process(runInteractiveCommand) +import qualified System.Info(os) +#endif + -- ----------------------------------------------------------------------------- -- Entry point @@ -89,6 +106,7 @@ data Flag | FlagAutoGHCiLibs | FlagSimpleOutput | FlagNamesOnly + | FlagIgnoreCase deriving Eq flags :: [OptDescr Flag] @@ -96,9 +114,9 @@ flags = [ Option [] ["user"] (NoArg FlagUser) "use the current user's package database", Option [] ["global"] (NoArg FlagGlobal) - "(default) use the global package database", + "use the global package database", Option ['f'] ["package-conf"] (ReqArg FlagConfig "FILE") - "act upon specified package config file (only)", + "use the specified package config file", Option [] ["global-conf"] (ReqArg FlagGlobalConfig "FILE") "location of the global package config", Option [] ["force"] (NoArg FlagForce) @@ -114,7 +132,9 @@ flags = [ Option [] ["simple-output"] (NoArg FlagSimpleOutput) "print output in easy-to-parse format for some commands", Option [] ["names-only"] (NoArg FlagNamesOnly) - "only print package names, not versions; can only be used with list --simple-output" + "only print package names, not versions; can only be used with list --simple-output", + Option [] ["ignore-case"] (NoArg FlagIgnoreCase) + "ignore case for substring matching" ] deprecFlags :: [OptDescr Flag] @@ -123,7 +143,7 @@ deprecFlags = [ ] ourCopyright :: String -ourCopyright = "GHC package manager version " ++ version ++ "\n" +ourCopyright = "GHC package manager version " ++ Version.version ++ "\n" usageHeader :: String -> String usageHeader prog = substProg prog $ @@ -149,24 +169,46 @@ usageHeader prog = substProg prog $ " $p list [pkg]\n" ++ " List registered packages in the global database, and also the\n" ++ " user database if --user is given. If a package name is given\n" ++ - " all the registered versions will be listed in ascending order.\n" ++ + " All the registered versions will be listed in ascending order.\n" ++ + " Accepts the --simple-output flag.\n" ++ + "\n" ++ + " $p find-module {module}\n" ++ + " List registered packages exposing module {module} in the global\n" ++ + " database, and also the user database if --user is given. \n" ++ + " All the registered versions will be listed in ascending order.\n" ++ " Accepts the --simple-output flag.\n" ++ "\n" ++ - " $p latest pkg\n" ++ + " $p latest {pkg-id}\n" ++ " Prints the highest registered version of a package.\n" ++ "\n" ++ " $p check\n" ++ " Check the consistency of package depenencies and list broken packages.\n" ++ " Accepts the --simple-output flag.\n" ++ "\n" ++ - " $p describe {pkg-id}\n" ++ + " $p describe {pkg}\n" ++ " Give the registered description for the specified package. The\n" ++ " description is returned in precisely the syntax required by $p\n" ++ " register.\n" ++ "\n" ++ - " $p field {pkg-id} {field}\n" ++ + " $p field {pkg} {field}\n" ++ " Extract the specified field of the package description for the\n" ++ - " specified package.\n" ++ + " specified package. Accepts comma-separated multiple fields.\n" ++ + "\n" ++ + " Substring matching is supported for {module} in find-module and\n" ++ + " for {pkg} in list, describe, and field, where a '*' indicates\n" ++ + " open substring ends (prefix*, *suffix, *infix*).\n" ++ + "\n" ++ + " 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"++ + " 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, 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"++ + " given, the default is --global --user.\n"++ "\n" ++ " The following optional flags are also accepted:\n" @@ -180,8 +222,11 @@ substProg prog (c:xs) = c : substProg prog xs data Force = ForceAll | ForceFiles | NoForce +data PackageArg = Id PackageIdentifier | Substring String (String->Bool) + runit :: [Flag] -> [String] -> IO () runit cli nonopts = do + installSignalHandlers -- catch ^C and clean up prog <- getProgramName let force @@ -189,9 +234,42 @@ runit cli nonopts = do | FlagForceFiles `elem` cli = ForceFiles | otherwise = NoForce auto_ghci_libs = FlagAutoGHCiLibs `elem` cli + splitFields fields = unfoldr splitComma (',':fields) + where splitComma "" = Nothing + splitComma fs = Just $ break (==',') (tail fs) + + substringCheck :: String -> Maybe (String -> Bool) + substringCheck "" = Nothing + substringCheck "*" = Just (const True) + substringCheck [_] = Nothing + substringCheck (h:t) = + case (h, init t, last t) of + ('*',s,'*') -> Just (isInfixOf (f s) . f) + ('*',_, _ ) -> Just (isSuffixOf (f t) . f) + ( _ ,s,'*') -> Just (isPrefixOf (f (h:s)) . f) + _ -> Nothing + where f | FlagIgnoreCase `elem` cli = map toLower + | otherwise = id +#if defined(GLOB) + glob x | System.Info.os=="mingw32" = do + -- glob echoes its argument, after win32 filename globbing + (_,o,_,_) <- runInteractiveCommand ("glob "++x) + txt <- hGetContents o + return (read txt) + glob x | otherwise = return [x] +#endif -- -- first, parse the command case nonopts of +#if defined(GLOB) + -- dummy command to demonstrate usage and permit testing + -- without messing things up; use glob to selectively enable + -- windows filename globbing for file parameters + -- register, update, FlagGlobalConfig, FlagConfig; others? + ["glob", filename] -> do + print filename + glob filename >>= print +#endif ["register", filename] -> registerPackage filename cli auto_ghci_libs False force ["update", filename] -> @@ -207,20 +285,28 @@ runit cli nonopts = do hidePackage pkgid cli ["list"] -> do listPackages cli Nothing Nothing - ["list", pkgid_str] -> do - pkgid <- readGlobPkgId pkgid_str - listPackages cli (Just pkgid) Nothing + ["list", pkgid_str] -> + case substringCheck pkgid_str of + Nothing -> do pkgid <- readGlobPkgId pkgid_str + listPackages cli (Just (Id pkgid)) Nothing + Just m -> listPackages cli (Just (Substring pkgid_str m)) Nothing ["find-module", moduleName] -> do - listPackages cli Nothing (Just moduleName) + let match = maybe (==moduleName) id (substringCheck moduleName) + listPackages cli Nothing (Just match) ["latest", pkgid_str] -> do pkgid <- readGlobPkgId pkgid_str latestPackage cli pkgid - ["describe", pkgid_str] -> do - pkgid <- readGlobPkgId pkgid_str - describePackage cli pkgid - ["field", pkgid_str, field] -> do - pkgid <- readGlobPkgId pkgid_str - describeField cli pkgid field + ["describe", pkgid_str] -> + case substringCheck pkgid_str of + Nothing -> do pkgid <- readGlobPkgId pkgid_str + describePackage cli (Id pkgid) + Just m -> describePackage cli (Substring pkgid_str m) + ["field", pkgid_str, fields] -> + case substringCheck pkgid_str of + Nothing -> do pkgid <- readGlobPkgId pkgid_str + describeField cli (Id pkgid) (splitFields fields) + Just m -> describeField cli (Substring pkgid_str m) + (splitFields fields) ["check"] -> do checkConsistency cli [] -> do @@ -298,7 +384,7 @@ getPkgDatabases modify flags = do appdir <- getAppUserDataDirectory "ghc" let - subdir = targetARCH ++ '-':targetOS ++ '-':version + subdir = targetARCH ++ '-':targetOS ++ '-':Version.version archdir = appdir subdir user_conf = archdir "package.conf" user_exists <- doesFileExist user_conf @@ -309,7 +395,7 @@ getPkgDatabases modify flags = do | modify || user_exists = user_conf : global_confs ++ [global_conf] | otherwise = global_confs ++ [global_conf] - e_pkg_path <- try (getEnv "GHC_PACKAGE_PATH") + e_pkg_path <- try (System.Environment.getEnv "GHC_PACKAGE_PATH") let env_stack = case e_pkg_path of Left _ -> sys_databases @@ -322,29 +408,40 @@ getPkgDatabases modify flags = do -- This is the database we modify by default. virt_global_conf = last env_stack - -- -f flags on the command line add to the database stack, unless any - -- of them are present in the stack already. - let flag_stack = filter (`notElem` env_stack) - [ f | FlagConfig f <- reverse flags ] ++ env_stack + let db_flags = [ f | Just f <- map is_db_flag flags ] + where is_db_flag FlagUser = Just user_conf + is_db_flag FlagGlobal = Just virt_global_conf + is_db_flag (FlagConfig f) = Just f + is_db_flag _ = Nothing - -- Now we have the full stack of databases. Next, if the current - -- command is a "modify" type command, then we truncate the stack - -- so that the topmost element is the database being modified. final_stack <- if not modify - then return flag_stack + then -- For a "read" command, we use all the databases + -- specified on the command line. If there are no + -- command-line flags specifying databases, the default + -- is to use all the ones we know about. + if null db_flags then return env_stack + else return (reverse (nub db_flags)) else let - go (FlagUser : fs) = modifying user_conf - go (FlagGlobal : fs) = modifying virt_global_conf - go (FlagConfig f : fs) = modifying f - go (_ : fs) = go fs - go [] = modifying virt_global_conf + -- For a "modify" command, treat all the databases as + -- a stack, where we are modifying the top one, but it + -- can refer to packages in databases further down the + -- stack. + + -- -f flags on the command line add to the database + -- stack, unless any of them are present in the stack + -- already. + flag_stack = filter (`notElem` env_stack) + [ f | FlagConfig f <- reverse flags ] + ++ env_stack modifying f | f `elem` flag_stack = return (dropWhile (/= f) flag_stack) | otherwise = die ("requesting modification of database:\n\t" ++ f ++ "\n\twhich is not in the database stack.") in - go flags + if null db_flags + then modifying virt_global_conf + else modifying (head db_flags) db_stack <- mapM readParseDatabase final_stack return db_stack @@ -354,8 +451,8 @@ readParseDatabase filename = do str <- readFile filename `Exception.catch` \_ -> return emptyPackageConfig let packages = read str Exception.evaluate packages - `Exception.catch` \_ -> - die (filename ++ ": parse error in package config file") + `Exception.catch` \e-> + die ("error while parsing " ++ filename ++ ": " ++ show e) return (filename,packages) emptyPackageConfig :: String @@ -427,7 +524,7 @@ modifyPackage modifyPackage fn pkgid flags = do db_stack <- getPkgDatabases True{-modify-} flags let ((db_name, pkgs) : _) = db_stack - ps <- findPackages [(db_name,pkgs)] pkgid + ps <- findPackages [(db_name,pkgs)] (Id pkgid) let pids = map package ps let new_config = concat (map modify pkgs) modify pkg @@ -439,7 +536,7 @@ modifyPackage fn pkgid flags = do -- ----------------------------------------------------------------------------- -- Listing packages -listPackages :: [Flag] -> Maybe PackageIdentifier -> Maybe String -> IO () +listPackages :: [Flag] -> Maybe PackageArg -> Maybe (String->Bool) -> IO () listPackages flags mPackageName mModuleName = do let simple_output = FlagSimpleOutput `elem` flags db_stack <- getPkgDatabases False flags @@ -447,8 +544,8 @@ listPackages flags mPackageName mModuleName = do | Just this <- mPackageName = map (\(conf,pkgs) -> (conf, filter (this `matchesPkg`) pkgs)) db_stack - | Just this <- mModuleName = -- packages which expose mModuleName - map (\(conf,pkgs) -> (conf, filter (this `exposedInPkg`) pkgs)) + | Just match <- mModuleName = -- packages which expose mModuleName + map (\(conf,pkgs) -> (conf, filter (match `exposedInPkg`) pkgs)) db_stack | otherwise = db_stack @@ -462,6 +559,8 @@ listPackages flags mPackageName mModuleName = do EQ -> pkgVersion p1 `compare` pkgVersion p2 where (p1,p2) = (package pkg1, package pkg2) + match `exposedInPkg` pkg = any match (exposedModules pkg) + pkg_map = map (\p -> (package p, p)) $ concatMap snd db_stack show_func = if simple_output then show_simple else mapM_ (show_normal pkg_map) @@ -483,8 +582,8 @@ listPackages flags mPackageName mModuleName = do else showPackageId pkgs = map showPkg $ sortBy compPkgIdVer $ map package (concatMap snd db_stack) - when (null pkgs) $ die "no matches" - hPutStrLn stdout $ concat $ intersperse " " pkgs + when (not (null pkgs)) $ + hPutStrLn stdout $ concat $ intersperse " " pkgs -- ----------------------------------------------------------------------------- -- Prints the highest (hidden or exposed) version of a package @@ -492,7 +591,7 @@ listPackages flags mPackageName mModuleName = do latestPackage :: [Flag] -> PackageIdentifier -> IO () latestPackage flags pkgid = do db_stack <- getPkgDatabases False flags - ps <- findPackages db_stack pkgid + ps <- findPackages db_stack (Id pkgid) show_pkg (sortBy compPkgIdVer (map package ps)) where show_pkg [] = die "no matches" @@ -501,47 +600,51 @@ latestPackage flags pkgid = do -- ----------------------------------------------------------------------------- -- Describe -describePackage :: [Flag] -> PackageIdentifier -> IO () -describePackage flags pkgid = do +describePackage :: [Flag] -> PackageArg -> IO () +describePackage flags pkgarg = do db_stack <- getPkgDatabases False flags - ps <- findPackages db_stack pkgid + ps <- findPackages db_stack pkgarg mapM_ (putStrLn . showInstalledPackageInfo) ps -- PackageId is can have globVersion for the version -findPackages :: PackageDBStack -> PackageIdentifier -> IO [InstalledPackageInfo] -findPackages db_stack pkgid - = case [ p | p <- all_pkgs, pkgid `matchesPkg` p ] of - [] -> die ("cannot find package " ++ showPackageId pkgid) +findPackages :: PackageDBStack -> PackageArg -> IO [InstalledPackageInfo] +findPackages db_stack pkgarg + = case [ p | p <- all_pkgs, pkgarg `matchesPkg` p ] of + [] -> die ("cannot find package " ++ pkg_msg pkgarg) ps -> return ps where all_pkgs = concat (map snd db_stack) + pkg_msg (Id pkgid) = showPackageId pkgid + pkg_msg (Substring pkgpat _) = "matching "++pkgpat matches :: PackageIdentifier -> PackageIdentifier -> Bool pid `matches` pid' = (pkgName pid == pkgName pid') && (pkgVersion pid == pkgVersion pid' || not (realVersion pid)) -matchesPkg :: PackageIdentifier -> InstalledPackageInfo -> Bool -pid `matchesPkg` pkg = pid `matches` package pkg +matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool +(Id pid) `matchesPkg` pkg = pid `matches` package pkg +(Substring _ m) `matchesPkg` pkg = m (pkgName (package pkg)) compPkgIdVer :: PackageIdentifier -> PackageIdentifier -> Ordering compPkgIdVer p1 p2 = pkgVersion p1 `compare` pkgVersion p2 -exposedInPkg :: String -> InstalledPackageInfo -> Bool -moduleName `exposedInPkg` pkg = moduleName `elem` exposedModules pkg - -- ----------------------------------------------------------------------------- -- Field -describeField :: [Flag] -> PackageIdentifier -> String -> IO () -describeField flags pkgid field = do +describeField :: [Flag] -> PackageArg -> [String] -> IO () +describeField flags pkgarg fields = do db_stack <- getPkgDatabases False flags - case toField field of - Nothing -> die ("unknown field: " ++ field) - Just fn -> do - ps <- findPackages db_stack pkgid - let top_dir = takeDirectory (fst (last db_stack)) - mapM_ (putStrLn . fn) (mungePackagePaths top_dir ps) + fns <- toFields fields + ps <- findPackages db_stack pkgarg + let top_dir = takeDirectory (fst (last db_stack)) + mapM_ (selectFields fns) (mungePackagePaths top_dir ps) + where toFields [] = return [] + toFields (f:fs) = case toField f of + Nothing -> die ("unknown field: " ++ f) + Just fn -> do fns <- toFields fs + return (fn:fns) + selectFields fns info = mapM_ (\fn->putStrLn (fn info)) fns mungePackagePaths :: String -> [InstalledPackageInfo] -> [InstalledPackageInfo] -- Replace the strings "$topdir" and "$httptopdir" at the beginning of a path @@ -597,7 +700,9 @@ strList = show checkConsistency :: [Flag] -> IO () checkConsistency flags = do - db_stack <- getPkgDatabases False flags + db_stack <- getPkgDatabases True flags + -- check behaves like modify for the purposes of deciding which + -- databases to use, because ordering is important. let pkgs = map (\p -> (package p, p)) $ concatMap snd db_stack broken_pkgs = do (pid, p) <- pkgs @@ -620,11 +725,16 @@ missingPackageDeps :: InstalledPackageInfo -> [PackageIdentifier] missingPackageDeps pkg pkg_map = [ d | d <- depends pkg, isNothing (lookup d pkg_map)] ++ - [ d | d <- depends pkg, Just p <- return (lookup d pkg_map), isBrokenPackage p pkg_map] + [ d | d <- depends pkg, Just p <- return (lookup d pkg_map), + isBrokenPackage p pkg_map] isBrokenPackage :: InstalledPackageInfo -> [(PackageIdentifier, InstalledPackageInfo)] -> Bool -isBrokenPackage pkg pkg_map = not . null $ missingPackageDeps pkg pkg_map - +isBrokenPackage pkg pkg_map + = not . null $ missingPackageDeps pkg (filter notme pkg_map) + where notme (p,ipi) = package pkg /= p + -- remove p from the database when we invoke missingPackageDeps, + -- because we want mutually recursive groups of package to show up + -- as broken. (#1750) -- ----------------------------------------------------------------------------- -- Manipulating package.conf files @@ -657,17 +767,21 @@ savingOldConfig filename io = Exception.block $ do "to", show oldFile]) ioError err return False - hPutStrLn stdout "done." - io `catch` \e -> do - hPutStrLn stderr (show e) - hPutStr stdout ("\nWARNING: an error was encountered while writing" + (do hPutStrLn stdout "done."; io) + `Exception.catch` \e -> do + hPutStr stdout ("WARNING: an error was encountered while writing " ++ "the new configuration.\n") + -- remove any partially complete new version: + try (removeFile filename) + -- and attempt to restore the old one, if we had one: when restore_on_error $ do - hPutStr stdout "Attempting to restore the old configuration..." - do renameFile oldFile filename - hPutStrLn stdout "done." - `catch` \err -> hPutStrLn stdout ("Failed: " ++ show err) - ioError e + hPutStr stdout "Attempting to restore the old configuration... " + do renameFile oldFile filename + hPutStrLn stdout "done." + `catch` \err -> hPutStrLn stdout ("Failed: " ++ show err) + -- Note the above renameFile sometimes fails on Windows with + -- "permission denied", I have no idea why --SDM. + Exception.throwIO e ----------------------------------------------------------------------------- -- Sanity-check a new package config, and automatically build GHCi libs @@ -718,7 +832,7 @@ checkDuplicates db_stack pkg update force = do uncasep = map toLower . showPackageId dups = filter ((== uncasep pkgid) . uncasep) (map package pkgs) - when (not (null dups)) $ dieOrForceAll force $ + when (not update && not (null dups)) $ dieOrForceAll force $ "Package names may be treated case-insensitively in the future.\n"++ "Package " ++ showPackageId pkgid ++ " overlaps with: " ++ unwords (map showPackageId dups) @@ -852,7 +966,7 @@ expandEnvVars str force = go str "" lookupEnvVar :: String -> IO String lookupEnvVar nm = - catch (System.getEnv nm) + catch (System.Environment.getEnv nm) (\ _ -> do dieOrForceAll force ("Unable to expand variable " ++ show nm) return "") @@ -895,7 +1009,7 @@ my_head s [] = error s my_head s (x:xs) = x ----------------------------------------- --- Cut and pasted from ghc/compiler/SysTools +-- Cut and pasted from ghc/compiler/main/SysTools #if defined(mingw32_HOST_OS) subst :: Char -> Char -> String -> String @@ -925,3 +1039,37 @@ foreign import stdcall unsafe "GetModuleFileNameA" getExecDir :: String -> IO (Maybe String) getExecDir _ = return Nothing #endif + +----------------------------------------- +-- Adapted from ghc/compiler/utils/Panic + +installSignalHandlers :: IO () +installSignalHandlers = do + threadid <- myThreadId + let + interrupt = throwTo threadid (Exception.ErrorCall "interrupted") + -- +#if !defined(mingw32_HOST_OS) + installHandler sigQUIT (Catch interrupt) Nothing + installHandler sigINT (Catch interrupt) Nothing + return () +#elif __GLASGOW_HASKELL__ >= 603 + -- GHC 6.3+ has support for console events on Windows + -- NOTE: running GHCi under a bash shell for some reason requires + -- you to press Ctrl-Break rather than Ctrl-C to provoke + -- an interrupt. Ctrl-C is getting blocked somewhere, I don't know + -- why --SDM 17/12/2004 + let sig_handler ControlC = interrupt + sig_handler Break = interrupt + sig_handler _ = return () + + installHandler (Catch sig_handler) + return () +#else + return () -- nothing +#endif + +#if __GLASGOW_HASKELL__ <= 604 +isInfixOf :: (Eq a) => [a] -> [a] -> Bool +isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack) +#endif