1 /******************************** -*- C -*- ****************************
2  *
3  *	Run-time assembler for the SPARC
4  *
5  ***********************************************************************/
6 
7 
8 /***********************************************************************
9  *
10  * Copyright 1999, 2000, 2001, 2002 Ian Piumarta
11  *
12  * This file is part of GNU lightning.
13  *
14  * GNU lightning is free software; you can redistribute it and/or modify it
15  * under the terms of the GNU Lesser General Public License as published
16  * by the Free Software Foundation; either version 2.1, or (at your option)
17  * any later version.
18  *
19  * GNU lightning is distributed in the hope that it will be useful, but
20  * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
21  * or  FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser General Public
22  * License for more details.
23  *
24  * You should have received a copy of the GNU Lesser General Public License
25  * along with GNU lightning; see the file COPYING.LESSER; if not, write to the
26  * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston,
27  * MA 02110-1301, USA.
28  *
29  ***********************************************************************/
30 
31 
32 
33 
34 
35 #ifndef __lightning_asm_h
36 #define __lightning_asm_h
37 
38 
39 /* <imm> = [0-9]+		-> add i, one parameter (imm)
40  * <reg> = %<imm>		-> add r, one parameter (imm	or _Rr(imm) )
41  *	   %g<imm>		-> add r, one parameter (imm	or _Rg(imm) )
42  *	   %o<imm>		-> add r, one parameter (imm+8	or _Ro(imm) )
43  *	   %l<imm>		-> add r, one parameter (imm+16 or _Rl(imm) )
44  *	   %i<imm>		-> add r, one parameter (imm+24 or _Ri(imm) )
45  * <mem> = <imm>(<reg>)		-> add m, two parameters (reg,imm)
46  * <idx> = <reg>(<reg>)		-> add x, two parameters (reg,reg)
47  */
48 
49 
50 typedef unsigned int jit_insn;
51 
52 #ifndef LIGHTNING_DEBUG
53 #define _d30(BD)	((_jit_UL(BD) - _jit_UL(_jit.x.pc))>>2)
54 #define _d22(BD)	_ck_d(22, _d30(BD))
55 
56 #define _HI(I)		(_jit_UL(I) >>     (10))
57 #define _LO(I)		(_jit_UL(I) & _MASK(10))
58 
59 /* register names */
60 
61 #define _y		0
62 #define _psr		1
63 
64 #define _Rr(N)		( 0+(N))
65 #define _Rg(N)		( 0+(N))
66 #define _Ro(N)		( 8+(N))
67 #define _Rl(N)		(16+(N))
68 #define _Ri(N)		(24+(N))
69 
70 /* instruction formats -- Figure 5-1, page 44 in */
71 /* SPARC International, "The SPARC Architecture Manual, Version 8", Prentice-Hall, 1992.  */
72 
73 #define _0i(RD,     OP2,	  IMM)	_jit_I((0<<30)|		(_u5(RD)<<25)|(_u3(OP2)<<22)|					       _u22(IMM))
74 #define _0(  A, CC, OP2,	  DSP)	_jit_I((0<<30)|(_u1(A)<<29)|(_u4(CC)<<25)|(_u3(OP2)<<22)|					       _d22(DSP))
75 #define _0d( A, CC, OP2,	  DSP)	_jit_I((0<<30)|(_u1(A)<<29)|(_u4(CC)<<25)|(_u3(OP2)<<22)|					       _u22(DSP))
76 
77 #define _1(			  DSP)	_jit_I((1<<30)|										       _d30(DSP))
78 
79 #define _2( RD, OP3, RS1, I, ASI, RS2)	_jit_I((2<<30)|		(_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|(_u8(ASI)<<5)|_u5 (RS2))
80 #define _2i(RD, OP3, RS1, I,	  IMM)	_jit_I((2<<30)|		(_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|	       _s13(IMM))
81 #define _2f(RD, OP3, RS1,    OPF, RS2)	_jit_I((2<<30)|		(_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|		 (_u9(OPF)<<5)|_u5 (RS2))
82 
83 #define _3( RD, OP3, RS1, I, ASI, RS2)	_jit_I((3<<30)|		(_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|(_u8(ASI)<<5)|_u5 (RS2))
84 #define _3i(RD, OP3, RS1, I,	  IMM)	_jit_I((3<<30)|		(_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|	       _s13(IMM))
85 
86 #define _FP1(RD, RS1, OPF, RS2)	_2f((RD), 52, (RS1), (OPF), (RS2))
87 #define _FP2(RD, RS1, OPF, RS2)	_2f((RD), 53, (RS1), (OPF), (RS2))
88 
89 /* basic instructions  [Section B, page 87] */
90 
91 #define ADDrrr(RS1, RS2, RD)	_2   ((RD),  0, (RS1), 0, 0, (RS2))
92 #define ADDrir(RS1, IMM, RD)	_2i  ((RD),  0, (RS1), 1,    (IMM))
93 #define ADDCCrrr(RS1, RS2, RD)	_2   ((RD), 16, (RS1), 0, 0, (RS2))
94 #define ADDCCrir(RS1, IMM, RD)	_2i  ((RD), 16, (RS1), 1,    (IMM))
95 #define ADDXrrr(RS1, RS2, RD)	_2   ((RD),  8, (RS1), 0, 0, (RS2))
96 #define ADDXrir(RS1, IMM, RD)	_2i  ((RD),  8, (RS1), 1,    (IMM))
97 #define ADDXCCrrr(RS1, RS2, RD)	_2   ((RD), 24, (RS1), 0, 0, (RS2))
98 #define ADDXCCrir(RS1, IMM, RD)	_2i  ((RD), 24, (RS1), 1,    (IMM))
99 #define ANDrrr(RS1, RS2, RD)	_2   ((RD),  1, (RS1), 0, 0, (RS2))
100 #define ANDrir(RS1, IMM, RD)	_2i  ((RD),  1, (RS1), 1,    (IMM))
101 #define ANDCCrrr(RS1, RS2, RD)	_2   ((RD), 17, (RS1), 0, 0, (RS2))
102 #define ANDCCrir(RS1, IMM, RD)	_2i  ((RD), 17, (RS1), 1,    (IMM))
103 
104 #define BNi(DISP)		_0   (0,  0, 2, (DISP))
105 #define BN_Ai(DISP)		_0   (1,  0, 2, (DISP))
106 #define BEi(DISP)		_0   (0,  1, 2, (DISP))
107 #define BE_Ai(DISP)		_0   (1,  1, 2, (DISP))
108 #define BLEi(DISP)		_0   (0,  2, 2, (DISP))
109 #define BLE_Ai(DISP)		_0   (1,  2, 2, (DISP))
110 #define BLi(DISP)		_0   (0,  3, 2, (DISP))
111 #define BL_Ai(DISP)		_0   (1,  3, 2, (DISP))
112 #define BLEUi(DISP)		_0   (0,  4, 2, (DISP))
113 #define BLEU_Ai(DISP)		_0   (1,  4, 2, (DISP))
114 #define BCSi(DISP)		_0   (0,  5, 2, (DISP))
115 #define BCS_Ai(DISP)		_0   (1,  5, 2, (DISP))
116 #define BNEGi(DISP)		_0   (0,  6, 2, (DISP))
117 #define BNEG_Ai(DISP)		_0   (1,  6, 2, (DISP))
118 #define BVSi(DISP)		_0   (0,  7, 2, (DISP))
119 #define BVS_Ai(DISP)		_0   (1,  7, 2, (DISP))
120 #define BAi(DISP)		_0   (0,  8, 2, (DISP))
121 #define BA_Ai(DISP)		_0   (1,  8, 2, (DISP))
122 #define BNEi(DISP)		_0   (0,  9, 2, (DISP))
123 #define BNE_Ai(DISP)		_0   (1,  9, 2, (DISP))
124 #define BGi(DISP)		_0   (0, 10, 2, (DISP))
125 #define BG_Ai(DISP)		_0   (1, 10, 2, (DISP))
126 #define BGEi(DISP)		_0   (0, 11, 2, (DISP))
127 #define BGE_Ai(DISP)		_0   (1, 11, 2, (DISP))
128 #define BGUi(DISP)		_0   (0, 12, 2, (DISP))
129 #define BGU_Ai(DISP)		_0   (1, 12, 2, (DISP))
130 #define BCCi(DISP)		_0   (0, 13, 2, (DISP))
131 #define BCC_Ai(DISP)		_0   (1, 13, 2, (DISP))
132 #define BPOSi(DISP)		_0   (0, 14, 2, (DISP))
133 #define BPOS_Ai(DISP)		_0   (1, 14, 2, (DISP))
134 #define BVCi(DISP)		_0   (0, 15, 2, (DISP))
135 #define BVC_Ai(DISP)		_0   (1, 15, 2, (DISP))
136 
137 #define CALLi(DISP)		_1   ((DISP))
138 
139 #define FLUSHrr(RS1, RS2)	_2   (0, 0x3b, (RS1), 0, 0, (RS2))
140 #define FLUSHir(IMM, RS1)	_2i  (0, 0x3b, (RS1), 1,    (IMM))
141 
142 #define JMPLxr(RS1, RS2, RD)	_2   ((RD), 56, (RS1), 0, 0, (RS2))
143 #define JMPLmr(RS1, IMM, RD)	_2i  ((RD), 56, (RS1), 1,    (IMM))
144 
145 #define LDxr(RS1, RS2, RD)	_3   ((RD),  0, (RS1), 0, 0, (RS2))
146 #define LDmr(RS1, IMM, RD)	_3i  ((RD),  0, (RS1), 1,    (IMM))
147 #define LDUBxr(RS1, RS2, RD)	_3   ((RD),  1, (RS1), 0, 0, (RS2))
148 #define LDUBmr(RS1, IMM, RD)	_3i  ((RD),  1, (RS1), 1,    (IMM))
149 #define LDUHxr(RS1, RS2, RD)	_3   ((RD),  2, (RS1), 0, 0, (RS2))
150 #define LDUHmr(RS1, IMM, RD)	_3i  ((RD),  2, (RS1), 1,    (IMM))
151 #define LDDxr(RS1, RS2, RD)	_3   ((RD),  3, (RS1), 0, 0, (RS2))
152 #define LDDmr(RS1, IMM, RD)	_3i  ((RD),  3, (RS1), 1,    (IMM))
153 #define LDSBxr(RS1, RS2, RD)	_3   ((RD),  9, (RS1), 0, 0, (RS2))
154 #define LDSBmr(RS1, IMM, RD)	_3i  ((RD),  9, (RS1), 1,    (IMM))
155 #define LDSHxr(RS1, RS2, RD)	_3   ((RD), 10, (RS1), 0, 0, (RS2))
156 #define LDSHmr(RS1, IMM, RD)	_3i  ((RD), 10, (RS1), 1,    (IMM))
157 
158 #define ORrrr(RS1, RS2, RD)	_2   ((RD),  2, (RS1), 0, 0, (RS2))
159 #define ORrir(RS1, IMM, RD)	_2i  ((RD),  2, (RS1), 1,    (IMM))
160 #define ORCCrrr(RS1, RS2, RD)	_2   ((RD), 18, (RS1), 0, 0, (RS2))
161 #define ORCCrir(RS1, IMM, RD)	_2i  ((RD), 18, (RS1), 1,    (IMM))
162 
163 #define RDir(RS, RD)		 _2   ((RD), (RS)|0x28, 0, 0, 0,0)
164 #define RESTORErrr(RS1, RS2, RD) _2   ((RD), 61, (RS1), 0, 0, (RS2))
165 #define RESTORErir(RS1, IMM, RD) _2i  ((RD), 61, (RS1), 1,    (IMM))
166 
167 #define SAVErrr(RS1, RS2, RD)	_2   ((RD), 60, (RS1), 0, 0, (RS2))
168 #define SAVErir(RS1, IMM, RD)	_2i  ((RD), 60, (RS1), 1,    (IMM))
169 #define SDIVrrr(RS1, RS2, RD)	_2   ((RD), 15, (RS1), 0, 0, (RS2))
170 #define SDIVrir(RS1, IMM, RD)	_2i  ((RD), 15, (RS1), 1,    (IMM))
171 #define SDIVCCrrr(RS1, RS2, RD) _2   ((RD), 31, (RS1), 0, 0, (RS2))
172 #define SDIVCCrir(RS1, IMM, RD) _2i  ((RD), 31, (RS1), 1,    (IMM))
173 #define SETHIir(IMM, RD)	_0i  ((RD), 4, (IMM))
174 #define SLLrrr(RS1, RS2, RD)	_2   ((RD), 37, (RS1), 0, 0, (RS2))
175 #define SLLrir(RS1, IMM, RD)	_2i  ((RD), 37, (RS1), 1,    (IMM))
176 #define SMULrrr(RS1, RS2, RD)	_2   ((RD), 11, (RS1), 0, 0, (RS2))
177 #define SMULrir(RS1, IMM, RD)	_2i  ((RD), 11, (RS1), 1,    (IMM))
178 #define SMULCCrrr(RS1, RS2, RD) _2   ((RD), 27, (RS1), 0, 0, (RS2))
179 #define SMULCCrir(RS1, IMM, RD) _2i  ((RD), 27, (RS1), 1,    (IMM))
180 #define SRArrr(RS1, RS2, RD)	_2   ((RD), 39, (RS1), 0, 0, (RS2))
181 #define SRArir(RS1, IMM, RD)	_2i  ((RD), 39, (RS1), 1,    (IMM))
182 #define SRLrrr(RS1, RS2, RD)	_2   ((RD), 38, (RS1), 0, 0, (RS2))
183 #define SRLrir(RS1, IMM, RD)	_2i  ((RD), 38, (RS1), 1,    (IMM))
184 #define STrx(RS, RD1, RD2)	_3   ((RS),  4, (RD1), 0, 0, (RD2))
185 #define STrm(RS, RD, IMM)	_3i  ((RS),  4, (RD),  1,    (IMM))
186 #define STBrx(RS, RD1, RD2)	_3   ((RS),  5, (RD1), 0, 0, (RD2))
187 #define STBrm(RS, RD, IMM)	_3i  ((RS),  5, (RD),  1,    (IMM))
188 #define STBAR()			_0i  (0, 0x28, 15, 0, 0)
189 #define STHrx(RS, RD1, RD2)	_3   ((RS),  6, (RD1), 0, 0, (RD2))
190 #define STHrm(RS, RD, IMM)	_3i  ((RS),  6, (RD),  1,    (IMM))
191 #define STDrx(RS, RD1, RD2)	_3   ((RS),  7, (RD1), 0, 0, (RD2))
192 #define STDrm(RS, RD, IMM)	_3i  ((RS),  7, (RD),  1,    (IMM))
193 #define SUBrrr(RS1, RS2, RD)	_2   ((RD),  4, (RS1), 0, 0, (RS2))
194 #define SUBrir(RS1, IMM, RD)	_2i  ((RD),  4, (RS1), 1,    (IMM))
195 #define SUBCCrrr(RS1, RS2, RD)	_2   ((RD), 20, (RS1), 0, 0, (RS2))
196 #define SUBCCrir(RS1, IMM, RD)	_2i  ((RD), 20, (RS1), 1,    (IMM))
197 #define SUBXrrr(RS1, RS2, RD)	_2   ((RD), 12, (RS1), 0, 0, (RS2))
198 #define SUBXrir(RS1, IMM, RD)	_2i  ((RD), 12, (RS1), 1,    (IMM))
199 #define SUBXCCrrr(RS1, RS2, RD)	_2   ((RD), 28, (RS1), 0, 0, (RS2))
200 #define SUBXCCrir(RS1, IMM, RD)	_2i  ((RD), 28, (RS1), 1,    (IMM))
201 
202 #define UDIVrrr(RS1, RS2, RD)	_2   ((RD), 14, (RS1), 0, 0, (RS2))
203 #define UDIVrir(RS1, IMM, RD)	_2i  ((RD), 14, (RS1), 1,    (IMM))
204 #define UDIVCCrrr(RS1, RS2, RD) _2   ((RD), 30, (RS1), 0, 0, (RS2))
205 #define UDIVCCrir(RS1, IMM, RD) _2i  ((RD), 30, (RS1), 1,    (IMM))
206 #define UMULrrr(RS1, RS2, RD)	_2   ((RD), 10, (RS1), 0, 0, (RS2))
207 #define UMULrir(RS1, IMM, RD)	_2i  ((RD), 10, (RS1), 1,    (IMM))
208 #define UMULCCrrr(RS1, RS2, RD) _2   ((RD), 26, (RS1), 0, 0, (RS2))
209 #define UMULCCrir(RS1, IMM, RD) _2i  ((RD), 26, (RS1), 1,    (IMM))
210 
211 #define WRrri(RS1, RS2, RD)	_2   (0, (RD)|0x30,   RS1, 0, 0, (RS2))
212 #define WRrii(RS1, IMM, RD)	_2i  (0, (RD)|0x30,   RS1, 1,	 (IMM))
213 
214 #define XORrrr(RS1, RS2, RD)	_2   ((RD),  3, (RS1), 0, 0, (RS2))
215 #define XORrir(RS1, IMM, RD)	_2i  ((RD),  3, (RS1), 1,    (IMM))
216 #define XORCCrrr(RS1, RS2, RD)	_2   ((RD), 19, (RS1), 0, 0, (RS2))
217 #define XORCCrir(RS1, IMM, RD)	_2i  ((RD), 19, (RS1), 1,    (IMM))
218 
219 /* synonyms */
220 
221 #define Bi(DISP)		BAi((DISP))
222 #define B_Ai(DISP)		BA_Ai((DISP))
223 #define BNZi(DISP)		BNEi((DISP))
224 #define BNZ_Ai(DISP)		BNE_Ai((DISP))
225 #define BZi(DISP)		BEi((DISP))
226 #define BZ_Ai(DISP)		BE_Ai((DISP))
227 #define BGEUi(DISP)		BCCi((DISP))
228 #define BGEU_Ai(DISP)		BCC_Ai((DISP))
229 #define BLUi(DISP)		BCSi((DISP))
230 #define BLU_Ai(DISP)		BCS_Ai((DISP))
231 
232 #define LDUWxr(RS1, RS2, RD)	LDxr((RS1), (RS2), (RD))
233 #define LDUWmr(RS1, IMM, RD)	LDmr((RS1), (IMM), (RD))
234 #define LDSWxr(RS1, RS2, RD)	LDxr((RS1), (RS2), (RD))
235 #define LDSWmr(RS1, IMM, RD)	LDmr((RS1), (IMM), (RD))
236 
237 #define STWrx(RS, RD1, RD2)	STrx((RS), (RD1),   (RD2))
238 #define STWrm(RS, RD, IMM)	STrm((RS), (RD), (IMM))
239 
240 /* synthetic instructions [Table A-1, page 85] */
241 
242 #define BCLRrr(R,S)		ANDNrrr((R), (S), (S))
243 #define BCLRir(I,R)		ANDNrir((R), (I), (R))
244 #define BSETrr(R,S)		ORrrr((R), (S), (S))
245 #define BSETir(I,R)		ORrir((R), (I), (R))
246 #define BTOGrr(R,S)		XORrrr((R), (S), (S))
247 #define BTOGir(I,R)		XORrir((R), (I), (R))
248 #define BTSTrr(R,S)		ANDCCrrr((R), (S), 0)
249 #define BTSTir(I,R)		ANDCCrir((R), (I), 0)
250 
251 #define CALLm(R,I)		JMPLmr((R), (I), _Ro(7))
252 #define CALLx(R,S)		JMPLxr((R), (S), _Ro(7))
253 
254 #define CLRr(R)			ORrrr(0, 0, (R))
255 #define CLRBm(R,I)		STBrm(0, (R), (I))
256 #define CLRBx(R,S)		STBrm(0, (R), (S))
257 #define CLRHm(R,I)		STHrm(0, (R), (I))
258 #define CLRHx(R,S)		STHrm(0, (R), (S))
259 #define CLRm(R,I)		STrm(0, (R), (I))
260 #define CLRx(R,S)		STrm(0, (R), (S))
261 
262 #define CMPrr(RS1, RS2)		SUBCCrrr((RS1), (RS2), 0)
263 #define CMPri(RS1, IMM)		SUBCCrir((RS1), (IMM), 0)
264 
265 #define DECr(R)			SUBrir((R), 1, (R))
266 #define DECir(I,R)		SUBrir((R), (I), (R))
267 #define DECCCr(R)		SUBCCrir((R), 1, (R))
268 #define DECCCir(I,R)		SUBCCrir((R), (I), (R))
269 
270 #define INCr(R)			ADDrir((R), 1, (R))
271 #define INCir(I,R)		ADDrir((R), (I), (R))
272 #define INCCCr(R)		ADDCCrir((R), 1, (R))
273 #define INCCCir(I,R)		ADDCCrir((R), (I), (R))
274 
275 #define JMPm(R,I)		JMPLmr((R), (I), 0)
276 #define JMPx(R,S)		JMPLxr((R), (S), 0)
277 
278 #define MOVrr(R,S)		ORrrr(0, (R), (S))
279 #define MOVir(I, R)		ORrir(0, (I), (R))
280 
281 #define NEGrr(R,S)		SUBrrr(0, (R), (S))
282 #define NEGr(R)			SUBrrr(0, (R), (R))
283 #define NOP()			SETHIir(0, 0)
284 
285 #define NOTrr(R,S)		XNORrrr((R), 0, (S))
286 #define NOTr(R)			XNORrrr((R), 0, (R))
287 
288 #define RESTORE()		RESTORErrr(0, 0, 0)
289 #define RET()			JMPLmr(_Ri(7),8 ,0)
290 #define RETL()			JMPLmr(_Ro(7),8 ,0)
291 
292 #define SAVE()			SAVErrr(0, 0, 0)
293 #define SETir(I,R)		(_siP(13,(I)) ? MOVir((I),(R)) : SETir2(_HI(I), _LO(I), (R)))
294 #define SETir2(H,L,R)		(SETHIir(H,R), (L ? ORrir(R,L,R) : 0))
295 
296 /* BNZ,a executes the delay instruction if NZ (so skips if Z)
297  * BZ,a  executes the delay instruction if Z  (so skips if NZ). */
298 #define SKIPZ()			_0d  (1,  9, 2, 2) /* BNZ,a .+8 */
299 #define SKIPNZ()		_0d  (1,  1, 2, 2) /* BZ,a  .+8 */
300 #define SKIP()			_0d  (1,  0, 2, 0) /* BN,a  .   */
301 
302 #define TSTr(R)			ORCCrrr(0, (R), 0)
303 
304 #define WRii(IMM, RD)		WRrii(0, (IMM), (RD))
305 #define WRri(RS2, RD)		WRrri(0, (RS2), (RD))
306 
307 #define LDFSRx(RS1, RS2)	_3   (0, 33, (RS1), 0, 0, (RS2))
308 #define LDFSRm(RS1, IMM)	_3i  (0, 33, (RS1), 1,    (IMM))
309 #define STFSRx(RD1, RD2)	_3   (0, 37, (RD1), 0, 0, (RD2))
310 #define STFSRm(RD, IMM)		_3i  (0, 37, (RD),  1,    (IMM))
311 
312 #define FITODrr(FRS, FRD)		_FP1((FRD),  0, 200, (FRS))
313 #define FITOSrr(FRS, FRD)		_FP1((FRD),  0, 196, (FRS))
314 #define FDTOIrr(FRS, FRD)		_FP1((FRD),  0, 210, (FRS))
315 #define FSTOIrr(FRS, FRD)		_FP1((FRD),  0, 209, (FRS))
316 #define FSTODrr(FRS, FRD)		_FP1((FRD),  0, 201, (FRS))
317 #define FDTOSrr(FRS, FRD)		_FP1((FRD),  0, 198, (FRS))
318 #define FMOVSrr(FRS, FRD)		_FP1((FRD),  0,   1, (FRS))
319 #define FNEGSrr(FRS, FRD)		_FP1((FRD),  0,   5, (FRS))
320 #define FABSSrr(FRS, FRD)		_FP1((FRD),  0,   9, (FRS))
321 #define FMOVDrr(FRS, FRD)		_FP1((FRD),  0,   2, (FRS))
322 #define FNEGDrr(FRS, FRD)		_FP1((FRD),  0,   6, (FRS))
323 #define FABSDrr(FRS, FRD)		_FP1((FRD),  0,  10, (FRS))
324 #define FSQRTDrr(FRS, FRD)		_FP1((FRD),  0,  42, (FRS))
325 #define FSQRTSrr(FRS, FRD)		_FP1((FRD),  0,  41, (FRS))
326 
327 #define FADDSrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  65, (FRS2))
328 #define FSUBSrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  69, (FRS2))
329 #define FMULSrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  73, (FRS2))
330 #define FDIVSrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  77, (FRS2))
331 
332 #define FADDDrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  66, (FRS2))
333 #define FSUBDrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  70, (FRS2))
334 #define FMULDrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  74, (FRS2))
335 #define FDIVDrrr(FRS1, FRS2, FRD)	_FP1((FRD),  (FRS1),  78, (FRS2))
336 
337 #define FCMPSrr(FRS1, FRS2)		_FP2(0,      (FRS1),  81, (FRS2))
338 #define FCMPDrr(FRS1, FRS2)		_FP2(0,      (FRS1),  82, (FRS2))
339 
340 #define LDFxr(RS1, RS2, RD)	_3   ((RD), 32, (RS1), 0, 0, (RS2))
341 #define LDFmr(RS1, IMM, RD)	_3i  ((RD), 32, (RS1), 1,    (IMM))
342 #define LDDFxr(RS1, RS2, RD)	_3   ((RD), 35, (RS1), 0, 0, (RS2))
343 #define LDDFmr(RS1, IMM, RD)	_3i  ((RD), 35, (RS1), 1,    (IMM))
344 #define STFrx(RS, RD1, RD2)	_3   ((RS), 36, (RD1), 0, 0, (RD2))
345 #define STFrm(RS, RD1, IMM)	_3i  ((RS), 36, (RD1), 1,    (IMM))
346 #define STDFrx(RS, RD1, RD2)	_3   ((RS), 39, (RD1), 0, 0, (RD2))
347 #define STDFrm(RS, RD1, IMM)	_3i  ((RS), 39, (RD1), 1,    (IMM))
348 
349 #define FBNi(DISP)		_0   (0,  0, 6, (DISP))
350 #define FBN_Ai(DISP)		_0   (1,  0, 6, (DISP))
351 #define FBNEi(DISP)		_0   (0,  1, 6, (DISP))
352 #define FBNE_Ai(DISP)		_0   (1,  1, 6, (DISP))
353 #define FBLGi(DISP)		_0   (0,  2, 6, (DISP))
354 #define FBLG_Ai(DISP)		_0   (1,  2, 6, (DISP))
355 #define FBULi(DISP)		_0   (0,  3, 6, (DISP))
356 #define FBUL_Ai(DISP)		_0   (1,  3, 6, (DISP))
357 #define FBLi(DISP)		_0   (0,  4, 6, (DISP))
358 #define FBL_Ai(DISP)		_0   (1,  4, 6, (DISP))
359 #define FBUGi(DISP)		_0   (0,  5, 6, (DISP))
360 #define FBUG_Ai(DISP)		_0   (1,  5, 6, (DISP))
361 #define FBGi(DISP)		_0   (0,  6, 6, (DISP))
362 #define FBG_Ai(DISP)		_0   (1,  6, 6, (DISP))
363 #define FBUi(DISP)		_0   (0,  7, 6, (DISP))
364 #define FBU_Ai(DISP)		_0   (1,  7, 6, (DISP))
365 #define FBAi(DISP)		_0   (0,  8, 6, (DISP))
366 #define FBA_Ai(DISP)		_0   (1,  8, 6, (DISP))
367 #define FBEi(DISP)		_0   (0,  9, 6, (DISP))
368 #define FBE_Ai(DISP)		_0   (1,  9, 6, (DISP))
369 #define FBUEi(DISP)		_0   (0, 10, 6, (DISP))
370 #define FBUE_Ai(DISP)		_0   (1, 10, 6, (DISP))
371 #define FBGEi(DISP)		_0   (0, 11, 6, (DISP))
372 #define FBGE_Ai(DISP)		_0   (1, 11, 6, (DISP))
373 #define FBUGEi(DISP)		_0   (0, 12, 6, (DISP))
374 #define FBUGE_Ai(DISP)		_0   (1, 12, 6, (DISP))
375 #define FBLEi(DISP)		_0   (0, 13, 6, (DISP))
376 #define FBLE_Ai(DISP)		_0   (1, 13, 6, (DISP))
377 #define FBULEi(DISP)		_0   (0, 14, 6, (DISP))
378 #define FBULE_Ai(DISP)		_0   (1, 14, 6, (DISP))
379 #define FBOi(DISP)		_0   (0, 15, 6, (DISP))
380 #define FBO_Ai(DISP)		_0   (1, 15, 6, (DISP))
381 
382 #endif
383 #endif /* __ccg_asm_sparc_h */
384