summaryrefslogtreecommitdiff
path: root/ghc/compiler/nativeGen/Stix.lhs
blob: 8269dbdb3d8f0ab3c6190c623c513eae7d006ee8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
%
% (c) The AQUA Project, Glasgow University, 1993-1995
%

\begin{code}
#include "HsVersions.h"

module Stix (
	CodeSegment(..), StixReg(..), StixTree(..), StixTreeList(..),
	sStLitLbl,

	stgBaseReg, stgStkOReg, stgNode, stgTagReg, stgRetReg,
	stgSpA, stgSuA, stgSpB, stgSuB, stgHp, stgHpLim, stgLivenessReg,
--	stgActivityReg,
	stgStdUpdRetVecReg, stgStkStubReg,
	getUniqLabelNCG

	-- And for self-sufficiency, by golly...
    ) where

import AbsCSyn	    ( MagicId(..), kindFromMagicId, node, infoptr )
import PrelInfo	    ( showPrimOp, PrimOp
		      IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp)
			  IF_ATTACK_PRAGMAS(COMMA pprPrimOp)
		    )
import CLabel   ( CLabel, mkAsmTempLabel )
import Outputable
import UniqSupply
import Unpretty
import Util
\end{code}

Here is the tag at the nodes of our @StixTree@.	 Notice its
relationship with @PrimOp@ in prelude/PrimOp.

\begin{code}

data StixTree =

	-- Segment (text or data)

	StSegment CodeSegment

	-- We can tag the leaves with constants/immediates.

      | StInt	  Integer      -- ** add Kind at some point
      | StDouble  Rational
      | StString  FAST_STRING
      | StLitLbl  Unpretty	-- literal labels (will be _-prefixed on some machines)
      | StLitLit  FAST_STRING	-- innards from CLitLit
      | StCLbl	  CLabel	-- labels that we might index into

	-- Abstract registers of various kinds

      | StReg StixReg

	-- A typed offset from a base location

      | StIndex PrimRep StixTree StixTree -- kind, base, offset

	-- An indirection from an address to its contents.

      | StInd PrimRep StixTree

	-- Assignment is typed to determine size and register placement

      | StAssign PrimRep StixTree StixTree -- dst, src

	-- A simple assembly label that we might jump to.

      | StLabel CLabel

	-- A function header and footer

      | StFunBegin CLabel
      | StFunEnd CLabel

	-- An unconditional jump. This instruction is terminal.
	-- Dynamic targets are allowed

      | StJump StixTree

    	-- A fall-through, from slow to fast

      | StFallThrough CLabel

	-- A conditional jump.	This instruction can be non-terminal :-)
	-- Only static, local, forward labels are allowed

      | StCondJump CLabel StixTree

	-- Raw data (as in an info table).

      | StData PrimRep	[StixTree]

    	-- Primitive Operations

      | StPrim PrimOp [StixTree]

    	-- Calls to C functions

      | StCall FAST_STRING PrimRep [StixTree]

	-- Comments, of course

      | StComment FAST_STRING	-- For assembly comments

      deriving ()

sStLitLbl :: FAST_STRING -> StixTree
sStLitLbl s = StLitLbl (uppPStr s)
\end{code}

Stix registers can have two forms.  They {\em may} or {\em may not}
map to real, machine level registers.

\begin{code}

data StixReg = StixMagicId MagicId	-- Regs which are part of the abstract machine model

	     | StixTemp Unique PrimRep -- "Regs" which model local variables (CTemps) in
					-- the abstract C.
	     deriving ()

\end{code}

We hope that every machine supports the idea of data segment and text
segment (or that it has no segments at all, and we can lump these together).

\begin{code}

data CodeSegment = DataSegment | TextSegment deriving (Eq)

type StixTreeList = [StixTree] -> [StixTree]

\end{code}

-- Stix Trees for STG registers

\begin{code}

stgBaseReg, stgStkOReg, stgNode, stgTagReg, stgRetReg, stgSpA, stgSuA,
    stgSpB, stgSuB, stgHp, stgHpLim, stgLivenessReg{-, stgActivityReg-}, stgStdUpdRetVecReg,
    stgStkStubReg :: StixTree

stgBaseReg = StReg (StixMagicId BaseReg)
stgStkOReg = StReg (StixMagicId StkOReg)
stgNode = StReg (StixMagicId node)
stgInfoPtr = StReg (StixMagicId infoptr)
stgTagReg = StReg (StixMagicId TagReg)
stgRetReg = StReg (StixMagicId RetReg)
stgSpA = StReg (StixMagicId SpA)
stgSuA = StReg (StixMagicId SuA)
stgSpB = StReg (StixMagicId SpB)
stgSuB = StReg (StixMagicId SuB)
stgHp = StReg (StixMagicId Hp)
stgHpLim = StReg (StixMagicId HpLim)
stgLivenessReg = StReg (StixMagicId LivenessReg)
--stgActivityReg = StReg (StixMagicId ActivityReg)
stgStdUpdRetVecReg = StReg (StixMagicId StdUpdRetVecReg)
stgStkStubReg = StReg (StixMagicId StkStubReg)

getUniqLabelNCG :: UniqSM CLabel
getUniqLabelNCG =
      getUnique	      `thenUs` \ u ->
      returnUs (mkAsmTempLabel u)

\end{code}