[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / nativeGen / SparcDesc.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1995
3 %
4 \section[SparcDesc]{The Sparc Machine Description}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module SparcDesc (
10         mkSparc,
11
12         -- and assorted nonsense referenced by the class methods
13
14         PprStyle, SMRep, MagicId, RegLoc, StixTree, PrimKind, SwitchResult
15
16     ) where
17
18 import AbsCSyn
19 import AbsPrel      ( PrimOp(..)
20                       IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp)
21                           IF_ATTACK_PRAGMAS(COMMA pprPrimOp)
22                     )
23 import AsmRegAlloc  ( Reg, MachineCode(..), MachineRegisters(..),
24                       RegLiveness(..), RegUsage(..), FutureLive(..)
25                     )
26 import CLabelInfo   ( CLabel )
27 import CmdLineOpts  ( GlobalSwitch(..), stringSwitchSet, switchIsOn, SwitchResult(..) )
28 import HeapOffs     ( hpRelToInt )
29 import MachDesc
30 import Maybes       ( Maybe(..) )
31 import OrdList
32 import Outputable
33 import PrimKind     ( PrimKind(..) )
34 import SMRep        ( SMRep(..), SMSpecRepKind(..), SMUpdateKind(..) )
35 import SparcCode
36 import SparcGen     ( sparcCodeGen )
37 import Stix
38 import StixMacro
39 import StixPrim
40 import SplitUniq
41 import Unique
42 import Util
43
44 \end{code}
45
46 Header sizes depend only on command-line options, not on the target
47 architecture.  (I think.)
48
49 \begin{code}
50
51 fhs :: (GlobalSwitch -> SwitchResult) -> Int
52
53 fhs switches = 1 + profFHS + ageFHS
54   where
55     profFHS = if switchIsOn switches SccProfilingOn then 1 else 0
56     ageFHS  = if switchIsOn switches SccProfilingOn then 1 else 0
57
58 vhs :: (GlobalSwitch -> SwitchResult) -> SMRep -> Int
59
60 vhs switches sm = case sm of
61     StaticRep _ _          -> 0
62     SpecialisedRep _ _ _ _ -> 0
63     GenericRep _ _ _       -> 0
64     BigTupleRep _          -> 1
65     MuTupleRep _           -> 2 {- (1 + GC_MUT_RESERVED_WORDS) -}
66     DataRep _              -> 1
67     DynamicRep             -> 2
68     BlackHoleRep           -> 0
69     PhantomRep             -> panic "vhs:phantom"
70
71 \end{code}
72
73 Here we map STG registers onto appropriate Stix Trees.  First, we
74 handle the two constants, @STK_STUB_closure@ and @vtbl_StdUpdFrame@.
75 The rest are either in real machine registers or stored as offsets
76 from BaseReg.
77
78 \begin{code}
79
80 sparcReg :: (GlobalSwitch -> SwitchResult) -> MagicId -> RegLoc
81
82 sparcReg switches x =
83     case stgRegMap x of
84         Just reg -> Save nonReg
85         Nothing -> Always nonReg
86     where nonReg = case x of
87             StkStubReg -> sStLitLbl SLIT("STK_STUB_closure")
88             StdUpdRetVecReg -> sStLitLbl SLIT("vtbl_StdUpdFrame")
89             BaseReg -> sStLitLbl SLIT("MainRegTable")
90             Hp -> StInd PtrKind (sStLitLbl SLIT("StorageMgrInfo"))
91             HpLim -> StInd PtrKind (sStLitLbl SLIT("StorageMgrInfo+4"))
92             TagReg -> StInd IntKind (StPrim IntSubOp [infoptr, StInt (1*4)])
93                       where 
94                           r2 = VanillaReg PtrKind ILIT(2)
95                           infoptr = case sparcReg switches r2 of
96                                         Always tree -> tree
97                                         Save _ -> StReg (StixMagicId r2)
98             _ -> StInd (kindFromMagicId x)
99                        (StPrim IntAddOp [baseLoc, StInt (toInteger (offset*4))])
100           baseLoc = case stgRegMap BaseReg of
101             Just _ -> StReg (StixMagicId BaseReg)
102             Nothing -> sStLitLbl SLIT("MainRegTable")
103           offset = baseRegOffset x
104                     
105 \end{code}
106
107 Sizes in bytes.
108
109 \begin{code}
110
111 size pk = case kindToSize pk of
112     {SB -> 1; UB -> 1; HW -> 2; UHW -> 2; W -> 4; D -> 8; F -> 4; DF -> 8}
113
114 \end{code}
115
116 Now the volatile saves and restores.  We add the basic guys to the list of ``user''
117 registers provided.  Note that there are more basic registers on the restore list,
118 because some are reloaded from constants.
119
120 \begin{code}
121
122 vsaves switches vols = 
123     map save ((filter callerSaves) ([BaseReg,SpA,SuA,SpB,SuB,Hp,HpLim,RetReg,ActivityReg] ++ vols))
124     where
125         save x = StAssign (kindFromMagicId x) loc reg
126                     where reg = StReg (StixMagicId x)
127                           loc = case sparcReg switches x of
128                                     Save loc -> loc
129                                     Always loc -> panic "vsaves"
130
131 vrests switches vols = 
132     map restore ((filter callerSaves) 
133         ([BaseReg,SpA,SuA,SpB,SuB,Hp,HpLim,RetReg,ActivityReg,StkStubReg,StdUpdRetVecReg] ++ vols))
134     where
135         restore x = StAssign (kindFromMagicId x) reg loc
136                     where reg = StReg (StixMagicId x)
137                           loc = case sparcReg switches x of
138                                     Save loc -> loc
139                                     Always loc -> panic "vrests"
140
141 \end{code}
142
143 Static closure sizes.
144
145 \begin{code}
146
147 charLikeSize, intLikeSize :: Target -> Int
148
149 charLikeSize target = 
150     size PtrKind * (fixedHeaderSize target + varHeaderSize target charLikeRep + 1)
151     where charLikeRep = SpecialisedRep CharLikeRep 0 1 SMNormalForm
152
153 intLikeSize target = 
154     size PtrKind * (fixedHeaderSize target + varHeaderSize target intLikeRep + 1)
155     where intLikeRep = SpecialisedRep IntLikeRep 0 1 SMNormalForm
156
157 mhs, dhs :: (GlobalSwitch -> SwitchResult) -> StixTree
158
159 mhs switches = StInt (toInteger words)
160   where 
161     words = fhs switches + vhs switches (MuTupleRep 0)
162
163 dhs switches = StInt (toInteger words)
164   where 
165     words = fhs switches + vhs switches (DataRep 0)
166
167 \end{code}
168
169 Setting up a sparc target.
170
171 \begin{code}
172
173 mkSparc :: Bool -> (GlobalSwitch -> SwitchResult) -> Target
174
175 mkSparc decentOS switches = 
176     let fhs' = fhs switches
177         vhs' = vhs switches
178         sparcReg' = sparcReg switches
179         vsaves' = vsaves switches
180         vrests' = vrests switches
181         hprel = hpRelToInt target 
182         as = amodeCode target
183         as' = amodeCode' target
184         csz = charLikeSize target
185         isz = intLikeSize target
186         mhs' = mhs switches
187         dhs' = dhs switches
188         ps = genPrimCode target
189         mc = genMacroCode target
190         hc = doHeapCheck target
191         target = mkTarget switches fhs' vhs' sparcReg' id size vsaves' vrests' 
192                           hprel as as' csz isz mhs' dhs' ps mc hc
193                           sparcCodeGen decentOS id
194     in target
195
196 \end{code}
197             
198
199