summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorLemmih <lemmih@gmail.com>2006-03-04 19:14:10 +0000
committerLemmih <lemmih@gmail.com>2006-03-04 19:14:10 +0000
commit374bc02f5feb4f5bf709d0a04d15ce28ec71eef1 (patch)
treee72aafd96473a781cfdc1b250cc6e8a7d090e185 /ghc/compiler
parent674689e20127e199e76cd19dd2f81dc5c2346bac (diff)
downloadhaskell-374bc02f5feb4f5bf709d0a04d15ce28ec71eef1.tar.gz
'have_object' isn't needed in a typed environment.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/main/DriverPipeline.hs3
-rw-r--r--ghc/compiler/main/HscMain.lhs20
2 files changed, 11 insertions, 12 deletions
diff --git a/ghc/compiler/main/DriverPipeline.hs b/ghc/compiler/main/DriverPipeline.hs
index bbc8051246..cd11e0f361 100644
--- a/ghc/compiler/main/DriverPipeline.hs
+++ b/ghc/compiler/main/DriverPipeline.hs
@@ -213,7 +213,7 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do
let runCompiler compiler handle
= do mbResult <- compiler hsc_env' mod_summary
- source_unchanged have_object old_iface
+ source_unchanged old_iface
(Just (mod_index, nmods))
case mbResult of
Nothing -> return CompErrs
@@ -751,7 +751,6 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma
-- run the compiler!
mbResult <- hscCompileOneShot hsc_env
mod_summary source_unchanged
- False -- No object file
Nothing -- No iface
Nothing -- No "module i of n" progress info
diff --git a/ghc/compiler/main/HscMain.lhs b/ghc/compiler/main/HscMain.lhs
index 95ea74ebfc..26fe813759 100644
--- a/ghc/compiler/main/HscMain.lhs
+++ b/ghc/compiler/main/HscMain.lhs
@@ -181,7 +181,7 @@ data InteractiveStatus
| InteractiveRecomp Bool -- Same as HscStatus
CompiledByteCode
-type NoRecomp result = HscEnv -> ModSummary -> Bool -> ModIface -> Maybe (Int,Int) -> IO result
+type NoRecomp result = HscEnv -> ModSummary -> ModIface -> Maybe (Int,Int) -> IO result
type FrontEnd core = HscEnv -> ModSummary -> Maybe (Int,Int) -> IO (Maybe core)
type BackEnd core prepCore = HscEnv -> ModSummary -> Maybe ModIface -> core -> IO prepCore
type CodeGen prepCore result = HscEnv -> ModSummary -> prepCore -> IO result
@@ -191,7 +191,6 @@ type CodeGen prepCore result = HscEnv -> ModSummary -> prepCore -> IO result
type Compiler result = HscEnv
-> ModSummary
-> Bool -- True <=> source unchanged
- -> Bool -- True <=> have an object file (for msgs only)
-> Maybe ModIface -- Old interface, if available
-> Maybe (Int,Int) -- Just (i,n) <=> module i of n (for msgs)
-> IO (Maybe result)
@@ -207,14 +206,14 @@ hscMkCompiler :: NoRecomp result -- What to do when recompilation isn't
-> Compiler result
hscMkCompiler norecomp frontend backend codegen
hsc_env mod_summary source_unchanged
- have_object mbOldIface mbModIndex
+ mbOldIface mbModIndex
= do (recomp_reqd, mbCheckedIface)
<- {-# SCC "checkOldIface" #-}
checkOldIface hsc_env mod_summary
source_unchanged mbOldIface
case mbCheckedIface of
Just iface | not recomp_reqd
- -> do result <- norecomp hsc_env mod_summary have_object iface mbModIndex
+ -> do result <- norecomp hsc_env mod_summary iface mbModIndex
return (Just result)
_otherwise
-> do mbCore <- frontend hsc_env mod_summary mbModIndex
@@ -283,7 +282,7 @@ hscCompileInteractive hsc_env mod_summary =
norecompOneShot :: a -> NoRecomp a
norecompOneShot a hsc_env mod_summary
- have_object old_iface
+ old_iface
mb_mod_index
= do compilationProgressMsg (hsc_dflags hsc_env) $
"compilation IS NOT required"
@@ -291,17 +290,17 @@ norecompOneShot a hsc_env mod_summary
return a
norecompMake :: NoRecomp (HscStatus, ModIface, ModDetails)
-norecompMake = norecompWorker HscNoRecomp
+norecompMake = norecompWorker HscNoRecomp False
norecompInteractive :: NoRecomp (InteractiveStatus, ModIface, ModDetails)
-norecompInteractive = norecompWorker InteractiveNoRecomp
+norecompInteractive = norecompWorker InteractiveNoRecomp True
-norecompWorker :: a -> NoRecomp (a, ModIface, ModDetails)
-norecompWorker a hsc_env mod_summary have_object
+norecompWorker :: a -> Bool -> NoRecomp (a, ModIface, ModDetails)
+norecompWorker a isInterp hsc_env mod_summary
old_iface mb_mod_index
= do compilationProgressMsg (hsc_dflags hsc_env) $
(showModuleIndex mb_mod_index ++
- "Skipping " ++ showModMsg have_object mod_summary)
+ "Skipping " ++ showModMsg isInterp mod_summary)
new_details <- {-# SCC "tcRnIface" #-}
initIfaceCheck hsc_env $
typecheckIface old_iface
@@ -333,6 +332,7 @@ hscCoreFrontEnd hsc_env mod_summary mb_mod_index = do {
Nothing -> return Nothing
Just mod_guts -> return (Just mod_guts) -- No desugaring to do!
}}
+
hscFileFrontEnd :: FrontEnd ModGuts
hscFileFrontEnd hsc_env mod_summary mb_mod_index = do {