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