[project @ 2002-09-09 11:32:37 by simonmar]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
1 -----------------------------------------------------------------------------
2 -- $Id: Main.hs,v 1.27 2002/09/09 11:32:37 simonmar Exp $
3 --
4 -- Package management tool
5 -----------------------------------------------------------------------------
6
7 module Main where
8
9 import Package
10
11 #if __GLASGOW_HASKELL__ >= 504
12 import System.Console.GetOpt
13 import Text.PrettyPrint
14 import qualified Control.Exception as Exception
15 #else
16 import GetOpt
17 import Pretty
18 import qualified Exception
19 #endif
20
21 import Monad
22 import Directory
23 import System   ( getEnv, getArgs, 
24                   system, exitWith,
25                   ExitCode(..)
26                 )
27 import IO
28 import List ( isPrefixOf )
29
30 import ParsePkgConfLite
31
32 #include "../../includes/config.h"
33
34 #ifdef mingw32_HOST_OS
35 import Win32DLL
36 #endif
37
38 main = do
39   args <- getArgs
40
41   case getOpt Permute flags args of
42         (clis@(_:_),[],[]) -> runit clis
43         (_,_,errors) -> die (concat errors ++ 
44                              usageInfo usageHeader flags)
45
46 data Flag 
47   = Config FilePath
48   | Input FilePath
49   | List | Add Bool {- True => replace existing info -}
50   | Remove String | Show String 
51   | Field String | AutoGHCiLibs | Force
52   deriving (Eq)
53
54 isAction (Config _)     = False
55 isAction (Field _)      = False
56 isAction (Input _)      = False
57 isAction (AutoGHCiLibs) = False
58 isAction (Force)        = False
59 isAction _              = True
60
61 usageHeader = "ghc-pkg [OPTION...]"
62
63 flags = [
64   Option ['f'] ["config-file"] (ReqArg Config "FILE")
65         "Use the specified package config file",
66   Option ['l'] ["list-packages"] (NoArg List)
67         "List the currently installed packages",
68   Option ['a'] ["add-package"] (NoArg (Add False))
69         "Add a new package",
70   Option ['u'] ["update-package"] (NoArg (Add True))
71         "Update package with new configuration",
72   Option ['i'] ["input-file"] (ReqArg Input "FILE")
73         "Read new package info from specified file",
74   Option ['s'] ["show-package"] (ReqArg Show "NAME")
75         "Show the configuration for package NAME",
76   Option [] ["field"] (ReqArg Field "FIELD")
77         "(with --show-package) Show field FIELD only",
78   Option [] ["force"] (NoArg Force)
79         "ignore missing directories/libraries",
80   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
81         "Remove an installed package",
82   Option ['g'] ["auto-ghci-libs"] (NoArg AutoGHCiLibs)
83         "Automatically build libs for GHCi (with -a)"
84   ]
85
86 #ifdef mingw32_HOST_OS
87 subst a b ls = map (\ x -> if x == a then b else x) ls
88
89 unDosifyPath xs = subst '\\' '/' xs
90 #endif
91
92 runit clis = do
93   conf_file <- 
94      case [ f | Config f <- clis ] of
95         fs@(_:_)  -> return (last fs)
96 #ifndef mingw32_HOST_OS
97         [] -> die "missing -f option, location of package.conf unknown"
98 #else
99         [] -> do h <- getModuleHandle Nothing
100                  n <- getModuleFileName h
101                  return (reverse (drop (length "/bin/ghc-pkg.exe") (reverse (unDosifyPath n))) ++ "/package.conf")
102 #endif
103
104   let toField "import_dirs"     = return import_dirs
105       toField "source_dirs"     = return source_dirs
106       toField "library_dirs"    = return library_dirs
107       toField "hs_libraries"    = return hs_libraries
108       toField "extra_libraries" = return extra_libraries
109       toField "include_dirs"    = return include_dirs
110       toField "c_includes"      = return c_includes
111       toField "package_deps"    = return package_deps
112       toField "extra_ghc_opts"  = return extra_ghc_opts
113       toField "extra_cc_opts"   = return extra_cc_opts
114       toField "extra_ld_opts"   = return extra_ld_opts  
115       toField "framework_dirs"  = return framework_dirs  
116       toField "extra_frameworks"= return extra_frameworks  
117       toField s                 = die ("unknown field: `" ++ s ++ "'")
118
119   fields <- mapM toField [ f | Field f <- clis ]
120
121   s <- readFile conf_file
122   let packages = parsePackageConfig s
123   eval_catch packages (\_ -> die "parse error in package config file")
124
125   let auto_ghci_libs = any isAuto clis 
126          where isAuto AutoGHCiLibs = True; isAuto _ = False
127       input_file = head ([ f | (Input f) <- clis] ++ ["-"])
128
129       force = Force `elem` clis
130
131   case [ c | c <- clis, isAction c ] of
132     [ List ]     -> listPackages packages
133     [ Add upd ]  -> addPackage packages conf_file input_file 
134                         auto_ghci_libs upd force
135     [ Remove p ] -> removePackage packages conf_file p
136     [ Show p ]   -> showPackage packages conf_file p fields
137     _            -> die (usageInfo usageHeader flags)
138
139
140 listPackages :: [PackageConfig] -> IO ()
141 listPackages packages = hPutStrLn stdout (listPkgs packages)
142
143 showPackage :: [PackageConfig]
144             -> FilePath
145             -> String
146             -> [PackageConfig -> [String]]
147             -> IO ()
148 showPackage packages pkgconf pkg_name fields =
149   case [ p | p <- packages, name p == pkg_name ] of
150     []    -> die ("can't find package `" ++ pkg_name ++ "'")
151     [pkg] | null fields -> hPutStrLn stdout (render (dumpPkgGuts pkg))
152           | otherwise   -> hPutStrLn stdout (render (vcat 
153                                 (map (vcat . map text) (map ($pkg) fields))))
154     _     -> die "showPackage: internal error"
155
156 addPackage :: [PackageConfig] -> FilePath -> FilePath
157          -> Bool -> Bool -> Bool -> IO ()
158 addPackage packages pkgconf inputFile auto_ghci_libs updatePkg force = do
159   checkConfigAccess pkgconf
160   s <-
161     case inputFile of
162       "-" -> do
163         hPutStr stdout "Reading package info from stdin... "
164         getContents
165       f   -> do
166         hPutStr stdout ("Reading package info from " ++ show f)
167         readFile f
168   let new_pkg = parseOnePackageConfig s
169   eval_catch new_pkg (\_ -> die "parse error in package info")
170   hPutStrLn stdout "done."
171   hPutStr stdout "Expanding embedded variables..."
172   new_exp_pkg <- expandEnvVars new_pkg force
173   hPutStrLn stdout "done."
174   new_details <- validatePackageConfig new_exp_pkg packages 
175                         auto_ghci_libs updatePkg force
176   savePackageConfig pkgconf
177   maybeRestoreOldConfig pkgconf $
178     writeNewConfig pkgconf new_details
179
180 removePackage :: [PackageConfig] -> FilePath -> String -> IO ()
181 removePackage packages pkgconf pkgName = do  
182   checkConfigAccess pkgconf
183   when (pkgName `notElem` map name packages)
184        (die ("package `" ++ pkgName ++ "' not installed"))
185   savePackageConfig pkgconf
186   maybeRestoreOldConfig pkgconf $
187     writeNewConfig pkgconf (filter ((/= pkgName) . name) packages)
188
189 checkConfigAccess :: FilePath -> IO ()
190 checkConfigAccess pkgconf = do
191   access <- getPermissions pkgconf
192   when (not (writable access))
193       (die "you don't have permission to modify the package configuration file")
194
195 maybeRestoreOldConfig :: String -> IO () -> IO ()
196 maybeRestoreOldConfig conf_file io
197   = my_catch io (\e -> do
198         hPutStr stdout "\nWARNING: an error was encountered while the new \n\ 
199                        \configuration was being written.  Attempting to \n\ 
200                        \restore the old configuration... "
201         renameFile (conf_file ++ ".old")  conf_file
202         hPutStrLn stdout "done."
203         my_throw e
204     )
205
206 writeNewConfig :: String -> [PackageConfig] -> IO ()
207 writeNewConfig conf_file packages = do
208   hPutStr stdout "Writing new package config file... "
209   h <- openFile conf_file WriteMode
210   hPutStrLn h (dumpPackages packages)
211   hClose h
212   hPutStrLn stdout "done."
213
214 savePackageConfig :: String -> IO ()
215 savePackageConfig conf_file = do
216   hPutStr stdout "Saving old package config file... "
217     -- mv rather than cp because we've already done an hGetContents
218     -- on this file so we won't be able to open it for writing
219     -- unless we move the old one out of the way...
220   let oldFile = conf_file ++ ".old"
221   doesExist <- doesFileExist oldFile  `catch` (\ _ -> return False)
222   when doesExist (removeFile oldFile `catch` (const $ return ()))
223   catch (renameFile conf_file oldFile)
224         (\ err -> do
225                 hPutStrLn stderr (unwords [ "Unable to rename "
226                                           , show conf_file
227                                           , " to "
228                                           , show oldFile
229                                           ])
230                 ioError err)
231   hPutStrLn stdout "done."
232
233 -----------------------------------------------------------------------------
234 -- Sanity-check a new package config, and automatically build GHCi libs
235 -- if requested.
236
237 validatePackageConfig :: PackageConfig 
238                       -> [PackageConfig]
239                       -> Bool
240                       -> Bool
241                       -> Bool
242                       -> IO [PackageConfig]
243 validatePackageConfig pkg pkgs auto_ghci_libs updatePkg force = do
244   when (not updatePkg && (name pkg `elem` map name pkgs))
245        (die ("package `" ++ name pkg ++ "' is already installed"))
246   mapM_ (checkDep pkgs force) (package_deps pkg)
247   mapM_ (checkDir force) (import_dirs pkg)
248   mapM_ (checkDir force) (source_dirs pkg)
249   mapM_ (checkDir force) (library_dirs pkg)
250   mapM_ (checkDir force) (include_dirs pkg)
251   mapM_ (checkHSLib (library_dirs pkg) auto_ghci_libs force) (hs_libraries pkg)
252   -- ToDo: check these somehow?
253   --    extra_libraries :: [String],
254   --    c_includes      :: [String],
255   let existing_pkgs
256        | updatePkg = filter ((/=(name pkg)).name) pkgs  
257        | otherwise = pkgs
258   return (existing_pkgs ++ [pkg])
259
260 checkDir force d
261  | "$libdir" `isPrefixOf` d = return ()
262         -- can't check this, because we don't know what $libdir is
263  | otherwise = do
264    there <- doesDirectoryExist d
265    when (not there)
266        (dieOrForce force ("`" ++ d ++ "' doesn't exist or isn't a directory"))
267
268 checkDep :: [PackageConfig] -> Bool -> String -> IO ()
269 checkDep pkgs force n
270   | n `elem` map name pkgs = return ()
271   | otherwise = dieOrForce force ("dependency `" ++ n ++ "' doesn't exist")
272
273 checkHSLib :: [String] -> Bool -> Bool -> String -> IO ()
274 checkHSLib dirs auto_ghci_libs force lib = do
275   let batch_lib_file = "lib" ++ lib ++ ".a"
276   bs <- mapM (doesLibExistIn batch_lib_file) dirs
277   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
278         [] -> dieOrForce force ("cannot find `" ++ batch_lib_file ++
279                                  "' on library path") 
280         (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
281
282 doesLibExistIn lib d
283  | "$libdir" `isPrefixOf` d = return True
284  | otherwise                = doesFileExist (d ++ '/':lib)
285
286 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
287 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build = do
288   let ghci_lib_file = lib ++ ".o"
289       ghci_lib_path = batch_lib_dir ++ '/':ghci_lib_file
290   bs <- mapM (\d -> doesFileExist (d ++ '/':ghci_lib_file)) dirs
291   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
292         [] | auto_build -> 
293                 autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
294            | otherwise  -> 
295                 hPutStrLn stderr ("warning: can't find GHCi lib `"
296                                          ++ ghci_lib_file ++ "'")
297         (dir:_) -> return ()
298
299 -- automatically build the GHCi version of a batch lib, 
300 -- using ld --whole-archive.
301
302 autoBuildGHCiLib dir batch_file ghci_file = do
303   let ghci_lib_file  = dir ++ '/':ghci_file
304       batch_lib_file = dir ++ '/':batch_file
305   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
306 #ifdef darwin_TARGET_OS
307   system("ld -r -x -o " ++ ghci_lib_file ++ 
308          " -all_load " ++ batch_lib_file)
309 #else
310   system("ld -r -x -o " ++ ghci_lib_file ++ 
311          " --whole-archive " ++ batch_lib_file)
312 #endif
313   hPutStrLn stderr (" done.")
314
315 -----------------------------------------------------------------------------
316 expandEnvVars :: PackageConfig -> Bool -> IO PackageConfig
317 expandEnvVars pkg force = do
318    -- permit _all_ strings to contain ${..} environment variable references,
319    -- arguably too flexible.
320   nm       <- expandString (name pkg)
321   imp_dirs <- expandStrings (import_dirs pkg) 
322   src_dirs <- expandStrings (source_dirs pkg) 
323   lib_dirs <- expandStrings (library_dirs pkg) 
324   hs_libs  <- expandStrings (hs_libraries pkg)
325   ex_libs  <- expandStrings (extra_libraries pkg)
326   inc_dirs <- expandStrings (include_dirs pkg)
327   c_incs   <- expandStrings (c_includes pkg)
328   p_deps   <- expandStrings (package_deps pkg)
329   e_g_opts <- expandStrings (extra_ghc_opts pkg)
330   e_c_opts <- expandStrings (extra_cc_opts pkg)
331   e_l_opts <- expandStrings (extra_ld_opts pkg)
332   f_dirs   <- expandStrings (framework_dirs pkg)
333   e_frames <- expandStrings (extra_frameworks pkg)
334   return (pkg { name            = nm
335               , import_dirs     = imp_dirs
336               , source_dirs     = src_dirs
337               , library_dirs    = lib_dirs
338               , hs_libraries    = hs_libs
339               , extra_libraries = ex_libs
340               , include_dirs    = inc_dirs
341               , c_includes      = c_incs
342               , package_deps    = p_deps
343               , extra_ghc_opts  = e_g_opts
344               , extra_cc_opts   = e_c_opts
345               , extra_ld_opts   = e_l_opts
346               , framework_dirs  = f_dirs
347               , extra_frameworks= e_frames
348               })
349   where
350    expandStrings = mapM expandString
351    
352     -- Just for fun, keep this in the IO monad.
353    expandString :: String -> IO String
354    expandString str =
355      case break (=='$') str of
356        (xs, _:'{':rs) ->
357          case span (/='}') rs of
358            (nm,_:remainder) -> do
359               nm'  <- lookupEnvVar nm
360               str' <- expandString remainder
361               return (nm' ++ str')
362            _ -> return str -- no closing '}'
363        _ -> return str     
364
365    lookupEnvVar nm = 
366         catch (System.getEnv nm)
367            (\ _ -> do dieOrForce force ("Unable to expand variable " ++ 
368                                         show nm)
369                       return "")
370
371 -----------------------------------------------------------------------------
372
373 die :: String -> IO a
374 die s = do { hFlush stdout ; hPutStrLn stderr s; exitWith (ExitFailure 1) }
375
376 dieOrForce :: Bool -> String -> IO ()
377 dieOrForce force s 
378   | force     = do hFlush stdout; hPutStrLn stderr (s ++ " (ignoring)")
379   | otherwise = die s
380
381 -----------------------------------------------------------------------------
382 -- Exceptions
383
384 #ifndef __GLASGOW_HASKELL__
385
386 eval_catch a h = a `seq` return ()
387 my_catch = IO.catch
388 my_throw = IO.fail
389
390 #else /* GHC */
391
392 my_throw = Exception.throw
393 #if __GLASGOW_HASKELL__ > 408
394 eval_catch = Exception.catch . Exception.evaluate
395 my_catch = Exception.catch
396 #else
397 eval_catch = Exception.catchAll
398 my_catch = Exception.catchAllIO
399 #endif
400
401 #endif