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