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