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