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