Category : C Source Code
Archive   : RTX.ZIP
Filename : REGS.ASM

 
Output of file : REGS.ASM contained in archive : RTX.ZIP
title "rtx register support"
page ,132

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Interrupt/ Register Support for RTX ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; (C) Copyright, 1991. Mike Podanoffsky ;
; All Rights Reserved. ;
; ;
; Technical questions: 508/ 454-1620. ;
;.......................................................;

include stddefs.asm

rtx_text segment word public 'CODE'
rtx_text ends

reg_supp segment para public 'CODE'
assume cs:reg_supp,ds:reg_supp,es:reg_supp,ss:reg_supp

public insideDos ;switch used when in Dos
public ischeduler ;iret scheduler call
public scheduler ;far call scheduler call
public setClockInterrupt ;tells clock ISR when to int
public keyboardEventFct ;keyboard event function

public condenableInts ;allow ints on cond
public enableInts ;enable interrupts
public disableInts ;disable interrupts
public enableSched ;enable scheduler
public disableSched ;disable scheduler

public save_initregs ;used to init a task's stack
public init_IntTraps ;initial state interrupt traps
public restore_IntTraps ;restore interrupt traps

extrn terminateTask_id:far
extrn scheduleTask:far
extrn saveCurrentTask_Stack:far
extrn returntask_StackFrame:far
extrn waitKbdEvent:far
extrn setKbdEvent:far
extrn getPriority:far
extrn setPriority:far
extrn countDown_Timers:far
extrn showcounts:far


;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Flags/ Storage Definitions ;
;.......................................................;

insideDos: dw 0
schedulerPending: dw 0
Rtx_DataSegment: dw 0


_originalDosTrap: dd 0
_originalTickInt: dd 0
_originalKbdSvcTrap: dd 0
_originalKbdHdwTrap: dd 0
_originalScrnTrap: dd 0

total_ints: dw 0
_ClockArmValue: dd 0


;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Macro Definitions. ;
;.......................................................;

_Int macro loc

inc word ptr cs:[insideDos]

pushf
call dword ptr cs:[loc] ;keep rentrancy problems down.
call enableSched

endm


;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; save_initregs ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Initializes stack for task so that it appears sus- ;
; pended to the scheduler. ;
; ;
; void far * pascal save_initregs ;
; ( void far * stack, ;
; void far * start_addr, ;
; void far * argument, ;
; int task_id ); ;
; ;
;.......................................................;

entry save_initregs ;emulates Pascal conventions
;
arg __task_id ; int task_id
darg __argument ; void far * argument,
darg __start_addr ; void far *start_addr,
darg __stack ; void far * stack,

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; order of items stored to task's stack
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
_task_id equ 40
_argument equ 36 ;void far *
_taskExit equ 32 ;task exit address

_start_addr equ 28 ;start address
_pushf equ 26 ;push flag emulation
_push_ax equ 24 ;ax
_push_bx equ 22 ;bx
_push_cx equ 20 ;cx
_push_dx equ 18 ;dx
_push_si equ 16 ;si
_push_di equ 14 ;di
_push_bp equ 12 ;bp

_push_ds equ 10 ;ds
_push_es equ 08 ;es

_push_dta equ 04 ;dta
_push_stackf equ 00 ;null stack frame pointer(req'd )

FLAGS_VALUE equ 0246h ;ei zr nc


;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; execution starts here.
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
saveSegments

push ds
pop es ;insure es: = ds:
getdarg ds,bx,__stack ;where we'll emulate this.

sub bx,128 ;disk transfer address
push bx
push ds ;ds:bx

sub bx,_task_id+2 ;total arguments we'll store

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; task stack will contain task_id, return address, ...
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
getarg ax,__task_id ;
mov word ptr _task_id [bx],ax

getdarg dx,ax,__argument
mov word ptr _argument+2 [bx],dx
mov word ptr _argument [bx],ax

mov word ptr _taskExit+2 [bx], seg taskExit
mov word ptr _taskExit [bx], offset taskExit

mov word ptr _pushf [bx], FLAGS_VALUE ;flags.

getdarg dx,ax,__start_addr
mov word ptr _start_addr+2 [bx],dx
mov word ptr _start_addr [bx],ax

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; now save on stack ALL registers
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
xor ax,ax
mov word ptr _push_ax [bx],ax
mov word ptr _push_bx [bx],ax
mov word ptr _push_cx [bx],ax
mov word ptr _push_dx [bx],ax
mov word ptr _push_si [bx],ax
mov word ptr _push_di [bx],ax
mov word ptr _push_bp [bx],ax

mov word ptr _push_ds [bx],ss
mov word ptr _push_es [bx],ss

pop word ptr _push_dta [bx] ; seg (dta)
pop word ptr _push_dta + 2 [bx] ; address

xor ax,ax
mov word ptr _push_stackf [bx],ax ; seg (stack frame)
mov word ptr _push_stackf+ 2 [bx],ax ; address

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; return adjusted stack address
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
mov dx,ds
mov ax,bx ; dx:ax contain remaining stack.

restoreSegments
return pascal

save_initregs endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; scheduler ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; No parameters. ;
; ;
; Will suspend current task, schedule next task. ;
; See related function: ischedule() for isr calls. ;
; ;
;.......................................................;

scheduler proc far

pushf ;save flags
cli ;stop interrupts
cmp word ptr cs:[ insideDos ],0 ;inside DOS ?
jz scheduler_04 ;don't schedule -->
mov word ptr cs:[schedulerPending],-1 ;say we'll stay pending
jmp scheduler_40 ;exit -->

scheduler_04:
inc word ptr cs:[ insideDos ]
sti ;its safe to interr now

SaveRegisters

callDos GetDiskTransferAddr
push bx
push es ; save dta on stack.

mov ds, word ptr cs:[Rtx_DataSegment]
mov es, word ptr cs:[Rtx_DataSegment]

cli
call rtx_text:returntask_StackFrame
push dx ;save current stack frame.
push ax

mov dx,ss
mov ax,sp
push dx
push ax
call rtx_text:saveCurrentTask_Stack
sti

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; round robin task within priority
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

xor dx,dx
push dx
push dx ;NULL pointer means curr task
call rtx_text:getPriority ;return priority
or ax,ax
jz scheduler_32

xor dx,dx
push dx
push dx ;NULL pointer means curr task
push ax ;reset priority
call rtx_text:setPriority

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; if return, stack switch
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
scheduler_32:
call rtx_text:scheduleTask

mov cx,ax
or cx,dx ;NULL value ?
jnz scheduler_36temp ;don't switch stacks -->
int 3
jmp scheduler_38

scheduler_36temp:
cli ;switch task stacks.
mov ss,dx
mov sp,ax

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; if return, stack switch
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
scheduler_38:
call rtx_text:saveCurrentTask_Stack ;restore stack frame.
call rtx_text:showcounts

sti ;ok ints now

pop ds ;restore dta.
pop dx
callDos SetDiskTransferAddr

RestoreRegisters
dec word ptr cs:[insideDos]
mov word ptr cs:[schedulerPending],0

scheduler_40:
popf ;this will restore ints
ret

scheduler endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; scheduler ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; No parameters. ;
; ;
; Will suspend current task, schedule next task. ;
; Performs an iret. Some ISRs may find this call ;
; preferable. ;
; ;
;.......................................................;

ischeduler proc far

call scheduler
iret
ischeduler endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; taskExit() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; This process is called whenever a task terminates. ;
; Calls scheduler to release task. ;
; ;
;.......................................................;

taskExit proc far
mov bp,sp ;didn't get here through a call
mov dx,word ptr [bp] ;should be task_id

; switch to temp stack, then ...
cli
mov ds, word ptr cs:[Rtx_DataSegment]
mov ax,seg temp_stack
mov ss,ax
mov sp,offset temp_stack

sti

push dx ;copy to stack
call rtx_text:terminateTask_id ;terminate task

taskExit_08:
call scheduler
jmp taskExit_08

taskExit endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; enableSched ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; No Parameters. ;
; ;
; The flag insideDos is used to prevent the scheduler ;
; from running. This performs similar to disabling ;
; interrupts, except only the scheduler is disabled. ;
; ;
;.......................................................;

enableSched proc far

pushf
dec word ptr cs:[ insideDos ]
jnz enableSched_08 ;still busy -->
cmp word ptr cs:[schedulerPending],0
jz enableSched_08 ;not pending -->

call scheduler

enableSched_08: popf
ret

enableSched endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; disableSched ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; No Parameters. ;
; ;
; The flag insideDos is used to prevent the scheduler ;
; from running. This performs similar to disabling ;
; interrupts, except only the scheduler is disabled. ;
; ;
;.......................................................;

disableSched proc far

inc word ptr cs:[ insideDos ]
ret

disableSched endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; enableInts() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Enables interrupts for C programs. ;
; ;
;.......................................................;

enableInts proc far

sti
ret

enableInts endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; disableInts() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Disables interrupts for C programs. ;
; ;
;.......................................................;

disableInts proc far

pushf
pop ax ;copy flags to ax.
and ax,_flags_if
jz disableInts_08 ;if ints were disabled -->
mov ax,1 ;if ints are enabled.

disableInts_08:
cli
ret

disableInts endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; condenableInts() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Conditional enables interrupts. Use disableInts to ;
; disable interrupts. This is a convenience function. ;
; ;
;.......................................................;

entry condenableInts ;emulates Pascal conventions
;
arg __condition ; int previous status

getarg ax, __condition
or ax,ax
jz condenableInts_08
sti

condenableInts_08:
return pascal

condenableInts endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; setClockInterrupt ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; call with long argument on stack. ;
; ;
; argument will have value of clock when the clock ;
; isr will call scheduler. ;
; ;
; push ax ;least signif word ;
; push dx ;most signif word ;
; call setClockInterrupt ;
; ;
;.......................................................;

entry setClockInterrupt ;emulates Pascal conventions
darg __argument ; void far * argument,

getdarg dx,ax,__argument

mov word ptr cs:[ _ClockArmValue + 2 ], dx
mov word ptr cs:[ _ClockArmValue ], ax
return pascal

setClockInterrupt endp

;'int 08'''''''''''''''''''''''''''''''''''''''''''''''';
; TimerTick ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; This ISR is called every clock tick (int 08) ;
; If the current clock value at interrupt equals or ;
; passes the next required clock value, the scheduler ;
; is called to determine what action is required next. ;
; ;
;.......................................................;

TimerTick proc far

push ax
push bx
push dx
push ds

_Int _originalTickInt ;emulate int call
inc word ptr cs:[ total_ints ]

;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
; see if min timer value expired.
;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
mov ax,40h
mov ds,ax
mov bx, 6Ch

mov ax,word ptr [ bx ]
mov dx,word ptr [ bx + 2 ]

push cs
pop ds ; set ds to current.
sub ax,word ptr [ _ClockArmValue ]
sbb dx,word ptr [ _ClockArmValue + 2 ]
jg TimerTick_40

sti
xor ax,ax
mov word ptr [ _ClockArmValue ],ax
mov word ptr [ _ClockArmValue + 2 ],ax

saveRegisters
mov ds, word ptr cs:[Rtx_DataSegment]
call rtx_text:countDown_Timers ;see if timers elapsed
call scheduler ;see if task time slice
restoreRegisters

TimerTick_40:
pop ds
pop dx
pop bx
pop ax

iret

TimerTick endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; restore_IntTraps() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Restores interrupt traps before exit. ;
; ;
;.......................................................;

restore_IntTraps proc far

lds dx,dword ptr cs:[_originalDosTrap]
callDos SetIntVector, 21h ;restore vector to Int21.

lds dx,dword ptr cs:[_originalKbdHdwTrap]
callDos SetIntVector, 09h

lds dx,dword ptr cs:[_originalScrnTrap]
callDos SetIntVector, 10h

lds dx,dword ptr cs:[_originalKbdSvcTrap]
callDos SetIntVector, 16h

lds dx,dword ptr cs:[_originalTickInt]
callDos SetIntVector, 08h

ret
restore_IntTraps endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Int21() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Int 21 traps to here. We can detect DMA address ;
; change, terminate process, and whether we are ;
; entering/exiting DOS. ;
; ;
;.......................................................;

Int21 proc far

cmp ah,ExitProgram
jz Int21_12
cmp ah,TerminateProcess
jnz Int21_20

Int21_12:
push ax ;save return code.

lds dx,dword ptr cs:[_originalDosTrap]
callDos SetIntVector, 21h ;restore vector to Int21.
call restore_IntTraps
pop ax

Int21_20:
_Int _originalDosTrap ;emulate int call
ret 2 ;pass through our own status.

Int21 endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Int16() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Int 16 is used to read the keyboard. It needs to ;
; trap to a waitKbdEvent() function which sets the ;
; KBD event flag in the current task and exits to the ;
; scheduler. ;
; ;
;.......................................................;

Int16 proc far
or ah,ah ;is it a keyboard wait call ?
jnz Int16_22 ;no, go ahead and execute -->

SaveRegisters
mov ah,1
int 16h ;we'll call ourselves
jnz Int16_20 ;if key available, no need waiting -->

mov ds, word ptr cs:[Rtx_DataSegment]
call rtx_text:waitKbdEvent ;wait on kbd event.

Int16_20:
RestoreRegisters

Int16_22:
_Int _originalKbdSvcTrap
ret 2 ;pass through our own status.
Int16 endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Int09() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Int 09 is the keyboard interrupt. If a key is ;
; detected and saved by the ROM BIOS it will force ;
; the setKbdEvent and call the scheduler to evaluate ;
; task priorities. ;
; ;
;.......................................................;

Int09 proc far

_Int _originalKbdHdwTrap ;do normal kbd duties.

push ax
push bx
push ds
mov ax,40h
mov ds,ax ;look at bios kbd area
mov bx,1Ah

cli
mov ax,word ptr [ bx ] ; 1Ah
cmp ax,word ptr [ bx + 2 ] ; 1Ch
sti
jz Int09_20 ; if zero, no keys pending ->

SaveRegisters
mov ds, word ptr cs:[Rtx_DataSegment]
call rtx_text:setKbdEvent ;say keyboard event occourred.
call scheduler
RestoreRegisters

Int09_20:
pop ds
pop bx
pop ax

iret
Int09 endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; KeyboardEventFct ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Sample of an event fct. This returns true (non-zero);
; when keyboard data is available; false (zero) when no;
; keyboard data is available. ;
; ;
;.......................................................;

entry keyboardEventFct ;emulates Pascal conventions
;
darg __argument ; void far * argument,
arg __event_id ; event event_id

push bx
push ds
mov ax,40h
mov ds,ax ;look at bios kbd area
mov bx,1Ah

cli
mov ax,word ptr [ bx ] ; 1Ah
cmp ax,word ptr [ bx + 2 ] ; 1Ch
sti

mov ax, 0 ;false if no input available.
jz keyboardEventFct_08 ; if zero, no keys pending ->

mov ax, 1 ;true if input available.

keyboardEventFct_08:
pop ds
pop bx
return pascal

keyboardEventFct endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; Int10() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; This would handle any program to Int 10 calls. There;
; are no screen special considerations unless you need ;
; to support different windows per task. ;
; ;
;.......................................................;

Int10 proc

_Int _originalScrnTrap

iret
Int10 endp

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; init_IntTraps() ;
;- - - - - - - - - - - - - - - - - - - - - - - - - - - -;
; ;
; Init int traps for whole system. Called by ;
; initTaskSystem(). ;
; ;
;.......................................................;

init_IntTraps proc far

saveSegments
mov word ptr cs:[Rtx_DataSegment], ds

push cs
pop ds

setIntTrap 09h, Int09, _originalKbdHdwTrap
setIntTrap 10h, Int10, _originalScrnTrap
setIntTrap 16h, Int16, _originalKbdSvcTrap
setIntTrap 08h, TimerTick, _originalTickInt
setIntTrap 21h, Int21, _originalDosTrap

mov word ptr [insideDos],0000
restoreSegments
ret
init_IntTraps endp

reg_supp ends

;''''''''''''''''''''''''''''''''''''''''''''''''''''''';
; temporary stack ;
;.......................................................;

t_stack segment para 'DATA'
dw 2000 dup( 0 )
temp_stack dd 0
t_stack ends

end




  3 Responses to “Category : C Source Code
Archive   : RTX.ZIP
Filename : REGS.ASM

  1. Very nice! Thank you for this wonderful archive. I wonder why I found it only now. Long live the BBS file archives!

  2. This is so awesome! 😀 I’d be cool if you could download an entire archive of this at once, though.

  3. But one thing that puzzles me is the “mtswslnkmcjklsdlsbdmMICROSOFT” string. There is an article about it here. It is definitely worth a read: http://www.os2museum.com/wp/mtswslnk/