[project @ 2001-03-23 16:36:20 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
index 5c32153..c81294c 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverPipeline.hs,v 1.38 2000/12/05 12:19:49 rrt Exp $
+-- $Id: DriverPipeline.hs,v 1.57 2001/03/23 16:36:20 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -7,22 +7,26 @@
 --
 -----------------------------------------------------------------------------
 
+#include "../includes/config.h"
+
 module DriverPipeline (
 
        -- interfaces for the batch-mode driver
    GhcMode(..), getGhcMode, v_GhcMode,
-   genPipeline, runPipeline,
+   genPipeline, runPipeline, pipeLoop,
 
        -- interfaces for the compilation manager (interpreted/batch-mode)
    preprocess, compile, CompResult(..),
 
        -- batch-mode linking interface
-   doLink
+   doLink,
+        -- DLL building
+   doMkDLL
   ) where
 
 #include "HsVersions.h"
 
-import CmStaticInfo ( GhciMode(..) )
+import CmStaticInfo
 import CmTypes
 import GetImports
 import DriverState
@@ -32,12 +36,14 @@ import DriverPhases
 import DriverFlags
 import HscMain
 import TmpFiles
+import Finder
 import HscTypes
 import Outputable
 import Module
 import ErrUtils
 import CmdLineOpts
 import Config
+import Panic
 import Util
 
 import Time            ( getClockTime )
@@ -50,12 +56,15 @@ import IO
 import Monad
 import Maybe
 
+import PackedString
+import MatchPS
+
 -----------------------------------------------------------------------------
 -- GHC modes of operation
 
 data GhcMode
   = DoMkDependHS                       -- ghc -M
-  | DoMkDLL                            -- ghc -mk-dll
+  | DoMkDLL                            -- ghc --mk-dll
   | StopBefore Phase                   -- ghc -E | -C | -S | -c
   | DoMake                             -- ghc --make
   | DoInteractive                      -- ghc --interactive
@@ -66,6 +75,7 @@ GLOBAL_VAR(v_GhcMode, error "todo", GhcMode)
 
 modeFlag :: String -> Maybe GhcMode
 modeFlag "-M"           = Just $ DoMkDependHS
+modeFlag "--mk-dll"      = Just $ DoMkDLL
 modeFlag "-E"           = Just $ StopBefore Hsc
 modeFlag "-C"           = Just $ StopBefore HCc
 modeFlag "-S"           = Just $ StopBefore As
@@ -85,13 +95,13 @@ getGhcMode flags
        ([(flag,one)], rest) -> return (rest, one, flag)
        (_    , _   ) -> 
          throwDyn (OtherError 
-               "only one of the flags -M, -E, -C, -S, -c, --make, --interactive is allowed")
+               "only one of the flags -M, -E, -C, -S, -c, --make, --interactive, -mk-dll is allowed")
 
 -----------------------------------------------------------------------------
 -- genPipeline
 --
 -- Herein is all the magic about which phases to run in which order, whether
--- the intermediate files should be in /tmp or in the current directory,
+-- the intermediate files should be in TMPDIR or in the current directory,
 -- what the suffix of the intermediate files should be, etc.
 
 -- The following compilation pipeline algorithm is fairly hacky.  A
@@ -144,12 +154,16 @@ genPipeline todo stop_flag persistent_output lang filename
    ----------- -----  ----   ---   --   --  -  -  -
     (_basename, suffix) = splitFilename filename
 
-    start_phase = startPhase suffix
+    start = startPhase suffix
+
+      -- special case for mkdependHS: .hspp files go through MkDependHS
+    start_phase | todo == DoMkDependHS && start == Hsc  = MkDependHS
+               | otherwise = start
 
     haskellish = haskellish_suffix suffix
     cish = cish_suffix suffix
 
-   -- for a .hc file we need to force lang to HscC
+       -- for a .hc file we need to force lang to HscC
     real_lang | start_phase == HCc  = HscC
              | otherwise           = lang
 
@@ -171,12 +185,17 @@ genPipeline todo stop_flag persistent_output lang filename
 
        HscJava | split           -> not_valid
                | otherwise       -> error "not implemented: compiling via Java"
+#ifdef ILX
+       HscILX  | split           -> not_valid
+               | otherwise       -> [ Unlit, Cpp, Hsc ]
+#endif
 
       | cish      = [ Cc, As ]
 
       | otherwise = [ ]  -- just pass this file through to the linker
 
        -- ToDo: this is somewhat cryptic
+
     not_valid = throwDyn (OtherError ("invalid option combination"))
    ----------- -----  ----   ---   --   --  -  -  -
 
@@ -186,18 +205,6 @@ genPipeline todo stop_flag persistent_output lang filename
                                    ++ filename))
        else do
 
-       -- if we can't find the phase we're supposed to stop before,
-       -- something has gone wrong.
-   case todo of
-       StopBefore phase -> 
-          when (phase /= Ln 
-                && phase `notElem` pipeline
-                && not (phase == As && SplitAs `elem` pipeline)) $
-             throwDyn (OtherError 
-               ("flag " ++ stop_flag
-                ++ " is incompatible with source file `" ++ filename ++ "'"))
-       _ -> return ()
-
    let
    ----------- -----  ----   ---   --   --  -  -  -
       myPhaseInputExt Ln = case osuf of Nothing -> phaseInputExt Ln
@@ -229,18 +236,33 @@ genPipeline todo stop_flag persistent_output lang filename
        -- the suffix on an output file is determined by the next phase
        -- in the pipeline, so we add linking to the end of the pipeline
        -- to force the output from the final phase to be a .o file.
-      stop_phase = case todo of StopBefore phase -> phase
-                               DoMkDependHS     -> Ln
-                               DoLink           -> Ln
-      annotated_pipeline = annotatePipeline (pipeline ++ [ Ln ]) stop_phase
+      stop_phase = case todo of 
+                       StopBefore As | split -> SplitAs
+                       StopBefore phase      -> phase
+                       DoMkDependHS          -> Ln
+                       DoLink                -> Ln
+
+      annotated_pipeline = annotatePipeline (pipeline ++ [Ln]) stop_phase
 
       phase_ne p (p1,_,_) = (p1 /= p)
    ----------- -----  ----   ---   --   --  -  -  -
 
-   return $
-     dropWhile (phase_ne start_phase) . 
-       foldr (\p ps -> if phase_ne stop_phase p then p:ps else [])  []
-               $ annotated_pipeline
+       -- if we can't find the phase we're supposed to stop before,
+       -- something has gone wrong.  This test carefully avoids the
+       -- case where we aren't supposed to do any compilation, because the file
+       -- is already in linkable form (for example).
+   if start_phase `elem` pipeline && 
+       (stop_phase /= Ln && stop_phase `notElem` pipeline)
+      then throwDyn (OtherError 
+               ("flag " ++ stop_flag
+                ++ " is incompatible with source file `" ++ filename ++ "'"))
+      else do
+
+   return (
+     takeWhile (phase_ne stop_phase ) $
+     dropWhile (phase_ne start_phase) $
+     annotated_pipeline
+    )
 
 
 runPipeline
@@ -300,14 +322,9 @@ run_phase Unlit _basename _suff input_fn output_fn
 run_phase Cpp basename suff input_fn output_fn
   = do src_opts <- getOptionsFromSource input_fn
        unhandled_flags <- processArgs dynamic_flags src_opts []
+       checkProcessArgsResult unhandled_flags basename suff
 
-       when (not (null unhandled_flags)) 
-            (throwDyn (OtherError (
-                          basename ++ "." ++ suff 
-                          ++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t" 
-                          ++ unwords unhandled_flags)) (ExitFailure 1))
-
-       do_cpp <- readState cpp_flag
+       do_cpp <- dynFlag cppFlag
        if do_cpp
           then do
                    cpp <- readIORef v_Pgm_P
@@ -320,19 +337,21 @@ run_phase Cpp basename suff input_fn output_fn
                                                        ++ pkg_include_dirs)
 
            verb <- getVerbFlag
+           (md_c_flags, _) <- machdepCCOpts
 
            runSomething "C pre-processor" 
                (unwords
-                          (["echo '{-# LINE 1 \"" ++ input_fn ++ "\" -}'", ">", output_fn, "&&",
+                          (["echo '{-# LINE 1 \"" ++ input_fn ++ "\" #-}'", ">", output_fn, "&&",
                     cpp, verb] 
                    ++ include_paths
                    ++ hs_src_cpp_opts
                    ++ hscpp_opts
+                   ++ md_c_flags
                    ++ [ "-x", "c", input_fn, ">>", output_fn ]
                   ))
          else do
            runSomething "Ineffective C pre-processor"
-                  ("echo '{-# LINE 1 \""  ++ input_fn ++ "\" -}' > " 
+                  ("echo '{-# LINE 1 \""  ++ input_fn ++ "\" #-}' > " 
                    ++ output_fn ++ " && cat " ++ input_fn
                    ++ " >> " ++ output_fn)
        return True
@@ -419,6 +438,20 @@ run_phase Hsc basename suff input_fn output_fn
                           Nothing -> basename ++ '.':hisuf
                           Just fn -> fn
 
+  -- figure out which header files to #include in a generated .hc file
+       c_includes <- getPackageCIncludes
+       cmdline_includes <- dynFlag cmdlineHcIncludes -- -#include options
+
+       let cc_injects = unlines (map mk_include 
+                               (c_includes ++ reverse cmdline_includes))
+           mk_include h_file = 
+               case h_file of 
+                  '"':_{-"-} -> "#include "++h_file
+                  '<':_      -> "#include "++h_file
+                  _          -> "#include \""++h_file++"\""
+
+       writeIORef v_HCHeader cc_injects
+
   -- figure out if the source has changed, for recompilation avoidance.
   -- only do this if we're eventually going to generate a .o file.
   -- (ToDo: do when generating .hc files too?)
@@ -430,7 +463,7 @@ run_phase Hsc basename suff input_fn output_fn
   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
        do_recomp <- readIORef v_Recomp
        todo <- readIORef v_GhcMode
-        o_file' <- odir_ify (basename ++ '.':phase_input_ext Ln)
+        o_file' <- odir_ify (basename ++ '.':phaseInputExt Ln)
         o_file <- osuf_ify o_file'
        source_unchanged <- 
           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
@@ -444,13 +477,12 @@ run_phase Hsc basename suff input_fn output_fn
                                  then return True
                                  else return False
 
-   -- build a ModuleLocation to pass to hscMain.
-        let location = ModuleLocation {
-                          ml_hs_file   = Nothing,
-                          ml_hspp_file = Just input_fn,
-                          ml_hi_file   = Just hifile,
-                          ml_obj_file  = Just o_file
-                       }
+        -- build a ModuleLocation to pass to hscMain.
+        modsrc <- readFile input_fn
+        let (srcimps,imps,mod_name) = getImports modsrc
+
+       Just (mod, location)
+          <- mkHomeModuleLocn mod_name basename (basename ++ '.':suff)
 
   -- get the DynFlags
         dyn_flags <- readIORef v_DynFlags
@@ -459,8 +491,10 @@ run_phase Hsc basename suff input_fn output_fn
         pcs <- initPersistentCompilerState
        result <- hscMain OneShot
                           dyn_flags{ hscOutName = output_fn }
+                         mod
+                         location{ ml_hspp_file=Just input_fn }
                          source_unchanged
-                         location
+                         False
                          Nothing        -- no iface
                          emptyModuleEnv -- HomeSymbolTable
                          emptyModuleEnv -- HomeIfaceTable
@@ -470,7 +504,11 @@ run_phase Hsc basename suff input_fn output_fn
 
            HscFail pcs -> throwDyn (PhaseFailed "hsc" (ExitFailure 1));
 
-            HscNoRecomp pcs details iface -> return False;
+            HscNoRecomp pcs details iface -> 
+               do {
+                 runSomething "Touching object file" ("touch " ++ o_file);
+                 return False;
+               };
 
            HscRecomp pcs details iface maybe_stub_h maybe_stub_c 
                      _maybe_interpreted_code -> do
@@ -490,7 +528,7 @@ run_phase Hsc basename suff input_fn output_fn
 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
 -- way too many hacks, and I can't say I've ever used it anyway.
 
-run_phase cc_phase _basename _suff input_fn output_fn
+run_phase cc_phase basename suff input_fn output_fn
    | cc_phase == Cc || cc_phase == HCc
    = do        cc <- readIORef v_Pgm_c
                cc_opts <- (getOpts opt_c)
@@ -505,26 +543,6 @@ run_phase cc_phase _basename _suff input_fn output_fn
        let include_paths = map (\p -> "-I"++p) (cmdline_include_dirs 
                                                        ++ pkg_include_dirs)
 
-       c_includes <- getPackageCIncludes
-       cmdline_includes <- readState cmdline_hc_includes -- -#include options
-
-       let cc_injects | hcc = unlines (map mk_include 
-                                       (c_includes ++ reverse cmdline_includes))
-                      | otherwise = ""
-           mk_include h_file = 
-               case h_file of 
-                  '"':_{-"-} -> "#include "++h_file
-                  '<':_      -> "#include "++h_file
-                  _          -> "#include \""++h_file++"\""
-
-       cc_help <- newTempName "c"
-       h <- openFile cc_help WriteMode
-       hPutStr h cc_injects
-       hPutStrLn h ("#include \"" ++ input_fn ++ "\"\n")
-       hClose h
-
-       ccout <- newTempName "ccout"
-
        mangle <- readIORef v_Do_asm_mangling
        (md_c_flags, md_regd_c_flags) <- machdepCCOpts
 
@@ -543,7 +561,7 @@ run_phase cc_phase _basename _suff input_fn output_fn
        excessPrecision <- readIORef v_Excess_precision
 
        runSomething "C Compiler"
-        (unwords ([ cc, "-x", "c", cc_help, "-o", output_fn ]
+        (unwords ([ cc, "-x", "c", input_fn, "-o", output_fn ]
                   ++ md_c_flags
                   ++ (if cc_phase == HCc && mangle
                         then md_regd_c_flags
@@ -555,7 +573,6 @@ run_phase cc_phase _basename _suff input_fn output_fn
                   ++ (if excessPrecision then [] else [ "-ffloat-store" ])
                   ++ include_paths
                   ++ pkg_extra_cc_opts
---                ++ [">", ccout]
                   ))
        return True
 
@@ -569,7 +586,7 @@ run_phase Mangle _basename _suff input_fn output_fn
        mangler_opts <- getOpts opt_m
        machdep_opts <-
         if (prefixMatch "i386" cTARGETPLATFORM)
-           then do n_regs <- readState stolen_x86_regs
+           then do n_regs <- dynFlag stolen_x86_regs
                    return [ show n_regs ]
            else return []
        runSomething "Assembly Mangler"
@@ -651,6 +668,100 @@ run_phase SplitAs basename _suff _input_fn _output_fn
        return True
 
 -----------------------------------------------------------------------------
+-- MoveBinary sort-of-phase
+-- After having produced a binary, move it somewhere else and generate a
+-- wrapper script calling the binary. Currently, we need this only in 
+-- a parallel way (i.e. in GUM), because PVM expects the binary in a
+-- central directory.
+-- This is called from doLink below, after linking. I haven't made it
+-- a separate phase to minimise interfering with other modules, and
+-- we don't need the generality of a phase (MoveBinary is always
+-- done after linking and makes only sense in a parallel setup)   -- HWL
+
+run_phase_MoveBinary input_fn
+  = do 
+        top_dir <- readIORef v_TopDir
+        pvm_root <- getEnv "PVM_ROOT"
+        pvm_arch <- getEnv "PVM_ARCH"
+        let 
+           pvm_executable_base = "=" ++ input_fn
+           pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
+           sysMan = top_dir ++ "/ghc/rts/parallel/SysMan";
+        -- nuke old binary; maybe use configur'ed names for cp and rm?
+        system ("rm -f " ++ pvm_executable)
+        -- move the newly created binary into PVM land
+        system ("cp -p " ++ input_fn ++ " " ++ pvm_executable)
+        -- generate a wrapper script for running a parallel prg under PVM
+        writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
+       return True
+
+-- generates a Perl skript starting a parallel prg under PVM
+mk_pvm_wrapper_script :: String -> String -> String -> String
+mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
+ [
+  "eval 'exec perl -S $0 ${1+\"$@\"}'", 
+  "  if $running_under_some_shell;",
+  "# =!=!=!=!=!=!=!=!=!=!=!",
+  "# This script is automatically generated: DO NOT EDIT!!!",
+  "# Generated by Glasgow Haskell Compiler",
+  "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
+  "#",
+  "$pvm_executable      = '" ++ pvm_executable ++ "';",
+  "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
+  "$SysMan = '" ++ sysMan ++ "';",
+  "",
+  {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
+  "# first, some magical shortcuts to run "commands" on the binary",
+  "# (which is hidden)",
+  "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
+  "    local($cmd) = $1;",
+  "    system("$cmd $pvm_executable");",
+  "    exit(0); # all done",
+  "}", -}
+  "",
+  "# Now, run the real binary; process the args first",
+  "$ENV{'PE'} = $pvm_executable_base;", --  ++ pvm_executable_base,
+  "$debug = '';",
+  "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
+  "@nonPVM_args = ();",
+  "$in_RTS_args = 0;",
+  "",
+  "args: while ($a = shift(@ARGV)) {",
+  "    if ( $a eq '+RTS' ) {",
+  "    $in_RTS_args = 1;",
+  "    } elsif ( $a eq '-RTS' ) {",
+  "    $in_RTS_args = 0;",
+  "    }",
+  "    if ( $a eq '-d' && $in_RTS_args ) {",
+  "    $debug = '-';",
+  "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
+  "    $nprocessors = $1;",
+  "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
+  "    $nprocessors = $1;",
+  "    } else {",
+  "    push(@nonPVM_args, $a);",
+  "    }",
+  "}",
+  "",
+  "local($return_val) = 0;",
+  "# Start the parallel execution by calling SysMan",
+  "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
+  "$return_val = $?;",
+  "# ToDo: fix race condition moving files and flushing them!!",
+  "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
+  "exit($return_val);"
+ ]
+
+-----------------------------------------------------------------------------
+-- Complain about non-dynamic flags in OPTIONS pragmas
+
+checkProcessArgsResult flags basename suff
+  = do when (not (null flags)) (throwDyn (OtherError (
+           basename ++ "." ++ suff 
+           ++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t" 
+           ++ unwords flags)) (ExitFailure 1))
+
+-----------------------------------------------------------------------------
 -- Linking
 
 doLink :: [String] -> IO ()
@@ -690,9 +801,8 @@ doLink o_files = do
 #ifdef mingw32_TARGET_OS
     let extra_os = if static || no_hs_main
                    then []
---                   else [ head (lib_paths (head rts_pkg)) ++ "/Main.dll_o",
---                          head (lib_paths (head std_pkg)) ++ "/PrelMain.dll_o" ]
-                    else []
+                   else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
+                          head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
 #endif
     (md_c_flags, _) <- machdepCCOpts
     runSomething "Linker"
@@ -717,6 +827,80 @@ doLink o_files = do
 #endif
        )
        )
+    -- parallel only: move binary to another dir -- HWL
+    ways_ <- readIORef v_Ways
+    when (WayPar `elem` ways_) (do 
+                                  success <- run_phase_MoveBinary output_fn
+                                  if success then return ()
+                                             else throwDyn (OtherError ("cannot move binary to PVM dir")))
+
+-----------------------------------------------------------------------------
+-- Making a DLL
+
+-- only for Win32, but bits that are #ifdefed in doLn are still #ifdefed here
+-- in a vain attempt to aid future portability
+doMkDLL :: [String] -> IO ()
+doMkDLL o_files = do
+    ln <- readIORef v_Pgm_dll
+    verb <- getVerbFlag
+    static <- readIORef v_Static
+    let imp = if static then "" else "_imp"
+    no_hs_main <- readIORef v_NoHsMain
+
+    o_file <- readIORef v_Output_file
+    let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
+
+    pkg_lib_paths <- getPackageLibraryPath
+    let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
+
+    lib_paths <- readIORef v_Library_paths
+    let lib_path_opts = map ("-L"++) lib_paths
+
+    pkg_libs <- getPackageLibraries
+    let pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
+
+    libs <- readIORef v_Cmdline_libraries
+    let lib_opts = map ("-l"++) (reverse libs)
+        -- reverse because they're added in reverse order from the cmd line
+
+    pkg_extra_ld_opts <- getPackageExtraLdOpts
+
+       -- probably _stub.o files
+    extra_ld_inputs <- readIORef v_Ld_inputs
+
+       -- opts from -optdll-<blah>
+    extra_ld_opts <- getStaticOpts v_Opt_dll
+
+    rts_pkg <- getPackageDetails ["rts"]
+    std_pkg <- getPackageDetails ["std"]
+#ifdef mingw32_TARGET_OS
+    let extra_os = if static || no_hs_main
+                   then []
+                   else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
+                          head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
+#endif
+    (md_c_flags, _) <- machdepCCOpts
+    runSomething "DLL creator"
+       (unwords
+        ([ ln, verb, "-o", output_fn ]
+        ++ md_c_flags
+        ++ o_files
+#ifdef mingw32_TARGET_OS
+        ++ extra_os
+        ++ [ "--target=i386-mingw32" ]
+#endif
+        ++ extra_ld_inputs
+        ++ lib_path_opts
+        ++ lib_opts
+        ++ pkg_lib_path_opts
+        ++ pkg_lib_opts
+        ++ pkg_extra_ld_opts
+         ++ (case findPS (packString (concat extra_ld_opts)) (packString "--def") of
+               Nothing -> [ "--export-all" ]
+              Just _  -> [ "" ])
+        ++ extra_ld_opts
+       )
+       )
 
 -----------------------------------------------------------------------------
 -- Just preprocess a file, put the result in a temp. file (used by the
@@ -725,14 +909,12 @@ doLink o_files = do
 preprocess :: FilePath -> IO FilePath
 preprocess filename =
   ASSERT(haskellish_file filename) 
-  do init_driver_state <- readIORef v_InitDriverState
-     writeIORef v_Driver_state init_driver_state
-
+  do init_dyn_flags <- readIORef v_InitDynFlags
+     writeIORef v_DynFlags init_dyn_flags
      pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
                        defaultHscLang filename
      runPipeline pipeline filename False{-no linking-} False{-no -o flag-}
 
-
 -----------------------------------------------------------------------------
 -- Compile a single module, under the control of the compilation manager.
 --
@@ -751,7 +933,8 @@ preprocess filename =
 
 compile :: GhciMode                -- distinguish batch from interactive
         -> ModSummary              -- summary, including source
-       -> Bool                    -- source unchanged?
+       -> Bool                    -- True <=> source unchanged
+       -> Bool                    -- True <=> have object
         -> Maybe ModIface          -- old interface, if available
         -> HomeSymbolTable         -- for home module ModDetails
        -> HomeIfaceTable          -- for home module Ifaces
@@ -769,11 +952,10 @@ data CompResult
    | CompErrs PersistentCompilerState  -- updated PCS
 
 
-compile ghci_mode summary source_unchanged old_iface hst hit pcs = do 
+compile ghci_mode summary source_unchanged have_object 
+       old_iface hst hit pcs = do 
    init_dyn_flags <- readIORef v_InitDynFlags
    writeIORef v_DynFlags init_dyn_flags
-   init_driver_state <- readIORef v_InitDriverState
-   writeIORef v_Driver_state init_driver_state
 
    showPass init_dyn_flags 
        (showSDoc (text "Compiling" <+> ppr (name_of_summary summary)))
@@ -794,12 +976,15 @@ compile ghci_mode summary source_unchanged old_iface hst hit pcs = do
                    HscAsm         -> newTempName (phaseInputExt As)
                    HscC           -> newTempName (phaseInputExt HCc)
                    HscJava        -> newTempName "java" -- ToDo
+#ifdef ILX
+                   HscILX         -> newTempName "ilx" -- ToDo
+#endif
                    HscInterpreted -> return (error "no output file")
 
    -- run the compiler
    hsc_result <- hscMain ghci_mode dyn_flags{ hscOutName = output_fn } 
-                        source_unchanged
-                         location old_iface hst hit pcs
+                        (ms_mod summary) location
+                        source_unchanged have_object old_iface hst hit pcs
 
    case hsc_result of
       HscFail pcs -> return (CompErrs pcs)
@@ -822,8 +1007,8 @@ compile ghci_mode summary source_unchanged old_iface hst hit pcs = do
                -- as our "unlinked" object.
                HscInterpreted -> 
                    case maybe_interpreted_code of
-                      Just (code,itbl_env) -> do tm <- getClockTime 
-                                                  return ([Trees code itbl_env], tm)
+                      Just (bcos,itbl_env) -> do tm <- getClockTime 
+                                                  return ([BCOs bcos itbl_env], tm)
                       Nothing -> panic "compile: no interpreted code"
 
                -- we're in batch mode: finish the compilation pipeline.