home *** CD-ROM | disk | FTP | other *** search
- page ,132
-
- comment !
- * netbios version of c-tree server
- * terminate/stay resident asm lang support
- *
- * This program is the CONFIDENTIAL and PROPRIETARY property
- * of FairCom(R) Corporation. Any unauthorized use, reproduction or
- * transfer of this program is strictly prohibited.
- *
- * Copyright (c) 1987, 1988, 1989 FairCom Corporation
- * (Subject to limited distribution and
- * restricted disclosure only.)
- * *** ALL RIGHTS RESERVED ***
- *
- * 4006 West Broadway
- * Columbia, MO 65203
- *
- *
- * c-tree(R) Version 4.3
- * Release C
- * February 7, 1989 17:30
- *
- !
-
- ;This module provides the ability to interrupt the main process
- ;(called user) and resume the ctree server (called task) whenever
- ;a netbios asynchonous command completes.
- ;
-
- extrn _disconnect:far ;(in ctsmsg.c) undo from netbios
-
- include asm.inc
-
-
- DSEG
- extrn __aintdiv:dword ;dos's div exception vector ptr that
- ;was saved by c-runtime init code
-
- MAXSEG = 20 ;size of _abrktb
- extrn __abrktb:word ;crt (c runtime) table of blocks
- ;alloc'd from dos
- extrn __asegds:word ;crt heaprec for malloc in DGROUP
- extrn __asizds:word ;crt size of DGROUP
- extrn __psp:word ;crt addr of program seg prefix
-
- ifdef FPLIB
- extrn __fpinit:word ;at +2 is non 0 if fp library loaded
- endif
- CSEG
-
-
-
- assume ds:nothing
-
- ;--------------------------------------------------------------------
- ;configuration control
- ;--------------------------------------------------------------------
- ;note: the same source module can be used for any C memory module
- ;(with appropiate 'far' modifiers). however it is recommended to
- ;assemble with a define (/D on the masm line) of one of the
- ;following: SMALL or COMPACT or MEDIUM or LARGE
- ;example: masm ctstsr /ml /DCOMPACT;
- ;--------------------------------------------------------------------
-
-
- DNCB_RETRY = 5*18 ;if an async netbios command cannot
- ;be started on first try, it is retried
- ;this many times. the retries occur on
- ;timer ticks (5*18 == try for 5 seconds)
-
- ;comment out next to use dos default of 20 file max
- FID_TABLE_SZ = 255 ;up to 255 files open
-
-
- ;if FPLIB is defined, then the C floating point emulator vectors
- ;will be saved/restored for tasks. Define this if necessary to
- ;use floating point in C code (note. float keys can be used without
- ;using library. see FPLIB and NO_FPLIB in C code).
-
- ;;FPLIB = 1
-
- ;--------------------------------------------------------------------
- ; program segment prefix
- ;--------------------------------------------------------------------
- ;--------------------------------------------------------------------
-
- PSP struc
- pp_int20 dw ? ;+00 exit instruction
- pp_mtop dw ? ; 02 paragraph past end of mem
- pp_4 db ? ; 04
- pp_cpmcall db ? ; 05 long call opcode
- pp_cpmmtop dw ? ; 06 long call oprand adj to look like mtop
- pp_cpmcallseg dw ? ; 08 rest of long call
- pp_i22term dd ? ; 0a exit to parent addr
- pp_i23ctlcp dd ? ; 0e ctl-c trap of parent
- pp_i24cerrp dd ? ; 12 critical err trap of parent
- pp_parent dw ? ; 16 psp of parent
- pp_fidtbl db 20 dup (?) ; 18 file id table
- pp_envseg dw ? ; 2c seg of environment
- pp_spsave dw ? ; 2e sp save while in dos or execing child
- pp_sssave dw ? ; 30 ss save "
- pp_fidtbllen dw ? ; 32 length of fidtbl
- pp_fidtblptr dd ? ; 34 ptr to fidtbl
- pp_shr0 dw ? ; 38 set to ffff (used by share.exe)
- pp_shr1 dw ? ; 3a set to ffff (used by share.exe)
- db 14h dup (?) ; 3c
- pp_call50 dw ? ; 50 old convention dos entry
- pp_call50ret db ? ; 52
- db 09h dup (?) ; 53
- pp_fcb0 db 16 dup (?) ; 5c
- pp_fcb1 db 16 dup (?) ; 6c
- db 4 dup (?) ; 7c
- pp_cmdtail db 128 dup (?) ; 80
- PSP ends
-
- ;--------------------------------------------------------------------
- ;DOSSTATE structure
- ;--------------------------------------------------------------------
- ; msdos 3.x user context area - everything except current directorys
- ; the address of this table is obtained with DOS 5d06h call:
- ; in: ax = 5d06h
- ; out: ds:si = addr of context data
- ; dx = len of context data when in_dos flag clear
- ; cx = len of context data when in_dos flag set
- ; (struc of this small context is shown below)
- ;--------------------------------------------------------------------
-
- DOSSTATE struc
- dst_in_i24 db ? ;00 dos is in int 24 counting flag
- dst_in_dos db ? ;01 dos is in use counting flag
- dst_wpe_drv db ? ;02 drive number of write prot error
- dst_errloc db ? ;03 extended error locus
- dst_err dw ? ;04 extended error
- dst_erract db ? ;06 extended error suggested action
- dst_errclass db ? ;07 extended error class
- dst_errvol dd ? ;08 extended error volume label ptr
- dst_dta dd ? ;0c data transfer address
- dst_psp dw ? ;10 program segment prefix
- dst_i23_sp dw ? ;12 sp save during int 23
- dst_retcode dw ? ;14 dos return code
- dst_defdrv db ? ;16 default drive
- dst_breakon db ? ;17 check for ctl-break on/off flag
- ;18h sizeof dosstate
- DOSSTATE ends
-
- ;--------------------------------------------------------------------
- ;CONTEXT structure
- ;--------------------------------------------------------------------
- ;this is the layout of context data saved for both the user and the
- ;task programs.
- ;--------------------------------------------------------------------
- ifdef FPLIB
- CONTEXT struc
- co_ifp dd 11 dup (?) ;floating pt int vects 34-3e
- co_i1b dd ? ;int 1b vector (kbd break)
- co_i23 dd ? ;int 23 vector (dos ^C)
- co_i24 dd ? ;int 24 vector (dos critical error)
- co_dssz dw ? ;size used in next member
- co_dosstate db ? ;buffer for psp, dta etc
- ; (actually more than one byte long
- ; so make sure its last in struc)
- CONTEXT ends
-
- else ;(NO_FPLIB)
- CONTEXT struc
- co_i1b dd ? ;int 1b vector (kbd break)
- co_i23 dd ? ;int 23 vector (dos ^C)
- co_i24 dd ? ;int 24 vector (dos critical error)
- co_dssz dw ? ;size used in next member
- co_dosstate db ? ;buffer for psp, dta etc
- ; (actually more than one byte long
- ; so make sure its last in struc)
- CONTEXT ends
- endif
-
- ;--------------------------------------------------------------------
- ; netbios command block
- ;--------------------------------------------------------------------
- ;the ncb_next field is used in here to link together netbios commands
- ;that cannot be started right away (in case netbios runs out of
- ;resources)
- ;--------------------------------------------------------------------
-
- NCBanr = 80h
- ; network command block
-
- NCB struc
- ncb_cmd db ? ;command code
- ncb_err db ? ;error return
- ncb_lsn db ? ;session id
- ncb_namenum db ? ;name number
- ncb_bufptr dd ? ;buffer address
- ncb_buflen dw ? ;buffer length
- ncb_rname db 16 dup (?) ;remote name
- ncb_lname db 16 dup (?) ;local name
- ncb_rto db ? ;receive timeout
- ncb_sto db ? ;send timeout
- ncb_anrptr dd ? ;anr entry
- ncb_lana db ? ;adapter number
- ncb_done db ? ;cmd complete when not ff
- ncb_next dd ? ;* next on list
- ncb_res1 dd ? ;*
- ncb_res2 db 6 dup (?) ;*
- NCB ends
-
- ;* used only by netbios
-
- ;--------------------------------------------------------------------
- ;local data
- ;--------------------------------------------------------------------
- ;all this data is in the code segment for easy addressibilty from
- ;int trap routines
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i08_passon,i13_passon,i21_passon,i28_passon,i2a_passon
- public u_sp,u_ss,u_ctxt_ptr,t_sp,t_ss,t_ctxt_ptr
- public dos_state,dctx_szsmall,dctx_szlarge
- ifdef FPLIB
- public usefp_flag
- endif
- public task_pending,in_task_flag
- public dncb_head,dncb_retry
- endif
-
- ; --- original vectors for interrupts trapped ---
- even
- i08_passon dd ? ;timer tick
- i13_passon dd ? ;disk i/o
- i21_passon dd ? ;dos entry
- i28_passon dd ? ;dos idle while waiting for console
- i2a_passon dd ? ;dos idle while waiting for device (ah=84h)
-
-
- ; --- save areas for context switches ---
- even
- u_sp dw OTX init_ustk ;user sp save when in task context
- u_ss dw seg _TEXT
- u_ctxt_ptr dd ? ;save area for user context
-
- t_sp dw ? ;task sp save when in user context
- t_ss dw ?
- t_ctxt_ptr dd ? ;save area for task context
-
- dos_state dd ? ;pointer to dos variables
- dctx_szsmall dw ? ;size of dos variables for context sw.
- ; when dos not busy or int 28 task switch
- ; typically 24 bytes
- dctx_szlarge dw ? ;size of dos variables for context sw.
- ; when int 2a, ah=84 task switch
- ; typically some 2k bytes
-
- ifdef FPLIB
- usefp_flag dw 0 ;set to one if fp library loaded
- endif
-
- ; --- task switch control ---
- even
- task_pending dw 0 ;task event happened
- in_task_flag dw 0 ;task is active
- task_inhib_flags dw 0 ;bits set to inhibit task activate
- had_i2a84 dw 0 ;counts how many times int 24, ah=84h
- ;occurred since last netbios event. DOS
- ;issues this when it is polling a char
- ;device and dos can be safely interrupted,
- ;however, large DOS data area has to be
- ;saved. therefore this counter inhibits
- ;switching in case an int 28 (smaller save)
- ;comes along
- timeout dw 0 ;clock tick downcounter schedules task on 0
- had_timeout dw 0 ;had timeout flag
-
- ; --- delayed start ncbs ---
- even
- dncb_head dd 0 ;ncb's to be started when netbios allows it
- dncb_retry dw 0 ;retry counter for delayed start ncbs
-
-
- ; --- fixed up user's stack for first call to wait_task ---
- ;this will go to code that does and int 21 with ax = term, stay resident
- ifdef DEBUG
- public init_ustk, task_memsize
- endif
- even
- dw 64 dup (?) ;slack
- init_ustk dw 0 ;bx
- dw 0 ;cx
- task_memsize dw ? ;dx
- dw 0 ;si
- dw 0 ;di
- dw 0 ;bp
- dw seg _TEXT ;ds
- dw seg _TEXT ;es
- dw OTX go_tsr ;near ret
-
-
- ;
- ;replacement file-id so dos can open more than 20 files
- ;
-
- ifdef FID_TABLE_SZ
- ifdef DEBUG
- public fid_table
- endif
- fid_table db FID_TABLE_SZ dup (0ffh)
- endif
-
-
- ;--------------------------------------------------------------------
- ;UCOUNT do_nb(NCB far *)
- ;--------------------------------------------------------------------
- ;this is called from ctnbios to issue command to netbios. if the
- ;command cannot be started, then it will be reissued periodically
- ;from timer tick trap.
- ;--------------------------------------------------------------------
-
- public _do_nb
- _do_nb proc far
- push bp
- mov bp,sp
- les bx,[bp+6] ;es:bx -> ncb
- int 5ch ;call netbios
- or al,al
- jz ast4 ;if no immed err
- test es:[bx].ncb_cmd,NCBanr
- jz ast4 ;if not a nowait cmd
- cmp es:[bx].ncb_cmd,0ffh
- jz ast4 ;if just an install check
- mov es:[bx].ncb_done,0ffh ;simulate cmd in progress
- mov es:[bx].ncb_err,0ffh
- mov WO es:[bx].ncb_next,0 ;put on can't start list
- mov WO es:[bx].ncb_next + 2,0
- PUSHM <ds,si>
- cli
- lds si,cs:dncb_head
- mov ax,ds
- or ax,si
- jnz ast1
- mov WO cs:dncb_head,bx ;list is empty so put at top
- mov WO cs:dncb_head + 2,es
- mov dncb_retry,DNCB_RETRY
- jmp ast3 ;return success
- ast1: mov ax,WO [si].ncb_next
- or ax,WO [si].ncb_next+2
- jz ast2 ;found end
- lds si,[si].ncb_next ;keep looking
- jmp ast1
- ast2: mov WO [si].ncb_next,bx ;put on end
- mov WO [si].ncb_next + 2,es
- ast3: sti
- POPM <si,ds>
- xor ax,ax ;return success
- ast4: mov ah,0 ;success (if nowait) or err code
- pop bp
- ret
- _do_nb endp
-
- ;--------------------------------------------------------------------
- ;chk_ancb_start
- ;--------------------------------------------------------------------
- ;called from timer tick trap to see if any ncb's are on can't start
- ;list. if any are on the list, a start is attempted. eventually
- ;a timeout will occur and then the command complete will be simulated
- ;with error sts.
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public chk_ancb_start
- endif
-
- chk_ancb_start:
- PUSHM <ax,bx,es>
- cas1: les bx,cs:dncb_head
- mov ax,es
- or ax,bx
- jz cas4 ;if list empty
- mov ax,WO es:[bx].ncb_next ;remove 1st
- mov WO cs:dncb_head,ax
- mov ax,WO es:[bx].ncb_next + 2
- mov WO cs:dncb_head + 2,ax
- int 5ch ;try to start
- or al,al
- jnz cas2 ;if no luck
- mov cs:dncb_retry,DNCB_RETRY ;good, restart timeout
- jmp cas1 ;try to start another
- cas2: dec cs:dncb_retry ;check timeout
- jnz cas3 ;if not timeout
- pushf
- cli
- call es:[bx].ncb_anrptr ;command complete
- mov cs:dncb_retry,1 ;fail the rest
- jmp cas1
-
- cas3: mov es:[bx].ncb_done,0ffh ;no timeout, requeue
- mov es:[bx].ncb_err,0ffh
- mov ax,WO cs:dncb_head
- mov WO es:[bx].ncb_next,ax
- mov ax,WO cs:dncb_head + 2
- mov WO es:[bx].ncb_next + 2,ax
- cas4: POPM <es,bx,ax>
- ret
-
-
- ;--------------------------------------------------------------------
- ;misc dos traps
- ;--------------------------------------------------------------------
- ;these are set during task (server) context
- ;i24 (critical err) just causes dos call to fail
- ;i23 (ctl-brk dos) don't let user trap get control
- ;i1b (ctl-brk bios) " " " " " "
- ;
- ;note: during heavy server activity ctl-brks may get lost.
- ;--------------------------------------------------------------------
-
- ;misc default traps for task context
-
- ifdef DEBUG
- public i24_trap,i1b_trap,i23_trap
- endif
-
- i24_trap:
- mov al,3 ;fail the call
- i1b_trap:
- i23_trap:
- iret
-
- ;--------------------------------------------------------------------
- ;int 8 trap
- ;--------------------------------------------------------------------
- ;check timeout specified on call to task_wait. schedule task if
- ;timer runs out
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i08_trap
- endif
-
- i08_trap:
- pushf
- call cs:i08_passon
- call chk_ancb_start ;service netbios cmds needing start
- cmp cs:in_task_flag,0
- jnz tk2 ;if already in task
- cmp cs:timeout,0
- jz tk1 ;if no timeout or already timed out
- dec cs:timeout
- jnz tk1 ;if didn't time out
- mov cs:had_timeout,-1 ;set flag
- mov cs:task_pending,1 ;schedule server
- tk1: call chk_dotask ;run task if needed and possible
- tk2: iret
-
- ;--------------------------------------------------------------------
- ;int 13 trap
- ;--------------------------------------------------------------------
- ;inhibit task switch if user program calls bios direct
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i13_trap
- endif
-
- i13_trap:
- or cs:task_inhib_flags,1
- pushf
- call cs:i13_passon
- pushf
- and cs:task_inhib_flags,not 1
- call chk_dotask
- popf
- sti
- retf 2
-
- ;--------------------------------------------------------------------
- ;int 21 trap
- ;--------------------------------------------------------------------
- ;during user context:
- ; trapped to give more opportunities to run task when event pending
- ;during task context:
- ; trapped to (1) force error on mem alloc's (2) clean up if task
- ; terminates
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i21_trap
- endif
-
- i21_trap:
- cmp cs:in_task_flag,0
- jnz dtr2 ;if server task context
- ;selected calls will be passed onto dos without our ret
- ;info on the stack. In those cases we're just outta luck
- ;until the next dos call
- cmp ah,0 ;terminate
- jz dtr1
- cmp ah,26h ;build psp
- jz dtr1
- cmp ah,4bh ;exec
- jz dtr1
- ;manipulate to get user's orig flags
- push ax
- push bp
- mov bp,sp
- mov ax,[bp+8]
- xchg ax,[bp+2]
- pop bp
- call cs:i21_passon ;perform the dos func
- push bp
- mov bp,sp
- pushf
- pop WO [bp+6] ;in case dos returned info in flags
- pop bp
- call chk_dotask
- iret
- dtr1: jmp cs:i21_passon
- dtr2: cmp ah,4ch ;terminate?
- jz killtask
- cmp ah,48h ;alloc?
- jz dtr3
- cmp ah,4ah ;mod alloc?
- jnz dtr1
- dtr3: mov ax,8 ;no mem dos err
- xor bx,bx
- stc
- sti
- retf 2
-
- ;--------------------------------------------------------------------
- ;killtask
- ;--------------------------------------------------------------------
- ;entered from i21_trap if server task issued dos terminate call
- ;unhook from ints, undo netbios connections, release all memory
- ;and vanish into thin air
- ;
- ;NOTE: if this is to be used with other tsr's, then they should
- ;be removed first if they are loaded after this. It might also be
- ;possible to look at int vectors and deduce another tsr is loaded
- ;and, if so, not completely eliminate ourselves.
- ;--------------------------------------------------------------------
- ifdef DEBUG
- public killtask, clsall
- endif
-
- killtask:
-
- mov ax,DGROUP
- mov ds,ax
-
- assume ds:DGROUP
-
- ;kill netbios connections if not already done
- call _disconnect ;in ctsmsg.c
-
- push ds
- assume ds:nothing
- ;unlink int traps
-
- lds dx,cs:i08_passon
- DOS 2508h
- lds dx,cs:i13_passon
- DOS 2513h
- lds dx,cs:i21_passon
- DOS 2521h
- lds dx,cs:i28_passon
- DOS 2528h
- lds dx,cs:i2a_passon
- DOS 252ah
-
- pop ds
- assume ds:DGROUP
-
- ;close all open files
-
- mov es,__psp
- push ds
- lds si,es:[0].pp_fidtblptr
- mov cx,es:[0].pp_fidtbllen
- xor bx,bx
- clsall: cmp BY [si+bx],0ffh
- jz cla1
- DOS 3eh
- cla1: inc bx
- loop clsall
- pop ds
-
- ;free all memory associated with task
- mov es,__psp
- mov ax,es:[0].pp_envseg ;env ptr
- mov es,ax
- or ax,ax
- jz kt1
- DOS 49h ;free env
- kt1:
- lea si,__abrktb+4 ;free all far segs
- mov cx,MAXSEG-1
- kt2: mov ax,[si+2]
- or ax,ax
- jz kt3
- mov es,ax
- DOS 49h
- add si,4
- loop kt2
- kt3: mov es,__psp ;free the main seg
- DOS 49h
-
- ;return to interrupted thread
-
- mov cs:task_pending,0
- call far ptr _task_wait ;won't return
-
- assume ds:nothing
-
- ;--------------------------------------------------------------------
- ;int 28
- ;--------------------------------------------------------------------
- ;dos issues this when it is polling keyboard
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i28_trap
- endif
-
- i28_trap:
- cmp cs:task_pending,0
- jz i281
- cmp cs:in_task_flag,0
- jnz i281
- push ax
- call do_task_sm
- pop ax
- i281: jmp cs:i28_passon
-
-
- ;--------------------------------------------------------------------
- ;int 2a
- ;--------------------------------------------------------------------
- ;dos issues this when it is polling char device. if a task switch
- ;is desired from this point, a large amount of data inside dos has
- ;to be saved. therefore a counter is used to slow down usage in the
- ;hope that a int 28 will occur
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i2a_trap
- endif
-
- i2a_trap:
- cmp ah,84h
- jz i2a2
- i2a1: jmp cs:i2a_passon
- i2a2: cmp cs:task_pending,0
- jz i2a1
- cmp cs:in_task_flag,0
- jnz i2a1
- inc cs:had_i2a84
- cmp cs:had_i2a84,3
- jb i2a1
- push ax
- mov ax,cs:dctx_szlarge
- call do_task
- pop ax
- iret
-
- ;--------------------------------------------------------------------
- ;fanrf - async netbios command completed notification
- ;--------------------------------------------------------------------
- ;all async ncbs from server have an extra word in front that is set
- ;to 1 by this when command completes. task_pending flag is set in
- ;case system state is such that the server can't be resumed
- ;
- ;note:
- ; some netbios' may call this routine with the hardware int service
- ; routine still pending. In this case we dont want to run the server
- ; because this in-service interrupt will likely block the disk controller
- ; interrupt. (a less-common but possible case is nested ints where another
- ; is higher than disk-ctrlr).
- ;
- ; if the netbios does this, then the system will still work but
- ; performance will be degraded.
- ;
- ; One solution is to identify the netbios hdwe interrupt and trap
- ; it in here. For example for IRQ3. add set trap in task_init and
- ; clear trap in killtask.
- ;
- ; i0b_trap:
- ; pushf
- ; call cs:i0b_passon
- ; call chk_dotask ;switch tasks when isr bit clear
- ; iret
- ;--------------------------------------------------------------------
-
- ;es:bx -> ncb that has a word flag in front of it
- public _fanrf
- _fanrf proc far
- mov WO es:[bx-2],1 ;set done flag (xncb.f)
- mov cs:had_timeout,0
- inc cs:task_pending
- mov cs:had_i2a84,0
- cmp cs:in_task_flag,0
- jnz fanr1
- ;*****************
- push ax
- mov al,0bh ;read in-service reg
- out 20h,al
- in al,20h
- and al,0ffh
- pop ax
- ;*****************
- jnz fanr1 ;inhibit task switch in hardware isr
- call chk_dotask
- fanr1: iret
- _fanrf endp
-
- ;--------------------------------------------------------------------
- ;clear_task_events()
- ;--------------------------------------------------------------------
- ;server calls this just prior to polling all possible events. this
- ;avoids a redundant poll pass.
- ;--------------------------------------------------------------------
-
- public _clear_task_events
- _clear_task_events proc far
- mov cs:task_pending,0
- ret
- _clear_task_events endp
-
- ;--------------------------------------------------------------------
- ;chk_dotask
- ;--------------------------------------------------------------------
- ;called from various int traps and event processors to see if it is
- ;desired and possible to switch to server task
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public chk_dotask
- endif
-
- chk_dotask:
- cmp cs:task_pending,0
- jz cdt1 ;if no event pending
- cmp cs:in_task_flag,0
- jnz cdt1 ;if already in task
- cmp cs:task_inhib_flags,0
- jnz cdt1 ;if misc lockout flags set
- PUSHM <ds,si>
- lds si,cs:dos_state
- cmp WO [si],0
- POPM <si,ds>
- jnz cdt1 ;if user in dos, then wait till
- ;(1) user exits (2) int 28 (3) int 2a
- push ax
- call do_task_sm ;switch, saving small part of dos vars
- pop ax
- cdt1: ret
-
- ;--------------------------------------------------------------------
- ;UCOUNT task_wait(timeout)
- ;--------------------------------------------------------------------
- ;called from server (ctsmsg) to wait for event. The user process is
- ;resumed. The first time this is called, the user process has been
- ;set up to be a tsr call to dos, which gets back to command.com
- ;returns -1 if event was timeout, else 0
- ;--------------------------------------------------------------------
-
- public _task_wait
- _task_wait proc far
- push bp
- mov bp,sp
- mov ax,[bp+6] ;get timeout value
- pop bp
- mov cs:timeout,ax
- cmp cs:task_pending,0 ;chk if new event already queued
- jz tw1
- xor ax,ax
- mov cs:task_pending,ax
- ret ;ret right away if so
- tw1:
- ;save server task context
- PUSHM <es,ds,bp,di,si,dx,cx,bx>
- mov t_sp,sp ;save task's sp
- mov t_ss,ss
-
- les di,cs:t_ctxt_ptr;save task's context
- mov ax,cs:dctx_szsmall
- call save_context
-
- ;restore user context
-
- lds si,cs:u_ctxt_ptr;get user's context
- call restore_context
-
- cli
- mov ss,u_ss ;user's sp restored
- mov sp,u_sp
- sti
- POPM <bx,cx,dx,si,di,bp,ds,es>
-
- ;one last check for new event occurred
- cli
- cmp cs:task_pending,0
- jnz do_task ;got one, so switch back with ax set
- mov cs:in_task_flag,0
- sti
- _task_wait endp
- ret ;resume trap, which will ret
- ;to int'd user
-
- ;--------------------------------------------------------------------
- ;do_task and do_task_sm
- ;--------------------------------------------------------------------
- ;called when (1) in user context (2) server event pending and (3) dos
- ;not in use or at task-switch checkpoint
- ;
- ;this suspends the user and resumes the server task (ie, return from
- ;task_wait())
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public do_task, do_task_sm
- endif
- do_task_sm:
- mov ax,cs:dctx_szsmall
- do_task: ;ax has dos save size
- mov cs:in_task_flag,1 ;set in task context
- sti
- PUSHM <es,ds,bp,di,si,dx,cx,bx> ;save user's regs
- mov cs:u_sp,sp ;save user's sp
- mov cs:u_ss,ss
- cli
- mov ss,cs:t_ss ;restore task's stack
- mov sp,cs:t_sp
- sti
- les di,cs:u_ctxt_ptr ;save user's context
- call save_context
- lds si,cs:t_ctxt_ptr ;restore task's context
- call restore_context
- POPM <bx,cx,dx,si,di,bp,ds,es> ;restore task's regs
- xor ax,ax
- mov cs:task_pending,ax ;clear task pending flag
- xchg ax,cs:had_timeout ;get had timeout for return
- retf
-
-
-
- ;--------------------------------------------------------------------
- ;save_context
- ;--------------------------------------------------------------------
- ;utility used to save current context
- ;in:
- ; es:di = save area
- ; ax is size of dos context to save
- ;out:
- ; ax,di,si,ds destroyed
- ;
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public save_context
- endif
-
- save_context:
- cld
- xor cx,cx
- mov ds,cx
- ifdef FPLIB
- cmp cs:usefp_flag,0 ;save fp ints if used
- jnz gc2
- add di,11*4 ;else skip fp save area
- jmp short gc3
- gc2: mov si,34h*4
- mov cx,11*2
- rep movsw
- gc3:
- endif
- mov si,1bh*4 ;get int 1b vect
- movsw
- movsw
- mov si,23h*4 ;get ints 23,24 vects
- movsw
- movsw
- movsw
- movsw
- stosw ;dos context save size
- mov cx,ax
- lds si,cs:dos_state ;get dos user context
- shr cx,1
- rep movsw
- jnc gc1
- movsb
- gc1: ret
-
- ;--------------------------------------------------------------------
- ;restore_context
- ;--------------------------------------------------------------------
- ;utility used to save current context
- ;in:
- ; ds:si = save area
- ;out:
- ; ax size of restored dos context
- ; cx,di,si,es destroyed
- ;
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public restore_context
- endif
-
- restore_context:
- cld
- xor ax,ax
- mov es,ax
- ifdef FPLIB
- cmp cs:usefp_flag,0 ;restore fp ints if used
- jnz sc2
- add si,11*4 ;else skip fp save area
- jmp short sc3
- sc2: mov di,34h*4
- mov cx,11*2
- rep movsw
- sc3:
- endif
- mov di,1bh*4 ;set int 1b vect
- cli
- movsw
- movsw
- mov di,23h*4 ;get ints 23,24 vects
- movsw
- movsw
- movsw
- movsw
- sti
- lodsw ;dos context save size
- mov cx,ax
- les di,cs:dos_state ;set dos user context
- push [si].dst_psp ;get psp for restore
- shr cx,1
- rep movsw
- jnc sc1
- movsb
- sc1: pop cx
- push ax
- push bx
- mov ah,50h
- mov bx,cx
- pushf
- cli
- call cs:i21_passon
- pop bx
- pop ax
- ret
-
-
- ;--------------------------------------------------------------------
- ;task_init(ctxtsavebufptr)
- ;--------------------------------------------------------------------
- ;called from ctsmsg to divide the system into two processes -- the
- ;user and the server task. When it returns, the server task is
- ;running and the user is suspended. When the server suspends, the
- ;user will resume at a go term/stay resident instruction, which will
- ;return to the shell, leaving the server in memory (the user has its
- ;own little stack for this exit process)
- ;
- ;for the C small and medium models, this cuts off the heap at its
- ;first free space. for other models, the thing to do is link
- ;with /CP:1 as noted in MS C users guide
- ;
- ;the dos internal handle table is moved to a bigger area so more
- ;files can be opened by the server task.
- ;--------------------------------------------------------------------
-
-
- __savebuf = 6
- ifdef DEBUG
- public go_tsr
- endif
-
- ;the code for the initial 'user task'
- go_tsr:
- mov ax,3100h
- int 21h
-
- public _task_init
- _task_init proc far
- assume ds:DGROUP
- push bp
- mov bp,sp
- push di
- push si
-
- call fxalloc ;cut off mainseg if possible, get size of it
-
- ifdef FPLIB
- ;set flag if fp lib used
- mov ax,__fpinit+2
- mov cs:usefp_flag,ax ;non 0 if in use
- endif
-
- push ds
-
-
- ifdef FID_TABLE_SZ
- ; set bigger file id table for dos
- mov es,__psp
- lds si,es:[0].pp_fidtblptr
- assume ds:nothing
- mov cx,es:[0].pp_fidtbllen
- cmp cx,FID_TABLE_SZ
- jae iti2
- mov di,OTX fid_table
- mov WO es:[0].pp_fidtblptr,di
- mov WO es:[0].pp_fidtblptr+2,cs
- mov es:[0].pp_fidtbllen,FID_TABLE_SZ
- push cs
- pop es
- rep movsb ;copy already open file ids
- iti2:
- endif
-
- assume ds:nothing
- push cs
- pop ds
- assume ds:_TEXT
-
- ; set ptrs to context save areas
-
- mov ax,[bp+__savebuf+2] ;segment
- mov WO u_ctxt_ptr+2,ax
- mov WO t_ctxt_ptr+2,ax
- mov ax,[bp+__savebuf] ;offset
- mov WO u_ctxt_ptr,ax
- mov bx,dctx_szlarge
- add bx,size CONTEXT - 1
- inc bx
- and bx,not 1
- add ax,bx
- mov WO t_ctxt_ptr,ax
-
- ; copy current context to user context save
-
- les di,u_ctxt_ptr ;save user's context
- mov ax,dctx_szsmall
- push ds
- call save_context
- pop ds
-
- ; if fp lib in use, try to find a vector to an iret in dos so
- ; int vectors will look cleaner (cosmetic)
-
- ifdef FPLIB
- cmp cs:usefp_flag,0
- jz civ2
- xor ax,ax
- mov ds,ax
- lds bx,ds:[3fh*4]
- mov ax,ds
- cmp ax,WO cs:dos_state+2
- jnz civ2
- mov al,[bx] ;get ins at ds:bx
- cmp al,0cfh ;iretins
- jnz civ2
- les di,cs:u_ctxt_ptr
- add di,co_ifp ;fix up fp ints in saved user state
- mov cx,11
- civ1: mov ax,bx
- stosw
- mov ax,ds
- stosw
- loop civ1
- civ2:
- endif
-
- push cs
- pop ds
-
- ; turn off break checking
-
- mov dl,0
- DOS 3301h
-
- ; save int vectors
- it3:
- DOS 3508h
- mov WO i08_passon,bx
- mov WO i08_passon+2,es
- DOS 3513h
- mov WO i13_passon,bx
- mov WO i13_passon+2,es
- DOS 3521h
- mov WO i21_passon,bx
- mov WO i21_passon+2,es
- DOS 3528h
- mov WO i28_passon,bx
- mov WO i28_passon+2,es
- DOS 352ah
- mov WO i2a_passon,bx
- mov WO i2a_passon+2,es
-
- mov cs:in_task_flag,1 ;set in task
-
- ;set int vect traps
- mov dx,OTX i08_trap
- DOS 2508h
- mov dx,OTX i13_trap
- DOS 2513h
- mov dx,OTX i21_trap
- DOS 2521h
- mov dx,OTX i28_trap
- DOS 2528h
- mov dx,OTX i2a_trap
- DOS 252ah
-
-
- ;set up error traps
-
- mov dx,OTX i1b_trap
- DOS 251bh
- mov dx,OTX i23_trap
- DOS 2523h
- mov dx,OTX i24_trap
- DOS 2524h
- ; restore dos's div by 0 trap
- mov ax,seg DGROUP
- mov ds,ax
- assume ds:DGROUP
- lds dx,__aintdiv
- assume ds:nothing
- DOS 2500h
- xor ax,ax
- itxit:
- pop ds
- assume ds:nothing
- pop si
- pop di
- pop bp
- ret
- _task_init endp
-
- ;--------------------------------------------------------------------
- ;fxalloc
- ;--------------------------------------------------------------------
- ;if no _fmallocs have been done, this cuts off the main data seg
- ;just past last used heap space. This works for MSC 3 and 4, and
- ;probably for 5 too.
- ;
- ;the size of the main segment (psp to end of data seg) is saved
- ;for the TSR parameter
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public fxalloc
- endif
- assume ds:DGROUP
- fxalloc:
- cmp __abrktb+6,0 ;_abrktb[1].sg
- jnz fx6
- mov si,__asegds+0 ;_asegds.bottom
- or si,si
- jnz fx1
- mov di,__abrktb ;__abrktb[0].sz
- jmp fx5a ;make di end of dseg
- fx1: mov __asegds+2,si ;_asegds.roveroff
- xor di,di
- fx2: mov ax,[si]
- cmp ax,0fffeh
- jz fx4
- test ax,1
- jnz fx3
- mov di,si ;last alloc'd block found
- fx3: and ax,not 1
- add si,ax
- add si,2
- jmp fx2
- fx4: or di,di
- jnz fx5
- mov di,__abrktb
- mov WO [di],1 ;dummy free block
- fx5: mov ax,[di]
- and ax,not 1
- add di,ax
- add di,2
- mov WO [di],0fffeh
- add di,2
-
- mov __asegds+6,di ;_asegds.top
- mov __abrktb,di ;_abrktb[0].sz
- fx5a:
- mov __asizds,di
-
- mov ax,di
- add ax,15
- rcr ax,1
- mov cl,3
- shr ax,cl
- mov es,__psp
- mov bx,ds
- add ax,bx
- mov es:[0].pp_mtop,ax
- DOS 4ah
-
- fx6: mov bx,__psp
- mov es,bx
- mov ax,es:[0].pp_mtop ;get main seg size
- sub ax,bx
- mov cs:task_memsize,ax
- ret
- assume ds:nothing
-
- ;--------------------------------------------------------------------
- ;UCOUNT task_preinit()
- ;--------------------------------------------------------------------
- ;this returns the size of a buffer needed at task_init() time.
- ;0 is returned if not dos 3
- ;--------------------------------------------------------------------
-
-
- ; get adr, len of dos data for context switches
- ;returns length of area to be alloc'd
- ; or NULL if bad dos ver
-
- public _task_preinit
- _task_preinit proc far
- push bp
- mov bp,sp
- push di
- push si
- ; check dos version
-
- DOS 30h
- cmp al,3
- jz tpi1
- xor ax,ax ;return NULL for bad dos ver
- jmp tpi2
- tpi1:
- push ds
- DOS 5d06h ;see notes in struc section
- mov ax,ds
- pop ds
- mov WO cs:dos_state,si
- mov WO cs:dos_state+2,ax
- mov cs:dctx_szsmall,dx
- mov cs:dctx_szlarge,cx
- mov ax,cx
- add ax,size CONTEXT - 1
- inc ax
- and ax,not 1
- shl ax,1
- tpi2: pop si
- pop di
- pop bp
- ret
- _task_preinit endp
-
-
- END_MOD
- end
-