[project @ 2001-06-04 06:20:35 by qrczak]
[ghc-hetmet.git] / ghc / utils / ghc-pkg / Main.hs
1 -----------------------------------------------------------------------------
2 -- $Id: Main.hs,v 1.10 2001/06/04 06:20:35 qrczak 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 main = do
22   args <- getArgs
23
24   case getOpt Permute flags args of
25         (clis,[],[]) -> runit clis
26         (_,_,errors) -> die (concat errors ++ 
27                              usageInfo usageHeader flags)
28
29 data Flag = Config String | List | Add | Remove String | Show String | Field String
30 isConfigOrField (Config _) = True
31 isConfigOrField (Field _) = True
32 isConfigOrField _ = False
33
34 usageHeader = "ghc-pkg [OPTION...]"
35
36 flags = [
37   Option ['f'] ["config-file"] (ReqArg Config "FILE")
38         "Use the specified package config file",
39   Option ['l'] ["list-packages"] (NoArg List)
40         "List the currently installed packages",
41   Option ['a'] ["add-package"] (NoArg Add)
42         "Add a new package",
43   Option ['s'] ["show-package"] (ReqArg Show "NAME")
44         "Show the configuration for package NAME",
45   Option [] ["field"] (ReqArg Field "FIELD")
46         "(with --show-package) Show field FIELD only",
47   Option ['r'] ["remove-package"] (ReqArg Remove "NAME")
48         "Remove an installed package"
49   ]
50
51 runit clis = do
52   conf_file <- 
53      case [ f | Config f <- clis ] of
54         []  -> die "missing -f option, location of package.conf unknown"
55         [f] -> return f
56         _   -> die (usageInfo usageHeader flags)
57
58   let toField "import_dirs"     = return import_dirs
59       toField "source_dirs"     = return source_dirs
60       toField "library_dirs"    = return library_dirs
61       toField "hs_libraries"    = return hs_libraries
62       toField "extra_libraries" = return extra_libraries
63       toField "include_dirs"    = return include_dirs
64       toField "c_includes"      = return c_includes
65       toField "package_deps"    = return package_deps
66       toField "extra_ghc_opts"  = return extra_ghc_opts
67       toField "extra_cc_opts"   = return extra_cc_opts
68       toField "extra_ld_opts"   = return extra_ld_opts  
69       toField s                 = die ("unknown field: `" ++ s ++ "'")
70
71   fields <- mapM toField [ f | Field f <- clis ]
72
73   s <- readFile conf_file
74   let details = read s :: [PackageConfig]
75   eval_catch details (\_ -> die "parse error in package config file")
76
77   case [ c | c <- clis, not (isConfigOrField c) ] of
78     [ List ]     -> listPackages details
79     [ Add  ]     -> addPackage details conf_file
80     [ Remove p ] -> removePackage details conf_file p
81     [ Show p ]   -> showPackage details conf_file p fields
82     _            -> die (usageInfo usageHeader flags)
83
84
85 listPackages :: [PackageConfig] -> IO ()
86 listPackages details = do 
87   hPutStr stdout (listPkgs details)
88   hPutChar stdout '\n'
89
90 showPackage :: [PackageConfig] -> FilePath -> String
91          -> [PackageConfig->[String]] -> IO ()
92 showPackage details pkgconf pkg_name fields =
93   case [ p | p <- details, name p == pkg_name ] of
94     []    -> die ("can't find package `" ++ pkg_name ++ "'")
95     [pkg] | null fields -> hPutStrLn stdout (render (dumpPkgGuts pkg))
96           | otherwise   -> hPutStrLn stdout (render (vcat 
97                                 (map (vcat . map text) (map ($pkg) fields))))
98     _     -> die "showPackage: internal error"
99
100 addPackage :: [PackageConfig] -> FilePath -> IO ()
101 addPackage details pkgconf = do
102   checkConfigAccess pkgconf
103   hPutStr stdout "Reading package info from stdin... "
104   s <- getContents
105   let new_pkg = read s :: PackageConfig
106   eval_catch new_pkg (\_ -> die "parse error in package info")
107   hPutStrLn stdout "done."
108   if (name new_pkg `elem` map name details)
109         then die ("package `" ++ name new_pkg ++ "' already installed")
110         else do
111   savePackageConfig pkgconf
112   maybeRestoreOldConfig pkgconf $
113     writeNewConfig pkgconf (details ++ [new_pkg])
114
115 removePackage :: [PackageConfig] -> FilePath -> String -> IO ()
116 removePackage details pkgconf pkg = do  
117   checkConfigAccess pkgconf
118   if (pkg `notElem` map name details)
119         then die ("package `" ++ pkg ++ "' not installed")
120         else do
121   savePackageConfig pkgconf
122   maybeRestoreOldConfig pkgconf $
123     writeNewConfig pkgconf (filter ((/= pkg) . name) details)
124
125 checkConfigAccess :: FilePath -> IO ()
126 checkConfigAccess pkgconf = do
127   access <- getPermissions pkgconf
128   when (not (writable access))
129       (die "you don't have permission to modify the package configuration file")
130
131 maybeRestoreOldConfig :: String -> IO () -> IO ()
132 maybeRestoreOldConfig conf_file io
133   = my_catch io (\e -> do
134         hPutStr stdout "\nWARNING: an error was encountered while the new \n\ 
135                        \configuration was being written.  Attempting to \n\ 
136                        \restore the old configuration... "
137         renameFile (conf_file ++ ".old")  conf_file
138         hPutStrLn stdout "done."
139         my_throw e
140     )
141
142 writeNewConfig :: String -> [PackageConfig] -> IO ()
143 writeNewConfig conf_file details = do
144   hPutStr stdout "Writing new package config file... "
145   h <- openFile conf_file WriteMode
146   hPutStrLn h (dumpPackages details)
147   hClose h
148   hPutStrLn stdout "done."
149
150 savePackageConfig :: String -> IO ()
151 savePackageConfig conf_file = do
152   hPutStr stdout "Saving old package config file... "
153     -- mv rather than cp because we've already done an hGetContents
154     -- on this file so we won't be able to open it for writing
155     -- unless we move the old one out of the way...
156   renameFile conf_file (conf_file ++ ".old") 
157   hPutStrLn stdout "done."
158
159 -----------------------------------------------------------------------------
160
161 die :: String -> IO a
162 die s = do { hPutStrLn stderr s; exitWith (ExitFailure 1) }
163
164 -----------------------------------------------------------------------------
165 -- Exceptions
166
167 #ifndef __GLASGOW_HASKELL__
168
169 eval_catch a h = a `seq` return ()
170 my_catch = IO.catch
171 my_throw = IO.fail
172
173 #else /* GHC */
174
175 my_throw = Exception.throw
176 #if __GLASGOW_HASKELL__ > 408
177 eval_catch = Exception.catch . Exception.evaluate
178 my_catch = Exception.catch
179 #else
180 eval_catch = Exception.catchAll
181 my_catch = Exception.catchAllIO
182 #endif
183
184 #endif