|
|
DataMuseum.dkPresents historical artifacts from the history of: Rational R1000/400 Tapes |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about Rational R1000/400 Tapes Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - downloadIndex: A T
Length: 28980 (0x7134)
Types: TextFile
Names: »ADAROOT_SHARED_ASM«
└─⟦afbc8121e⟧ Bits:30000532 8mm tape, Rational 1000, MC68020_OS2000 7_2_2
└─⟦77aa8350c⟧ »DATA«
└─⟦f794ecd1d⟧
└─⟦24d1ddd49⟧
└─⟦this⟧
; The use of this system is subject to the software license terms and
; conditions agreed upon between Rational and the Customer.
;
; Copyright 1988 by Rational.
;
; RESTRICTED RIGHTS LEGEND
;
; Use, duplication, or disclosure by the Government is subject to
; restrictions as set forth in subdivision (b)(3)(ii) of the Rights in
; Technical Data and Computer Software clause at 52.227-7013.
;
;
; Rational
; 3320 Scott Boulevard
; Santa Clara, California 95054-3197
;
; PROPRIETARY AND CONFIDENTIAL INFORMATION OF RATIONAL;
; USE OR COPYING WITHOUT EXPRESS WRITTEN AUTHORIZATION
; IS STRICTLY PROHIBITED. THIS MATERIAL IS PROTECTED AS
; AN UNPUBLISHED WORK UNDER THE U.S. COPYRIGHT ACT OF
; 1976. CREATED 1988. ALL RIGHTS RESERVED.
;
;
.module "ADAROOT_SHARED"
;
; This assembly file is the root of the ADA runtime support
; for an programs which may create tasks.
;
.include "^^standard_assembler_include_file"
.include "^^common.runtime_definitions"
.include "^^common.os2000_definitions"
comp_unit runtime_compunit
.sect ada_runtime_code,code,relocatable,alignment:=2
;
; Entry points from the elaboration code for a sequential program
;
.gbl.l _.start_sequential
.gbl.l __middle_sequential
.gbl.l _.finish_sequential
;
; Entry points from the elaboration code for a tasking program
;
.gbl.l _.start_tasking
.gbl.l __middle_tasking
.gbl.l _.finish_tasking
.gbl.l __process_exit ; called from task end
.gbl.l __undefined_trap ; referenced in module header
.gbl.l __get_fp ; return current frame pointer
.ext.l __root_finish_return
.ext.l __task_create_return
.ext.l __task_finish_return
.ext.l __rt_elaborate_indirect
.ext.l __rt_finalize_indirect
.ext.l __heap_ptr;
.ext.l __heap_size_var;
.ext.l __os_param_ptr;
.ext.l __os_param_size;
.ext.l __module_base_address
.ext.l __global_base
.ext.l __root_tcb
.ext.l __root_task_id
.ext.l __data_size_var
.ext.l __main_code_start_var
.ext.l __task_code_start_var
.ext.a __msgq_entry_pointer
.ext.a __process_descriptor_pointer
.ext.a __runtime_entry_pointer
.ext.l __report_fatal_error
.ext.l __issue_warning
.ext.l __main_handler_ferror
.ext.l __error_path
.ext.l __sequential_finalization
.ext.l __sequential_elaboration
.ext.l __tasking_elaboration
.ext.l __tasking_finalization
.ext.l __task_end
.ext.l __raise_exception
.ext.l __program_error
.ext.l __numeric_error
.ext.l __constraint_error
.ext.l __trace_exception
.ext.l __tasking_lock
.ext.l __serialization.acquire_lock
.ext.l __release_task_lock
.ext.l __set_exception
.ext.l __get_exception
.ext.l __set_exception_indirect
.ext.l __get_exception_indirect
.ext.l __abort_main_program
.ext.l __abort_main_indirect
.ext.l __sequential_delay_statement
.ext.l __tasking_delay_statement
.ext.l __tdlystm_indirect
.ext.l __sequential_signal_intercept
.ext.l __tasking_signal_intercept
.ext.l __signal_intercept_indirect
.ext.l __runtime_compatibility_value
;
; Definitions of 68881 trap enable bit assignments and rounding mode
;
bsun$enable equ 2#1000_0000_0000_0000#;
snan$enable equ 2#0100_0000_0000_0000#;
operr$enable equ 2#0010_0000_0000_0000#;
ovfl$enable equ 2#0001_0000_0000_0000#;
unfl$enable equ 2#0000_1000_0000_0000#;
dz$enable equ 2#0000_0100_0000_0000#;
inex2$enable equ 2#0000_0010_0000_0000#;
inex1$enable equ 2#0000_0001_0000_0000#;
m68881$traps equ operr$enable ! ovfl$enable ! dz$enable;
round$extended equ 2#0000_0000_0000_0000#;
round$single equ 2#0000_0000_0100_0000#;
round$double equ 2#0000_0000_1000_0000#;
round$nearest equ 2#0000_0000_0000_0000#;
round$zero equ 2#0000_0000_0001_0000#;
round$minf equ 2#0000_0000_0010_0000#;
round$pinf equ 2#0000_0000_0011_0000#;
m68881$round equ round$extended ! round$nearest
m68881$control equ m68881$traps ! m68881$round
;
; Return frame pointer one level up. Thus is A calls B which calls
; __get_fp, the value returned is the frame pointer for routine A.
;
subprogram sp_rt,sp.internal,linkage.none
.local
.align 2
__get_fp:
move.l a6,d0 ; get current fp
move.l (d0.l*1),d0 ; Get fp one level up
rts ; -> Done
;
\f
;
; Initial entry point from the program after fork;
; the global data pointer has already been setup
; in the unshared program code. The current process id
; has been moved from D0 to D4. Address to return
; to in the program on top of stack
;
subprogram sp_rt,sp.internal,linkage.none
_.start_sequential:
.local
lea (__sequential_elaboration,pc),a0 ; store indirection
move.l a0,(__rt_elaborate_indirect,a5) ; for runtime elab
lea (__sequential_finalization,pc),a0 ; store indirection
move.l a0,(__rt_finalize_indirect,a5) ; for runtime finalize
lea (set$current$exception,pc),a0 ; store indirection
move.l a0,(__set_exception_indirect,a5) ; for set_exception
lea (get$current$exception,pc),a0 ; store indirection
move.l a0,(__get_exception_indirect,a5) ; for get_exception
lea (__sequential_delay_statement,pc),a0 ; store indirection
move.l a0,(__tdlystm_indirect,a5) ; for delay_statement
lea (__sequential_signal_intercept,pc),a0 ; store indirection
move.l a0,(__signal_intercept_indirect,a5) ; for signal_intercept
bra.b common_start
subprogram sp_rt,sp.internal,linkage.none
_.start_tasking:
.local
lea (__tasking_elaboration,pc),a0 ; store indirection
move.l a0,(__rt_elaborate_indirect,a5) ; for runtime elab
lea (__tasking_finalization,pc),a0 ; store indirection
move.l a0,(__rt_finalize_indirect,a5) ; for runtime finalize
lea (__set_exception,pc),a0 ; store indirection
move.l a0,(__set_exception_indirect,a5) ; for set_exception
lea (__get_exception,pc),a0 ; store indirection
move.l a0,(__get_exception_indirect,a5) ; for get_exception
lea (__tasking_delay_statement,pc),a0 ; store indirection
move.l a0,(__tdlystm_indirect,a5) ; for delay_statement
lea (__tasking_signal_intercept,pc),a0 ; store indirection
move.l a0,(__signal_intercept_indirect,a5) ; for signal_intercept
lea (__abort_main_program,pc),a0 ; store indirection
move.l a0,(__abort_main_indirect,a5) ; for abort main
;
; setup base frame and exception handler
;
common_start:
.local
movea.l (sp)+,a0 ; a0 := return pc
lea.l (__root_tcb,a5),a4 ; compute address of root tcb
move.l a4,-(a7) ; push root tcb ptr on the stack;
clr.l -(a7) ; bogus return pc
pea (main_handler:16,pc) ; setup handler
clr.l -(a7) ; bogus saved fp
movea.l a7,a6 ; establish frame
move.l a0,-(sp) ; save return pc
;
; setup the unhandled exception message
;
move.w #elaboration$ferror,(__main_handler_ferror,a5)
;
; setup info in root tcb
;
move.l (__data_size_var,a5),d7 ; get program data area size
adda.l d7,a1 ; compute low stack bound
move.l a1,(tcb.stack_bounds.first,a4) ; save low stack bound
sub.l d7,d6 ; subtract data from total
sub.l d5,d6 ; subtract param size
move.l d6,(tcb.stack_bounds.size,a4) ; rest is stack size
lea.l (__main_code_start_var,a5),a0 ;
move.l a0,(tcb.code_start,a4) ; save code start pointer
move.l d4,(tcb.process_id,a4) ; save process id
move.l a5,(__global_base,a5) ; save global base register
move.l a2,(__os_param_ptr,a5) ; save parameter pointer
move.l d5,(__os_param_size,a5) ; save size of command line params
move.l a3,(__module_base_address,a5) ; save module base address
lea (__task_code_start:16,pc),a0 ; save code start
move.l a0,(__task_code_start_var,a5) ; for Activate_Offspring
move.l a4,(__root_task_id,a5) ; save ref to tcb for debugger
;
; Setup pointers from CPT to message queues and
; OS-2000 process descriptor; runtime entry table
; pointer was setup in user program at jump into
; this code.
;
;
move.l sp,d0 ; get current stack pointer
andi.l #(-a32_size),d0 ; mask for high order bits
move.l (cct_start + pi_cpt,d0),d1 ; get cpt address
move.l (cpt_msgq_pointer,d1),d2 ; get msgq table pointer
move.l d2,(__msgq_entry_pointer,a5) ; store pointer
movea.l (cpt_current_proc,d1),a0 ; get process dscptr pointer
move.l a0,(__process_descriptor_pointer,a5)
;
; Setup Ada information in OS-2000 process descriptor
; for the current process
;
; Current registers: A4 - Current Task Id (TCB pointer
; A1 - Low stack bound for task
; A0 - Address of process desc object
;
; The runtime is compiled without stack checks, so a cushion
; of stack space must be reserved to allow the most space
; consumptive runtime call to execute.
;
movea.l (a0),a0 ; get current process dsptr
move.l a4,(art$tsk_id,a0) ; store TCB pointer
move.l a4,(art$prgkey,a0) ; store TCB pointer as key
lea (runtime$stack$cushion,a1),a1 ; reserve stack cushion
move.l a1,(art$stk_lo,a0) ; store stack bound
clr.l (art$savefp,a0) ; clear saved frame pointer
;
; Check Standard I/O paths and open if not defined
;
$check_standard_input:
move.w #standard_input,d0 ; path number
move.w #ss_eof,d1 ; EOF function code
trap #os9_call ; make status call
.dc.w i$getstt
bcc.b $check_standard_output ; check for error
cmp.w #e$bpnum,d1 ; see if bad path error
bne.b $check_standard_output ; if not bad path, then ok
lea ($nil_device_name:16,pc),a0 ; open nil device
move.w #read_mode,d0 ; file access mode
trap #os9_call ; make open call
.dc.w i$open
$check_standard_output:
move.w #standard_output,d0 ; path number
move.w #ss_eof,d1 ; EOF function code
trap #os9_call ; make status call
.dc.w i$getstt
bcc.b $check_standard_error ; check for error
cmp.w #e$bpnum,d1 ; see if bad path error
bne.b $check_standard_error ; if not bad path, then ok
lea ($nil_device_name:16,pc),a0 ; open nil device
move.w #write_mode,d0 ; file access mode
trap #os9_call ; make open call
.dc.w i$open
$check_standard_error:
move.w #standard_error,d0 ; path number
move.w #ss_eof,d1 ; EOF function code
trap #os9_call ; make status call
.dc.w i$getstt
bcc.b $init_error_file ; check for error
cmp.w #e$bpnum,d1 ; see if bad path error
bne.b $init_error_file ; if not bad path, then ok
lea.l ($nil_device_name:16,pc),a0 ; open nil device
move.w #write_mode,d0 ; file access mode
trap #os9_call ; make open call
.dc.w i$open
;
; Initialize path to error message file
;
$init_error_file:
moveq.l #read_mode,d0 ; access mode = read
lea.l ($error_msg_file:16,pc),a0 ; pointer to file name
trap #os9_call
.dc.w i$open
bcc.b $got_emf ; check for errors
moveq.l #0,d0 ; error, so set path to 0
$got_emf:
move.w d0,(__error_path,a5) ; save path to error file
;
; Check if user program was linked with a compatible version
; of the Ada Runtime.
;
cmpi.b #compatibility_version,(__runtime_compatibility_value,a5)
beq.b $setup_trap_handlers ; program/runtime compatible
move.l #rt$incompatible$ferror,-(sp) ; incompatible!
bra.w report_error_and_die ; issue message and terminate
;
; Setup trap handler and signal intercept
;
$setup_trap_handlers:
movea.w #0,a0 ; use current stack
lea (trap$table:16,pc),a1 ; address of trap table
trap #os9_call ; make system call
.dc.w f$strap ; to setup trap table
bcc.b $setup_fpu ; check for errors
move.l #init$trap$handler$ferror,-(sp) ; if error then
bsr.l __report_fatal_error ; issure error message
$setup_fpu:
fmove.l #m68881$control,fpcr ; enable 68881 traps and rounding
lea (__signal_intercept:16,pc),a0 ; signal interceptor
movea.l a6,a1 ; save a6
movea.l a5,a6 ; ref to global data
trap #os9_call ; install signal
.dc.w f$icpt ; intercept routine
movea.l a1,a6 ; restore a6
;
; Create heap for the program
;
move.l (__Heap_Size_Var,a5),d0 ; get heap size to request
beq.b $no_heap ; if zero, don't attempt allocate
trap #os9_call ; make system call to allocate mem
.dc.w f$srqmem
bcc.b $heap_created ; if no error, then have memory
move.l #heap$create$warning,-(sp) ; else give warning msg
bsr.l __issue_warning ; about failure
$no_heap:
clr.l d0 ; zero heap values
movea.l d0,a2 ; clear pointer to heap
move.l d0,(__heap_size_var,a5) ; clear heap size var
$heap_created:
move.l a2,(__heap_ptr,a5) ; store pointer to heap
jsr ([__rt_elaborate_indirect,a5]) ; elaborate runtime
move.w #lib$exception$ferror,(__main_handler_ferror,a5)
rts
$error_msg_file: .asciz "/h0/sys/art_errmsg"
.align
$nil_device_name: .asciz "/nil"
.align
;
; Exception handler for unhandled exceptions
;
subprogram sp_rt,sp.internal,linkage.none
main_handler:
.local
nop
cmpi.l #0,d0 ; is this abort exception?
beq.b main_suicide
move.w (__main_handler_ferror,a5),d1
move.l d1,-(sp)
bsr.l __report_fatal_error
main_suicide:
move.w #finalization$ferror,(__main_handler_ferror,a5)
jsr ([__rt_finalize_indirect,a5]) ; do runtime finalization
moveq #some$error,d1
trap #os9_call
.dc.w f$exit
;
; Finish entry point from program
;
subprogram sp_rt,sp.internal,linkage.simple
_.finish_sequential:
_.finish_tasking:
move.w #finalization$ferror,(__main_handler_ferror,a5)
jsr ([__rt_finalize_indirect,a5]) ; do runtime finalization
rts
;
; Called from the program after elaboration of library units
; but before the call to the main program.
;
subprogram sp_rt,sp.internal,linkage.simple
__middle_sequential:
__middle_tasking:
move.w #main$exception$ferror,(__main_handler_ferror,a5)
rts
;
\f
;
; Set and Get exception for sequential programs
;
; procedure Set_Current_Exception (Id : System.Address);
;
subprogram sp_rt,sp.internal,linkage.simple
set$current$exception:
move.l (4,sp),(__root_tcb+tcb.exception_id,a5)
rtd #4
;
; function Get_Current_Exception return System.Address;
;
subprogram sp_rt,sp.internal,linkage.simple
get$current$exception:
move.l (__root_tcb+tcb.exception_id,a5),d0
rts
;
\f
;
; This is one jump away from the entry point for the module
; that is passed to the F$Fork call whenever an Ada task is
; activated. Interesting register values at this point include:
;
; A1 - high end of our parameter area (= base of our stack)
; A7- low end of our parameter area (= high end of our data area)
; D0 - Our Os9 process id
; D6 - total memory allocation (A1 - D6 = low end our data area)
;
; Format of parameter area is defined by Tasking_Types.Fork_Parameters:
; This code address (32 bits), followed by the base address for
; global data (32 bits), followed by the address of our TCB (32 bits)
; The TCB is completely filled in, except for the Stack_Bounds field,
; which we initialize here. The Activations_In_Progress field contains
; the task's static link.
; The last object in Fork_Parameters is the address of an instance
; variable. This is zero unless the task is declared in the outer
; scope of a shared code generic, in which case it needs the IV to
; reference objects declared in the outermost scope (which go in the
; instance variable). If the Instance_Variable field of Fork_Parameters
; is non-null, then the task is expecting the IV to be passed as its
; second parameter.
;
subprogram sp_rt,sp.internal,linkage.none
__task_code_start:
.local
movea.l (12,a7), a3 ; the instance variable
movea.l (8,a7),a4 ; our TCB's address
movea.l (4,a7),a5 ; base address for global data
clr.l (a7)
pea (ada$task$exception$handler,pc) ; establish handler
clr.l -(a7) ; bogus saved fp
movea.l a7,a6 ; establish frame pointer
move.l (tcb.activations_in_progress,a4),-(a7) ; static link
tst.l a3 ; Is the IV null?
beq.l $push_tcb
move.l a3,-(a7) ; if not, push it on the stack
$push_tcb:
move.l a4,-(a7) ; push TCB ref on stack
move.l a4,(12,a6) ; Put TCB where debugger expects it
move.l d0,(tcb.process_id,a4) ; set process id in TCB
suba.l d6,a1 ; get low stack bound
move.l a1,(tcb.stack_bounds.first,a4) ; set low stack bound in TCB
move.l d6,(tcb.stack_bounds.size,a4) ; set stack size in TCB
;
; Setup Ada information in OS-2000 process descriptor
; for the current process
;
; Current registers: A4 - Current Task Id (TCB pointer
; A1 - Low stack bound for task
;
; The runtime is compiled without stack checks, so a cushion
; of stack space must be reserved to allow the most space
; consumptive runtime call to execute.
;
; Also, clear parent and sibling id's in process descriptor
; so that descriptor will be reclaimed when process EXIT's.
;
movea.l ([__process_descriptor_pointer,a5]),a0 ; get current descriptor
move.l a4,(art$tsk_id,a0) ; store TCB pointer
lea (runtime$stack$cushion,a1),a1 ; reserve stack cushion
move.l a1,(art$stk_lo,a0) ; store stack bound
clr.l (art$savefp,a0) ; clear saved frame pointer
lea (__root_tcb,a5),a1 ; compute root tcb addr
move.l a1,(art$prgkey,a0) ; store as program key
clr.w (p$pid,a0) ; clear parent id
clr.w (p$sid,a0) ; clear sibling id
;
; Setup trap handler for process
;
movea.w #0,a0 ; use current stack
lea (trap$table,pc),a1 ; address of trap table
trap #os9_call ; make system call
.dc.w f$strap ; to setup trap table
bcc.b $traps_done ; check error status
move.l #init$trap$handler$ferror,-(sp) ; if error
bsr.l __report_fatal_error ; then give error message
$traps_done:
fmove.l #m68881$control,fpcr ; enable 68881 traps/rounding
lea.l (__signal_intercept,pc),a0 ; signal interceptor
movea.l a6,a1 ; save a6
movea.l a5,a6 ; ref to global data
trap #os9_call ; install signal handler
.dc.w f$icpt
movea.l a1,a6 ; restore a6
pea (__tasking_lock,a5) ; pass the lock
bsr.l __serialization.acquire_lock ; synchronize activation group
bsr.l __release_task_lock ; so low priority member cannot
; starve higer priority
movea.l (-4,a6),a1 ; pass static link in a1
jmp ([__task_create_return,a5]) ; branch to user program
;
; Exception handler for an Ada task
;
subprogram sp_rt,sp.internal,linkage.simple
ada$task$exception$handler:
nop
tst.l d0 ; is this an abort exception
beq.b $task_suicide
move.l #task$exception$warning,-(sp) ; unhandle exception warning
statement 0,0,1
bsr.l __issue_warning
statement 0,0,0
$task_suicide:
bsr.l __task_end ; suicide (should not return)
;
; procedure Suicide;
;
subprogram sp_rt,sp.internal,linkage.simple
__process_exit:
jmp ([__task_finish_return,a5]) ; branch to user for exit
;
;
;
;
.local
trap$table:
$e$0: .dc.w t_adderr, program_error_trap - ($e$0 + 4);
$e$1: .dc.w t_buserr, program_error_trap - ($e$1 + 4)
$e$2: .dc.w t_illins, program_error_trap - ($e$2 + 4)
$e$3: .dc.w t_chk, constraint_error_trap - ($e$3 + 4)
$e$4: .dc.w t_trapv, numeric_error_trap - ($e$4 + 4)
$e$5: .dc.w t_fpdivzer, numeric_error_trap - ($e$5 + 4)
$e$6: .dc.w t_fpinxact, numeric_error_trap - ($e$6 + 4)
$e$7: .dc.w t_fpnotnum, numeric_error_trap - ($e$7 + 4)
$e$8: .dc.w t_fpoprerr, numeric_error_trap - ($e$8 + 4)
$e$9: .dc.w t_fpoverfl, numeric_error_trap - ($e$9 + 4)
$e$a: .dc.w t_fpundrfl, numeric_error_trap - ($e$a + 4)
$e$b: .dc.w t_fpunordc, numeric_error_trap - ($e$b + 4)
$e$c: .dc.w t_zerdiv, numeric_error_trap - ($e$c +4)
.dc.w -1
;
; Unhandled trap handler
;
subprogram sp_rt,sp.internal,linkage.trap
__unexpected_trap:
__undefined_trap:
.local
statement 8,0,0 ; return pc in A0
bsr.b restore_trap_registers
statement 1,0,0 ; return pc in D1
movea.l a1,a7 ; restore stack pointer
move.l d1,-(sp) ; push pc on stack
statement 16,0,0
clr.l -(sp) ; push null for exception name
statement 16,0,1
bsr.l __trace_exception ; go to tracing routine
statement 16,0,0
clr.l -(sp) ; push null for exception name
statement 16,0,1
move.l #unhandled$main$trap$ferror,-(sp)
statement 16,0,2
report_error_and_die:
bsr.w __report_fatal_error
moveq #some$error,d1
trap #os9_call
.dc.w f$exit
;
; This subprogram restores register d2-d7/a2-a7
; from the OS2000 provided save area
;
subprogram sp_rt,sp.internal,linkage.trap
restore_trap_registers:
.local
statement 8,0,0 ; return pc in A0
move.l a0, d1 ; save raise PC in d1
statement 1,0,0 ; return pc in D1
movea.l a5,a0 ; get address of register save area
addq.l #8,a0 ; skip d0, d1
movem.l (a0)+,d2-d7 ; restore data registers
addq.l #8,a0 ; skip a0, a1
movem.l (a0)+,a2-a6 ; restore address registers
rts
;
; trap handler for generating Constraint_Error
;
subprogram sp_rt,sp.internal,linkage.trap
constraint_error_trap:
.local
statement 8,0,0 ; raise pc in A0
bsr.b restore_trap_registers
statement 1,0,0 ; raise pc in D1
movea.l a1,a7 ; restore stack pointer
move.l #__constraint_error,d0
add.l a5,d0
move.l d1,-(a7) ; push return pc for "call"
statement 16,0,0
fnop ; synchronize fpu exceptions
bra.l __Raise_Exception ; raise exception
;
; trap handler for generating Program_Error
;
subprogram sp_rt,sp.internal,linkage.trap
program_error_trap:
.local
statement 8,0,0 ; raise pc in A0
bsr.b restore_trap_registers
statement 1,0,0 ; raise pc in D1
movea.l a1,a7 ; restore stack pointer
move.l #__program_error,d0
add.l a5,d0
move.l d1,-(a7) ; push return pc for "call"
statement 16,0,0
fnop ; synchronize fpu exceptions
bra.l __Raise_Exception ; raise exception
;
; trap handler for generating Numeric_Error
;
subprogram sp_rt,sp.internal,linkage.trap
numeric_error_trap:
statement 8,0,0 ; return pc in a0
bsr.b restore_trap_registers
statement 1,0,0 ; raise pc in d1
movea.l a1,a7 ; restore stack pointer
move.l #__numeric_error,d0
add.l a5,d0
move.l d1,-(a7) ; push return pc for "call"
statement 16,0,0
fnop ; in case pending flt exception
bra.l __raise_exception ; raise exception
;
; trap handler for signals
;
subprogram sp_rt,sp.internal,linkage.none
__signal_intercept:
move.l a5,-(sp) ; save a5
movea.l a6,a5
clr.l d0
move.w d1,d0
move.l d0,-(sp)
movea.l (__signal_intercept_indirect,a5),a0
jsr (a0)
movea.l (sp)+,a5 ; restore a5
trap #os9_call
.dc.w f$rte
end_subprograms
.end