Skip to content

Commit

Permalink
Start separating out the RTS and Haskell imports of MachRegs.h
Browse files Browse the repository at this point in the history
No functional differences yet
  • Loading branch information
Ian Lynagh committed Aug 6, 2012
1 parent 6997bb5 commit 8e7fb28
Show file tree
Hide file tree
Showing 13 changed files with 128 additions and 51 deletions.
2 changes: 1 addition & 1 deletion compiler/codeGen/CgUtils.hs
Expand Up @@ -45,7 +45,7 @@ module CgUtils (
) where

#include "HsVersions.h"
#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"

import BlockId
import CgMonad
Expand Down
2 changes: 1 addition & 1 deletion compiler/codeGen/StgCmmUtils.hs
Expand Up @@ -50,7 +50,7 @@ module StgCmmUtils (
) where

#include "HsVersions.h"
#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"

import StgCmmMonad
import StgCmmClosure
Expand Down
2 changes: 1 addition & 1 deletion compiler/nativeGen/PPC/Regs.hs
Expand Up @@ -55,7 +55,7 @@ where

#include "nativeGen/NCG.h"
#include "HsVersions.h"
#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"

import Reg
import RegClass
Expand Down
2 changes: 1 addition & 1 deletion compiler/nativeGen/RegAlloc/Linear/Main.hs
Expand Up @@ -130,7 +130,7 @@ import Data.Maybe
import Data.List
import Control.Monad

#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"


-- -----------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion compiler/nativeGen/SPARC/RegPlate.hs
Expand Up @@ -100,7 +100,7 @@ import FastBool
#define f31 63


#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"

-- | Check whether a machine register is free for allocation.
freeReg :: RegNo -> FastBool
Expand Down
2 changes: 1 addition & 1 deletion compiler/nativeGen/X86/Regs.hs
Expand Up @@ -51,7 +51,7 @@ where
#include "nativeGen/NCG.h"
#include "HsVersions.h"

#include "../includes/stg/MachRegs.h"
#include "../includes/stg/HaskellMachRegs.h"

import Reg
import RegClass
Expand Down
2 changes: 1 addition & 1 deletion includes/Cmm.h
Expand Up @@ -346,7 +346,7 @@
* Need MachRegs, because some of the RTS code is conditionally
* compiled based on REG_R1, REG_R2, etc.
*/
#include "stg/MachRegs.h"
#include "stg/RtsMachRegs.h"

#include "rts/storage/Liveness.h"
#include "rts/prof/LDV.h"
Expand Down
3 changes: 2 additions & 1 deletion includes/HaskellConstants.hs
Expand Up @@ -16,7 +16,8 @@ settings for the target plat instead).
-}
#include "../includes/ghcautoconf.h"

#include "stg/MachRegs.h"
#include "stg/HaskellMachRegs.h"

#include "rts/Constants.h"
#include "MachDeps.h"
#include "../includes/dist-derivedconstants/header/DerivedConstants.h"
Expand Down
2 changes: 1 addition & 1 deletion includes/Stg.h
Expand Up @@ -229,7 +229,7 @@ typedef StgFunPtr F_;
-------------------------------------------------------------------------- */

#include "stg/DLL.h"
#include "stg/MachRegs.h"
#include "stg/RtsMachRegs.h"
#include "stg/Regs.h"
#include "stg/Ticky.h"

Expand Down
47 changes: 47 additions & 0 deletions includes/stg/HaskellMachRegs.h
@@ -0,0 +1,47 @@
/* -----------------------------------------------------------------------------
*
* (c) The GHC Team, 1998-2011
*
* Registers used in STG code. Might or might not correspond to
* actual machine registers.
*
* Do not #include this file directly: #include "Rts.h" instead.
*
* To understand the structure of the RTS headers, see the wiki:
* http://hackage.haskell.org/trac/ghc/wiki/Commentary/SourceTree/Includes
*
* ---------------------------------------------------------------------------*/

#ifndef HASKELLMACHREGS_H
#define HASKELLMACHREGS_H

/*
* Defining NO_REGS causes no global registers to be used. NO_REGS is
* typically defined by GHC, via a command-line option passed to gcc,
* when the -funregisterised flag is given.
*
* NB. When NO_REGS is on, calling & return conventions may be
* different. For example, all function arguments will be passed on
* the stack, and components of an unboxed tuple will be returned on
* the stack rather than in registers.
*/
#ifdef NO_REGS

#define MACHREGS_NO_REGS 1

#else

#define MACHREGS_NO_REGS 0

#define MACHREGS_i386 i386_TARGET_ARCH
#define MACHREGS_x86_64 x86_64_TARGET_ARCH
#define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH)
#define MACHREGS_sparc sparc_TARGET_ARCH
#define MACHREGS_arm arm_TARGET_ARCH
#define MACHREGS_darwin darwin_TARGET_OS

#endif

#include "stg/MachRegs.h"

#endif /* HASKELLMACHREGS_H */
64 changes: 23 additions & 41 deletions includes/stg/MachRegs.h
Expand Up @@ -20,38 +20,21 @@
*/

/*
* Defining NO_REGS causes no global registers to be used. NO_REGS is
* Defining MACHREGS_NO_REGS to 1 causes no global registers to be used.
* MACHREGS_NO_REGS is typically controlled by NO_REGS, which is
* typically defined by GHC, via a command-line option passed to gcc,
* when the -funregisterised flag is given.
*
* NB. When NO_REGS is on, calling & return conventions may be
* NB. When MACHREGS_NO_REGS to 1, calling & return conventions may be
* different. For example, all function arguments will be passed on
* the stack, and components of an unboxed tuple will be returned on
* the stack rather than in registers.
*/
#ifndef NO_REGS
#if MACHREGS_NO_REGS == 1

/* NOTE: when testing the platform in this file we must test either
* *_HOST_ARCH and *_TARGET_ARCH, depending on whether COMPILING_GHC
* is set. This is because when we're compiling the RTS and HC code,
* the platform we're running on is the HOST, but when compiling GHC
* we want to know about the register mapping on the TARGET platform.
*/
#ifdef COMPILING_GHC
#define i386_REGS i386_TARGET_ARCH
#define x86_64_REGS x86_64_TARGET_ARCH
#define powerpc_REGS (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH)
#define sparc_REGS sparc_TARGET_ARCH
#define arm_REGS arm_TARGET_ARCH
#define darwin_REGS darwin_TARGET_OS
#else
#define i386_REGS i386_HOST_ARCH
#define x86_64_REGS x86_64_HOST_ARCH
#define powerpc_REGS (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH)
#define sparc_REGS sparc_HOST_ARCH
#define arm_REGS arm_HOST_ARCH
#define darwin_REGS darwin_HOST_OS
#endif
/* Nothing */

#elif MACHREGS_NO_REGS == 0

/* ----------------------------------------------------------------------------
Caller saves and callee-saves regs.
Expand Down Expand Up @@ -84,7 +67,7 @@
Leaving SpLim out of the picture.
-------------------------------------------------------------------------- */

#if i386_REGS
#if MACHREGS_i386

#define REG(x) __asm__("%" #x)

Expand All @@ -110,8 +93,6 @@
#define MAX_REAL_DOUBLE_REG 0
#define MAX_REAL_LONG_REG 0

#endif /* iX86 */

/* -----------------------------------------------------------------------------
The x86-64 register mapping
Expand Down Expand Up @@ -141,7 +122,7 @@
--------------------------------------------------------------------------- */

#if x86_64_REGS
#elif MACHREGS_x86_64

#define REG(x) __asm__("%" #x)

Expand Down Expand Up @@ -186,8 +167,6 @@
#define MAX_REAL_DOUBLE_REG 2
#define MAX_REAL_LONG_REG 0

#endif /* x86_64 */

/* -----------------------------------------------------------------------------
The PowerPC register mapping
Expand Down Expand Up @@ -218,7 +197,7 @@
We can do the Whole Business with callee-save registers only!
-------------------------------------------------------------------------- */

#if powerpc_REGS
#elif MACHREGS_powerpc

#define REG(x) __asm__(#x)

Expand All @@ -231,7 +210,7 @@
#define REG_R7 r20
#define REG_R8 r21

#if darwin_REGS
#if MACHREGS_darwin

#define REG_F1 f14
#define REG_F2 f15
Expand Down Expand Up @@ -260,8 +239,6 @@

#define REG_Base r27

#endif /* powerpc */

/* -----------------------------------------------------------------------------
The Sun SPARC register mapping
Expand Down Expand Up @@ -353,7 +330,7 @@
-------------------------------------------------------------------------- */

#if sparc_REGS
#elif MACHREGS_sparc

#define REG(x) __asm__("%" #x)

Expand Down Expand Up @@ -396,8 +373,6 @@

#define NCG_FirstFloatReg f22

#endif /* sparc */

/* -----------------------------------------------------------------------------
The ARM EABI register mapping
Expand Down Expand Up @@ -433,8 +408,7 @@
d16-d31/q8-q15 Argument / result/ scratch registers
----------------------------------------------------------------------------- */


#if arm_REGS
#elif MACHREGS_arm

#define REG(x) __asm__(#x)

Expand All @@ -459,9 +433,17 @@
#define REG_D2 d11
#endif

#endif /* arm */
#else

#error Cannot find platform to give register info for

#endif

#endif /* NO_REGS */
#else

#error Bad MACHREGS_NO_REGS value

#endif

/* -----------------------------------------------------------------------------
* These constants define how many stg registers will be used for
Expand Down
47 changes: 47 additions & 0 deletions includes/stg/RtsMachRegs.h
@@ -0,0 +1,47 @@
/* -----------------------------------------------------------------------------
*
* (c) The GHC Team, 1998-2011
*
* Registers used in STG code. Might or might not correspond to
* actual machine registers.
*
* Do not #include this file directly: #include "Rts.h" instead.
*
* To understand the structure of the RTS headers, see the wiki:
* http://hackage.haskell.org/trac/ghc/wiki/Commentary/SourceTree/Includes
*
* ---------------------------------------------------------------------------*/

#ifndef RTSMACHREGS_H
#define RTSMACHREGS_H

/*
* Defining NO_REGS causes no global registers to be used. NO_REGS is
* typically defined by GHC, via a command-line option passed to gcc,
* when the -funregisterised flag is given.
*
* NB. When NO_REGS is on, calling & return conventions may be
* different. For example, all function arguments will be passed on
* the stack, and components of an unboxed tuple will be returned on
* the stack rather than in registers.
*/
#ifdef NO_REGS

#define MACHREGS_NO_REGS 1

#else

#define MACHREGS_NO_REGS 0

#define MACHREGS_i386 i386_HOST_ARCH
#define MACHREGS_x86_64 x86_64_HOST_ARCH
#define MACHREGS_powerpc (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH)
#define MACHREGS_sparc sparc_HOST_ARCH
#define MACHREGS_arm arm_HOST_ARCH
#define MACHREGS_darwin darwin_HOST_OS

#endif

#include "stg/MachRegs.h"

#endif /* RTSMACHREGS_H */
2 changes: 1 addition & 1 deletion utils/genapply/GenApply.hs
Expand Up @@ -8,7 +8,7 @@
module Main(main) where

#include "../../includes/ghcconfig.h"
#include "../../includes/stg/MachRegs.h"
#include "../../includes/stg/RtsMachRegs.h"
#include "../../includes/rts/Constants.h"

-- Needed for TAG_BITS
Expand Down

0 comments on commit 8e7fb28

Please sign in to comment.