[project @ 2001-12-30 19:51:33 by sof]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
1 -----------------------------------------------------------------------------
2 -- $Id: Main.hs,v 1.19 2001/12/30 19:51:33 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
19 import IO
20
21 #include "../../includes/config.h"
22
23 #ifdef mingw32_TARGET_OS
24 import Win32DLL
25 #endif
26
27 main = do
28   args <- getArgs
29
30   case getOpt Permute flags args of
31         (clis@(_:_),[],[]) -> runit clis
32         (_,_,errors) -> die (concat errors ++ 
33                              usageInfo usageHeader flags)
34
35 data Flag 
36   = Config FilePath
37   | Input FilePath
38   | List | Add | Update | Remove String | Show String 
39   | Field String | AutoGHCiLibs
40
41 isAction (Config _)     = False
42 isAction (Field _)      = False
43 isAction (Input _)      = False
44 isAction (AutoGHCiLibs) = False
45 isAction _              = True
46
47 usageHeader = "ghc-pkg [OPTION...]"
48
49 flags = [
50   Option ['f'] ["config-file"] (ReqArg Config "FILE")
51         "Use the specified package config file",
52   Option ['l'] ["list-packages"] (NoArg List)
53         "List the currently installed packages",
54   Option ['a'] ["add-package"] (NoArg Add)
55         "Add a new package",
56   Option ['u'] ["update-package"] (NoArg Update)
57         "Update package with new configuration",
58   Option ['i'] ["input-file"] (ReqArg Input "FILE")
59         "Read new package info from specified file",
60   Option ['s'] ["show-package"] (ReqArg Show "NAME")
61         "Show the configuration for package NAME",
62   Option [] ["field"] (ReqArg Field "FIELD")
63         "(with --show-package) Show field FIELD only",
64   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
65         "Remove an installed package",
66   Option ['g'] ["auto-ghci-libs"] (NoArg AutoGHCiLibs)
67         "Automatically build libs for GHCi (with -a)"
68   ]
69
70 #ifdef mingw32_TARGET_OS
71 subst a b ls = map (\ x -> if x == a then b else x) ls
72
73 unDosifyPath xs = subst '\\' '/' xs
74 #endif
75
76 runit clis = do
77   conf_file <- 
78      case [ f | Config f <- clis ] of
79         fs@(_:_)  -> return (last fs)
80 #ifndef mingw32_TARGET_OS
81         [] -> die "missing -f option, location of package.conf unknown"
82 #else
83         [] -> do h <- getModuleHandle Nothing
84                  n <- getModuleFileName h
85                  return (reverse (drop (length "/bin/ghc-pkg.exe") (reverse (unDosifyPath n))) ++ "/package.conf")
86 #endif
87
88   let toField "import_dirs"     = return import_dirs
89       toField "source_dirs"     = return source_dirs
90       toField "library_dirs"    = return library_dirs
91       toField "hs_libraries"    = return hs_libraries
92       toField "extra_libraries" = return extra_libraries
93       toField "include_dirs"    = return include_dirs
94       toField "c_includes"      = return c_includes
95       toField "package_deps"    = return package_deps
96       toField "extra_ghc_opts"  = return extra_ghc_opts
97       toField "extra_cc_opts"   = return extra_cc_opts
98       toField "extra_ld_opts"   = return extra_ld_opts  
99       toField s                 = die ("unknown field: `" ++ s ++ "'")
100
101   fields <- mapM toField [ f | Field f <- clis ]
102
103   s <- readFile conf_file
104   let details = read s :: [PackageConfig]
105   eval_catch details (\_ -> die "parse error in package config file")
106
107   let auto_ghci_libs = any isAuto clis 
108          where isAuto AutoGHCiLibs = True; isAuto _ = False
109       input_file = head ([ f | (Input f) <- clis] ++ ["-"])
110
111   case [ c | c <- clis, isAction c ] of
112     [ List ]     -> listPackages details
113     [ Add  ]     -> addPackage details conf_file input_file auto_ghci_libs False{-add-}
114     [ Update ]   -> addPackage details conf_file input_file auto_ghci_libs True{-update-}
115     [ Remove p ] -> removePackage details conf_file p
116     [ Show p ]   -> showPackage details conf_file p fields
117     _            -> die (usageInfo usageHeader flags)
118
119
120 listPackages :: [PackageConfig] -> IO ()
121 listPackages details = do 
122   hPutStr stdout (listPkgs details)
123   hPutChar stdout '\n'
124
125 showPackage :: [PackageConfig] -> FilePath -> String
126          -> [PackageConfig->[String]] -> IO ()
127 showPackage details pkgconf pkg_name fields =
128   case [ p | p <- details, name p == pkg_name ] of
129     []    -> die ("can't find package `" ++ pkg_name ++ "'")
130     [pkg] | null fields -> hPutStrLn stdout (render (dumpPkgGuts pkg))
131           | otherwise   -> hPutStrLn stdout (render (vcat 
132                                 (map (vcat . map text) (map ($pkg) fields))))
133     _     -> die "showPackage: internal error"
134
135 addPackage :: [PackageConfig] -> FilePath -> FilePath -> Bool -> Bool -> IO ()
136 addPackage details pkgconf inputFile auto_ghci_libs updatePkg = do
137   checkConfigAccess pkgconf
138   s <-
139     case inputFile of
140       "-" -> do
141         hPutStr stdout "Reading package info from stdin... "
142         getContents
143       f   -> do
144         hPutStr stdout ("Reading package info from " ++ show f)
145         readFile f
146   let new_pkg = read s :: PackageConfig
147   eval_catch new_pkg (\_ -> die "parse error in package info")
148   hPutStrLn stdout "done."
149   new_details <- validatePackageConfig new_pkg details auto_ghci_libs updatePkg
150   savePackageConfig pkgconf
151   maybeRestoreOldConfig pkgconf $
152     writeNewConfig pkgconf new_details
153
154 removePackage :: [PackageConfig] -> FilePath -> String -> IO ()
155 removePackage details pkgconf pkgName = do  
156   checkConfigAccess pkgconf
157   if (pkgName `notElem` map name details)
158         then die ("package `" ++ pkgName ++ "' not installed")
159         else do
160   savePackageConfig pkgconf
161   maybeRestoreOldConfig pkgconf $
162     writeNewConfig pkgconf (filter ((/= pkgName) . name) details)
163
164 checkConfigAccess :: FilePath -> IO ()
165 checkConfigAccess pkgconf = do
166   access <- getPermissions pkgconf
167   when (not (writable access))
168       (die "you don't have permission to modify the package configuration file")
169
170 maybeRestoreOldConfig :: String -> IO () -> IO ()
171 maybeRestoreOldConfig conf_file io
172   = my_catch io (\e -> do
173         hPutStr stdout "\nWARNING: an error was encountered while the new \n\ 
174                        \configuration was being written.  Attempting to \n\ 
175                        \restore the old configuration... "
176         renameFile (conf_file ++ ".old")  conf_file
177         hPutStrLn stdout "done."
178         my_throw e
179     )
180
181 writeNewConfig :: String -> [PackageConfig] -> IO ()
182 writeNewConfig conf_file details = do
183   hPutStr stdout "Writing new package config file... "
184   h <- openFile conf_file WriteMode
185   hPutStrLn h (dumpPackages details)
186   hClose h
187   hPutStrLn stdout "done."
188
189 savePackageConfig :: String -> IO ()
190 savePackageConfig conf_file = do
191   hPutStr stdout "Saving old package config file... "
192     -- mv rather than cp because we've already done an hGetContents
193     -- on this file so we won't be able to open it for writing
194     -- unless we move the old one out of the way...
195   let oldFile = conf_file ++ ".old"
196   doesExist <- doesFileExist oldFile  `catch` (\ _ -> return False)
197   when doesExist (removeFile oldFile `catch` (const $ return ()))
198   catch (renameFile conf_file oldFile)
199         (\ err -> do
200                 hPutStrLn stderr (unwords [ "Unable to rename "
201                                           , show conf_file
202                                           , " to "
203                                           , show oldFile
204                                           ])
205                 ioError err)
206   hPutStrLn stdout "done."
207
208 -----------------------------------------------------------------------------
209 -- Sanity-check a new package config, and automatically build GHCi libs
210 -- if requested.
211
212 validatePackageConfig :: PackageConfig 
213                       -> [PackageConfig]
214                       -> Bool
215                       -> Bool
216                       -> IO [PackageConfig]
217 validatePackageConfig pkg pkgs auto_ghci_libs updatePkg = do
218   if (not updatePkg && (name pkg `elem` map name pkgs))
219         then die ("package `" ++ name pkg ++ "' is already installed")
220         else do
221   mapM_ (checkDep pkgs) (package_deps pkg)
222   mapM_ checkDir (import_dirs pkg)
223   mapM_ checkDir (source_dirs pkg)
224   mapM_ checkDir (library_dirs pkg)
225   mapM_ checkDir (include_dirs pkg)
226   mapM_ (checkHSLib (library_dirs pkg) auto_ghci_libs) (hs_libraries pkg)
227   -- ToDo: check these somehow?
228   --    extra_libraries :: [String],
229   --    c_includes      :: [String],
230   let existing_pkgs
231        | updatePkg = filter ((/=(name pkg)).name) pkgs  
232        | otherwise = pkgs
233   return (existing_pkgs ++ [pkg])
234
235 checkDir d = do
236   b <- doesDirectoryExist d
237   if b then return ()
238        else die ("`" ++ d ++ "' doesn't exist or isn't a directory")
239
240 checkDep :: [PackageConfig] -> String -> IO ()
241 checkDep pkgs n
242   | n `elem` map name pkgs = return ()
243   | otherwise = die ("dependency `" ++ n ++ "' doesn't exist")
244
245 checkHSLib :: [String] -> Bool -> String -> IO ()
246 checkHSLib dirs auto_ghci_libs lib = do
247   let batch_lib_file = "lib" ++ lib ++ ".a"
248   bs <- mapM (\d -> doesFileExist (d ++ '/':batch_lib_file)) dirs
249   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
250         [] -> die ("cannot find `" ++ batch_lib_file ++ "' on library path") 
251         (dir:_) -> checkGHCiLib dirs dir batch_lib_file lib auto_ghci_libs
252
253 checkGHCiLib :: [String] -> String -> String -> String -> Bool -> IO ()
254 checkGHCiLib dirs batch_lib_dir batch_lib_file lib auto_build = do
255   let ghci_lib_file = lib ++ ".o"
256       ghci_lib_path = batch_lib_dir ++ '/':ghci_lib_file
257   bs <- mapM (\d -> doesFileExist (d ++ '/':ghci_lib_file)) dirs
258   case [ dir | (exists,dir) <- zip bs dirs, exists ] of
259         [] | auto_build -> 
260                 autoBuildGHCiLib batch_lib_dir batch_lib_file ghci_lib_file
261            | otherwise  -> 
262                 hPutStrLn stderr ("warning: can't find GHCi lib `"
263                                          ++ ghci_lib_file ++ "'")
264         (dir:_) -> return ()
265
266 -- automatically build the GHCi version of a batch lib, 
267 -- using ld --whole-archive.
268
269 autoBuildGHCiLib dir batch_file ghci_file = do
270   let ghci_lib_file  = dir ++ '/':ghci_file
271       batch_lib_file = dir ++ '/':batch_file
272   hPutStr stderr ("building GHCi library `" ++ ghci_lib_file ++ "'...")
273   system("ld -r -x -o " ++ ghci_lib_file ++ 
274          " --whole-archive " ++ batch_lib_file)
275   hPutStrLn stderr (" done.")
276
277 -----------------------------------------------------------------------------
278
279 die :: String -> IO a
280 die s = do { hPutStrLn stderr s; exitWith (ExitFailure 1) }
281
282 -----------------------------------------------------------------------------
283 -- Exceptions
284
285 #ifndef __GLASGOW_HASKELL__
286
287 eval_catch a h = a `seq` return ()
288 my_catch = IO.catch
289 my_throw = IO.fail
290
291 #else /* GHC */
292
293 my_throw = Exception.throw
294 #if __GLASGOW_HASKELL__ > 408
295 eval_catch = Exception.catch . Exception.evaluate
296 my_catch = Exception.catch
297 #else
298 eval_catch = Exception.catchAll
299 my_catch = Exception.catchAllIO
300 #endif
301
302 #endif