[project @ 2005-03-15 12:11:39 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / GHC.hs
1 --
2 -- (c) The University of Glasgow, 2004
3 --
4 -- The GHC API
5 --
6
7 module GHC (
8         -- * Initialisation
9         GhcSession,
10         GhcMode(..),
11         defaultErrorHandler,
12         defaultCleanupHandler,
13         init,
14         newSession,
15
16         -- * Flags and settings
17         DynFlags(..),
18         DynFlag(..),
19         getSessionDynFlags,
20         setSessionDynFlags,
21         setMsgHandler,
22   ) where
23
24 import HscTypes         ( GhcMode(..) )
25 import qualified ErrUtils
26
27 -- -----------------------------------------------------------------------------
28 -- Initialisation
29
30 -- | abstract type representing a session with GHC.  A session
31 -- includes the currently loaded modules, and any bindings made using
32 -- interactive evaluation.
33 data Session = 
34   Session {
35         sess_hscenv :: IORef HscEnv  -- will include the InteractiveContext
36   }
37
38 -- | Install some default exception handlers and run the inner computation.
39 -- Unless you want to handle exceptions yourself, you should wrap this around
40 -- the top level of your program.  The default handlers output the error
41 -- message(s) to stderr and exit cleanly.
42 defaultErrorHandler :: IO a -> IO a
43 defaultErrorHandler inner = 
44   -- top-level exception handler: any unrecognised exception is a compiler bug.
45   handle (\exception -> do
46            hFlush stdout
47            case exception of
48                 -- an IO exception probably isn't our fault, so don't panic
49                 IOException _ ->  hPutStrLn stderr (show exception)
50                 AsyncException StackOverflow ->
51                         hPutStrLn stderr "stack overflow: use +RTS -K<size> to increase it"
52                 _other ->  hPutStr stderr (show (Panic (show exception)))
53            exitWith (ExitFailure 1)
54          ) $
55
56   -- all error messages are propagated as exceptions
57   handleDyn (\dyn -> do
58                 hFlush stdout
59                 case dyn of
60                      PhaseFailed _ code -> exitWith code
61                      Interrupted -> exitWith (ExitFailure 1)
62                      _ -> do hPutStrLn stderr (show (dyn :: GhcException))
63                              exitWith (ExitFailure 1)
64             ) $
65   inner
66
67 -- | Install a default cleanup handler to remove temporary files
68 -- deposited by a GHC run.  This is seperate from
69 -- 'defaultErrorHandler', because you might want to override the error
70 -- handling, but still get the ordinary cleanup behaviour.
71 defaultCleanupHandler :: IO a -> IO a
72 defaultCleanupHandler inner = 
73    -- make sure we clean up after ourselves
74    later (do  forget_it <- readIORef v_Keep_tmp_files
75               unless forget_it $ do
76               verb <- dynFlag verbosity
77               cleanTempFiles verb
78      ) $
79         -- exceptions will be blocked while we clean the temporary files,
80         -- so there shouldn't be any difficulty if we receive further
81         -- signals.
82    inner
83
84
85 -- | Initialises GHC.  This must be done /once/ only.  Takes the
86 -- command-line arguments.  All command-line arguments beginning with
87 -- '-' are interpreted as flags.  All others are returned.
88 --
89 init :: [String] -> IO [String]
90 init args = do
91    -- catch ^C
92    installSignalHandlers
93
94    argv <- getArgs
95    let (minusB_args, argv') = partition (prefixMatch "-B") argv
96    top_dir <- initSysTools minusB_args
97
98         -- Process all the other arguments, and get the source files
99    non_static <- processArgs static_flags argv' []
100    mode <- readIORef v_CmdLineMode
101
102         -- Read all package.conf files (system, user, -package-conf)
103    readPackageConfigs
104
105         -- load explicit packages (those named with -package on the cmdline)
106    loadExplicitPackages
107
108         -- -O and --interactive are not a good combination
109         -- ditto with any kind of way selection
110    orig_ways <- readIORef v_Ways
111    when (notNull orig_ways && isInteractive mode) $
112       do throwDyn (UsageError 
113                    "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
114
115         -- Find the build tag, and re-process the build-specific options.
116         -- Also add in flags for unregisterised compilation, if 
117         -- GhcUnregisterised=YES.
118    way_opts <- findBuildTag
119    let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
120                   | otherwise = []
121    pkg_extra_opts <- getPackageExtraGhcOpts
122    extra_non_static <- processArgs static_flags 
123                            (unreg_opts ++ way_opts ++ pkg_extra_opts) []
124
125         -- Give the static flags to hsc
126    static_opts <- buildStaticHscOpts
127    writeIORef v_Static_hsc_opts static_opts
128
129    -- build the default DynFlags (these may be adjusted on a per
130    -- module basis by OPTIONS pragmas and settings in the interpreter).
131
132    stg_todo  <- buildStgToDo
133
134    -- set the "global" HscLang.  The HscLang can be further adjusted on a module
135    -- by module basis, using only the -fvia-C and -fasm flags.  If the global
136    -- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
137    dyn_flags <- getDynFlags
138    let lang = case mode of 
139                  DoInteractive  -> HscInterpreted
140                  DoEval _       -> HscInterpreted
141                  _other         -> hscLang dyn_flags
142
143    setDynFlags (dyn_flags{ stgToDo  = stg_todo,
144                            hscLang  = lang,
145                            -- leave out hscOutName for now
146                            hscOutName = panic "Main.main:hscOutName not set",
147                            verbosity = case mode of
148                                          DoEval _ -> 0
149                                          _other   -> 1
150                         })
151
152         -- The rest of the arguments are "dynamic"
153         -- Leftover ones are presumably files
154    fileish_args <- processArgs dynamic_flags (extra_non_static ++ non_static) []
155
156         -- save the "initial DynFlags" away
157    saveDynFlags
158
159         -- and return the leftover args
160    return fileish_args
161
162
163 -- | Starts a new session.  A session consists of a set of loaded
164 -- modules, a set of options (DynFlags), and an interactive context.
165 -- ToDo: GhcMode should say "keep typechecked code" and/or "keep renamed
166 -- code".
167 newSession :: GhcMode -> IO Session
168 newSession mode = do
169   dflags <- getDynFlags
170   env <- newHscEnv mode dflags
171   ref <- newIORef env
172   panic "do we need to set v_CmdLineMode? finder uses it."
173   return (Session {sess_hscenv = ref})
174
175 -- -----------------------------------------------------------------------------
176 -- Flags & settings
177
178 -- | Grabs the DynFlags from the Session
179 getSessionDynFlags :: Session -> IO DynFlags
180 getSessionDynFlags sess = do
181   env <- readIORef (sess_hscenv sess)
182   return (hsc_dflags env)
183
184 -- | Updates the DynFlags in a Session
185 updateSessionDynFlags :: Session -> DynFlags -> IO ()
186 updateSessionDynFlags sess dflags = do
187   env <- readIORef (sess_hscenv sess)
188   writeIORef (sess_hscenv sess) env{hsc_dflags=dflags}
189
190 -- | Messages during compilation (eg. warnings and progress messages)
191 -- are reported using this callback.  By default, these messages are
192 -- printed to stderr.
193 setMsgHandler :: (String -> IO ()) -> IO ()
194 setMsgHandler = ErrUtils.setMsgHandler
195
196 -- -----------------------------------------------------------------------------
197 -- Loading a program
198
199 -- | A compilation target.
200 data Target = Target TargetId (Maybe StringBuffer)
201         -- A target may be supplied with the actual text of the
202         -- module.  If so, use this instead of the file contents (this
203         -- is for use in an IDE where the file hasn't been saved by
204         -- the user yet).
205
206 data TargetId
207   = TargetModule String         -- A module name: search for the file
208   | TargetFile   FilePath       -- A filename: parse it to find the module name.
209
210 -- ToDo: think about relative vs. absolute file paths. And what
211 -- happens when the current directory changes.
212
213 -- | Sets the targets for this session.  Each target may be a module name
214 -- or a filename.  The targets correspond to the set of root modules for
215 -- the program/library.  Unloading the current program is achieved by
216 -- setting the current set of targets to be empty.
217 setTargets :: Session -> [Target] -> IO ()
218
219 -- | returns the current set of targets
220 --getTargets :: Session -> IO [Target]
221
222 -- Add another target, or update an existing target with new content.
223 addTarget :: Session -> Target -> IO Module
224
225 -- Remove a target
226 removeTarget :: Session -> Module -> IO ()
227
228 -- Try to load the program.  If a Module is supplied, then just
229 -- attempt to load up to this target.  If no Module is supplied,
230 -- then try to load all targets.
231 load :: Session -> Maybe Module -> IO LoadResult
232
233 -- | The result of load.
234 data LoadResult
235   = LoadOk      Errors  -- ^ all specified targets were loaded successfully.
236   | LoadFailed  Errors  -- ^ not all modules were loaded.
237
238 type Errors = [ErrMsg]
239
240 data ErrMsg = ErrMsg { 
241         errMsgSeverity  :: Severity,  -- warning, error, etc.
242         errMsgSpans     :: [SrcSpan],
243         errMsgShortDoc  :: Doc,
244         errMsgExtraInfo :: Doc
245         }
246
247 -- -----------------------------------------------------------------------------
248 -- inspecting the session
249
250 -- | Get the set of modules in the current session
251 getLoadedModules :: Session -> IO [Module]
252
253 -- | Get the module dependency graph
254 getModuleGraph :: Session -> IO (DiGraph ModSummary)
255
256 getModuleInfo :: Session -> Module -> IO ModuleInfo
257
258 data ObjectCode
259   = ByteCode
260   | BinaryCode FilePath
261
262 data ModuleInfo = ModuleInfo {
263   lm_modulename :: Module,
264   lm_summary    :: ModSummary,
265   lm_interface  :: ModIface,
266   lm_tc_code    :: Maybe TypecheckedCode,
267   lm_rn_code    :: Maybe RenamedCode,
268   lm_obj        :: Maybe ObjectCode
269   }
270
271 type TypecheckedCode = HsTypecheckedGroup
272 type RenamedCode     = [HsGroup Name]
273
274 -- ToDo: typechecks abstract syntax or renamed abstract syntax.  Issues:
275 --   - typechecked syntax includes extra dictionary translation and
276 --     AbsBinds which need to be translated back into something closer to
277 --     the original source.
278 --   - renamed syntax currently doesn't exist in a single blob, since
279 --     renaming and typechecking are interleaved at splice points.  We'd
280 --     need a restriction that there are no splices in the source module.
281
282 -- ToDo:
283 --   - Data and Typeable instances for HsSyn.
284
285 -- ToDo:
286 --   - things that aren't in the output of the renamer:
287 --     - the export list
288 --     - the imports
289
290 -- ToDo:
291 --   - things that aren't in the output of the typechecker right now:
292 --     - the export list
293 --     - the imports
294 --     - type signatures
295 --     - type/data/newtype declarations
296 --     - class declarations
297 --     - instances
298 --   - extra things in the typechecker's output:
299 --     - default methods are turned into top-level decls.
300 --     - dictionary bindings
301
302 -- ToDo: check for small transformations that happen to the syntax in
303 -- the typechecker (eg. -e ==> negate e, perhaps for fromIntegral)
304
305 -- ToDo: maybe use TH syntax instead of IfaceSyn?  There's already a way
306 -- to get from TyCons, Ids etc. to TH syntax (reify).
307
308 -- :browse will use either lm_toplev or inspect lm_interface, depending
309 -- on whether the module is interpreted or not.
310
311 -- various abstract syntax types (perhaps IfaceBlah)
312 data Type = ...
313 data Kind = ...
314
315 -- This is for reconstructing refactored source code
316 -- Calls the lexer repeatedly.
317 -- ToDo: add comment tokens to token stream
318 getTokenStream :: Session -> Module -> IO [Located Token]
319
320 -- -----------------------------------------------------------------------------
321 -- Interactive evaluation
322
323 -- | Set the interactive evaluation context.
324 --
325 -- Setting the context doesn't throw away any bindings; the bindings
326 -- we've built up in the InteractiveContext simply move to the new
327 -- module.  They always shadow anything in scope in the current context.
328 setContext :: Session
329            -> [Module]  -- entire top level scope of these modules
330            -> [Module]  -- exports only of these modules
331            -> IO ()
332
333 -- | Get the interactive evaluation context.
334 getContext :: Session -> IO ([Module],[Module])
335
336 -- | Looks up an identifier in the current interactive context (for :info)
337 lookupThing :: Session -> String -> IO [TyThing]
338
339 -- | Looks up a Name in the current interactive context (for inspecting
340 -- the result names from 'runStmt').
341 lookupName :: Session -> Name -> IO TyThing
342
343 -- | Get the type of an expression
344 exprType :: Session -> String -> IO (Either Errors Type)
345
346 -- | Get the kind of a  type
347 typeKind  :: Session -> String -> IO (Either Errors Kind)
348
349 data RunResult
350   = RunOk [Name]                -- ^ names bound by this evaluation
351   | RunFailed Errors            -- ^ statement failed compilation
352   | RunException Exception      -- ^ statement raised an exception
353
354 -- | Run a statement in the current interactive context.  Statemenet
355 -- may bind multple values.
356 runStmt :: Session -> String -> IO RunResult
357
358 -- | Return a list of the transient bindings in the current interactive
359 -- context (i.e. those bindings made via runStmt).
360 getInteractiveBindings :: Session -> IO [TyThing]