diff --git a/ghc/compiler/main/DriverFlags.hs b/ghc/compiler/main/DriverFlags.hs
index bce5d9f76ea89ff72682c168af4ce6d1b52a9a34..bcff33fd7616d30dda26544f08d4cbd3fd80d0e9 100644
--- a/ghc/compiler/main/DriverFlags.hs
+++ b/ghc/compiler/main/DriverFlags.hs
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverFlags.hs,v 1.14 2000/10/31 17:30:17 simonpj Exp $
+-- $Id: DriverFlags.hs,v 1.15 2000/11/08 15:25:25 simonmar Exp $
 --
 -- Driver flags
 --
@@ -199,7 +199,7 @@ static_flags =
 	------- Output Redirection ------------------------------------------
   ,  ( "odir"		, HasArg (writeIORef v_Output_dir  . Just) )
   ,  ( "o"		, SepArg (writeIORef v_Output_file . Just) )
-  ,  ( "osuf"		, HasArg (writeIORef v_Output_suf  . Just) )
+  ,  ( "osuf"		, HasArg (writeIORef v_Object_suf  . Just) )
   ,  ( "hisuf"		, HasArg (writeIORef v_Hi_suf) )
   ,  ( "tmpdir"		, HasArg (writeIORef v_TmpDir . (++ "/")) )
   ,  ( "ohi"		, HasArg (\s -> case s of 
diff --git a/ghc/compiler/main/DriverPipeline.hs b/ghc/compiler/main/DriverPipeline.hs
index 4f06e1106a8e6dc7a7c8ade82807561751757079..3fad46e6927db47cc06b6bfa4d3ab4b598e354c2 100644
--- a/ghc/compiler/main/DriverPipeline.hs
+++ b/ghc/compiler/main/DriverPipeline.hs
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverPipeline.hs,v 1.15 2000/11/02 13:58:45 sewardj Exp $
+-- $Id: DriverPipeline.hs,v 1.16 2000/11/08 15:25:25 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -134,6 +134,7 @@ genPipeline todo stop_flag filename
    keep_hc    <- readIORef v_Keep_hc_files
    keep_raw_s <- readIORef v_Keep_raw_s_files
    keep_s     <- readIORef v_Keep_s_files
+   osuf       <- readIORef v_Object_suf
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
@@ -195,6 +196,10 @@ genPipeline todo stop_flag filename
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
+      myPhaseInputExt Ln = case osuf of Nothing -> phaseInputExt Ln
+					Just s  -> s
+      myPhaseInputExt other = phaseInputExt other
+
       annotatePipeline
 	 :: [Phase]		-- raw pipeline
 	 -> Phase		-- phase to stop before
@@ -202,7 +207,7 @@ genPipeline todo stop_flag filename
       annotatePipeline []     _    = []
       annotatePipeline (Ln:_) _    = []
       annotatePipeline (phase:next_phase:ps) stop = 
-     	  (phase, keep_this_output, phaseInputExt next_phase)
+     	  (phase, keep_this_output, myPhaseInputExt next_phase)
 	     : annotatePipeline (next_phase:ps) stop
      	  where
      		keep_this_output
@@ -276,8 +281,7 @@ pipeLoop ((phase, keep, o_suffix):phases)
    		       Just s  -> return s
    		       Nothing -> error "outputFileName"
    	       else if keep == Persistent
-   			   then do f <- odir_ify (orig_basename ++ '.':suffix)
-   				   osuf_ify f
+   			   then odir_ify (orig_basename ++ '.':suffix)
    			   else newTempName suffix
 
 -------------------------------------------------------------------------------
@@ -342,9 +346,9 @@ run_phase MkDependHS basename suff input_fn _output_fn = do
 
    deps <- mapM (findDependency basename) imports
 
-   osuf_opt <- readIORef v_Output_suf
+   osuf_opt <- readIORef v_Object_suf
    let osuf = case osuf_opt of
-			Nothing -> "o"
+			Nothing -> phaseInputExt Ln
 			Just s  -> s
 
    extra_suffixes <- readIORef v_Dep_suffixes
diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs
index cfad97a58844788b0d5f408bbc23915167c065e2..e0ee8b9cc785d323be9592965c9fd2c05d079193 100644
--- a/ghc/compiler/main/DriverState.hs
+++ b/ghc/compiler/main/DriverState.hs
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverState.hs,v 1.10 2000/10/27 15:40:01 simonpj Exp $
+-- $Id: DriverState.hs,v 1.11 2000/11/08 15:25:25 simonmar Exp $
 --
 -- Settings for the driver
 --
@@ -161,7 +161,7 @@ GLOBAL_VAR(v_Hsc_Lang, if cGhcWithNativeCodeGen == "YES" &&
 	   HscLang)
 
 GLOBAL_VAR(v_Output_dir,  Nothing, Maybe String)
-GLOBAL_VAR(v_Output_suf,  Nothing, Maybe String)
+GLOBAL_VAR(v_Object_suf,  Nothing, Maybe String)
 GLOBAL_VAR(v_Output_file, Nothing, Maybe String)
 GLOBAL_VAR(v_Output_hi,   Nothing, Maybe String)
 
@@ -176,7 +176,7 @@ odir_ify f = do
 
 osuf_ify :: String -> IO String
 osuf_ify f = do
-  osuf_opt <- readIORef v_Output_suf
+  osuf_opt <- readIORef v_Object_suf
   case osuf_opt of
 	Nothing -> return f
 	Just s  -> return (newsuf s f)
diff --git a/ghc/compiler/main/Finder.lhs b/ghc/compiler/main/Finder.lhs
index 732047bfb649456f0d225f463763866d37c52822..c833bf6c11399841c7f126375020e075e5105bd2 100644
--- a/ghc/compiler/main/Finder.lhs
+++ b/ghc/compiler/main/Finder.lhs
@@ -20,6 +20,7 @@ import Module
 import FiniteMap
 import Util
 import Panic		( panic )
+import Config
 
 import IOExts
 import Directory
@@ -110,9 +111,25 @@ maybeHomeModule mod_name = do
 
    case lookupFM home_map lhs of {
 	Just path ->  mkHomeModuleLocn mod_name (path ++ '/':basename) lhs;
-	Nothing -> return Nothing
+	Nothing -> do
+
+   -- can't find a source file anywhere, check for a lone .hi file.
+   hisuf <- readIORef v_Hi_suf
+   let hi = basename ++ '.':hisuf
+   case lookupFM home_map hi of {
+	Just path ->  mkHomeModuleLocn mod_name (path ++ '/':basename) hs;
+	Nothing -> do
 
-   }}
+   -- last chance: .hi-boot and .hi-boot-<ver>
+   let hi_boot = basename ++ ".hi-boot"
+   let hi_boot_ver = basename ++ ".hi-boot-" ++ cHscIfaceFileVersion
+   case lookupFM home_map hi_boot of {
+	Just path ->  mkHomeModuleLocn mod_name (path ++ '/':basename) hs;
+	Nothing -> do
+   case lookupFM home_map hi_boot_ver of {
+	Just path ->  mkHomeModuleLocn mod_name (path ++ '/':basename) hs;
+	Nothing -> return Nothing
+   }}}}}
 
 mkHomeModuleLocn mod_name basename source_fn = do
 
diff --git a/ghc/compiler/main/Main.hs b/ghc/compiler/main/Main.hs
index d81b9fe939df218f8d35ee3cd3bf4b2e6b9066d8..7dfcd97da243823b78eb50ce04ebc03c7e858aba 100644
--- a/ghc/compiler/main/Main.hs
+++ b/ghc/compiler/main/Main.hs
@@ -1,6 +1,6 @@
 {-# OPTIONS -W -fno-warn-incomplete-patterns #-}
 -----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.17 2000/11/03 10:42:39 simonmar Exp $
+-- $Id: Main.hs,v 1.18 2000/11/08 15:25:25 simonmar Exp $
 --
 -- GHC Driver program
 --
@@ -228,9 +228,11 @@ main =
    pipelines <- mapM (genPipeline mode stop_flag) srcs
    let src_pipelines = zip srcs pipelines
 
+	-- sanity checking
    o_file <- readIORef v_Output_file
-   if isJust o_file && mode /= DoLink && length srcs > 1
-	then throwDyn (UsageError "can't apply -o option to multiple source files")
+   ohi    <- readIORef v_Output_hi
+   if length srcs > 1 && (isJust ohi || (isJust o_file && mode /= DoLink))
+	then throwDyn (UsageError "can't apply -o or -ohi options to multiple source files")
 	else do
 
    if null srcs then throwDyn (UsageError "no input files") else do