Skip to content

Commit

Permalink
Rejig TABLES_NEXT_TO_CODE: the -unreg flag was broken by earlier changes
Browse files Browse the repository at this point in the history
A GHC binary can generally build either registerised or unregisterised
code, unless it is unregisterised only.  

The previous changes broke this, but I think I've now restored it.
  • Loading branch information
Simon Marlow committed Oct 17, 2006
1 parent f1842ca commit 80564dd
Show file tree
Hide file tree
Showing 9 changed files with 55 additions and 63 deletions.
11 changes: 7 additions & 4 deletions compiler/Makefile
Expand Up @@ -217,6 +217,7 @@ $(CONFIG_HS) : $(FPTOOLS_TOP)/mk/config.mk Makefile
@echo "cHscIfaceFileVersion = \"$(HscIfaceFileVersion)\"" >> $(CONFIG_HS)
@echo "cGhcWithNativeCodeGen = \"$(GhcWithNativeCodeGen)\"" >> $(CONFIG_HS)
@echo "cGhcUnregisterised = \"$(GhcUnregisterised)\"" >> $(CONFIG_HS)
@echo "cGhcEnableTablesNextToCode = \"$(GhcEnableTablesNextToCode)\"" >> $(CONFIG_HS)
@echo "cLeadingUnderscore = \"$(LeadingUnderscore)\"" >> $(CONFIG_HS)
@echo "cRAWCPP_FLAGS = \"$(RAWCPP_FLAGS)\"" >> $(CONFIG_HS)
@echo "cGCC = \"$(WhatGccIsCalled)\"" >> $(CONFIG_HS)
Expand Down Expand Up @@ -346,10 +347,6 @@ endif
@echo "#define HOST_VENDOR \"$(TargetVendor_CPP)\"" >> $@
@echo "#define TARGET_VENDOR \"$(TargetVendor_CPP)\"" >> $@
@echo >> $@
ifeq "$(GhcWithTablesNextToCode)" "YES"
@echo "#define TABLES_NEXT_TO_CODE 1" >> $@
endif
@echo >> $@
@echo "#endif /* __PLATFORM_H__ */" >> $@
@echo "Done."

Expand Down Expand Up @@ -420,6 +417,12 @@ SRC_HC_OPTS += -DGHCI -package template-haskell
# SRC_HC_OPTS += -DGHCI -DBREAKPOINT -package template-haskell
PKG_DEPENDS += template-haskell

# Should GHCI be building info tables in the TABLES_NEXT_TO_CODE style
# or not?
ifeq "$(GhcEnableTablesNextToCode) $(GhcUnregisterised)" "YES NO"
SRC_HC_OPTS += -DGHCI_TABLES_NEXT_TO_CODE
endif

# Use threaded RTS with GHCi, so threads don't get blocked at the prompt.
SRC_HC_OPTS += -threaded

Expand Down
1 change: 1 addition & 0 deletions compiler/cmm/CmmOpt.hs
Expand Up @@ -19,6 +19,7 @@ import CmmUtils
import CLabel
import MachOp
import SMRep
import StaticFlags

import UniqFM
import Unique
Expand Down
13 changes: 7 additions & 6 deletions compiler/codeGen/CgInfoTbls.hs
Expand Up @@ -202,18 +202,19 @@ retVec :: CmmExpr -> CmmExpr -> CmmExpr
-- Get a return vector from the info pointer
retVec info_amode zero_indexed_tag
= let slot = vectorSlot info_amode zero_indexed_tag
#if defined(x86_64_TARGET_ARCH) && defined(TABLES_NEXT_TO_CODE)
tableEntry = CmmMachOp (MO_S_Conv I32 I64) [CmmLoad slot I32]
table_slot = CmmLoad slot wordRep
#if defined(x86_64_TARGET_ARCH)
offset_slot = CmmMachOp (MO_S_Conv I32 I64) [CmmLoad slot I32]
-- offsets are 32-bits on x86-64, due to the inability of
-- the tools to handle 64-bit PC-relative relocations. See also
-- PprMach.pprDataItem, and InfoTables.h:OFFSET_FIELD().
#else
tableEntry = CmmLoad slot wordRep
offset_slot = table_slot
#endif
in if tablesNextToCode
then CmmMachOp (MO_Add wordRep) [tableEntry, info_amode]
else tableEntry
then CmmMachOp (MO_Add wordRep) [offset_slot, info_amode]
else table_slot

emitReturnTarget
:: Name
-> CgStmts -- The direct-return code (if any)
Expand Down
11 changes: 0 additions & 11 deletions compiler/codeGen/SMRep.lhs
Expand Up @@ -31,7 +31,6 @@ module SMRep (
isStaticRep,
fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
profHdrSize, thunkHdrSize,
tablesNextToCode,
smRepClosureType, smRepClosureTypeInt,
rET_SMALL, rET_VEC_SMALL, rET_BIG, rET_VEC_BIG
Expand Down Expand Up @@ -294,16 +293,6 @@ thunkHdrSize = fixedHdrSize + smp_hdr
where smp_hdr = sIZEOF_StgSMPThunkHeader `quot` wORD_SIZE
\end{code}

\begin{code}
-- IA64 mangler doesn't place tables next to code
tablesNextToCode :: Bool
#if defined(ia64_TARGET_ARCH) || defined(powerpc64_TARGET_ARCH)
tablesNextToCode = False
#else
tablesNextToCode = not opt_Unregisterised
#endif
\end{code}

\begin{code}
isStaticRep :: SMRep -> Bool
isStaticRep (GenericRep is_static _ _ _) = is_static
Expand Down
26 changes: 13 additions & 13 deletions compiler/ghci/ByteCodeItbls.lhs
Expand Up @@ -92,14 +92,14 @@ make_constr_itbls cons
| ptrs + nptrs >= mIN_PAYLOAD_SIZE = nptrs
| otherwise = mIN_PAYLOAD_SIZE - ptrs
itbl = StgInfoTable {
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
entry = entry_addr,
#endif
ptrs = fromIntegral ptrs,
nptrs = fromIntegral nptrs_really,
tipe = fromIntegral cONSTR,
srtlen = fromIntegral conNo
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
, code = code
#endif
}
Expand All @@ -113,7 +113,7 @@ make_constr_itbls cons
--putStrLn ("# nptrs of itbl is " ++ show nptrs_really)
poke addr itbl
return (getName dcon, addr
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
`plusPtr` (2 * wORD_SIZE)
#endif
)
Expand Down Expand Up @@ -279,14 +279,14 @@ type HalfWord = Word16
#endif
data StgInfoTable = StgInfoTable {
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
entry :: Ptr (),
#endif
ptrs :: HalfWord,
nptrs :: HalfWord,
tipe :: HalfWord,
srtlen :: HalfWord
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
, code :: [ItblCode]
#endif
}
Expand All @@ -296,14 +296,14 @@ instance Storable StgInfoTable where
sizeOf itbl
= sum
[
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
fieldSz entry itbl,
#endif
fieldSz ptrs itbl,
fieldSz nptrs itbl,
fieldSz tipe itbl,
fieldSz srtlen itbl
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
,fieldSz (head.code) itbl * itblCodeLength
#endif
]
Expand All @@ -314,40 +314,40 @@ instance Storable StgInfoTable where
poke a0 itbl
= runState (castPtr a0)
$ do
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
store (entry itbl)
#endif
store (ptrs itbl)
store (nptrs itbl)
store (tipe itbl)
store (srtlen itbl)
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
sequence_ (map store (code itbl))
#endif
peek a0
= runState (castPtr a0)
$ do
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
entry <- load
#endif
ptrs <- load
nptrs <- load
tipe <- load
srtlen <- load
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
code <- sequence (replicate itblCodeLength load)
#endif
return
StgInfoTable {
#ifndef TABLES_NEXT_TO_CODE
#ifndef GHCI_TABLES_NEXT_TO_CODE
entry = entry,
#endif
ptrs = ptrs,
nptrs = nptrs,
tipe = tipe,
srtlen = srtlen
#ifdef TABLES_NEXT_TO_CODE
#ifdef GHCI_TABLES_NEXT_TO_CODE
,code = code
#endif
}
Expand Down
19 changes: 16 additions & 3 deletions compiler/main/StaticFlags.hs
Expand Up @@ -64,13 +64,13 @@ module StaticFlags (
opt_EmitExternalCore,
opt_PIC,
v_Ld_inputs,
tablesNextToCode
) where

#include "HsVersions.h"

import CmdLineParser
import Config ( cProjectVersionInt, cProjectPatchLevel,
cGhcUnregisterised )
import Config
import FastString ( FastString, mkFastString )
import Util
import Maybes ( firstJust )
Expand Down Expand Up @@ -99,7 +99,12 @@ parseStaticFlags args = do
let unreg_flags | cGhcUnregisterised == "YES" = unregFlags
| otherwise = []

(more_leftover, errs) <- processArgs static_flags (unreg_flags ++ way_flags)
-- TABLES_NEXT_TO_CODE affects the info table layout.
let cg_flags | tablesNextToCode = ["-optc-DTABLES_NEXT_TO_CODE"]
| otherwise = []

(more_leftover, errs) <- processArgs static_flags
(unreg_flags ++ cg_flags ++ way_flags)
when (not (null errs)) $ ghcError (UsageError (unlines errs))
return (more_leftover++leftover)

Expand Down Expand Up @@ -284,6 +289,14 @@ opt_UF_DearOp = ( 4 :: Int)

opt_Static = lookUp FSLIT("-static")
opt_Unregisterised = lookUp FSLIT("-funregisterised")

-- Derived, not a real option. Determines whether we will be compiling
-- info tables that reside just before the entry code, or with an
-- indirection to the entry code. See TABLES_NEXT_TO_CODE in
-- includes/InfoTables.h.
tablesNextToCode = not opt_Unregisterised
&& cGhcEnableTablesNextToCode == "YES"

opt_EmitExternalCore = lookUp FSLIT("-fext-core")

-- Include full span info in error messages, instead of just the start position.
Expand Down
10 changes: 3 additions & 7 deletions includes/Makefile
Expand Up @@ -11,15 +11,11 @@ H_FILES = $(filter-out gmp.h,$(wildcard *.h)) gmp.h
#
# Options
#
ifeq "$(GhcWithNoRegs)" "YES"
SRC_CC_OPTS += -DNO_REGS
ifeq "$(GhcUnregisterised)" "YES"
SRC_CC_OPTS += -DNO_REGS -DUSE_MINIINTERPRETER
endif

ifeq "$(GhcWithMiniInterpreter)" "YES"
SRC_CC_OPTS += -DUSE_MINIINTERPRETER
endif

ifeq "$(GhcWithTablesNextToCode)" "YES"
ifeq "$(GhcEnableTablesNextToCode) $(GhcUnregisterised)" "YES NO"
SRC_CC_OPTS += -DTABLES_NEXT_TO_CODE
endif

Expand Down
22 changes: 8 additions & 14 deletions mk/config.mk.in
Expand Up @@ -277,21 +277,15 @@ else
GhcWithInterpreter=NO
endif

# GhcWithTablesNextToCode, which corresponds to the TABLES_NEXT_TO_CODE
# CPP symbol, says whether to assume that info tables are assumed to
# reside just before the code for a function.
ifeq "$(GhcUnregisterised)" "YES"
GhcWithTablesNextToCode=NO
GhcWithNoRegs=YES
GhcWithMiniInterpreter=YES
else
ifeq "$(findstring $(HostArch_CPP), ia64 powerpc64)" ""
GhcWithTablesNextToCode=YES
# GhcEnableTablesNextToCode tells us whether the target architecture
# supports placing info tables directly before the entry code
# (see TABLES_NEXT_TO_CODE in the RTS). Whether we actually compile for
# TABLES_NEXT_TO_CODE depends on whether we're building unregisterised
# code or not, which may be decided by options to the compiler later.
ifneq "$(findstring $(TargetArch_CPP), ia64 powerpc64)" ""
GhcEnableTablesNextToCode=NO
else
GhcWithTablesNextToCode=NO
endif
GhcWithNoRegs=NO
GhcWithMiniInterpreter=NO
GhcEnableTablesNextToCode=YES
endif

#
Expand Down
5 changes: 0 additions & 5 deletions rts/Makefile
Expand Up @@ -124,11 +124,6 @@ SRC_CC_OPTS += -DNOSMP
SRC_HC_OPTS += -optc-DNOSMP
endif

ifeq "$(GhcWithTablesNextToCode)" "YES"
SRC_CC_OPTS += -DTABLES_NEXT_TO_CODE
SRC_HC_OPTS += -optc-DTABLES_NEXT_TO_CODE
endif

ifneq "$(DLLized)" "YES"
SRC_HC_OPTS += -static
endif
Expand Down

0 comments on commit 80564dd

Please sign in to comment.