summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CodeGen.lhs
diff options
context:
space:
mode:
authorsimonmar <unknown>2005-03-21 10:50:34 +0000
committersimonmar <unknown>2005-03-21 10:50:34 +0000
commit50159f6c4a3560662e37c55e64af1fb0b685011e (patch)
treeb2480dbca15f7825f885c8b5bbefeac00fc22bb8 /ghc/compiler/codeGen/CodeGen.lhs
parentcbe4c3a7cc2b1e627b308aff520a9f354f7a730b (diff)
downloadhaskell-50159f6c4a3560662e37c55e64af1fb0b685011e.tar.gz
[project @ 2005-03-21 10:50:22 by simonmar]
Complete the transition of -split-objs into a dynamic flag (looks like I half-finished it in the last commit). Also: complete the transition of -tmpdir into a dynamic flag, which involves some rearrangement of code from SysTools into DynFlags. Someday, initSysTools should move wholesale into initDynFlags, because most of the state that it initialises is now part of the DynFlags structure, and the rest could be moved in easily.
Diffstat (limited to 'ghc/compiler/codeGen/CodeGen.lhs')
-rw-r--r--ghc/compiler/codeGen/CodeGen.lhs14
1 files changed, 7 insertions, 7 deletions
diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs
index fa92421b21..11dafdd363 100644
--- a/ghc/compiler/codeGen/CodeGen.lhs
+++ b/ghc/compiler/codeGen/CodeGen.lhs
@@ -39,8 +39,8 @@ import MachOp ( wordRep, MachHint(..) )
import StgSyn
import PrelNames ( gHC_PRIM, rOOT_MAIN, mAIN, pREL_TOP_HANDLER )
-import DynFlags ( DynFlags(..), DynFlag(..) )
-import StaticFlags ( opt_SplitObjs, opt_SccProfilingOn )
+import DynFlags ( DynFlags(..), DynFlag(..), dopt )
+import StaticFlags ( opt_SccProfilingOn )
import HscTypes ( ForeignStubs(..), TypeEnv, typeEnvTyCons )
import CostCentre ( CollectedCCs )
@@ -281,7 +281,7 @@ variable.
\begin{code}
cgTopBinding :: DynFlags -> (StgBinding,[(Id,[Id])]) -> Code
cgTopBinding dflags (StgNonRec id rhs, srts)
- = do { id' <- maybeExternaliseId id
+ = do { id' <- maybeExternaliseId dflags id
; mapM_ (mkSRT dflags [id']) srts
; (id,info) <- cgTopRhs id' rhs
; addBindC id info -- Add the *un-externalised* Id to the envt,
@@ -290,7 +290,7 @@ cgTopBinding dflags (StgNonRec id rhs, srts)
cgTopBinding dflags (StgRec pairs, srts)
= do { let (bndrs, rhss) = unzip pairs
- ; bndrs' <- mapFCs maybeExternaliseId bndrs
+ ; bndrs' <- mapFCs (maybeExternaliseId dflags) bndrs
; let pairs' = zip bndrs' rhss
; mapM_ (mkSRT dflags bndrs') srts
; _new_binds <- fixC (\ new_binds -> do
@@ -342,9 +342,9 @@ If we're splitting the object, we need to externalise all the top-level names
which refers to this name).
\begin{code}
-maybeExternaliseId :: Id -> FCode Id
-maybeExternaliseId id
- | opt_SplitObjs, -- Externalise the name for -split-objs
+maybeExternaliseId :: DynFlags -> Id -> FCode Id
+maybeExternaliseId dflags id
+ | dopt Opt_SplitObjs dflags, -- Externalise the name for -split-objs
isInternalName name = do { mod <- moduleName
; returnFC (setIdName id (externalise mod)) }
| otherwise = returnFC id