summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen
diff options
context:
space:
mode:
authorpartain <unknown>1996-06-05 06:51:39 +0000
committerpartain <unknown>1996-06-05 06:51:39 +0000
commite7498a3ee1d0484d02a9e86633cc179c76ebf36e (patch)
treec1688b600d0b3c217b84cf07870379c29c969529 /ghc/compiler/codeGen
parent30cf375e0bc79a6b71074a5e0fd2ec393241a751 (diff)
downloadhaskell-e7498a3ee1d0484d02a9e86633cc179c76ebf36e.tar.gz
[project @ 1996-06-05 06:44:31 by partain]
SLPJ changes through 960604
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r--ghc/compiler/codeGen/CgBindery.lhs4
-rw-r--r--ghc/compiler/codeGen/CgCase.lhs7
-rw-r--r--ghc/compiler/codeGen/CgClosure.lhs13
-rw-r--r--ghc/compiler/codeGen/CgCompInfo.lhs3
-rw-r--r--ghc/compiler/codeGen/CgCon.lhs21
-rw-r--r--ghc/compiler/codeGen/CgConTbls.lhs16
-rw-r--r--ghc/compiler/codeGen/CgExpr.lhs4
-rw-r--r--ghc/compiler/codeGen/CgHeapery.lhs2
-rw-r--r--ghc/compiler/codeGen/CgLetNoEscape.lhs12
-rw-r--r--ghc/compiler/codeGen/CgMonad.lhs4
-rw-r--r--ghc/compiler/codeGen/CgRetConv.lhs10
-rw-r--r--ghc/compiler/codeGen/CgStackery.lhs2
-rw-r--r--ghc/compiler/codeGen/CgTailCall.lhs2
-rw-r--r--ghc/compiler/codeGen/CgUpdate.lhs2
-rw-r--r--ghc/compiler/codeGen/CgUsages.lhs6
-rw-r--r--ghc/compiler/codeGen/ClosureInfo.lhs58
-rw-r--r--ghc/compiler/codeGen/CodeGen.lhs2
-rw-r--r--ghc/compiler/codeGen/SMRep.lhs2
18 files changed, 80 insertions, 90 deletions
diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs
index b00aca77fa..8edd5bd9dc 100644
--- a/ghc/compiler/codeGen/CgBindery.lhs
+++ b/ghc/compiler/codeGen/CgBindery.lhs
@@ -26,8 +26,8 @@ module CgBindery (
rebindToAStack, rebindToBStack
) where
-import Ubiq{-uitous-}
-import CgLoop1 -- here for paranoia-checking
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop1) -- here for paranoia-checking
import AbsCSyn
import CgMonad
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs
index 2d0f3aebd1..17d61261c1 100644
--- a/ghc/compiler/codeGen/CgCase.lhs
+++ b/ghc/compiler/codeGen/CgCase.lhs
@@ -12,8 +12,8 @@
module CgCase ( cgCase, saveVolatileVarsAndRegs ) where
-import Ubiq{-uitous-}
-import CgLoop2 ( cgExpr, getPrimOpArgAmodes )
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop2) ( cgExpr, getPrimOpArgAmodes )
import CgMonad
import StgSyn
@@ -41,7 +41,7 @@ import CgStackery ( allocAStack, allocBStack, allocAStackTop, allocBStackTop )
import CgTailCall ( tailCallBusiness, performReturn )
import CgUsages ( getSpARelOffset, getSpBRelOffset, freeBStkSlot )
import CLabel ( mkVecTblLabel, mkReturnPtLabel, mkDefaultLabel,
- mkAltLabel, mkClosureLabel
+ mkAltLabel
)
import ClosureInfo ( mkConLFInfo, mkLFArgument, layOutDynCon )
import CmdLineOpts ( opt_SccProfilingOn, opt_GranMacros )
@@ -645,7 +645,6 @@ cgAlgAlts gc_flag uniq restore_cc semi_tagging
where
lf_info = mkConLFInfo con
tag = dataConTag con
- closure_lbl = mkClosureLabel con
-- alloc_code generates code to allocate constructor con, whose args are
-- in the arguments to alloc_code, assigning the result to Node.
diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs
index 81ff55f65c..cfd5ceade1 100644
--- a/ghc/compiler/codeGen/CgClosure.lhs
+++ b/ghc/compiler/codeGen/CgClosure.lhs
@@ -12,8 +12,8 @@ with {\em closures} on the RHSs of let(rec)s. See also
module CgClosure ( cgTopRhsClosure, cgRhsClosure ) where
-import Ubiq{-uitous-}
-import CgLoop2 ( cgExpr, cgSccExpr )
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop2) ( cgExpr, cgSccExpr )
import CgMonad
import AbsCSyn
@@ -451,7 +451,10 @@ closureCodeBody binder_info closure_info cc all_args body
ViaNode | is_concurrent -> []
other -> panic "closureCodeBody:arg_regs"
- stk_args = drop (length arg_regs) all_args
+ num_arg_regs = length arg_regs
+
+ (reg_args, stk_args) = splitAt num_arg_regs all_args
+
(spA_stk_args, spB_stk_args, stk_bxd_w_offsets, stk_ubxd_w_offsets)
= mkVirtStkOffsets
0 0 -- Initial virtual SpA, SpB
@@ -509,7 +512,7 @@ closureCodeBody binder_info closure_info cc all_args body
-- Bind args to regs/stack as appropriate, and
-- record expected position of sps
- bindArgsToRegs all_args arg_regs `thenC`
+ bindArgsToRegs reg_args arg_regs `thenC`
mapCs bindNewToAStack stk_bxd_w_offsets `thenC`
mapCs bindNewToBStack stk_ubxd_w_offsets `thenC`
setRealAndVirtualSps spA_stk_args spB_stk_args `thenC`
@@ -863,8 +866,6 @@ setupUpdate closure_info code
`thenC`
returnFC amode
- closure_label = mkClosureLabel (closureId closure_info)
-
vector
= case (closureType closure_info) of
Nothing -> CReg StdUpdRetVecReg
diff --git a/ghc/compiler/codeGen/CgCompInfo.lhs b/ghc/compiler/codeGen/CgCompInfo.lhs
index 9b14dcdaf9..561f8bf477 100644
--- a/ghc/compiler/codeGen/CgCompInfo.lhs
+++ b/ghc/compiler/codeGen/CgCompInfo.lhs
@@ -63,9 +63,6 @@ module CgCompInfo (
spARelToInt,
spBRelToInt
-
- -- and to make the interface self-sufficient...
--- RegRelative
) where
-- This magical #include brings in all the everybody-knows-these magic
diff --git a/ghc/compiler/codeGen/CgCon.lhs b/ghc/compiler/codeGen/CgCon.lhs
index 0d0e620cf6..cb5337be61 100644
--- a/ghc/compiler/codeGen/CgCon.lhs
+++ b/ghc/compiler/codeGen/CgCon.lhs
@@ -16,7 +16,7 @@ module CgCon (
cgReturnDataCon
) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import CgMonad
import AbsCSyn
@@ -33,9 +33,8 @@ import CgCompInfo ( mAX_INTLIKE, mIN_INTLIKE )
import CgHeapery ( allocDynClosure )
import CgRetConv ( dataReturnConvAlg, DataReturnConvention(..) )
import CgTailCall ( performReturn, mkStaticAlgReturnCode )
-import CLabel ( mkClosureLabel, mkInfoTableLabel,
- mkPhantomInfoTableLabel,
- mkConEntryLabel, mkStdEntryLabel
+import CLabel ( mkClosureLabel, mkStaticClosureLabel,
+ mkConInfoTableLabel, mkPhantomInfoTableLabel
)
import ClosureInfo ( mkClosureLFInfo, mkConLFInfo, mkLFArgument,
layOutDynCon, layOutDynClosure,
@@ -157,13 +156,9 @@ cgTopRhsCon name con args all_zero_size_args
-- RETURN
returnFC (name, stableAmodeIdInfo name (CLbl closure_label PtrRep) lf_info)
where
- con_tycon = dataConTyCon con
- lf_info = mkConLFInfo con
-
- closure_label = mkClosureLabel name
- info_label = mkInfoTableLabel con
- con_entry_label = mkConEntryLabel con
- entry_label = mkStdEntryLabel name
+ con_tycon = dataConTyCon con
+ lf_info = mkConLFInfo con
+ closure_label = mkClosureLabel name
\end{code}
The general case is:
@@ -277,7 +272,7 @@ at all.
buildDynCon binder cc con args all_zero_size_args@True
= ASSERT(isDataCon con)
returnFC (stableAmodeIdInfo binder
- (CLbl (mkClosureLabel con) PtrRep)
+ (CLbl (mkStaticClosureLabel con) PtrRep)
(mkConLFInfo con))
\end{code}
@@ -427,7 +422,7 @@ cgReturnDataCon con amodes all_zero_size_args live_vars
-- MAKE NODE POINT TO IT
let reg_assts = move_to_reg amode node
- info_lbl = mkInfoTableLabel con
+ info_lbl = mkConInfoTableLabel con
in
-- RETURN
diff --git a/ghc/compiler/codeGen/CgConTbls.lhs b/ghc/compiler/codeGen/CgConTbls.lhs
index 98c5a1deed..7745466706 100644
--- a/ghc/compiler/codeGen/CgConTbls.lhs
+++ b/ghc/compiler/codeGen/CgConTbls.lhs
@@ -8,7 +8,7 @@
module CgConTbls ( genStaticConBits ) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import AbsCSyn
import CgMonad
@@ -23,7 +23,7 @@ import CgRetConv ( mkLiveRegsMask,
)
import CgTailCall ( performReturn, mkStaticAlgReturnCode )
import CgUsages ( getHpRelOffset )
-import CLabel ( mkConEntryLabel, mkClosureLabel,
+import CLabel ( mkConEntryLabel, mkStaticClosureLabel,
mkConUpdCodePtrVecLabel,
mkStdUpdCodePtrVecLabel, mkStdUpdVecTblLabel
)
@@ -35,7 +35,7 @@ import ClosureInfo ( layOutStaticClosure, layOutDynCon,
import CostCentre ( dontCareCostCentre )
import FiniteMap ( fmToList )
import HeapOffs ( zeroOff, VirtualHeapOffset(..) )
-import Id ( dataConTag, dataConSig,
+import Id ( dataConTag, dataConRawArgTys,
dataConArity, fIRST_TAG,
emptyIdSet,
GenId{-instance NamedThing-}
@@ -240,10 +240,10 @@ genConInfo comp_info tycon data_con
zero_size arg_ty = getPrimRepSize (typePrimRep arg_ty) == 0
- (_,_,arg_tys,_) = dataConSig data_con
- con_arity = dataConArity data_con
- entry_label = mkConEntryLabel data_con
- closure_label = mkClosureLabel data_con
+ arg_tys = dataConRawArgTys data_con
+ con_arity = dataConArity data_con
+ entry_label = mkConEntryLabel data_con
+ closure_label = mkStaticClosureLabel data_con
\end{code}
The entry code for a constructor now loads the info ptr by indirecting
@@ -288,7 +288,7 @@ mkConCodeAndInfo con
ReturnInHeap ->
let
- (_, _, arg_tys, _) = dataConSig con
+ arg_tys = dataConRawArgTys con
(closure_info, arg_things)
= layOutDynCon con typePrimRep arg_tys
diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs
index dd0b7f4d4f..a4a0746d3d 100644
--- a/ghc/compiler/codeGen/CgExpr.lhs
+++ b/ghc/compiler/codeGen/CgExpr.lhs
@@ -12,8 +12,8 @@
module CgExpr ( cgExpr, cgSccExpr, getPrimOpArgAmodes ) where
-import Ubiq{-uitous-}
-import CgLoop2 -- here for paranoia-checking
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop2) -- here for paranoia-checking
import StgSyn
import CgMonad
diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs
index fa8f1e0bdb..888908f612 100644
--- a/ghc/compiler/codeGen/CgHeapery.lhs
+++ b/ghc/compiler/codeGen/CgHeapery.lhs
@@ -14,7 +14,7 @@ module CgHeapery (
, heapCheckOnly, fetchAndReschedule, yield
) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import AbsCSyn
import CgMonad
diff --git a/ghc/compiler/codeGen/CgLetNoEscape.lhs b/ghc/compiler/codeGen/CgLetNoEscape.lhs
index f59ef4eb7c..3748ddd657 100644
--- a/ghc/compiler/codeGen/CgLetNoEscape.lhs
+++ b/ghc/compiler/codeGen/CgLetNoEscape.lhs
@@ -12,8 +12,8 @@
module CgLetNoEscape ( cgLetNoEscapeClosure ) where
-import Ubiq{-uitious-}
-import CgLoop2 ( cgExpr )
+IMP_Ubiq(){-uitious-}
+IMPORT_DELOOPER(CgLoop2) ( cgExpr )
import StgSyn
import CgMonad
@@ -169,9 +169,9 @@ cgLetNoEscapeBody :: [Id] -- Args
cgLetNoEscapeBody all_args rhs
= getVirtSps `thenFC` \ (vA, vB) ->
let
- arg_kinds = map idPrimRep all_args
- (arg_regs, _) = assignRegs [{-nothing live-}] arg_kinds
- stk_args = drop (length arg_regs) all_args
+ arg_kinds = map idPrimRep all_args
+ (arg_regs, _) = assignRegs [{-nothing live-}] arg_kinds
+ (reg_args, stk_args) = splitAt (length arg_regs) all_args
-- stk_args is the args which are passed on the stack at the fast-entry point
-- Using them, we define the stack layout
@@ -183,7 +183,7 @@ cgLetNoEscapeBody all_args rhs
in
-- Bind args to appropriate regs/stk locns
- bindArgsToRegs all_args arg_regs `thenC`
+ bindArgsToRegs reg_args arg_regs `thenC`
mapCs bindNewToAStack stk_bxd_w_offsets `thenC`
mapCs bindNewToBStack stk_ubxd_w_offsets `thenC`
setRealAndVirtualSps spA_stk_args spB_stk_args `thenC`
diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs
index 428d6f6881..ab22daeb24 100644
--- a/ghc/compiler/codeGen/CgMonad.lhs
+++ b/ghc/compiler/codeGen/CgMonad.lhs
@@ -47,8 +47,8 @@ module CgMonad (
CompilationInfo(..)
) where
-import Ubiq{-uitous-}
-import CgLoop1 -- stuff from CgBindery and CgUsages
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop1) -- stuff from CgBindery and CgUsages
import AbsCSyn
import AbsCUtils ( mkAbsCStmts )
diff --git a/ghc/compiler/codeGen/CgRetConv.lhs b/ghc/compiler/codeGen/CgRetConv.lhs
index 14e59f4526..fa3644038b 100644
--- a/ghc/compiler/codeGen/CgRetConv.lhs
+++ b/ghc/compiler/codeGen/CgRetConv.lhs
@@ -20,12 +20,10 @@ module CgRetConv (
assignPrimOpResultRegs,
makePrimOpArgsRobust,
assignRegs
-
- -- and to make the interface self-sufficient...
) where
-import Ubiq{-uitous-}
-import AbsCLoop -- paranoia checking
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(AbsCLoop) -- paranoia checking
import AbsCSyn -- quite a few things
import AbsCUtils ( mkAbstractCs, getAmodeRep,
@@ -36,7 +34,7 @@ import CgCompInfo ( mAX_FAMILY_SIZE_FOR_VEC_RETURNS,
mAX_Double_REG
)
import CmdLineOpts ( opt_ReturnInRegsThreshold )
-import Id ( isDataCon, dataConSig,
+import Id ( isDataCon, dataConRawArgTys,
DataCon(..), GenId{-instance Eq-}
)
import Maybes ( catMaybes )
@@ -123,7 +121,7 @@ dataReturnConvAlg data_con
[] -> ReturnInRegs reg_assignment
other -> ReturnInHeap -- Didn't fit in registers
where
- (_, _, arg_tys, _) = dataConSig data_con
+ arg_tys = dataConRawArgTys data_con
(reg_assignment, leftover_kinds)
= assignRegs [node, infoptr] -- taken...
diff --git a/ghc/compiler/codeGen/CgStackery.lhs b/ghc/compiler/codeGen/CgStackery.lhs
index 8e1c90a58e..caf38104dd 100644
--- a/ghc/compiler/codeGen/CgStackery.lhs
+++ b/ghc/compiler/codeGen/CgStackery.lhs
@@ -16,7 +16,7 @@ module CgStackery (
mkVirtStkOffsets, mkStkAmodes
) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import CgMonad
import AbsCSyn
diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs
index 15b2ae249b..770c4b52df 100644
--- a/ghc/compiler/codeGen/CgTailCall.lhs
+++ b/ghc/compiler/codeGen/CgTailCall.lhs
@@ -19,7 +19,7 @@ module CgTailCall (
tailCallBusiness
) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import CgMonad
import AbsCSyn
diff --git a/ghc/compiler/codeGen/CgUpdate.lhs b/ghc/compiler/codeGen/CgUpdate.lhs
index ff1a5546b9..70e344b7d9 100644
--- a/ghc/compiler/codeGen/CgUpdate.lhs
+++ b/ghc/compiler/codeGen/CgUpdate.lhs
@@ -8,7 +8,7 @@
module CgUpdate ( pushUpdateFrame ) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import CgMonad
import AbsCSyn
diff --git a/ghc/compiler/codeGen/CgUsages.lhs b/ghc/compiler/codeGen/CgUsages.lhs
index eec6be6067..e7e7b962cb 100644
--- a/ghc/compiler/codeGen/CgUsages.lhs
+++ b/ghc/compiler/codeGen/CgUsages.lhs
@@ -7,6 +7,8 @@ This module provides the functions to access (\tr{get*} functions) and
modify (\tr{set*} functions) the stacks and heap usage information.
\begin{code}
+#include "HsVersions.h"
+
module CgUsages (
initHeapUsage, setVirtHp, getVirtAndRealHp, setRealHp,
setRealAndVirtualSps,
@@ -18,8 +20,8 @@ module CgUsages (
freeBStkSlot
) where
-import Ubiq{-uitous-}
-import CgLoop1 -- here for paranoia-checking
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(CgLoop1) -- here for paranoia-checking
import AbsCSyn ( RegRelative(..), AbstractC, CAddrMode )
import CgMonad
diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs
index e45fdeccf6..960e6a9803 100644
--- a/ghc/compiler/codeGen/ClosureInfo.lhs
+++ b/ghc/compiler/codeGen/ClosureInfo.lhs
@@ -50,8 +50,8 @@ module ClosureInfo (
dataConLiveness -- concurrency
) where
-import Ubiq{-uitous-}
-import AbsCLoop -- here for paranoia-checking
+IMP_Ubiq(){-uitous-}
+IMPORT_DELOOPER(AbsCLoop) -- here for paranoia-checking
import AbsCSyn
import StgSyn
@@ -68,6 +68,7 @@ import CgRetConv ( assignRegs, dataReturnConvAlg,
)
import CLabel ( mkStdEntryLabel, mkFastEntryLabel,
mkPhantomInfoTableLabel, mkInfoTableLabel,
+ mkConInfoTableLabel,
mkBlackHoleInfoTableLabel, mkVapInfoTableLabel,
mkStaticInfoTableLabel, mkStaticConEntryLabel,
mkConEntryLabel, mkClosureLabel, mkVapEntryLabel
@@ -78,9 +79,9 @@ import HeapOffs ( intOff, addOff, totHdrSize, varHdrSize,
VirtualHeapOffset(..)
)
import Id ( idType, idPrimRep, getIdArity,
- externallyVisibleId, dataConSig,
+ externallyVisibleId,
dataConTag, fIRST_TAG,
- isDataCon, dataConArity, dataConTyCon,
+ isDataCon, isNullaryDataCon, dataConTyCon,
isTupleCon, DataCon(..),
GenId{-instance Eq-}
)
@@ -425,7 +426,7 @@ mkClosureLFInfo False -- don't bother if at top-level
offset_into_int_maybe = intOffsetIntoGoods the_offset
Just offset_into_int = offset_into_int_maybe
is_single_constructor = maybeToBool (maybeTyConSingleCon tycon)
- (_,_,_, tycon) = dataConSig con
+ tycon = dataConTyCon con
\end{code}
Same kind of thing, looking for vector-apply thunks, of the form:
@@ -477,14 +478,8 @@ isUpdatable Updatable = True
mkConLFInfo :: DataCon -> LambdaFormInfo
mkConLFInfo con
- = ASSERT(isDataCon con)
- let
- arity = dataConArity con
- in
- if isTupleCon con then
- LFTuple con (arity == 0)
- else
- LFCon con (arity == 0)
+ = -- the isNullaryDataCon will do this: ASSERT(isDataCon con)
+ (if isTupleCon con then LFTuple else LFCon) con (isNullaryDataCon con)
\end{code}
@@ -865,8 +860,8 @@ data EntryConvention
Int -- Its arity
[MagicId] -- Its register assignments (possibly empty)
-getEntryConvention :: Id -- Function being applied
- -> LambdaFormInfo -- Its info
+getEntryConvention :: Id -- Function being applied
+ -> LambdaFormInfo -- Its info
-> [PrimRep] -- Available arguments
-> FCode EntryConvention
@@ -894,13 +889,14 @@ getEntryConvention id lf_info arg_kinds
-> let itbl = if zero_arity then
mkPhantomInfoTableLabel con
else
- mkInfoTableLabel con
- in StdEntry (mkStdEntryLabel con) (Just itbl)
- -- Should have no args
+ mkConInfoTableLabel con
+ in
+ --false:ASSERT (null arg_kinds) -- Should have no args (meaning what?)
+ StdEntry (mkConEntryLabel con) (Just itbl)
+
LFTuple tup zero_arity
- -> StdEntry (mkStdEntryLabel tup)
- (Just (mkInfoTableLabel tup))
- -- Should have no args
+ -> --false:ASSERT (null arg_kinds) -- Should have no args (meaning what?)
+ StdEntry (mkConEntryLabel tup) (Just (mkConInfoTableLabel tup))
LFThunk _ _ updatable std_form_info
-> if updatable
@@ -1213,17 +1209,19 @@ infoTableLabelFromCI (MkClosureInfo id lf_info rep)
else -} mkInfoTableLabel id
mkConInfoPtr :: Id -> SMRep -> CLabel
-mkConInfoPtr id rep =
- case rep of
- PhantomRep -> mkPhantomInfoTableLabel id
- StaticRep _ _ -> mkStaticInfoTableLabel id
- _ -> mkInfoTableLabel id
+mkConInfoPtr con rep
+ = ASSERT(isDataCon con)
+ case rep of
+ PhantomRep -> mkPhantomInfoTableLabel con
+ StaticRep _ _ -> mkStaticInfoTableLabel con
+ _ -> mkConInfoTableLabel con
mkConEntryPtr :: Id -> SMRep -> CLabel
-mkConEntryPtr id rep =
- case rep of
- StaticRep _ _ -> mkStaticConEntryLabel id
- _ -> mkConEntryLabel id
+mkConEntryPtr con rep
+ = ASSERT(isDataCon con)
+ case rep of
+ StaticRep _ _ -> mkStaticConEntryLabel con
+ _ -> mkConEntryLabel con
closureLabelFromCI (MkClosureInfo id _ _) = mkClosureLabel id
diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs
index 016bd99ec3..590aa9f65e 100644
--- a/ghc/compiler/codeGen/CodeGen.lhs
+++ b/ghc/compiler/codeGen/CodeGen.lhs
@@ -19,7 +19,7 @@ functions drive the mangling of top-level bindings.
module CodeGen ( codeGen ) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import StgSyn
import CgMonad
diff --git a/ghc/compiler/codeGen/SMRep.lhs b/ghc/compiler/codeGen/SMRep.lhs
index 99432c7643..7c46adff06 100644
--- a/ghc/compiler/codeGen/SMRep.lhs
+++ b/ghc/compiler/codeGen/SMRep.lhs
@@ -17,7 +17,7 @@ module SMRep (
isIntLikeRep
) where
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
import Pretty ( ppStr )
import Util ( panic )