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