skeleton.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*	skeleton.sa 3.2 4/26/91
33*
34*	This file contains code that is system dependent and will
35*	need to be modified to install the FPSP.
36*
37*	Each entry point for exception 'xxxx' begins with a 'jmp fpsp_xxxx'.
38*	Put any target system specific handling that must be done immediately
39*	before the jump instruction.  If there no handling necessary, then
40*	the 'fpsp_xxxx' handler entry point should be placed in the exception
41*	table so that the 'jmp' can be eliminated. If the FPSP determines that the
42*	exception is one that must be reported then there will be a
43*	return from the package by a 'jmp real_xxxx'.  At that point
44*	the machine state will be identical to the state before
45*	the FPSP was entered.  In particular, whatever condition
46*	that caused the exception will still be pending when the FPSP
47*	package returns.  Thus, there will be system specific code
48*	to handle the exception.
49*
50*	If the exception was completely handled by the package, then
51*	the return will be via a 'jmp fpsp_done'.  Unless there is 
52*	OS specific work to be done (such as handling a context switch or
53*	interrupt) the user program can be resumed via 'rte'.
54*
55*	In the following skeleton code, some typical 'real_xxxx' handling
56*	code is shown.  This code may need to be moved to an appropriate
57*	place in the target system, or rewritten.
58*	
59
60SKELETON	IDNT    2,1 Motorola 040 Floating Point Software Package
61
62	section 15
63*
64*	The following counters are used for standalone testing
65*
66sigunimp	dc.l	0
67sigbsun		dc.l	0
68siginex		dc.l	0
69sigdz		dc.l	0
70sigunfl		dc.l	0
71sigovfl		dc.l	0
72sigoperr	dc.l	0
73sigsnan		dc.l	0
74sigunsupp	dc.l	0
75
76	section 8
77
78	include	fpsp.h
79
80	xref	b1238_fix
81
82*
83*	Divide by Zero exception
84*
85*	All dz exceptions are 'real', hence no fpsp_dz entry point.
86*
87	xdef	dz
88	xdef	real_dz
89dz:
90real_dz:
91	link		a6,#-LOCAL_SIZE
92	fsave		-(sp)
93	bclr.b		#E1,E_BYTE(a6)
94	frestore	(sp)+
95	unlk		a6
96
97	add.l	#1,sigdz		;for standalone testing
98
99	rte
100*
101*	Inexact exception
102*
103*	All inexact exceptions are real, but the 'real' handler
104*	will probably want to clear the pending exception.
105*	The provided code will clear the E3 exception (if pending), 
106*	otherwise clear the E1 exception.  The frestore is not really
107*	necessary for E1 exceptions.
108*
109* Code following the 'inex' label is to handle bug #1232.  In this
110* bug, if an E1 snan, ovfl, or unfl occured, and the process was
111* swapped out before taking the exception, the exception taken on
112* return was inex, rather than the correct exception.  The snan, ovfl,
113* and unfl exception to be taken must not have been enabled.  The
114* fix is to check for E1, and the existence of one of snan, ovfl,
115* or unfl bits set in the fpsr.  If any of these are set, branch
116* to the appropriate  handler for the exception in the fpsr.  Note
117* that this fix is only for d43b parts, and is skipped if the
118* version number is not $40.
119* 
120*
121	xdef	real_inex
122	xdef	inex
123inex:
124	link		a6,#-LOCAL_SIZE
125	fsave		-(sp)
126	cmpi.b		#VER_40,(sp)		;test version number
127	bne.b		not_fmt40
128	fmove.l		fpsr,-(sp)
129	btst.b		#E1,E_BYTE(a6)		;test for E1 set
130	beq.b		not_b1232
131	btst.b		#snan_bit,2(sp) ;test for snan
132	beq		inex_ckofl
133	add.l		#4,sp
134	frestore	(sp)+
135	unlk		a6
136	bra		snan
137inex_ckofl:
138	btst.b		#ovfl_bit,2(sp) ;test for ovfl
139	beq		inex_ckufl 
140	add.l		#4,sp
141	frestore	(sp)+
142	unlk		a6
143	bra		ovfl
144inex_ckufl:
145	btst.b		#unfl_bit,2(sp) ;test for unfl
146	beq		not_b1232
147	add.l		#4,sp
148	frestore	(sp)+
149	unlk		a6
150	bra		unfl
151
152*
153* We do not have the bug 1232 case.  Clean up the stack and call
154* real_inex.
155*
156not_b1232:
157	add.l		#4,sp
158	frestore	(sp)+
159	unlk		a6
160
161real_inex:
162
163	add.l		#1,siginex		;for standalone testing
164
165	link		a6,#-LOCAL_SIZE
166	fsave		-(sp)
167not_fmt40:
168	bclr.b		#E3,E_BYTE(a6)		;clear and test E3 flag
169	beq.b		inex_cke1
170*
171* Clear dirty bit on dest resister in the frame before branching
172* to b1238_fix.
173*
174	movem.l		d0/d1,USER_DA(a6)
175	bfextu		CMDREG1B(a6){6:3},d0		;get dest reg no
176	bclr.b		d0,FPR_DIRTY_BITS(a6)	;clr dest dirty bit
177	bsr.l		b1238_fix		;test for bug1238 case
178	movem.l		USER_DA(a6),d0/d1
179	bra.b		inex_done
180inex_cke1:
181	bclr.b		#E1,E_BYTE(a6)
182inex_done:
183	frestore	(sp)+
184	unlk		a6
185	rte
186	
187*
188*	Overflow exception
189*
190	xref	fpsp_ovfl
191	xdef	real_ovfl
192	xdef	ovfl
193ovfl:
194	jmp	fpsp_ovfl
195real_ovfl:
196
197	add.l		#1,sigovfl		;for standalone testing
198
199	link		a6,#-LOCAL_SIZE
200	fsave		-(sp)
201	bclr.b		#E3,E_BYTE(a6)		;clear and test E3 flag
202	bne.b		ovfl_done
203	bclr.b		#E1,E_BYTE(a6)
204ovfl_done:
205	frestore	(sp)+
206	unlk		a6
207	rte
208	
209*
210*	Underflow exception
211*
212	xref	fpsp_unfl
213	xdef	real_unfl
214	xdef	unfl
215unfl:
216	jmp	fpsp_unfl
217real_unfl:
218
219	add.l		#1,sigunfl		;for standalone testing
220
221	link		a6,#-LOCAL_SIZE
222	fsave		-(sp)
223	bclr.b		#E3,E_BYTE(a6)		;clear and test E3 flag
224	bne.b		unfl_done
225	bclr.b		#E1,E_BYTE(a6)
226unfl_done:
227	frestore	(sp)+
228	unlk		a6
229	rte
230	
231*
232*	Signalling NAN exception
233*
234	xref	fpsp_snan
235	xdef	real_snan
236	xdef	snan
237snan:
238	jmp	fpsp_snan
239real_snan:
240	link		a6,#-LOCAL_SIZE
241	fsave		-(sp)
242	bclr.b		#E1,E_BYTE(a6)	;snan is always an E1 exception
243	frestore	(sp)+
244	unlk		a6
245
246	add.l		#1,sigsnan		;for standalone testing
247	rte
248	
249*
250*	Operand Error exception
251*
252	xref	fpsp_operr
253	xdef	real_operr
254	xdef	operr
255operr:
256	jmp	fpsp_operr
257real_operr:
258	link		a6,#-LOCAL_SIZE
259	fsave		-(sp)
260	bclr.b		#E1,E_BYTE(a6)	;operr is always an E1 exception
261	frestore	(sp)+
262	unlk		a6
263
264	add.l		#1,sigoperr		;for standalone testing
265
266	rte
267	
268*
269*	BSUN exception
270*
271*	This sample handler simply clears the nan bit in the FPSR.
272*
273	xref	fpsp_bsun
274	xdef	real_bsun
275	xdef	bsun
276bsun:
277	jmp	fpsp_bsun
278real_bsun:
279	link		a6,#-LOCAL_SIZE
280	fsave		-(sp)
281	bclr.b		#E1,E_BYTE(a6)	;bsun is always an E1 exception
282	fmove.l		FPSR,-(sp)
283	bclr.b		#nan_bit,(sp)
284	fmove.l		(sp)+,FPSR
285	frestore	(sp)+
286	unlk		a6
287
288	add.l		#1,sigbsun		;for standalone testing
289
290	rte
291
292*
293*	F-line exception
294*
295*	A 'real' F-line exception is one that the FPSP isn't supposed to 
296*	handle. E.g. an instruction with a co-processor ID that is not 1.
297*
298*
299	xref	fpsp_fline
300	xdef	real_fline
301	xdef	fline
302fline:
303	jmp	fpsp_fline
304real_fline:
305
306	add.l		#1,sigunimp		;for standalone testing
307
308	rte
309
310*
311*	Unsupported data type exception
312*
313	xref	fpsp_unsupp
314	xdef	real_unsupp
315	xdef	unsupp
316unsupp:
317	jmp	fpsp_unsupp
318real_unsupp:
319	link		a6,#-LOCAL_SIZE
320	fsave		-(sp)
321	bclr.b		#E1,E_BYTE(a6)	;unsupp is always an E1 exception
322	frestore	(sp)+
323	unlk		a6
324
325	add.l		#1,sigunsupp		;for standalone testing
326
327	rte
328
329*
330*	Trace exception
331*
332	xdef	real_trace
333real_trace:
334	rte
335
336*
337*	fpsp_fmt_error --- exit point for frame format error
338*
339*	The fpu stack frame does not match the frames existing
340*	or planned at the time of this writing.  The fpsp is
341*	unable to handle frame sizes not in the following
342*	version:size pairs:
343*
344*	{4060, 4160} - busy frame
345*	{4028, 4130} - unimp frame
346*	{4000, 4100} - idle frame
347*
348*	This entry point simply holds an f-line illegal value.  
349*	Replace this with a call to your kernel panic code or
350*	code to handle future revisions of the fpu.
351*
352	xdef	fpsp_fmt_error
353fpsp_fmt_error:
354
355	dc.l	$f27f0000	;f-line illegal 
356
357*
358*	fpsp_done --- FPSP exit point
359*
360*	The exception has been handled by the package and we are ready
361*	to return to user mode, but there may be OS specific code
362*	to execute before we do.  If there is, do it now.
363*
364*
365	xdef	fpsp_done
366fpsp_done:
367	rte
368
369*
370*	mem_write --- write to user or supervisor address space
371*
372* Writes to memory while in supervisor mode.  copyout accomplishes
373* this via a 'moves' instruction.  copyout is a UNIX SVR3 (and later) function.
374* If you don't have copyout, use the local copy of the function below.
375*
376*	a0 - supervisor source address
377*	a1 - user destination address
378*	d0 - number of bytes to write (maximum count is 12)
379*
380* The supervisor source address is guaranteed to point into the supervisor
381* stack.  The result is that a UNIX
382* process is allowed to sleep as a consequence of a page fault during
383* copyout.  The probability of a page fault is exceedingly small because
384* the 68040 always reads the destination address and thus the page
385* faults should have already been handled.
386*
387* If the EXC_SR shows that the exception was from supervisor space,
388* then just do a dumb (and slow) memory move.  In a UNIX environment
389* there shouldn't be any supervisor mode floating point exceptions.
390*
391	xdef	mem_write
392mem_write:
393	btst.b	#5,EXC_SR(a6)	;check for supervisor state
394	beq.b	user_write
395super_write:
396	move.b	(a0)+,(a1)+
397	subq.l	#1,d0
398	bne.b	super_write
399	rts
400user_write:
401	move.l	d1,-(sp)	;preserve d1 just in case
402	move.l	d0,-(sp)
403	move.l	a1,-(sp)
404	move.l	a0,-(sp)
405	jsr		copyout
406	add.w	#12,sp
407	move.l	(sp)+,d1
408	rts
409*
410*	mem_read --- read from user or supervisor address space
411*
412* Reads from memory while in supervisor mode.  copyin accomplishes
413* this via a 'moves' instruction.  copyin is a UNIX SVR3 (and later) function.
414* If you don't have copyin, use the local copy of the function below.
415*
416* The FPSP calls mem_read to read the original F-line instruction in order
417* to extract the data register number when the 'Dn' addressing mode is
418* used.
419*
420*Input:
421*	a0 - user source address
422*	a1 - supervisor destination address
423*	d0 - number of bytes to read (maximum count is 12)
424*
425* Like mem_write, mem_read always reads with a supervisor 
426* destination address on the supervisor stack.  Also like mem_write,
427* the EXC_SR is checked and a simple memory copy is done if reading
428* from supervisor space is indicated.
429*
430	xdef	mem_read
431mem_read:
432	btst.b	#5,EXC_SR(a6)	;check for supervisor state
433	beq.b	user_read
434super_read:
435	move.b	(a0)+,(a1)+
436	subq.l	#1,d0
437	bne.b	super_read
438	rts
439user_read:
440	move.l	d1,-(sp)	;preserve d1 just in case
441	move.l	d0,-(sp)
442	move.l	a1,-(sp)
443	move.l	a0,-(sp)
444	jsr		copyin
445	add.w	#12,sp
446	move.l	(sp)+,d1
447	rts
448
449*
450* Use these routines if your kernel doesn't have copyout/copyin equivalents.
451* Assumes that D0/D1/A0/A1 are scratch registers. copyout overwrites DFC,
452* and copyin overwrites SFC.
453*
454copyout:
455	move.l	4(sp),a0	; source
456	move.l	8(sp),a1	; destination
457	move.l	12(sp),d0	; count
458	sub.l	#1,d0		; dec count by 1 for dbra
459	move.l	#1,d1
460	movec	d1,DFC		; set dfc for user data space
461moreout:
462	move.b	(a0)+,d1	; fetch supervisor byte
463	moves.b	d1,(a1)+	; write user byte
464	dbf.w	d0,moreout
465	rts
466
467copyin:
468	move.l	4(sp),a0	; source
469	move.l	8(sp),a1	; destination
470	move.l	12(sp),d0	; count
471	sub.l	#1,d0		; dec count by 1 for dbra
472	move.l	#1,d1
473	movec	d1,SFC		; set sfc for user space
474morein:
475	moves.b	(a0)+,d1	; fetch user byte
476	move.b	d1,(a1)+	; write supervisor byte
477	dbf.w	d0,morein
478	rts
479
480	end
481