Skip to content

Commit

Permalink
Define cTargetArch and start to use it rather than ifdefs
Browse files Browse the repository at this point in the history
Using Haskell conditionals means the compiler sees all the code, so
there should be less rot of code specific to uncommon arches. Code
for other platforms should still be optimised away, although if we want
to support targetting other arches then we'll need to compile it
for-real anyway.
  • Loading branch information
igfoo committed Jan 4, 2011
1 parent daee732 commit f0e3d79
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 14 deletions.
38 changes: 38 additions & 0 deletions compiler/ghc.mk
Expand Up @@ -49,6 +49,8 @@ compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/.
@echo '{-# LANGUAGE CPP #-}' >> $@
@echo 'module Config where' >> $@
@echo >> $@
@echo 'import Distribution.System' >> $@
@echo >> $@
@echo '#include "ghc_boot_platform.h"' >> $@
@echo >> $@
@echo 'cBuildPlatformString :: String' >> $@
Expand All @@ -58,6 +60,42 @@ compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/.
@echo 'cTargetPlatformString :: String' >> $@
@echo 'cTargetPlatformString = TargetPlatform_NAME' >> $@
@echo >> $@
# Sync this with checkArch in configure.ac
@echo 'cTargetArch :: Arch' >> $@
@echo '#if i386_TARGET_ARCH' >> $@
@echo 'cTargetArch = I386' >> $@
@echo '#elif x86_64_TARGET_ARCH' >> $@
@echo 'cTargetArch = X86_64' >> $@
@echo '#elif powerpc_TARGET_ARCH' >> $@
@echo 'cTargetArch = PPC' >> $@
@echo '#elif powerpc64_TARGET_ARCH' >> $@
@echo 'cTargetArch = PPC64' >> $@
@echo '#elif sparc_TARGET_ARCH || sparc64_TARGET_ARCH' >> $@
@echo 'cTargetArch = Sparc' >> $@
@echo '#elif arm_TARGET_ARCH' >> $@
@echo 'cTargetArch = Arm' >> $@
@echo '#elif mips_TARGET_ARCH || mipseb_TARGET_ARCH || mipsel_TARGET_ARCH' >> $@
@echo 'cTargetArch = Mips' >> $@
@echo '#elif 0' >> $@
@echo 'cTargetArch = SH' >> $@
@echo '#elif ia64_TARGET_ARCH' >> $@
@echo 'cTargetArch = IA64' >> $@
@echo '#elif s390_TARGET_ARCH' >> $@
@echo 'cTargetArch = S390' >> $@
@echo '#elif alpha_TARGET_ARCH' >> $@
@echo 'cTargetArch = Alpha' >> $@
@echo '#elif hppa_TARGET_ARCH || hppa1_1_TARGET_ARCH' >> $@
@echo 'cTargetArch = Hppa' >> $@
@echo '#elif rs6000_TARGET_ARCH' >> $@
@echo 'cTargetArch = Rs6000' >> $@
@echo '#elif m68k_TARGET_ARCH' >> $@
@echo 'cTargetArch = M68k' >> $@
@echo '#elif vax_TARGET_ARCH' >> $@
@echo 'cTargetArch = Vax' >> $@
@echo '#else' >> $@
@echo '#error Unknown target arch' >> $@
@echo '#endif' >> $@
@echo >> $@
@echo 'cProjectName :: String' >> $@
@echo 'cProjectName = "$(ProjectName)"' >> $@
@echo 'cProjectVersion :: String' >> $@
Expand Down
23 changes: 9 additions & 14 deletions compiler/nativeGen/AsmCodeGen.lhs
Expand Up @@ -72,13 +72,9 @@ import UniqFM
import Unique ( Unique, getUnique )
import UniqSupply
import DynFlags
#if powerpc_TARGET_ARCH
import StaticFlags ( opt_Static, opt_PIC )
#endif
import StaticFlags
import Util
#if !defined(darwin_TARGET_OS)
import Config ( cProjectVersion )
#endif
import Config
import Digraph
import qualified Pretty
Expand All @@ -96,6 +92,7 @@ import Data.List
import Data.Maybe
import Control.Monad
import System.IO
import Distribution.System
{-
The native-code generator has machine-independent and
Expand Down Expand Up @@ -836,23 +833,21 @@ cmmExprConFold referenceKind expr
(CmmLit $ CmmInt (fromIntegral off) wordWidth)
]
#if powerpc_TARGET_ARCH
-- On powerpc (non-PIC), it's easier to jump directly to a label than
-- to use the register table, so we replace these registers
-- with the corresponding labels:
-- On powerpc (non-PIC), it's easier to jump directly to a label than
-- to use the register table, so we replace these registers
-- with the corresponding labels:
CmmReg (CmmGlobal EagerBlackholeInfo)
| not opt_PIC
| cTargetArch == PPC && not opt_PIC
-> cmmExprConFold referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_EAGER_BLACKHOLE_info")))
CmmReg (CmmGlobal GCEnter1)
| not opt_PIC
| cTargetArch == PPC && not opt_PIC
-> cmmExprConFold referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_enter_1")))
CmmReg (CmmGlobal GCFun)
| not opt_PIC
| cTargetArch == PPC && not opt_PIC
-> cmmExprConFold referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_fun")))
#endif
other
-> return other
Expand Down
1 change: 1 addition & 0 deletions configure.ac
Expand Up @@ -282,6 +282,7 @@ x86_64-apple-darwin)
;;
esac

# Sync this with cTargetArch in compiler/ghc.mk
checkArch() {
case $1 in
alpha|arm|hppa|hppa1_1|i386|ia64|m68k|mips|mipseb|mipsel|powerpc|powerpc64|rs6000|s390|sparc|sparc64|vax|x86_64)
Expand Down

0 comments on commit f0e3d79

Please sign in to comment.