Skip to content
Snippets Groups Projects
Commit 75a5dd8e authored by John Ericson's avatar John Ericson Committed by Marge Bot
Browse files

Remove {Build,Host}Platform_NAME from header

They are only used in a file we construct directly, so just skip CPP.
parent 05419e55
No related branches found
No related tags found
No related merge requests found
......@@ -29,9 +29,14 @@ compiler_stage1_C_FILES_NODEPS = compiler/parser/cutils.c
# we just skip the check.
compiler_NO_CHECK = YES
# We need to decrement the 1-indexed compiler stage to be the 0-indexed stage
# we use everwhere else.
dec1 = 0
dec2 = 1
dec3 = 2
# TODO(@Ericson2314) Get rid of compiler-specific stage indices. I think the
# argument was stage n ghc is used to build stage n everything else, but I
# don't buy that argument.
ifneq "$(BINDIST)" "YES"
......@@ -48,40 +53,53 @@ $(foreach n,1 2 3, \
)
endif
compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/.
$(call removeFiles,$@)
@echo 'Creating $@ ... '
@echo '{-# LANGUAGE CPP #-}' >> $@
@echo 'module Config' >> $@
@echo ' ( module GHC.Version' >> $@
@echo ' , cBuildPlatformString' >> $@
@echo ' , cHostPlatformString' >> $@
@echo ' , cProjectName' >> $@
@echo ' , cBooterVersion' >> $@
@echo ' , cStage' >> $@
@echo ' ) where' >> $@
@echo >> $@
@echo 'import GhcPrelude' >> $@
@echo >> $@
@echo 'import GHC.Version' >> $@
@echo >> $@
@echo '#include "ghcplatform.h"' >> $@
@echo >> $@
@echo 'cBuildPlatformString :: String' >> $@
@echo 'cBuildPlatformString = BuildPlatform_NAME' >> $@
@echo >> $@
@echo 'cHostPlatformString :: String' >> $@
@echo 'cHostPlatformString = HostPlatform_NAME' >> $@
@echo >> $@
@echo 'cProjectName :: String' >> $@
@echo 'cProjectName = "$(ProjectName)"' >> $@
@echo >> $@
@echo 'cBooterVersion :: String' >> $@
@echo 'cBooterVersion = "$(GhcVersion)"' >> $@
@echo >> $@
@echo 'cStage :: String' >> $@
@echo 'cStage = show (STAGE :: Int)' >> $@
BUILDPLATFORM_1 = $(BUILDPLATFORM)
BUILDPLATFORM_2 = $(HOSTPLATFORM)
BUILDPLATFORM_3 = $(TARGETPLATFORM)
HOSTPLATFORM_1 = $(HOSTPLATFORM)
HOSTPLATFORM_2 = $(TARGETPLATFORM)
HOSTPLATFORM_3 = $(TARGETPLATFORM)
define compilerConfig
# $1 = compile stage (1-indexed)
compiler/stage$1/build/Config.hs : mk/config.mk mk/project.mk | $$$$(dir $$$$@)/.
$$(call removeFiles,$$@)
@echo 'Creating $$@ ... '
@echo '{-# LANGUAGE CPP #-}' >> $$@
@echo 'module Config' >> $$@
@echo ' ( module GHC.Version' >> $$@
@echo ' , cBuildPlatformString' >> $$@
@echo ' , cHostPlatformString' >> $$@
@echo ' , cProjectName' >> $$@
@echo ' , cBooterVersion' >> $$@
@echo ' , cStage' >> $$@
@echo ' ) where' >> $$@
@echo >> $$@
@echo 'import GhcPrelude' >> $$@
@echo >> $$@
@echo 'import GHC.Version' >> $$@
@echo >> $$@
@echo 'cBuildPlatformString :: String' >> $$@
@echo 'cBuildPlatformString = "$(BUILDPLATFORM_$1)"' >> $$@
@echo >> $$@
@echo 'cHostPlatformString :: String' >> $$@
@echo 'cHostPlatformString = "$(HOSTPLATFORM_$1)"' >> $$@
@echo >> $$@
@echo 'cProjectName :: String' >> $$@
@echo 'cProjectName = "$(ProjectName)"' >> $$@
@echo >> $$@
@echo 'cBooterVersion :: String' >> $$@
@echo 'cBooterVersion = "$(GhcVersion)"' >> $$@
@echo >> $$@
@echo 'cStage :: String' >> $$@
@echo 'cStage = show (STAGE :: Int)' >> $$@
@echo done.
endef
$(eval $(call compilerConfig,0))
$(eval $(call compilerConfig,1))
$(eval $(call compilerConfig,2))
# ----------------------------------------------------------------------------
# Generate supporting stuff for prelude/PrimOp.hs
......
......@@ -238,9 +238,6 @@ generateGhcPlatformH = do
[ "#if !defined(__GHCPLATFORM_H__)"
, "#define __GHCPLATFORM_H__"
, ""
, "#define BuildPlatform_NAME " ++ show buildPlatform
, "#define HostPlatform_NAME " ++ show hostPlatform
, ""
, "#define BuildPlatform_TYPE " ++ cppify buildPlatform
, "#define HostPlatform_TYPE " ++ cppify hostPlatform
, ""
......@@ -336,6 +333,10 @@ generateSettings = do
-- | Generate @Config.hs@ files.
generateConfigHs :: Expr String
generateConfigHs = do
stage <- getStage
let chooseSetting x y = getSetting $ if stage == Stage0 then x else y
buildPlatform <- chooseSetting BuildPlatform HostPlatform
hostPlatform <- chooseSetting HostPlatform TargetPlatform
trackGenerateHs
cProjectName <- getSetting ProjectName
cBooterVersion <- getSetting GhcVersion
......@@ -354,13 +355,11 @@ generateConfigHs = do
, ""
, "import GHC.Version"
, ""
, "#include \"ghcplatform.h\""
, ""
, "cBuildPlatformString :: String"
, "cBuildPlatformString = BuildPlatform_NAME"
, "cBuildPlatformString = " ++ show buildPlatform
, ""
, "cHostPlatformString :: String"
, "cHostPlatformString = HostPlatform_NAME"
, "cHostPlatformString = " ++ show hostPlatform
, ""
, "cProjectName :: String"
, "cProjectName = " ++ show cProjectName
......
......@@ -139,14 +139,6 @@ endef
$(eval $(call includesHeaderConfig,0))
$(eval $(call includesHeaderConfig,1))
BUILDPLATFORM_0 = $(BUILDPLATFORM)
BUILDPLATFORM_1 = $(HOSTPLATFORM)
BUILDPLATFORM_2 = $(TARGETPLATFORM)
HOSTPLATFORM_0 = $(HOSTPLATFORM)
HOSTPLATFORM_1 = $(TARGETPLATFORM)
HOSTPLATFORM_2 = $(TARGETPLATFORM)
BuildPlatform_0_CPP = $(BuildPlatform_CPP)
BuildPlatform_1_CPP = $(HostPlatform_CPP)
BuildPlatform_2_CPP = $(TargetPlatform_CPP)
......@@ -187,9 +179,6 @@ $$(includes_$1_H_PLATFORM) : includes/ghc.mk includes/Makefile | $$$$(dir $$$$@)
@echo "#if !defined(__GHCPLATFORM_H__)" > $$@
@echo "#define __GHCPLATFORM_H__" >> $$@
@echo >> $$@
@echo "#define BuildPlatform_NAME \"$(BUILDPLATFORM_$1)\"" >> $$@
@echo "#define HostPlatform_NAME \"$(HOSTPLATFORM_$1)\"" >> $$@
@echo >> $$@
@echo "#define BuildPlatform_TYPE $(BuildPlatform_$1_CPP)" >> $$@
@echo "#define HostPlatform_TYPE $(HostPlatform_$1_CPP)" >> $$@
@echo >> $$@
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment