xref: /netbsd/sys/arch/m68k/fpsp/x_operr.sa (revision bf9ec67e)
1*	$NetBSD: x_operr.sa,v 1.5 2001/09/16 16:34:32 wiz Exp $
2
3*	MOTOROLA MICROPROCESSOR & MEMORY TECHNOLOGY GROUP
4*	M68000 Hi-Performance Microprocessor Division
5*	M68040 Software Package
6*
7*	M68040 Software Package Copyright (c) 1993, 1994 Motorola Inc.
8*	All rights reserved.
9*
10*	THE SOFTWARE is provided on an "AS IS" basis and without warranty.
11*	To the maximum extent permitted by applicable law,
12*	MOTOROLA DISCLAIMS ALL WARRANTIES WHETHER EXPRESS OR IMPLIED,
13*	INCLUDING IMPLIED WARRANTIES OF MERCHANTABILITY OR FITNESS FOR A
14*	PARTICULAR PURPOSE and any warranty against infringement with
15*	regard to the SOFTWARE (INCLUDING ANY MODIFIED VERSIONS THEREOF)
16*	and any accompanying written materials.
17*
18*	To the maximum extent permitted by applicable law,
19*	IN NO EVENT SHALL MOTOROLA BE LIABLE FOR ANY DAMAGES WHATSOEVER
20*	(INCLUDING WITHOUT LIMITATION, DAMAGES FOR LOSS OF BUSINESS
21*	PROFITS, BUSINESS INTERRUPTION, LOSS OF BUSINESS INFORMATION, OR
22*	OTHER PECUNIARY LOSS) ARISING OF THE USE OR INABILITY TO USE THE
23*	SOFTWARE.  Motorola assumes no responsibility for the maintenance
24*	and support of the SOFTWARE.
25*
26*	You are hereby granted a copyright license to use, modify, and
27*	distribute the SOFTWARE so long as this entire notice is retained
28*	without alteration in any modified and/or redistributed versions,
29*	and that such modified versions are clearly identified as such.
30*	No licenses are granted by implication, estoppel or otherwise
31*	under any patents or trademarks of Motorola, Inc.
32
33*
34*	x_operr.sa 3.5 7/1/91
35*
36*	fpsp_operr --- FPSP handler for operand error exception
37*
38*	See 68040 User's Manual pp. 9-44f
39*
40* Note 1: For trap disabled 040 does the following:
41* If the dest is a fp reg, then an extended precision non_signaling
42* NAN is stored in the dest reg.  If the dest format is b, w, or l and
43* the source op is a NAN, then garbage is stored as the result (actually
44* the upper 32 bits of the mantissa are sent to the integer unit). If
45* the dest format is integer (b, w, l) and the operr is caused by
46* integer overflow, or the source op is inf, then the result stored is
47* garbage.
48* There are three cases in which operr is incorrectly signaled on the
49* 040.  This occurs for move_out of format b, w, or l for the largest
50* negative integer (-2^7 for b, -2^15 for w, -2^31 for l).
51*
52*	  On opclass = 011 fmove.(b,w,l) that causes a conversion
53*	  overflow -> OPERR, the exponent in wbte (and fpte) is:
54*		byte    56 - (62 - exp)
55*		word    48 - (62 - exp)
56*		long    32 - (62 - exp)
57*
58*			where exp = (true exp) - 1
59*
60*  So, wbtemp and fptemp will contain the following on erroneoulsy
61*	  signalled operr:
62*			fpts = 1
63*			fpte = $4000  (15 bit externally)
64*		byte	fptm = $ffffffff ffffff80
65*		word	fptm = $ffffffff ffff8000
66*		long	fptm = $ffffffff 80000000
67*
68* Note 2: For trap enabled 040 does the following:
69* If the inst is move_out, then same as Note 1.
70* If the inst is not move_out, the dest is not modified.
71* The exceptional operand is not defined for integer overflow
72* during a move_out.
73*
74
75X_OPERR	IDNT    2,1 Motorola 040 Floating Point Software Package
76
77	section	8
78
79	include	fpsp.h
80
81	xref	mem_write
82	xref	real_operr
83	xref	real_inex
84	xref	get_fline
85	xref	fpsp_done
86	xref	reg_dest
87
88	xdef	fpsp_operr
89fpsp_operr:
90*
91	link		a6,#-LOCAL_SIZE
92	fsave		-(a7)
93	movem.l		d0-d1/a0-a1,USER_DA(a6)
94	fmovem.x	fp0-fp3,USER_FP0(a6)
95	fmovem.l	fpcr/fpsr/fpiar,USER_FPCR(a6)
96
97*
98* Check if this is an opclass 3 instruction.
99*  If so, fall through, else branch to operr_end
100*
101	btst.b	#TFLAG,T_BYTE(a6)
102	beq.b	operr_end
103
104*
105* If the destination size is B,W,or L, the operr must be
106* handled here.
107*
108	move.l	CMDREG1B(a6),d0
109	bfextu	d0{3:3},d0	;0=long, 4=word, 6=byte
110	tst.b	d0		;determine size; check long
111	beq.w	operr_long
112	cmpi.b	#4,d0		;check word
113	beq.w	operr_word
114	cmpi.b	#6,d0		;check byte
115	beq.w	operr_byte
116
117*
118* The size is not B,W,or L, so the operr is handled by the
119* kernel handler.  Set the operr bits and clean up, leaving
120* only the integer exception frame on the stack, and the
121* fpu in the original exceptional state.
122*
123operr_end:
124	bset.b		#operr_bit,FPSR_EXCEPT(a6)
125	bset.b		#aiop_bit,FPSR_AEXCEPT(a6)
126
127	movem.l		USER_DA(a6),d0-d1/a0-a1
128	fmovem.x	USER_FP0(a6),fp0-fp3
129	fmovem.l	USER_FPCR(a6),fpcr/fpsr/fpiar
130	frestore	(a7)+
131	unlk		a6
132	bra.l		real_operr
133
134operr_long:
135	moveq.l	#4,d1		;write size to d1
136	move.b	STAG(a6),d0	;test stag for nan
137	andi.b	#$e0,d0		;clr all but tag
138	cmpi.b	#$60,d0		;check for nan
139	beq	operr_nan
140	cmpi.l	#$80000000,FPTEMP_LO(a6) ;test if ls lword is special
141	bne.b	chklerr		;if not equal, check for incorrect operr
142	bsr	check_upper	;check if exp and ms mant are special
143	tst.l	d0
144	bne.b	chklerr		;if d0 is true, check for incorrect operr
145	move.l	#$80000000,d0	;store special case result
146	bsr	operr_store
147	bra.w	not_enabled	;clean and exit
148*
149*	CHECK FOR INCORRECTLY GENERATED OPERR EXCEPTION HERE
150*
151chklerr:
152	move.w	FPTEMP_EX(a6),d0
153	and.w	#$7FFF,d0	;ignore sign bit
154	cmp.w	#$3FFE,d0	;this is the only possible exponent value
155	bne.b	chklerr2
156fixlong:
157	move.l	FPTEMP_LO(a6),d0
158	bsr	operr_store
159	bra.w	not_enabled
160chklerr2:
161	move.w	FPTEMP_EX(a6),d0
162	and.w	#$7FFF,d0	;ignore sign bit
163	cmp.w	#$4000,d0
164	bcc.w	store_max	;exponent out of range
165
166	move.l	FPTEMP_LO(a6),d0
167	and.l	#$7FFF0000,d0	;look for all 1's on bits 30-16
168	cmp.l	#$7FFF0000,d0
169	beq.b	fixlong
170
171	tst.l	FPTEMP_LO(a6)
172	bpl.b	chklepos
173	cmp.l	#$FFFFFFFF,FPTEMP_HI(a6)
174	beq.b	fixlong
175	bra.w	store_max
176chklepos:
177	tst.l	FPTEMP_HI(a6)
178	beq.b	fixlong
179	bra.w	store_max
180
181operr_word:
182	moveq.l	#2,d1		;write size to d1
183	move.b	STAG(a6),d0	;test stag for nan
184	andi.b	#$e0,d0		;clr all but tag
185	cmpi.b	#$60,d0		;check for nan
186	beq.w	operr_nan
187	cmpi.l	#$ffff8000,FPTEMP_LO(a6) ;test if ls lword is special
188	bne.b	chkwerr		;if not equal, check for incorrect operr
189	bsr	check_upper	;check if exp and ms mant are special
190	tst.l	d0
191	bne.b	chkwerr		;if d0 is true, check for incorrect operr
192	move.l	#$80000000,d0	;store special case result
193	bsr	operr_store
194	bra.w	not_enabled	;clean and exit
195*
196*	CHECK FOR INCORRECTLY GENERATED OPERR EXCEPTION HERE
197*
198chkwerr:
199	move.w	FPTEMP_EX(a6),d0
200	and.w	#$7FFF,d0	;ignore sign bit
201	cmp.w	#$3FFE,d0	;this is the only possible exponent value
202	bne.b	store_max
203	move.l	FPTEMP_LO(a6),d0
204	swap	d0
205	bsr	operr_store
206	bra.w	not_enabled
207
208operr_byte:
209	moveq.l	#1,d1		;write size to d1
210	move.b	STAG(a6),d0	;test stag for nan
211	andi.b	#$e0,d0		;clr all but tag
212	cmpi.b	#$60,d0		;check for nan
213	beq.b	operr_nan
214	cmpi.l	#$ffffff80,FPTEMP_LO(a6) ;test if ls lword is special
215	bne.b	chkberr		;if not equal, check for incorrect operr
216	bsr	check_upper	;check if exp and ms mant are special
217	tst.l	d0
218	bne.b	chkberr		;if d0 is true, check for incorrect operr
219	move.l	#$80000000,d0	;store special case result
220	bsr	operr_store
221	bra.w	not_enabled	;clean and exit
222*
223*	CHECK FOR INCORRECTLY GENERATED OPERR EXCEPTION HERE
224*
225chkberr:
226	move.w	FPTEMP_EX(a6),d0
227	and.w	#$7FFF,d0	;ignore sign bit
228	cmp.w	#$3FFE,d0	;this is the only possible exponent value
229	bne.b	store_max
230	move.l	FPTEMP_LO(a6),d0
231	asl.l	#8,d0
232	swap	d0
233	bsr	operr_store
234	bra.w	not_enabled
235
236*
237* This operr condition is not of the special case.  Set operr
238* and aiop and write the portion of the nan to memory for the
239* given size.
240*
241operr_nan:
242	or.l	#opaop_mask,USER_FPSR(a6) ;set operr & aiop
243
244	move.l	ETEMP_HI(a6),d0	;output will be from upper 32 bits
245	bsr	operr_store
246	bra	end_operr
247*
248* Store_max loads the max pos or negative for the size, sets
249* the operr and aiop bits, and clears inex and ainex, incorrectly
250* set by the 040.
251*
252store_max:
253	or.l	#opaop_mask,USER_FPSR(a6) ;set operr & aiop
254	bclr.b	#inex2_bit,FPSR_EXCEPT(a6)
255	bclr.b	#ainex_bit,FPSR_AEXCEPT(a6)
256	fmove.l	#0,FPSR
257
258	tst.w	FPTEMP_EX(a6)	;check sign
259	blt.b	load_neg
260	move.l	#$7fffffff,d0
261	bsr	operr_store
262	bra	end_operr
263load_neg:
264	move.l	#$80000000,d0
265	bsr	operr_store
266	bra	end_operr
267
268*
269* This routine stores the data in d0, for the given size in d1,
270* to memory or data register as required.  A read of the fline
271* is required to determine the destination.
272*
273operr_store:
274	move.l	d0,L_SCR1(a6)	;move write data to L_SCR1
275	move.l	d1,-(a7)	;save register size
276	bsr.l	get_fline	;fline returned in d0
277	move.l	(a7)+,d1
278	bftst	d0{26:3}		;if mode is zero, dest is Dn
279	bne.b	dest_mem
280*
281* Destination is Dn.  Get register number from d0. Data is on
282* the stack at (a7). D1 has size: 1=byte,2=word,4=long/single
283*
284	andi.l	#7,d0		;isolate register number
285	cmpi.l	#4,d1
286	beq.b	op_long		;the most frequent case
287	cmpi.l	#2,d1
288	bne.b	op_con
289	or.l	#8,d0
290	bra.b	op_con
291op_long:
292	or.l	#$10,d0
293op_con:
294	move.l	d0,d1		;format size:reg for reg_dest
295	bra.l	reg_dest	;call to reg_dest returns to caller
296*				;of operr_store
297*
298* Destination is memory.  Get <ea> from integer exception frame
299* and call mem_write.
300*
301dest_mem:
302	lea.l	L_SCR1(a6),a0	;put ptr to write data in a0
303	move.l	EXC_EA(a6),a1	;put user destination address in a1
304	move.l	d1,d0		;put size in d0
305	bsr.l	mem_write
306	rts
307*
308* Check the exponent for $c000 and the upper 32 bits of the
309* mantissa for $ffffffff.  If both are true, return d0 clr
310* and store the lower n bits of the least lword of FPTEMP
311* to d0 for write out.  If not, it is a real operr, and set d0.
312*
313check_upper:
314	cmpi.l	#$ffffffff,FPTEMP_HI(a6) ;check if first byte is all 1's
315	bne.b	true_operr	;if not all 1's then was true operr
316	cmpi.w	#$c000,FPTEMP_EX(a6) ;check if incorrectly signalled
317	beq.b	not_true_operr	;branch if not true operr
318	cmpi.w	#$bfff,FPTEMP_EX(a6) ;check if incorrectly signalled
319	beq.b	not_true_operr	;branch if not true operr
320true_operr:
321	move.l	#1,d0		;signal real operr
322	rts
323not_true_operr:
324	clr.l	d0		;signal no real operr
325	rts
326
327*
328* End_operr tests for operr enabled.  If not, it cleans up the stack
329* and does an rte.  If enabled, it cleans up the stack and branches
330* to the kernel operr handler with only the integer exception
331* frame on the stack and the fpu in the original exceptional state
332* with correct data written to the destination.
333*
334end_operr:
335	btst.b		#operr_bit,FPCR_ENABLE(a6)
336	beq.b		not_enabled
337enabled:
338	movem.l		USER_DA(a6),d0-d1/a0-a1
339	fmovem.x	USER_FP0(a6),fp0-fp3
340	fmovem.l	USER_FPCR(a6),fpcr/fpsr/fpiar
341	frestore	(a7)+
342	unlk		a6
343	bra.l		real_operr
344
345not_enabled:
346*
347* It is possible to have either inex2 or inex1 exceptions with the
348* operr.  If the inex enable bit is set in the FPCR, and either
349* inex2 or inex1 occurred, we must clean up and branch to the
350* real inex handler.
351*
352ck_inex:
353	move.b	FPCR_ENABLE(a6),d0
354	and.b	FPSR_EXCEPT(a6),d0
355	andi.b	#$3,d0
356	beq.w	operr_exit
357*
358* Inexact enabled and reported, and we must take an inexact exception.
359*
360take_inex:
361	move.b		#INEX_VEC,EXC_VEC+1(a6)
362	move.l		USER_FPSR(a6),FPSR_SHADOW(a6)
363	or.l		#sx_mask,E_BYTE(a6)
364	movem.l		USER_DA(a6),d0-d1/a0-a1
365	fmovem.x	USER_FP0(a6),fp0-fp3
366	fmovem.l	USER_FPCR(a6),fpcr/fpsr/fpiar
367	frestore	(a7)+
368	unlk		a6
369	bra.l		real_inex
370*
371* Since operr is only an E1 exception, there is no need to frestore
372* any state back to the fpu.
373*
374operr_exit:
375	movem.l		USER_DA(a6),d0-d1/a0-a1
376	fmovem.x	USER_FP0(a6),fp0-fp3
377	fmovem.l	USER_FPCR(a6),fpcr/fpsr/fpiar
378	unlk		a6
379	bra.l		fpsp_done
380
381	end
382