fix warnings
[ghc-hetmet.git] / compiler / main / HscMain.lhs
index 51d6d88..72abafb 100644 (file)
@@ -9,7 +9,7 @@
 -- The above warning supression flag is a temporary kludge.
 -- While working on this module you are encouraged to remove it and fix
 -- any warnings in the module. See
---     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
+--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
 -- for details
 
 module HscMain
@@ -210,6 +210,7 @@ data InteractiveStatus
     = InteractiveNoRecomp
     | InteractiveRecomp Bool     -- Same as HscStatus
                         CompiledByteCode
+                        ModBreaks
 
 
 -- I want Control.Monad.State! --Lemmih 03/07/2006
@@ -246,7 +247,6 @@ liftIO ioA = Comp $ \s -> do a <- ioA
                              return (a,s)
 
 type NoRecomp result = ModIface -> Comp result
-type FrontEnd core = Comp (Maybe core)
 
 -- FIXME: The old interface and module index are only using in 'batch' and
 --        'interactive' mode. They should be removed from 'oneshot' mode.
@@ -262,8 +262,8 @@ type Compiler result =  HscEnv
 -- then combines the FrontEnd and BackEnd to a working compiler.
 hscMkCompiler :: NoRecomp result         -- What to do when recompilation isn't required.
               -> (Maybe (Int,Int) -> Bool -> Comp ())
-              -> FrontEnd core
-              -> (core -> Comp result)   -- Backend.
+              -> Comp (Maybe ModGuts)       -- Front end
+              -> (ModGuts -> Comp result)   -- Backend.
               -> Compiler result
 hscMkCompiler norecomp messenger frontend backend
               hsc_env mod_summary source_unchanged
@@ -296,67 +296,52 @@ hscMkCompiler norecomp messenger frontend backend
 -- Compilers
 --------------------------------------------------------------
 
---        1         2         3         4         5         6         7         8          9
 -- Compile Haskell, boot and extCore in OneShot mode.
 hscCompileOneShot :: Compiler HscStatus
-hscCompileOneShot = hscCompileHardCode norecompOneShot oneShotMsg hscOneShot (hscConst (HscRecomp False))
+hscCompileOneShot
+   = hscCompiler norecompOneShot oneShotMsg backend boot_backend
+   where
+     backend inp  = hscSimplify inp >>= hscNormalIface >>= hscWriteIface >>= hscOneShot
+     boot_backend inp = hscSimpleIface inp >>= hscWriteIface >> return (HscRecomp False)
 
 -- Compile Haskell, boot and extCore in batch mode.
 hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)
-hscCompileBatch = hscCompileHardCode norecompBatch batchMsg hscBatch hscNothing
-
--- Compile to hardcode (C,asm,...). This general structure is shared by OneShot and Batch.
-hscCompileHardCode :: NoRecomp result                                  -- No recomp necessary
-                   -> (Maybe (Int,Int) -> Bool -> Comp ())             -- Message callback
-                   -> ((ModIface, ModDetails, CgGuts) -> Comp result)  -- Compile normal file
-                   -> ((ModIface, ModDetails, ModGuts) -> Comp result) -- Compile boot file
-                   -> Compiler result
-hscCompileHardCode norecomp msg compNormal compBoot hsc_env mod_summary =
-    compiler hsc_env mod_summary
-    where mkComp = hscMkCompiler norecomp msg
-          -- How to compile nonBoot files.
-          nonBootComp inp = hscSimplify inp >>= hscNormalIface >>=
-                            hscWriteIface >>= compNormal
-          -- How to compile boot files.
-          bootComp inp = hscSimpleIface inp >>= hscWriteIface >>= compBoot
-          compiler
-              = case ms_hsc_src mod_summary of
-                ExtCoreFile
-                    -> mkComp hscCoreFrontEnd nonBootComp
-                HsSrcFile
-                    -> mkComp hscFileFrontEnd nonBootComp
-                HsBootFile
-                    -> mkComp hscFileFrontEnd bootComp
+hscCompileBatch
+   = hscCompiler norecompBatch batchMsg backend boot_backend
+   where
+     backend inp  = hscSimplify inp >>= hscNormalIface >>= hscWriteIface >>= hscBatch
+     boot_backend inp = hscSimpleIface inp >>= hscWriteIface >>= hscNothing
 
 -- Type-check Haskell, boot and extCore.
 -- Does it make sense to compile extCore to nothing?
 hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails)
-hscCompileNothing hsc_env mod_summary
-    = compiler hsc_env mod_summary
-    where mkComp = hscMkCompiler norecompBatch batchMsg
-          pipeline inp = hscSimpleIface inp >>= hscIgnoreIface >>= hscNothing
-          compiler
-              = case ms_hsc_src mod_summary of
-                ExtCoreFile
-                    -> mkComp hscCoreFrontEnd pipeline
-                HsSrcFile
-                    -> mkComp hscFileFrontEnd pipeline
-                HsBootFile
-                    -> mkComp hscFileFrontEnd pipeline
+hscCompileNothing
+   = hscCompiler norecompBatch batchMsg backend backend
+   where
+     backend inp = hscSimpleIface inp >>= hscIgnoreIface >>= hscNothing
 
 -- Compile Haskell, extCore to bytecode.
 hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails)
-hscCompileInteractive hsc_env mod_summary =
-    hscMkCompiler norecompInteractive batchMsg
-                  frontend backend
-                  hsc_env mod_summary
-    where backend inp = hscSimplify inp >>= hscNormalIface >>= hscIgnoreIface >>= hscInteractive
-          frontend = case ms_hsc_src mod_summary of
-                       ExtCoreFile -> hscCoreFrontEnd
-                       HsSrcFile   -> hscFileFrontEnd
-                       HsBootFile  -> panic bootErrorMsg
-          bootErrorMsg = "Compiling a HsBootFile to bytecode doesn't make sense. " ++
-                         "Use 'hscCompileBatch' instead."
+hscCompileInteractive
+   = hscCompiler norecompInteractive batchMsg backend boot_backend
+   where
+     backend inp = hscSimplify inp >>= hscNormalIface >>= hscIgnoreIface >>= hscInteractive
+     boot_backend = panic "hscCompileInteractive: can't do boot files here"
+
+hscCompiler
+        :: NoRecomp result                                  -- No recomp necessary
+        -> (Maybe (Int,Int) -> Bool -> Comp ())             -- Message callback
+        -> (ModGuts -> Comp result)  -- Compile normal file
+        -> (ModGuts -> Comp result) -- Compile boot file
+        -> Compiler result
+hscCompiler norecomp msg nonBootComp bootComp hsc_env mod_summary =
+    hscMkCompiler norecomp msg frontend backend hsc_env mod_summary
+    where
+          (frontend,backend)
+              = case ms_hsc_src mod_summary of
+                ExtCoreFile -> (hscCoreFrontEnd, nonBootComp)
+                HsSrcFile   -> (hscFileFrontEnd, nonBootComp)
+                HsBootFile  -> (hscFileFrontEnd, bootComp)
 
 --------------------------------------------------------------
 -- NoRecomp handlers
@@ -417,7 +402,7 @@ batchMsg mb_mod_index recomp
 -- FrontEnds
 --------------------------------------------------------------
 
-hscCoreFrontEnd :: FrontEnd ModGuts
+hscCoreFrontEnd :: Comp (Maybe ModGuts)
 hscCoreFrontEnd =
     do hsc_env <- gets compHscEnv
        mod_summary <- gets compModSummary
@@ -442,7 +427,7 @@ hscCoreFrontEnd =
                      Just mod_guts -> return (Just mod_guts)         -- No desugaring to do!
 
         
-hscFileFrontEnd :: FrontEnd ModGuts
+hscFileFrontEnd :: Comp (Maybe ModGuts)
 hscFileFrontEnd =
     do hsc_env <- gets compHscEnv
        mod_summary <- gets compModSummary
@@ -634,7 +619,8 @@ hscInteractive (iface, details, cgguts)
                      cg_module   = this_mod,
                      cg_binds    = core_binds,
                      cg_tycons   = tycons,
-                     cg_foreign  = foreign_stubs } = cgguts
+                     cg_foreign  = foreign_stubs,
+                     cg_modBreaks = mod_breaks } = cgguts
              dflags = hsc_dflags hsc_env
              location = ms_location mod_summary
              data_tycons = filter isDataTyCon tycons
@@ -647,11 +633,11 @@ hscInteractive (iface, details, cgguts)
          prepd_binds <- {-# SCC "CorePrep" #-}
                         corePrepPgm dflags core_binds data_tycons ;
          -----------------  Generate byte code ------------------
-         comp_bc <- byteCodeGen dflags prepd_binds data_tycons (md_modBreaks details)
+         comp_bc <- byteCodeGen dflags prepd_binds data_tycons mod_breaks
          ------------------ Create f-x-dynamic C-side stuff ---
          (istub_h_exists, istub_c_exists) 
              <- outputForeignStubs dflags this_mod location foreign_stubs
-         return (InteractiveRecomp istub_c_exists comp_bc, iface, details)
+         return (InteractiveRecomp istub_c_exists comp_bc mod_breaks, iface, details)
 #else
     = panic "GHC not compiled with interpreter"
 #endif
@@ -693,7 +679,6 @@ hscFileCheck hsc_env mod_summary compileToCore = do {
                                md_exports   = tcg_exports   tc_result,
                                md_insts     = tcg_insts     tc_result,
                                md_fam_insts = tcg_fam_insts tc_result,
-                                md_modBreaks = emptyModBreaks,      
                                md_rules     = [panic "no rules"],
                                   -- Rules are CoreRules, not the
                                   -- RuleDecls we get out of the typechecker