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