GHC new build system megapatch
[ghc-hetmet.git] / utils / ghc-pkg / Main.hs
1 {-# OPTIONS -fglasgow-exts -cpp #-}
2 -----------------------------------------------------------------------------
3 --
4 -- (c) The University of Glasgow 2004.
5 --
6 -- Package management tool
7 --
8 -----------------------------------------------------------------------------
9
10 -- TODO:
11 -- * validate modules
12 -- * expanding of variables in new-style package conf
13 -- * version manipulation (checking whether old version exists,
14 --   hiding old version?)
15
16 module Main (main) where
17
18 import Version ( version, targetOS, targetARCH )
19 import Distribution.ModuleName hiding (main)
20 import Distribution.InstalledPackageInfo hiding (depends)
21 import Distribution.Compat.ReadP
22 import Distribution.ParseUtils
23 import Distribution.Package
24 import Distribution.Text
25 import Distribution.Version
26 import System.FilePath
27 import System.Cmd       ( rawSystem )
28 import System.Directory ( getAppUserDataDirectory, createDirectoryIfMissing )
29
30 import Prelude
31
32 #include "../../includes/ghcconfig.h"
33
34 import System.Console.GetOpt
35 import Text.PrettyPrint
36 #if __GLASGOW_HASKELL__ >= 609
37 import qualified Control.Exception as Exception
38 #else
39 import qualified Control.Exception.Extensible as Exception
40 #endif
41 import Data.Maybe
42
43 import Data.Char ( isSpace, toLower )
44 import Control.Monad
45 import System.Directory ( doesDirectoryExist, getDirectoryContents,
46                           doesFileExist, renameFile, removeFile )
47 import System.Exit ( exitWith, ExitCode(..) )
48 import System.Environment ( getArgs, getProgName, getEnv )
49 import System.IO
50 import System.IO.Error (try)
51 import Data.List
52 import Control.Concurrent
53
54 import Foreign
55 import Foreign.C
56 #ifdef mingw32_HOST_OS
57 import GHC.ConsoleHandler
58 #else
59 import System.Posix hiding (fdToHandle)
60 #endif
61
62 import IO ( isPermissionError )
63 import System.Posix.Internals
64 import GHC.Handle (fdToHandle)
65
66 #if defined(GLOB)
67 import System.Process(runInteractiveCommand)
68 import qualified System.Info(os)
69 #endif
70
71 -- -----------------------------------------------------------------------------
72 -- Entry point
73
74 main :: IO ()
75 main = do
76   args <- getArgs
77
78   case getOpt Permute (flags ++ deprecFlags) args of
79         (cli,_,[]) | FlagHelp `elem` cli -> do
80            prog <- getProgramName
81            bye (usageInfo (usageHeader prog) flags)
82         (cli,_,[]) | FlagVersion `elem` cli ->
83            bye ourCopyright
84         (cli,nonopts,[]) ->
85            runit cli nonopts
86         (_,_,errors) -> do
87            prog <- getProgramName
88            die (concat errors ++ usageInfo (usageHeader prog) flags)
89
90 -- -----------------------------------------------------------------------------
91 -- Command-line syntax
92
93 data Flag
94   = FlagUser
95   | FlagGlobal
96   | FlagHelp
97   | FlagVersion
98   | FlagConfig FilePath
99   | FlagGlobalConfig FilePath
100   | FlagForce
101   | FlagForceFiles
102   | FlagAutoGHCiLibs
103   | FlagSimpleOutput
104   | FlagNamesOnly
105   | FlagIgnoreCase
106   | FlagNoUserDb
107   deriving Eq
108
109 flags :: [OptDescr Flag]
110 flags = [
111   Option [] ["user"] (NoArg FlagUser)
112         "use the current user's package database",
113   Option [] ["global"] (NoArg FlagGlobal)
114         "use the global package database",
115   Option ['f'] ["package-conf"] (ReqArg FlagConfig "FILE")
116         "use the specified package config file",
117   Option [] ["global-conf"] (ReqArg FlagGlobalConfig "FILE")
118         "location of the global package config",
119   Option [] ["no-user-package-conf"] (NoArg FlagNoUserDb)
120         "never read the user package database",
121   Option [] ["force"] (NoArg FlagForce)
122          "ignore missing dependencies, directories, and libraries",
123   Option [] ["force-files"] (NoArg FlagForceFiles)
124          "ignore missing directories and libraries only",
125   Option ['g'] ["auto-ghci-libs"] (NoArg FlagAutoGHCiLibs)
126         "automatically build libs for GHCi (with register)",
127   Option ['?'] ["help"] (NoArg FlagHelp)
128         "display this help and exit",
129   Option ['V'] ["version"] (NoArg FlagVersion)
130         "output version information and exit",
131   Option [] ["simple-output"] (NoArg FlagSimpleOutput)
132         "print output in easy-to-parse format for some commands",
133   Option [] ["names-only"] (NoArg FlagNamesOnly)
134         "only print package names, not versions; can only be used with list --simple-output",
135   Option [] ["ignore-case"] (NoArg FlagIgnoreCase)
136         "ignore case for substring matching"
137   ]
138
139 deprecFlags :: [OptDescr Flag]
140 deprecFlags = [
141         -- put deprecated flags here
142   ]
143
144 ourCopyright :: String
145 ourCopyright = "GHC package manager version " ++ Version.version ++ "\n"
146
147 usageHeader :: String -> String
148 usageHeader prog = substProg prog $
149   "Usage:\n" ++
150   "  $p register {filename | -}\n" ++
151   "    Register the package using the specified installed package\n" ++
152   "    description. The syntax for the latter is given in the $p\n" ++
153   "    documentation.\n" ++
154   "\n" ++
155   "  $p update {filename | -}\n" ++
156   "    Register the package, overwriting any other package with the\n" ++
157   "    same name.\n" ++
158   "\n" ++
159   "  $p unregister {pkg-id}\n" ++
160   "    Unregister the specified package.\n" ++
161   "\n" ++
162   "  $p expose {pkg-id}\n" ++
163   "    Expose the specified package.\n" ++
164   "\n" ++
165   "  $p hide {pkg-id}\n" ++
166   "    Hide the specified package.\n" ++
167   "\n" ++
168   "  $p list [pkg]\n" ++
169   "    List registered packages in the global database, and also the\n" ++
170   "    user database if --user is given. If a package name is given\n" ++
171   "    all the registered versions will be listed in ascending order.\n" ++
172   "    Accepts the --simple-output flag.\n" ++
173   "\n" ++
174   "  $p find-module {module}\n" ++
175   "    List registered packages exposing module {module} in the global\n" ++
176   "    database, and also the user database if --user is given.\n" ++
177   "    All the registered versions will be listed in ascending order.\n" ++
178   "    Accepts the --simple-output flag.\n" ++
179   "\n" ++
180   "  $p latest {pkg-id}\n" ++
181   "    Prints the highest registered version of a package.\n" ++
182   "\n" ++
183   "  $p check\n" ++
184   "    Check the consistency of package depenencies and list broken packages.\n" ++
185   "    Accepts the --simple-output flag.\n" ++
186   "\n" ++
187   "  $p describe {pkg}\n" ++
188   "    Give the registered description for the specified package. The\n" ++
189   "    description is returned in precisely the syntax required by $p\n" ++
190   "    register.\n" ++
191   "\n" ++
192   "  $p field {pkg} {field}\n" ++
193   "    Extract the specified field of the package description for the\n" ++
194   "    specified package. Accepts comma-separated multiple fields.\n" ++
195   "\n" ++
196   "  $p dump\n" ++
197   "    Dump the registered description for every package.  This is like\n" ++
198   "    \"ghc-pkg describe '*'\", except that it is intended to be used\n" ++
199   "    by tools that parse the results, rather than humans.\n" ++
200   "\n" ++
201   " Substring matching is supported for {module} in find-module and\n" ++
202   " for {pkg} in list, describe, and field, where a '*' indicates\n" ++
203   " open substring ends (prefix*, *suffix, *infix*).\n" ++
204   "\n" ++
205   "  When asked to modify a database (register, unregister, update,\n"++
206   "  hide, expose, and also check), ghc-pkg modifies the global database by\n"++
207   "  default.  Specifying --user causes it to act on the user database,\n"++
208   "  or --package-conf can be used to act on another database\n"++
209   "  entirely. When multiple of these options are given, the rightmost\n"++
210   "  one is used as the database to act upon.\n"++
211   "\n"++
212   "  Commands that query the package database (list, latest, describe,\n"++
213   "  field) operate on the list of databases specified by the flags\n"++
214   "  --user, --global, and --package-conf.  If none of these flags are\n"++
215   "  given, the default is --global --user.\n"++
216   "\n" ++
217   " The following optional flags are also accepted:\n"
218
219 substProg :: String -> String -> String
220 substProg _ [] = []
221 substProg prog ('$':'p':xs) = prog ++ substProg prog xs
222 substProg prog (c:xs) = c : substProg prog xs
223
224 -- -----------------------------------------------------------------------------
225 -- Do the business
226
227 data Force = NoForce | ForceFiles | ForceAll | CannotForce
228   deriving (Eq,Ord)
229
230 data PackageArg = Id PackageIdentifier | Substring String (String->Bool)
231
232 runit :: [Flag] -> [String] -> IO ()
233 runit cli nonopts = do
234   installSignalHandlers -- catch ^C and clean up
235   prog <- getProgramName
236   let
237         force
238           | FlagForce `elem` cli        = ForceAll
239           | FlagForceFiles `elem` cli   = ForceFiles
240           | otherwise                   = NoForce
241         auto_ghci_libs = FlagAutoGHCiLibs `elem` cli
242         splitFields fields = unfoldr splitComma (',':fields)
243           where splitComma "" = Nothing
244                 splitComma fs = Just $ break (==',') (tail fs)
245
246         substringCheck :: String -> Maybe (String -> Bool)
247         substringCheck ""    = Nothing
248         substringCheck "*"   = Just (const True)
249         substringCheck [_]   = Nothing
250         substringCheck (h:t) =
251           case (h, init t, last t) of
252             ('*',s,'*') -> Just (isInfixOf (f s) . f)
253             ('*',_, _ ) -> Just (isSuffixOf (f t) . f)
254             ( _ ,s,'*') -> Just (isPrefixOf (f (h:s)) . f)
255             _           -> Nothing
256           where f | FlagIgnoreCase `elem` cli = map toLower
257                   | otherwise                 = id
258 #if defined(GLOB)
259         glob x | System.Info.os=="mingw32" = do
260           -- glob echoes its argument, after win32 filename globbing
261           (_,o,_,_) <- runInteractiveCommand ("glob "++x)
262           txt <- hGetContents o
263           return (read txt)
264         glob x | otherwise = return [x]
265 #endif
266   --
267   -- first, parse the command
268   case nonopts of
269 #if defined(GLOB)
270     -- dummy command to demonstrate usage and permit testing
271     -- without messing things up; use glob to selectively enable
272     -- windows filename globbing for file parameters
273     -- register, update, FlagGlobalConfig, FlagConfig; others?
274     ["glob", filename] -> do
275         print filename
276         glob filename >>= print
277 #endif
278     ["register", filename] ->
279         registerPackage filename cli auto_ghci_libs False force
280     ["update", filename] ->
281         registerPackage filename cli auto_ghci_libs True force
282     ["unregister", pkgid_str] -> do
283         pkgid <- readGlobPkgId pkgid_str
284         unregisterPackage pkgid cli force
285     ["expose", pkgid_str] -> do
286         pkgid <- readGlobPkgId pkgid_str
287         exposePackage pkgid cli force
288     ["hide",   pkgid_str] -> do
289         pkgid <- readGlobPkgId pkgid_str
290         hidePackage pkgid cli force
291     ["list"] -> do
292         listPackages cli Nothing Nothing
293     ["list", pkgid_str] ->
294         case substringCheck pkgid_str of
295           Nothing -> do pkgid <- readGlobPkgId pkgid_str
296                         listPackages cli (Just (Id pkgid)) Nothing
297           Just m -> listPackages cli (Just (Substring pkgid_str m)) Nothing
298     ["find-module", moduleName] -> do
299         let match = maybe (==moduleName) id (substringCheck moduleName)
300         listPackages cli Nothing (Just match)
301     ["latest", pkgid_str] -> do
302         pkgid <- readGlobPkgId pkgid_str
303         latestPackage cli pkgid
304     ["describe", pkgid_str] ->
305         case substringCheck pkgid_str of
306           Nothing -> do pkgid <- readGlobPkgId pkgid_str
307                         describePackage cli (Id pkgid)
308           Just m -> describePackage cli (Substring pkgid_str m)
309     ["field", pkgid_str, fields] ->
310         case substringCheck pkgid_str of
311           Nothing -> do pkgid <- readGlobPkgId pkgid_str
312                         describeField cli (Id pkgid) (splitFields fields)
313           Just m -> describeField cli (Substring pkgid_str m)
314                                       (splitFields fields)
315     ["check"] -> do
316         checkConsistency cli
317
318     ["dump"] -> do
319         dumpPackages cli
320
321     [] -> do
322         die ("missing command\n" ++
323                 usageInfo (usageHeader prog) flags)
324     (_cmd:_) -> do
325         die ("command-line syntax error\n" ++
326                 usageInfo (usageHeader prog) flags)
327
328 parseCheck :: ReadP a a -> String -> String -> IO a
329 parseCheck parser str what =
330   case [ x | (x,ys) <- readP_to_S parser str, all isSpace ys ] of
331     [x] -> return x
332     _ -> die ("cannot parse \'" ++ str ++ "\' as a " ++ what)
333
334 readGlobPkgId :: String -> IO PackageIdentifier
335 readGlobPkgId str = parseCheck parseGlobPackageId str "package identifier"
336
337 parseGlobPackageId :: ReadP r PackageIdentifier
338 parseGlobPackageId =
339   parse
340      +++
341   (do n <- parse
342       string "-*"
343       return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion }))
344
345 -- globVersion means "all versions"
346 globVersion :: Version
347 globVersion = Version{ versionBranch=[], versionTags=["*"] }
348
349 -- -----------------------------------------------------------------------------
350 -- Package databases
351
352 -- Some commands operate on a single database:
353 --      register, unregister, expose, hide
354 -- however these commands also check the union of the available databases
355 -- in order to check consistency.  For example, register will check that
356 -- dependencies exist before registering a package.
357 --
358 -- Some commands operate  on multiple databases, with overlapping semantics:
359 --      list, describe, field
360
361 type PackageDBName  = FilePath
362 type PackageDB      = [InstalledPackageInfo]
363
364 type NamedPackageDB = (PackageDBName, PackageDB)
365 type PackageDBStack = [NamedPackageDB]
366         -- A stack of package databases.  Convention: head is the topmost
367         -- in the stack.  Earlier entries override later one.
368
369 allPackagesInStack :: PackageDBStack -> [InstalledPackageInfo]
370 allPackagesInStack = concatMap snd
371
372 getPkgDatabases :: Bool -> [Flag] -> IO (PackageDBStack, Maybe PackageDBName)
373 getPkgDatabases modify my_flags = do
374   -- first we determine the location of the global package config.  On Windows,
375   -- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
376   -- location is passed to the binary using the --global-config flag by the
377   -- wrapper script.
378   let err_msg = "missing --global-conf option, location of global package.conf unknown\n"
379   global_conf <-
380      case [ f | FlagGlobalConfig f <- my_flags ] of
381         [] -> do mb_dir <- getLibDir
382                  case mb_dir of
383                         Nothing  -> die err_msg
384                         Just dir ->
385                             do let path = dir </> "package.conf"
386                                exists <- doesFileExist path
387                                unless exists $ die "Can't find package.conf"
388                                return path
389         fs -> return (last fs)
390
391   let global_conf_dir = global_conf ++ ".d"
392   global_conf_dir_exists <- doesDirectoryExist global_conf_dir
393   global_confs <-
394     if global_conf_dir_exists
395       then do files <- getDirectoryContents global_conf_dir
396               return [ global_conf_dir ++ '/' : file
397                      | file <- files
398                      , isSuffixOf ".conf" file]
399       else return []
400
401   let no_user_db = FlagNoUserDb `elem` my_flags
402
403   -- get the location of the user package database, and create it if necessary
404   -- getAppUserDataDirectory can fail (e.g. if $HOME isn't set)
405   appdir <- try $ getAppUserDataDirectory "ghc"
406
407   mb_user_conf <-
408      if no_user_db then return Nothing else
409      case appdir of
410        Right dir -> do
411                let subdir = targetARCH ++ '-':targetOS ++ '-':Version.version
412                    user_conf = dir </> subdir </> "package.conf"
413                user_exists <- doesFileExist user_conf
414                return (Just (user_conf,user_exists))
415        Left _ ->
416                return Nothing
417
418   -- If the user database doesn't exist, and this command isn't a
419   -- "modify" command, then we won't attempt to create or use it.
420   let sys_databases
421         | Just (user_conf,user_exists) <- mb_user_conf,
422           modify || user_exists = user_conf : global_confs ++ [global_conf]
423         | otherwise             = global_confs ++ [global_conf]
424
425   e_pkg_path <- try (System.Environment.getEnv "GHC_PACKAGE_PATH")
426   let env_stack =
427         case e_pkg_path of
428                 Left  _ -> sys_databases
429                 Right path
430                   | last cs == ""  -> init cs ++ sys_databases
431                   | otherwise      -> cs
432                   where cs = parseSearchPath path
433
434         -- The "global" database is always the one at the bottom of the stack.
435         -- This is the database we modify by default.
436       virt_global_conf = last env_stack
437
438   let db_flags = [ f | Just f <- map is_db_flag my_flags ]
439          where is_db_flag FlagUser
440                       | Just (user_conf, _user_exists) <- mb_user_conf 
441                       = Just user_conf
442                is_db_flag FlagGlobal     = Just virt_global_conf
443                is_db_flag (FlagConfig f) = Just f
444                is_db_flag _              = Nothing
445
446   (final_stack, to_modify) <-
447      if not modify
448         then    -- For a "read" command, we use all the databases
449                 -- specified on the command line.  If there are no
450                 -- command-line flags specifying databases, the default
451                 -- is to use all the ones we know about.
452              if null db_flags then return (env_stack, Nothing)
453                               else return (reverse (nub db_flags), Nothing)
454         else let
455                 -- For a "modify" command, treat all the databases as
456                 -- a stack, where we are modifying the top one, but it
457                 -- can refer to packages in databases further down the
458                 -- stack.
459
460                 -- -f flags on the command line add to the database
461                 -- stack, unless any of them are present in the stack
462                 -- already.
463                 flag_stack = filter (`notElem` env_stack)
464                                 [ f | FlagConfig f <- reverse my_flags ]
465                                 ++ env_stack
466
467                 -- the database we actually modify is the one mentioned
468                 -- rightmost on the command-line.
469                 to_modify = if null db_flags 
470                                 then Just virt_global_conf
471                                 else Just (last db_flags)
472              in
473                 return (flag_stack, to_modify)
474
475   db_stack <- mapM (readParseDatabase mb_user_conf) final_stack
476   return (db_stack, to_modify)
477
478 readParseDatabase :: Maybe (PackageDBName,Bool)
479                   -> PackageDBName
480                   -> IO (PackageDBName,PackageDB)
481 readParseDatabase mb_user_conf filename
482   -- the user database (only) is allowed to be non-existent
483   | Just (user_conf,False) <- mb_user_conf, filename == user_conf
484   = return (filename, [])
485   | otherwise
486   = do str <- readFile filename
487        let packages = map convertPackageInfoIn $ read str
488        Exception.evaluate packages
489          `catchError` \e->
490             die ("error while parsing " ++ filename ++ ": " ++ show e)
491        return (filename,packages)
492
493 -- -----------------------------------------------------------------------------
494 -- Registering
495
496 registerPackage :: FilePath
497                 -> [Flag]
498                 -> Bool              -- auto_ghci_libs
499                 -> Bool              -- update
500                 -> Force
501                 -> IO ()
502 registerPackage input my_flags auto_ghci_libs update force = do
503   (db_stack, Just to_modify) <- getPkgDatabases True my_flags
504   let
505         db_to_operate_on = my_head "register" $
506                            filter ((== to_modify).fst) db_stack
507   --
508   s <-
509     case input of
510       "-" -> do
511         putStr "Reading package info from stdin ... "
512         getContents
513       f   -> do
514         putStr ("Reading package info from " ++ show f ++ " ... ")
515         readFile f
516
517   expanded <- expandEnvVars s force
518
519   pkg <- parsePackageInfo expanded
520   putStrLn "done."
521
522   let unversioned_deps = filter (not . realVersion) (depends pkg)
523   unless (null unversioned_deps) $
524       die ("Unversioned dependencies found: " ++
525            unwords (map display unversioned_deps))
526
527   let truncated_stack = dropWhile ((/= to_modify).fst) db_stack
528   -- truncate the stack for validation, because we don't allow
529   -- packages lower in the stack to refer to those higher up.
530   validatePackageConfig pkg truncated_stack auto_ghci_libs update force
531   let new_details = filter not_this (snd db_to_operate_on) ++ [pkg]
532       not_this p = package p /= package pkg
533   writeNewConfig to_modify new_details
534
535 parsePackageInfo
536         :: String
537         -> IO InstalledPackageInfo
538 parsePackageInfo str =
539   case parseInstalledPackageInfo str of
540     ParseOk _warns ok -> return ok
541     ParseFailed err -> case locatedErrorMsg err of
542                            (Nothing, s) -> die s
543                            (Just l, s) -> die (show l ++ ": " ++ s)
544
545 -- -----------------------------------------------------------------------------
546 -- Exposing, Hiding, Unregistering are all similar
547
548 exposePackage :: PackageIdentifier ->  [Flag] -> Force -> IO ()
549 exposePackage = modifyPackage (\p -> [p{exposed=True}])
550
551 hidePackage :: PackageIdentifier ->  [Flag] -> Force -> IO ()
552 hidePackage = modifyPackage (\p -> [p{exposed=False}])
553
554 unregisterPackage :: PackageIdentifier ->  [Flag] -> Force -> IO ()
555 unregisterPackage = modifyPackage (\_ -> [])
556
557 modifyPackage
558   :: (InstalledPackageInfo -> [InstalledPackageInfo])
559   -> PackageIdentifier
560   -> [Flag]
561   -> Force
562   -> IO ()
563 modifyPackage fn pkgid my_flags force = do
564   (db_stack, Just _to_modify) <- getPkgDatabases True{-modify-} my_flags
565   ((db_name, pkgs), ps) <- fmap head $ findPackagesByDB db_stack (Id pkgid)
566 --  let ((db_name, pkgs) : rest_of_stack) = db_stack
567 --  ps <- findPackages [(db_name,pkgs)] (Id pkgid)
568   let 
569       pids = map package ps
570       modify pkg
571           | package pkg `elem` pids = fn pkg
572           | otherwise               = [pkg]
573       new_config = concat (map modify pkgs)
574
575   let
576       old_broken = brokenPackages (allPackagesInStack db_stack)
577       rest_of_stack = [ (nm, mypkgs)
578                       | (nm, mypkgs) <- db_stack, nm /= db_name ]
579       new_stack = (db_name,new_config) : rest_of_stack
580       new_broken = map package (brokenPackages (allPackagesInStack new_stack))
581       newly_broken = filter (`notElem` map package old_broken) new_broken
582   --
583   when (not (null newly_broken)) $
584       dieOrForceAll force ("unregistering " ++ display pkgid ++
585            " would break the following packages: "
586               ++ unwords (map display newly_broken))
587
588   writeNewConfig db_name new_config
589
590 -- -----------------------------------------------------------------------------
591 -- Listing packages
592
593 listPackages ::  [Flag] -> Maybe PackageArg -> Maybe (String->Bool) -> IO ()
594 listPackages my_flags mPackageName mModuleName = do
595   let simple_output = FlagSimpleOutput `elem` my_flags
596   (db_stack, _) <- getPkgDatabases False my_flags
597   let db_stack_filtered -- if a package is given, filter out all other packages
598         | Just this <- mPackageName =
599             map (\(conf,pkgs) -> (conf, filter (this `matchesPkg`) pkgs))
600                 db_stack
601         | Just match <- mModuleName = -- packages which expose mModuleName
602             map (\(conf,pkgs) -> (conf, filter (match `exposedInPkg`) pkgs))
603                 db_stack
604         | otherwise = db_stack
605
606       db_stack_sorted
607           = [ (db, sort_pkgs pkgs) | (db,pkgs) <- db_stack_filtered ]
608           where sort_pkgs = sortBy cmpPkgIds
609                 cmpPkgIds pkg1 pkg2 =
610                    case pkgName p1 `compare` pkgName p2 of
611                         LT -> LT
612                         GT -> GT
613                         EQ -> pkgVersion p1 `compare` pkgVersion p2
614                    where (p1,p2) = (package pkg1, package pkg2)
615
616       match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
617
618       pkg_map = allPackagesInStack db_stack
619       show_func = if simple_output then show_simple else mapM_ (show_normal pkg_map)
620
621   show_func (reverse db_stack_sorted)
622
623   where show_normal pkg_map (db_name,pkg_confs) =
624           hPutStrLn stdout (render $
625                 text db_name <> colon $$ nest 4 packages
626                 )
627            where packages = fsep (punctuate comma (map pp_pkg pkg_confs))
628                  broken = map package (brokenPackages pkg_map)
629                  pp_pkg p
630                    | package p `elem` broken = braces doc
631                    | exposed p = doc
632                    | otherwise = parens doc
633                    where doc = text (display (package p))
634
635         show_simple = simplePackageList my_flags . allPackagesInStack
636
637 simplePackageList :: [Flag] -> [InstalledPackageInfo] -> IO ()
638 simplePackageList my_flags pkgs = do
639    let showPkg = if FlagNamesOnly `elem` my_flags then display . pkgName
640                                                   else display
641        strs = map showPkg $ sortBy compPkgIdVer $ map package pkgs
642    when (not (null pkgs)) $
643       hPutStrLn stdout $ concat $ intersperse " " strs
644
645 -- -----------------------------------------------------------------------------
646 -- Prints the highest (hidden or exposed) version of a package
647
648 latestPackage ::  [Flag] -> PackageIdentifier -> IO ()
649 latestPackage my_flags pkgid = do
650   (db_stack, _) <- getPkgDatabases False my_flags
651   ps <- findPackages db_stack (Id pkgid)
652   show_pkg (sortBy compPkgIdVer (map package ps))
653   where
654     show_pkg [] = die "no matches"
655     show_pkg pids = hPutStrLn stdout (display (last pids))
656
657 -- -----------------------------------------------------------------------------
658 -- Describe
659
660 describePackage :: [Flag] -> PackageArg -> IO ()
661 describePackage my_flags pkgarg = do
662   (db_stack, _) <- getPkgDatabases False my_flags
663   ps <- findPackages db_stack pkgarg
664   doDump ps
665
666 dumpPackages :: [Flag] -> IO ()
667 dumpPackages my_flags = do
668   (db_stack, _) <- getPkgDatabases False my_flags
669   doDump (allPackagesInStack db_stack)
670
671 doDump :: [InstalledPackageInfo] -> IO ()
672 doDump = mapM_ putStrLn . intersperse "---" . map showInstalledPackageInfo
673
674 -- PackageId is can have globVersion for the version
675 findPackages :: PackageDBStack -> PackageArg -> IO [InstalledPackageInfo]
676 findPackages db_stack pkgarg
677   = fmap (concatMap snd) $ findPackagesByDB db_stack pkgarg
678
679 findPackagesByDB :: PackageDBStack -> PackageArg
680                  -> IO [(NamedPackageDB, [InstalledPackageInfo])]
681 findPackagesByDB db_stack pkgarg
682   = case [ (db, matched)
683          | db@(_, pkgs) <- db_stack,
684            let matched = filter (pkgarg `matchesPkg`) pkgs,
685            not (null matched) ] of
686         [] -> die ("cannot find package " ++ pkg_msg pkgarg)
687         ps -> return ps
688   where
689         pkg_msg (Id pkgid)           = display pkgid
690         pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
691
692 matches :: PackageIdentifier -> PackageIdentifier -> Bool
693 pid `matches` pid'
694   = (pkgName pid == pkgName pid')
695     && (pkgVersion pid == pkgVersion pid' || not (realVersion pid))
696
697 matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
698 (Id pid)        `matchesPkg` pkg = pid `matches` package pkg
699 (Substring _ m) `matchesPkg` pkg = m (display (package pkg))
700
701 compPkgIdVer :: PackageIdentifier -> PackageIdentifier -> Ordering
702 compPkgIdVer p1 p2 = pkgVersion p1 `compare` pkgVersion p2
703
704 -- -----------------------------------------------------------------------------
705 -- Field
706
707 describeField :: [Flag] -> PackageArg -> [String] -> IO ()
708 describeField my_flags pkgarg fields = do
709   (db_stack, _) <- getPkgDatabases False my_flags
710   fns <- toFields fields
711   ps <- findPackages db_stack pkgarg
712   let top_dir = takeDirectory (fst (last db_stack))
713   mapM_ (selectFields fns) (mungePackagePaths top_dir ps)
714   where toFields [] = return []
715         toFields (f:fs) = case toField f of
716             Nothing -> die ("unknown field: " ++ f)
717             Just fn -> do fns <- toFields fs
718                           return (fn:fns)
719         selectFields fns info = mapM_ (\fn->putStrLn (fn info)) fns
720
721 mungePackagePaths :: String -> [InstalledPackageInfo] -> [InstalledPackageInfo]
722 -- Replace the strings "$topdir" and "$httptopdir" at the beginning of a path
723 -- with the current topdir (obtained from the -B option).
724 mungePackagePaths top_dir ps = map munge_pkg ps
725   where
726   munge_pkg p = p{ importDirs        = munge_paths (importDirs p),
727                    includeDirs       = munge_paths (includeDirs p),
728                    libraryDirs       = munge_paths (libraryDirs p),
729                    frameworkDirs     = munge_paths (frameworkDirs p),
730                    haddockInterfaces = munge_paths (haddockInterfaces p),
731                    haddockHTMLs      = munge_paths (haddockHTMLs p)
732                  }
733
734   munge_paths = map munge_path
735
736   munge_path p
737    | Just p' <- maybePrefixMatch "$topdir"     p =            top_dir ++ p'
738    | Just p' <- maybePrefixMatch "$httptopdir" p = toHttpPath top_dir ++ p'
739    | otherwise                               = p
740
741   toHttpPath p = "file:///" ++ p
742
743 maybePrefixMatch :: String -> String -> Maybe String
744 maybePrefixMatch []    rest = Just rest
745 maybePrefixMatch (_:_) []   = Nothing
746 maybePrefixMatch (p:pat) (r:rest)
747   | p == r    = maybePrefixMatch pat rest
748   | otherwise = Nothing
749
750 toField :: String -> Maybe (InstalledPackageInfo -> String)
751 -- backwards compatibility:
752 toField "import_dirs"     = Just $ strList . importDirs
753 toField "source_dirs"     = Just $ strList . importDirs
754 toField "library_dirs"    = Just $ strList . libraryDirs
755 toField "hs_libraries"    = Just $ strList . hsLibraries
756 toField "extra_libraries" = Just $ strList . extraLibraries
757 toField "include_dirs"    = Just $ strList . includeDirs
758 toField "c_includes"      = Just $ strList . includes
759 toField "package_deps"    = Just $ strList . map display. depends
760 toField "extra_cc_opts"   = Just $ strList . ccOptions
761 toField "extra_ld_opts"   = Just $ strList . ldOptions
762 toField "framework_dirs"  = Just $ strList . frameworkDirs
763 toField "extra_frameworks"= Just $ strList . frameworks
764 toField s                 = showInstalledPackageInfoField s
765
766 strList :: [String] -> String
767 strList = show
768
769
770 -- -----------------------------------------------------------------------------
771 -- Check: Check consistency of installed packages
772
773 checkConsistency :: [Flag] -> IO ()
774 checkConsistency my_flags = do
775   (db_stack, _) <- getPkgDatabases True my_flags
776          -- check behaves like modify for the purposes of deciding which
777          -- databases to use, because ordering is important.
778
779   let simple_output = FlagSimpleOutput `elem` my_flags
780
781   let pkgs = allPackagesInStack db_stack
782
783       checkPackage p = do
784          (_,es) <- runValidate $ checkPackageConfig p db_stack False True
785          if null es
786             then return []
787             else do
788               when (not simple_output) $ do
789                   reportError ("There are problems in package " ++ display (package p) ++ ":")
790                   reportValidateErrors es "  " Nothing
791                   return ()
792               return [p]
793
794   broken_pkgs <- concat `fmap` mapM checkPackage pkgs
795
796   let filterOut pkgs1 pkgs2 = filter not_in pkgs2
797         where not_in p = package p `notElem` all_ps
798               all_ps = map package pkgs1
799
800   let not_broken_pkgs = filterOut broken_pkgs pkgs
801       (_, trans_broken_pkgs) = closure [] not_broken_pkgs
802       all_broken_pkgs = broken_pkgs ++ trans_broken_pkgs
803
804   when (not (null all_broken_pkgs)) $ do
805     if simple_output
806       then simplePackageList my_flags all_broken_pkgs
807       else do
808        reportError ("\nThe following packages are broken, either because they have a problem\n"++
809                 "listed above, or because they depend on a broken package.")
810        mapM_ (hPutStrLn stderr . display . package) all_broken_pkgs
811
812   when (not (null all_broken_pkgs)) $ exitWith (ExitFailure 1)
813
814
815 closure :: [InstalledPackageInfo] -> [InstalledPackageInfo]
816         -> ([InstalledPackageInfo], [InstalledPackageInfo])
817 closure pkgs db_stack = go pkgs db_stack
818  where
819    go avail not_avail =
820      case partition (depsAvailable avail) not_avail of
821         ([],        not_avail') -> (avail, not_avail')
822         (new_avail, not_avail') -> go (new_avail ++ avail) not_avail'
823
824    depsAvailable :: [InstalledPackageInfo] -> InstalledPackageInfo
825                  -> Bool
826    depsAvailable pkgs_ok pkg = null dangling
827         where dangling = filter (`notElem` pids) (depends pkg)
828               pids = map package pkgs_ok
829
830         -- we want mutually recursive groups of package to show up
831         -- as broken. (#1750)
832
833 brokenPackages :: [InstalledPackageInfo] -> [InstalledPackageInfo]
834 brokenPackages pkgs = snd (closure [] pkgs)
835
836 -- -----------------------------------------------------------------------------
837 -- Manipulating package.conf files
838
839 type InstalledPackageInfoString = InstalledPackageInfo_ String
840
841 convertPackageInfoOut :: InstalledPackageInfo -> InstalledPackageInfoString
842 convertPackageInfoOut
843     (pkgconf@(InstalledPackageInfo { exposedModules = e,
844                                      hiddenModules = h })) =
845         pkgconf{ exposedModules = map display e,
846                  hiddenModules  = map display h }
847
848 convertPackageInfoIn :: InstalledPackageInfoString -> InstalledPackageInfo
849 convertPackageInfoIn
850     (pkgconf@(InstalledPackageInfo { exposedModules = e,
851                                      hiddenModules = h })) =
852         pkgconf{ exposedModules = map convert e,
853                  hiddenModules  = map convert h }
854     where convert = fromJust . simpleParse
855
856 writeNewConfig :: FilePath -> [InstalledPackageInfo] -> IO ()
857 writeNewConfig filename packages = do
858   hPutStr stdout "Writing new package config file... "
859   createDirectoryIfMissing True $ takeDirectory filename
860   let shown = concat $ intersperse ",\n "
861                      $ map (show . convertPackageInfoOut) packages
862       fileContents = "[" ++ shown ++ "\n]"
863   writeFileAtomic filename fileContents
864     `catch` \e ->
865       if isPermissionError e
866       then die (filename ++ ": you don't have permission to modify this file")
867       else ioError e
868   hPutStrLn stdout "done."
869
870 -----------------------------------------------------------------------------
871 -- Sanity-check a new package config, and automatically build GHCi libs
872 -- if requested.
873
874 type ValidateError = (Force,String)
875
876 newtype Validate a = V { runValidate :: IO (a, [ValidateError]) }
877
878 instance Monad Validate where
879    return a = V $ return (a, [])
880    m >>= k = V $ do
881       (a, es) <- runValidate m
882       (b, es') <- runValidate (k a)
883       return (b,es++es')
884
885 verror :: Force -> String -> Validate ()
886 verror f s = V (return ((),[(f,s)]))
887
888 liftIO :: IO a -> Validate a
889 liftIO k = V (k >>= \a -> return (a,[]))
890
891 -- returns False if we should die
892 reportValidateErrors :: [ValidateError] -> String -> Maybe Force -> IO Bool
893 reportValidateErrors es prefix mb_force = do
894   oks <- mapM report es
895   return (and oks)
896   where
897     report (f,s)
898       | Just force <- mb_force
899       = if (force >= f)
900            then do reportError (prefix ++ s ++ " (ignoring)")
901                    return True
902            else if f < CannotForce
903                    then do reportError (prefix ++ s ++ " (use --force to override)")
904                            return False
905                    else do reportError err
906                            return False
907       | otherwise = do reportError err
908                        return False
909       where
910              err = prefix ++ s
911
912 validatePackageConfig :: InstalledPackageInfo
913                       -> PackageDBStack
914                       -> Bool   -- auto-ghc-libs
915                       -> Bool   -- update, or check
916                       -> Force
917                       -> IO ()
918 validatePackageConfig pkg db_stack auto_ghci_libs update force = do
919   (_,es) <- runValidate $ checkPackageConfig pkg db_stack auto_ghci_libs update
920   ok <- reportValidateErrors es (display (package pkg) ++ ": ") (Just force)
921   when (not ok) $ exitWith (ExitFailure 1)
922
923 checkPackageConfig :: InstalledPackageInfo
924                       -> PackageDBStack
925                       -> Bool   -- auto-ghc-libs
926                       -> Bool   -- update, or check
927                       -> Validate ()
928 checkPackageConfig pkg db_stack auto_ghci_libs update = do
929   checkPackageId pkg
930   checkDuplicates db_stack pkg update
931   mapM_ (checkDep db_stack) (depends pkg)
932   checkDuplicateDepends (depends pkg)
933   mapM_ (checkDir "import-dirs") (importDirs pkg)
934   mapM_ (checkDir "library-dirs") (libraryDirs pkg)
935   mapM_ (checkDir "include-dirs") (includeDirs pkg)
936   checkModules pkg
937   mapM_ (checkHSLib (libraryDirs pkg) auto_ghci_libs) (hsLibraries pkg)
938   -- ToDo: check these somehow?
939   --    extra_libraries :: [String],
940   --    c_includes      :: [String],
941
942 -- When the package name and version are put together, sometimes we can
943 -- end up with a package id that cannot be parsed.  This will lead to
944 -- difficulties when the user wants to refer to the package later, so
945 -- we check that the package id can be parsed properly here.
946 checkPackageId :: InstalledPackageInfo -> Validate ()
947 checkPackageId ipi =
948   let str = display (package ipi) in
949   case [ x :: PackageIdentifier | (x,ys) <- readP_to_S parse str, all isSpace ys ] of
950     [_] -> return ()
951     []  -> verror CannotForce ("invalid package identifier: " ++ str)
952     _   -> verror CannotForce ("ambiguous package identifier: " ++ str)
953
954 checkDuplicates :: PackageDBStack -> InstalledPackageInfo -> Bool -> Validate ()
955 checkDuplicates db_stack pkg update = do
956   let
957         pkgid = package pkg
958         (_top_db_name, pkgs) : _  = db_stack
959   --
960   -- Check whether this package id already exists in this DB
961   --
962   when (not update && (pkgid `elem` map package pkgs)) $
963        verror CannotForce $
964           "package " ++ display pkgid ++ " is already installed"
965
966   let
967         uncasep = map toLower . display
968         dups = filter ((== uncasep pkgid) . uncasep) (map package pkgs)
969
970   when (not update && not (null dups)) $ verror ForceAll $
971         "Package names may be treated case-insensitively in the future.\n"++
972         "Package " ++ display pkgid ++
973         " overlaps with: " ++ unwords (map display dups)
974
975
976 checkDir :: String -> String -> Validate ()
977 checkDir thisfield d
978  | "$topdir"     `isPrefixOf` d = return ()
979  | "$httptopdir" `isPrefixOf` d = return ()
980         -- can't check these, because we don't know what $(http)topdir is
981  | otherwise = do
982    there <- liftIO $ doesDirectoryExist d
983    when (not there) $
984        verror ForceFiles (thisfield ++ ": " ++ d ++ " doesn't exist or isn't a directory")
985
986 checkDep :: PackageDBStack -> PackageIdentifier -> Validate ()
987 checkDep db_stack pkgid
988   | pkgid `elem` pkgids || (not real_version && name_exists) = return ()
989   | otherwise = verror ForceAll ("dependency " ++ display pkgid
990                                  ++ " doesn't exist")
991   where
992         -- for backwards compat, we treat 0.0 as a special version,
993         -- and don't check that it actually exists.
994         real_version = realVersion pkgid
995
996         name_exists = any (\p -> pkgName (package p) == name) all_pkgs
997         name = pkgName pkgid
998
999         all_pkgs = allPackagesInStack db_stack
1000         pkgids = map package all_pkgs
1001
1002 checkDuplicateDepends :: [PackageIdentifier] -> Validate ()
1003 checkDuplicateDepends deps
1004   | null dups = return ()
1005   | otherwise = verror ForceAll ("package has duplicate dependencies: " ++
1006                                      unwords (map display dups))
1007   where
1008        dups = [ p | (p:_:_) <- group (sort deps) ]
1009
1010 realVersion :: PackageIdentifier -> Bool
1011 realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
1012
1013 checkHSLib :: [String] -> Bool -> String -> Validate ()
1014 checkHSLib dirs auto_ghci_libs lib = do
1015   let batch_lib_file = "lib" ++ lib ++ ".a"
1016   m <- liftIO $ doesFileExistOnPath batch_lib_file dirs
1017   case m of
1018     Nothing -> verror ForceFiles ("cannot find " ++ batch_lib_file ++
1019                                    " on library path")
1020     Just dir -> liftIO $ checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
1021
1022 doesFileExistOnPath :: String -> [FilePath] -> IO (Maybe FilePath)
1023 doesFileExistOnPath file path = go path
1024   where go []     = return Nothing
1025         go (p:ps) = do b <- doesFileExistIn file p
1026                        if b then return (Just p) else go ps
1027
1028 doesFileExistIn :: String -> String -> IO Bool
1029 doesFileExistIn lib d
1030  | "$topdir"     `isPrefixOf` d = return True
1031  | "$httptopdir" `isPrefixOf` d = return True
1032  | otherwise                = doesFileExist (d </> lib)
1033
1034 checkModules :: InstalledPackageInfo -> Validate ()
1035 checkModules pkg = do
1036   mapM_ findModule (exposedModules pkg ++ hiddenModules pkg)
1037   where
1038     findModule modl = do
1039       -- there's no .hi file for GHC.Prim
1040       if modl == fromString "GHC.Prim" then return () else do
1041       let file = toFilePath modl <.> "hi"
1042       m <- liftIO $ doesFileExistOnPath file (importDirs pkg)
1043       when (isNothing m) $
1044          verror ForceFiles ("file " ++ file ++ " is missing")
1045
1046 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
1047 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build
1048   | auto_build = autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
1049   | otherwise  = do
1050       m <- doesFileExistOnPath ghci_lib_file dirs
1051       when (isNothing m && ghci_lib_file /= "HSrts.o") $
1052         hPutStrLn stderr ("warning: can't find GHCi lib " ++ ghci_lib_file)
1053  where
1054     ghci_lib_file = lib <.> "o"
1055
1056 -- automatically build the GHCi version of a batch lib,
1057 -- using ld --whole-archive.
1058
1059 autoBuildGHCiLib :: String -> String -> String -> IO ()
1060 autoBuildGHCiLib dir batch_file ghci_file = do
1061   let ghci_lib_file  = dir ++ '/':ghci_file
1062       batch_lib_file = dir ++ '/':batch_file
1063   hPutStr stderr ("building GHCi library " ++ ghci_lib_file ++ "...")
1064 #if defined(darwin_HOST_OS)
1065   r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"-all_load",batch_lib_file]
1066 #elif defined(mingw32_HOST_OS)
1067   execDir <- getLibDir
1068   r <- rawSystem (maybe "" (++"/gcc-lib/") execDir++"ld") ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1069 #else
1070   r <- rawSystem "ld" ["-r","-x","-o",ghci_lib_file,"--whole-archive",batch_lib_file]
1071 #endif
1072   when (r /= ExitSuccess) $ exitWith r
1073   hPutStrLn stderr (" done.")
1074
1075 -- -----------------------------------------------------------------------------
1076 -- Searching for modules
1077
1078 #if not_yet
1079
1080 findModules :: [FilePath] -> IO [String]
1081 findModules paths =
1082   mms <- mapM searchDir paths
1083   return (concat mms)
1084
1085 searchDir path prefix = do
1086   fs <- getDirectoryEntries path `catch` \_ -> return []
1087   searchEntries path prefix fs
1088
1089 searchEntries path prefix [] = return []
1090 searchEntries path prefix (f:fs)
1091   | looks_like_a_module  =  do
1092         ms <- searchEntries path prefix fs
1093         return (prefix `joinModule` f : ms)
1094   | looks_like_a_component  =  do
1095         ms <- searchDir (path </> f) (prefix `joinModule` f)
1096         ms' <- searchEntries path prefix fs
1097         return (ms ++ ms')
1098   | otherwise
1099         searchEntries path prefix fs
1100
1101   where
1102         (base,suffix) = splitFileExt f
1103         looks_like_a_module =
1104                 suffix `elem` haskell_suffixes &&
1105                 all okInModuleName base
1106         looks_like_a_component =
1107                 null suffix && all okInModuleName base
1108
1109 okInModuleName c
1110
1111 #endif
1112
1113 -- ---------------------------------------------------------------------------
1114 -- expanding environment variables in the package configuration
1115
1116 expandEnvVars :: String -> Force -> IO String
1117 expandEnvVars str0 force = go str0 ""
1118  where
1119    go "" acc = return $! reverse acc
1120    go ('$':'{':str) acc | (var, '}':rest) <- break close str
1121         = do value <- lookupEnvVar var
1122              go rest (reverse value ++ acc)
1123         where close c = c == '}' || c == '\n' -- don't span newlines
1124    go (c:str) acc
1125         = go str (c:acc)
1126
1127    lookupEnvVar :: String -> IO String
1128    lookupEnvVar nm =
1129         catch (System.Environment.getEnv nm)
1130            (\ _ -> do dieOrForceAll force ("Unable to expand variable " ++
1131                                         show nm)
1132                       return "")
1133
1134 -----------------------------------------------------------------------------
1135
1136 getProgramName :: IO String
1137 getProgramName = liftM (`withoutSuffix` ".bin") getProgName
1138    where str `withoutSuffix` suff
1139             | suff `isSuffixOf` str = take (length str - length suff) str
1140             | otherwise             = str
1141
1142 bye :: String -> IO a
1143 bye s = putStr s >> exitWith ExitSuccess
1144
1145 die :: String -> IO a
1146 die = dieWith 1
1147
1148 dieWith :: Int -> String -> IO a
1149 dieWith ec s = do
1150   hFlush stdout
1151   prog <- getProgramName
1152   hPutStrLn stderr (prog ++ ": " ++ s)
1153   exitWith (ExitFailure ec)
1154
1155 dieOrForceAll :: Force -> String -> IO ()
1156 dieOrForceAll ForceAll s = ignoreError s
1157 dieOrForceAll _other s   = dieForcible s
1158
1159 ignoreError :: String -> IO ()
1160 ignoreError s = reportError (s ++ " (ignoring)")
1161
1162 reportError :: String -> IO ()
1163 reportError s = do hFlush stdout; hPutStrLn stderr s
1164
1165 dieForcible :: String -> IO ()
1166 dieForcible s = die (s ++ " (use --force to override)")
1167
1168 my_head :: String -> [a] -> a
1169 my_head s []      = error s
1170 my_head _ (x : _) = x
1171
1172 -----------------------------------------
1173 -- Cut and pasted from ghc/compiler/main/SysTools
1174
1175 #if defined(mingw32_HOST_OS)
1176 subst :: Char -> Char -> String -> String
1177 subst a b ls = map (\ x -> if x == a then b else x) ls
1178
1179 unDosifyPath :: FilePath -> FilePath
1180 unDosifyPath xs = subst '\\' '/' xs
1181
1182 getLibDir :: IO (Maybe String)
1183 getLibDir = fmap (fmap (</> "lib")) $ getExecDir "/bin/ghc-pkg.exe"
1184
1185 -- (getExecDir cmd) returns the directory in which the current
1186 --                  executable, which should be called 'cmd', is running
1187 -- So if the full path is /a/b/c/d/e, and you pass "d/e" as cmd,
1188 -- you'll get "/a/b/c" back as the result
1189 getExecDir :: String -> IO (Maybe String)
1190 getExecDir cmd =
1191     getExecPath >>= maybe (return Nothing) removeCmdSuffix
1192     where unDosifyPath = subst '\\' '/'
1193           initN n = reverse . drop n . reverse
1194           removeCmdSuffix = return . Just . initN (length cmd) . unDosifyPath
1195
1196 getExecPath :: IO (Maybe String)
1197 getExecPath =
1198      allocaArray len $ \buf -> do
1199          ret <- getModuleFileName nullPtr buf len
1200          if ret == 0 then return Nothing
1201                      else liftM Just $ peekCString buf
1202     where len = 2048 -- Plenty, PATH_MAX is 512 under Win32.
1203
1204 foreign import stdcall unsafe "GetModuleFileNameA"
1205     getModuleFileName :: Ptr () -> CString -> Int -> IO Int32
1206
1207 #else
1208 getLibDir :: IO (Maybe String)
1209 getLibDir = return Nothing
1210 #endif
1211
1212 -----------------------------------------
1213 -- Adapted from ghc/compiler/utils/Panic
1214
1215 installSignalHandlers :: IO ()
1216 installSignalHandlers = do
1217   threadid <- myThreadId
1218   let
1219       interrupt = Exception.throwTo threadid
1220                                     (Exception.ErrorCall "interrupted")
1221   --
1222 #if !defined(mingw32_HOST_OS)
1223   installHandler sigQUIT (Catch interrupt) Nothing
1224   installHandler sigINT  (Catch interrupt) Nothing
1225   return ()
1226 #elif __GLASGOW_HASKELL__ >= 603
1227   -- GHC 6.3+ has support for console events on Windows
1228   -- NOTE: running GHCi under a bash shell for some reason requires
1229   -- you to press Ctrl-Break rather than Ctrl-C to provoke
1230   -- an interrupt.  Ctrl-C is getting blocked somewhere, I don't know
1231   -- why --SDM 17/12/2004
1232   let sig_handler ControlC = interrupt
1233       sig_handler Break    = interrupt
1234       sig_handler _        = return ()
1235
1236   installHandler (Catch sig_handler)
1237   return ()
1238 #else
1239   return () -- nothing
1240 #endif
1241
1242 #if __GLASGOW_HASKELL__ <= 604
1243 isInfixOf               :: (Eq a) => [a] -> [a] -> Bool
1244 isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
1245 #endif
1246
1247 #if mingw32_HOST_OS || mingw32_TARGET_OS
1248 throwIOIO :: Exception.IOException -> IO a
1249 throwIOIO = Exception.throwIO
1250
1251 catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
1252 catchIO = Exception.catch
1253 #endif
1254
1255 catchError :: IO a -> (String -> IO a) -> IO a
1256 catchError io handler = io `Exception.catch` handler'
1257     where handler' (Exception.ErrorCall err) = handler err
1258
1259
1260 -- copied from Cabal's Distribution.Simple.Utils, except that we want
1261 -- to use text files here, rather than binary files.
1262 writeFileAtomic :: FilePath -> String -> IO ()
1263 writeFileAtomic targetFile content = do
1264   (newFile, newHandle) <- openNewFile targetDir template
1265   do  hPutStr newHandle content
1266       hClose newHandle
1267 #if mingw32_HOST_OS || mingw32_TARGET_OS
1268       renameFile newFile targetFile
1269         -- If the targetFile exists then renameFile will fail
1270         `catchIO` \err -> do
1271           exists <- doesFileExist targetFile
1272           if exists
1273             then do removeFile targetFile
1274                     -- Big fat hairy race condition
1275                     renameFile newFile targetFile
1276                     -- If the removeFile succeeds and the renameFile fails
1277                     -- then we've lost the atomic property.
1278             else throwIOIO err
1279 #else
1280       renameFile newFile targetFile
1281 #endif
1282    `Exception.onException` do hClose newHandle
1283                               removeFile newFile
1284   where
1285     template = targetName <.> "tmp"
1286     targetDir | null targetDir_ = "."
1287               | otherwise       = targetDir_
1288     --TODO: remove this when takeDirectory/splitFileName is fixed
1289     --      to always return a valid dir
1290     (targetDir_,targetName) = splitFileName targetFile
1291
1292 -- Ugh, this is a copy/paste of code from the base library, but
1293 -- if uses 666 rather than 600 for the permissions.
1294 openNewFile :: FilePath -> String -> IO (FilePath, Handle)
1295 openNewFile dir template = do
1296   pid <- c_getpid
1297   findTempName pid
1298   where
1299     -- We split off the last extension, so we can use .foo.ext files
1300     -- for temporary files (hidden on Unix OSes). Unfortunately we're
1301     -- below filepath in the hierarchy here.
1302     (prefix,suffix) =
1303        case break (== '.') $ reverse template of
1304          -- First case: template contains no '.'s. Just re-reverse it.
1305          (rev_suffix, "")       -> (reverse rev_suffix, "")
1306          -- Second case: template contains at least one '.'. Strip the
1307          -- dot from the prefix and prepend it to the suffix (if we don't
1308          -- do this, the unique number will get added after the '.' and
1309          -- thus be part of the extension, which is wrong.)
1310          (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
1311          -- Otherwise, something is wrong, because (break (== '.')) should
1312          -- always return a pair with either the empty string or a string
1313          -- beginning with '.' as the second component.
1314          _                      -> error "bug in System.IO.openTempFile"
1315
1316     oflags = rw_flags .|. o_EXCL
1317
1318     findTempName x = do
1319       fd <- withCString filepath $ \ f ->
1320               c_open f oflags 0o666
1321       if fd < 0
1322        then do
1323          errno <- getErrno
1324          if errno == eEXIST
1325            then findTempName (x+1)
1326            else ioError (errnoToIOError "openNewBinaryFile" errno Nothing (Just dir))
1327        else do
1328          -- XXX We want to tell fdToHandle what the filepath is,
1329          -- as any exceptions etc will only be able to report the
1330          -- fd currently
1331          h <-
1332 #if __GLASGOW_HASKELL__ >= 609
1333               fdToHandle fd
1334 #else
1335               fdToHandle (fromIntegral fd)
1336 #endif
1337               `Exception.onException` c_close fd
1338          return (filepath, h)
1339       where
1340         filename        = prefix ++ show x ++ suffix
1341         filepath        = dir `combine` filename
1342
1343 -- XXX Copied from GHC.Handle
1344 std_flags, output_flags, rw_flags :: CInt
1345 std_flags    = o_NONBLOCK   .|. o_NOCTTY
1346 output_flags = std_flags    .|. o_CREAT
1347 rw_flags     = output_flags .|. o_RDWR
1348
1349 -- | The function splits the given string to substrings
1350 -- using 'isSearchPathSeparator'.
1351 parseSearchPath :: String -> [FilePath]
1352 parseSearchPath path = split path
1353   where
1354     split :: String -> [String]
1355     split s =
1356       case rest' of
1357         []     -> [chunk]
1358         _:rest -> chunk : split rest
1359       where
1360         chunk =
1361           case chunk' of
1362 #ifdef mingw32_HOST_OS
1363             ('\"':xs@(_:_)) | last xs == '\"' -> init xs
1364 #endif
1365             _                                 -> chunk'
1366
1367         (chunk', rest') = break isSearchPathSeparator s