home *** CD-ROM | disk | FTP | other *** search
- page ,132
-
- comment !
- * server extension 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
- *
- !
-
-
- include asm.inc
-
- ;--------------------------------------------------------------------
- ;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;
- ;--------------------------------------------------------------------
-
-
- ;comment out next to use dos default of 20 file max
- FID_TABLE_SZ = 255 ;up to 255 files open
-
-
-
-
- ;--------------------------------------------------------------------
- ; SMB (Server Message Block)
- ;--------------------------------------------------------------------
- ; sm_res is the field used to hold the server extension name (8 chars)
- ; this verifies that the SMB is actually for this extension
- ; the values above are recommended. To include data in the packet:
- ; starting at sm_vwv:
- ; dw len_of_data + 3 ; length of byte area
- ; db 5 ; gen purpose byte data follows
- ; dw len_of_data ; len of gen purpose byte data
- ; db len_of_data dup (?) ; the actual data
- ;
- ; that last area contains params used by srvx process. This includes
- ; command code etc. Srvx will put its result here, subject to
- ; maximum len restriction (srvx_smbmax) Srvx should also put a
- ; 0 in smb_err and smb_errclass. Any real errors should be in a field
- ; inside the gen purpose byte data. If a user sends request to server
- ; where srvx is not installed, server will return smb_errclass = 0xff.
- ;--------------------------------------------------------------------
-
- SMB struc
- sm_id db 0ffh,'SMB' ; 00 verification string
- sm_cmd db 0ffh ; 04 command code
- sm_errclass db 0 ; 05 error class (DOS, Server, Hardware)
- sm_err24type db 0ffh ; 06 int 24 AH code
- sm_err dw 0 ; 07 error code
- sm_reb db 0 ; 09 nu
- sm_res dw 7 dup (?) ; 0a nu (*** SEE NOTE)
- sm_tid dw 0 ; 18 tree ID
- sm_pid dw 0 ;(or psp) ; 1a process ID (psp)
- sm_uid dw 0 ; 1c user ID
- sm_mid dw 0 ; 1e mux ID
- sm_wct db 0 ; 20 word parameter count
- sm_vwv dw ? ;see note ; 21 1st word param or begin of byte area
- SMB ends
-
-
- ;--------------------------------------------------------------------
- ; 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
-
-
- ;---------------------------------------------------------------------
- ; DATA
- ;---------------------------------------------------------------------
- ;
- 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
-
-
-
- SXEVinit = 1
- SXEVlusmb = 2
- SXEVrusmb = 3
- SXEVludis = 4
- SXEVrudis = 5
-
- public _srvx_smb, _srvx_ncb, _srvx_ses, _srvx_smbmax
- public _srvx_eventcode
-
- even
- _srvx_smb dd ? ;ptr to smb, ref'd by main code
- _srvx_ncb dd ? ;ptr to ncb
- _srvx_ses dw ? ;session number (0 if local user)
- _srvx_smbmax dw ? ;max len of response smb
- _srvx_eventcode dw SXEVinit
-
-
- CSEG
- assume ds:nothing
-
- ; NOTE: all data beyond this point is in code segment
-
- ;this is the layout of context data saved for both the user and the
- ;srvx programs.
-
- CONTEXT struc
- cx_i1b dd ? ;int 1b vector (kbd break)
- cx_i23 dd ? ;int 23 vector (dos ^C)
- cx_i24 dd ? ;int 24 vector (dos critical error)
- cx_dost db (size DOSSTATE) dup (?) ;dos variables
- cx_spare db 20 dup (?) ;
- CONTEXT ends
-
- ifdef DEBUG
- public u_ctxt, x_ctxt
- endif
-
- even
- u_ctxt CONTEXT <> ;save area for user context
- even
- x_ctxt CONTEXT <> ; for our context
-
- ;the program name is set in srvx_init(). It is compared against
- ;signature in SMB blocks.
-
- ifdef DEBUG
- public srvx_name
- endif
-
- srvx_name db 8 dup (' ') ;name of srvx process
-
- ;fixed up user's stack for first call to srvx_wait()
- ;this will go to code that does an 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 ;ret
-
- ;end of stack
-
-
- ;original vectors for interrupts we patch
-
- ifdef DEBUG
- public i2f_passon, upost_passon, i21_passon
- endif
-
-
- even
- i2f_passon dd ? ;continue for mux int intercept
- upost_passon dd ? ;server extension intercept
- i21_passon dd ? ;continue for int 21 intercept
-
- ;sp saves for context switches
-
- ifdef DEBUG
- public u_sp,u_ss,x_sp,x_ss;for debug
- endif
-
- even
- u_sp dw OTX init_ustk ;user sp save when in srvx context
- u_ss dw seg _TEXT
- x_sp dw ? ;sp save when in user context
- x_ss dw ?
-
-
- ifdef DEBUG
- public srvx_waiting, srvx_lock, srvx_mid, srvx_killed
- endif
-
- srvx_waiting db 0 ;flags blocked thread pending
- srvx_lock db 0 ;0-not in srvx, 1-in srvx, called by
- ; server, 2-in srvx, called by local
- ; user (via int 2f)
- srvx_mid db 0 ;mux id (int 2f, ah value noticed by us)
- srvx_killed db 0 ;set if server terminates
-
-
- ifdef DEBUG
- public dos_state, dctx_szsmall, dctx_szlarge
- endif
-
- even
- dos_state dd ? ;pointer to dos variables
- dctx_szsmall dw ? ;size of dos variables for context sw.
- dctx_szlarge dw ? ;size of dos variables for context sw.
- ; typically some 2k bytes (not used)
-
- ;
- ;replacement file-id so dos can open more than 20 files
- ;
-
- ifdef FID_TABLE_SZ
- ifdef DEBUG
- public fid_table
- endif
- even
- fid_table db FID_TABLE_SZ dup (0ffh)
- endif
-
-
- ;debug vars
-
- ifdef DEBUG
-
- public blocked
- blocked dw 0 ;
-
- endif
-
-
-
- ;--------------------------------------------------------------------
- ;int 21 trap
- ;--------------------------------------------------------------------
- ;trap is in effect only during srvx context:
- ; trapped to (1) force error on mem alloc's (2) clean up if task
- ; terminates
- ;--------------------------------------------------------------------
-
-
- ifdef DEBUG
- public i21_trap
- endif
-
- i21_trap:
-
- push ax ;check for user interrupted our thread
- mov ax,ss
- cmp ax,DGROUP
- pop ax
- jnz dtr2
-
- cmp ah,4ch ;terminate?
- jz killtask
- cmp ah,48h ;alloc?
- jz dtr1
- cmp ah,4ah ;mod alloc?
- jnz dtr2
- dtr1: mov ax,8 ;no mem dos err
- xor bx,bx
- stc
- sti
- retf 2
- dtr2: jmp cs:i21_passon
-
- ;--------------------------------------------------------------------
- ;killtask
- ;--------------------------------------------------------------------
- ;entered from i21_trap if server task issued dos terminate call
- ;unhook from traps, release all memory disappear
- ;
- ;NOTE: if this is to be used with other tsr's, then they should
- ;be removed first if they are loaded after this.
- ;--------------------------------------------------------------------
- ifdef DEBUG
- public killtask, clsall
- endif
-
- killtask:
-
- mov ax,DGROUP
- mov ds,ax
-
- assume ds:DGROUP
-
- push ds
- assume ds:nothing
- ;unlink int traps
-
- les bx,cs:upost_passon
- mov ax,0b804h
- int 2fh
-
- lds dx,cs:i2f_passon
- DOS 252fh
-
- 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
-
- ;flag killed
- mov cs:srvx_killed,1
-
- ;return to interrupted thread
-
- call far ptr _srvx_wait ;won't return
-
- assume ds:nothing
-
- ;--------------------------------------------------------------------
- ; srvx_trap
- ;--------------------------------------------------------------------
- ;
- ;This is the linkage to the resident file server.
- ;When the server receives a message from a workstation, we get to
- ;take a look at it and process it if we want to.
- ;
- ;The linkage was set up with int 2f, ax=b803 (get current post address)
- ;and int 2f, ax=b804 (set new post address).
- ;
- ;On entry:
- ; if ax == 0010h then
- ; /* smb request from user */
- ; ds:di points to the SMB message
- ; cx has max length for response smb.
- ; es:bx ptr to NCB
- ; dx has net bios session number
- ; if ax == 0106h then
- ; /* user has 'called' via netbios */
- ; es:bx ptr to NCB
- ; dx has net bios session number
- ; if ax == 0105h then
- ; /* user has 'hung-up' via netbios */
- ; es:bx ptr to NCB
- ; dx has net bios session number
- ;
- ;
- ;On exit: if we processed the message, iret with ax = 0 (actually jmps
- ;to got_request to resume our main code). If we don't process the
- ;message, then jmp to the next server extension (via address obtained
- ;on int 2f, ax=b803)
- ;
- ;No registers other than ax are changed. If we process SMB, then
- ;ax is set to 0.
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public srvx_trap
- endif
-
- srvx_trap:
- cmp ax,105h ;disconnect code?
- jnz sxt2
- push ax
- mov ax,SXEVrudis
- call got_req
- pop ax
- jmp short sxt3
- sxt2: cmp ax,10h ;is it SMB type?
- jz sxt4 ;keep checking if so
- sxt3: jmp cs:upost_passon ;pass to next extension
-
- sxt4: cmp [di].sm_cmd,0ffh ;is SMB command code an 'escape'
- jnz sxt3 ;if not, pass to next
- cld ;
- push es ;save regs needed for signature
- push ds ; compare
- push cx
- push di
- push si
- mov si,di ;ds:si -> smb
- add si,sm_res ;-> smb signature field
- push cs
- pop es
- mov di,OTX srvx_name ;name of our server extension
- mov cx,8/2
- repz cmpsw ;will match if user made this SMB
- pop si ; with us in mind
- pop di
- pop cx
- pop ds
- pop es
- jnz sxt3 ;jmp if not for us
- mov ax,0
- push ax ;ax = 0 to indicate msg processed
- mov ax,SXEVrusmb
- call got_req ;get back to waiting main program
- pop ax
- jnc sxt1 ;if not killed while in prog
- mov ax,10h
- jmp sxt3
- sxt1: iret
-
- ;--------------------------------------------------------------------
- ; i2f_trap
- ;--------------------------------------------------------------------
- ;
- ;Monitors int 2f for our multiplex ID assigned at startup time.
- ; int 2f, ah=id, al=0 is used for an install check.
- ; int 2f, ah=id, al!=1 is mechanism for local user (foreground process)
- ; to issue a request to us. In this case, user
- ; passes an SMB-like data structure in ds:di to us
- ; and cx has smb max len
- ;
- ;only AX is changed
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public i2f_trap
- endif
-
- i2f_trap:
- cmp ah,cs:srvx_mid ;make sure our mux ID
- jz muxus
- jmp cs:i2f_passon ;pass to next int 2f handler
- muxus: or al,al
- jnz mux1 ;jmp if not install check
- inc al ;return 'is installed'
- mux0: iret
- mux1:
- cld ;alway fwd dir
- cmp al,1
- jz mux2
- mov ax,0
- push ax
- mov ax,SXEVludis
- jmp short mux3
- mux2: mov ax,0
- push ax
- mov ax,SXEVlusmb ;flag that request is from local proc
- mux3: call got_req ;get to waiting main program
- pop ax
- jnc mux4 ;if not killed while in prog
- mov al,1 ;flag killed to user
- mux4: iret
-
- ;--------------------------------------------------------------------
- ; far srvx_wait();
- ;--------------------------------------------------------------------
- ;
- ;Main code calls this to wait on next user request. At the same time,
- ;the reply for the just-completed request is returned to the user (except
- ;the first time).
- ;
- ;The first time called, we will end up doing a DOS 'terminate stay resident'.
- ;The saved stack info was set up in init to cause a return to the TSR code.
- ;
- ;input: none
- ;output: (SMB far *) srvx_smb is pointer to the SMB associated with request
- ; We build response in this smb also.
- ; (unsigned) srvx_smbmax specifies maximum size of smb for response.
- ; returns 1 if request came from user via server, else 2 if request
- ; was via int 2f (local user)
- ;--------------------------------------------------------------------
-
- public _srvx_wait
-
- _srvx_wait proc far
- _srvx_wait endp
- PUSHM <bp,di,si,ds>
-
- mov cs:x_sp,sp ;save our sp
- mov cs:x_ss,ss
-
-
- mov di,OTX x_ctxt ;save our context
- call save_context
- ;remove the int 21 trap
- lds dx,cs:i21_passon
- DOS 2521h
- mov si,OTX u_ctxt ;restore user's context
- call restore_context
-
- cli
- mov ss,cs:u_ss ;user's sp restored
- mov sp,cs:u_sp
- sti
-
- POPM <bx,cx,dx,si,di,bp,ds,es>
- mov al,0
- cli
- xchg al,cs:srvx_lock
- cmp al,SXEVlusmb
- jnz sxw1
- cmp cs:srvx_waiting,0
- jz sxw1
- sti
- mov ah,84h
- int 2ah
- sxw1: xor ax,ax ;cf clear to indicate not killed
- ret ;return to (1) server or (2) local
- ;user that did an int 2f
-
- ;--------------------------------------------------------------------
- ; got_req
- ;--------------------------------------------------------------------
- ;
- ;This can be viewed as a continuation of respond_wait. Gets control when
- ;there is another (SMB) request to be processed
- ;
- ;in: al = 1 if from server, 2 if from local user
- ;
- ;It is possible for server and local user to make requests asynchronously.
- ;However, mutual exclusion lock is done here so that higher level has
- ;to worry about only 1 request at a time. Undoc'd DOS 3.x int 2a, ah=84
- ;function is used to sleep when it is found that other thread is using
- ;our code.
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public got_req
- endif
-
- got_req:
- gr1:
- cli ;ints off for lock'd test
- cmp cs:srvx_lock,0
- jz gr2 ;jmp if not locked
- mov cs:srvx_waiting,al
- sti
-
- ifdef DEBUG
- inc cs:blocked
- endif
-
- push ax
- mov ah,84h ;sleep till tick or other event
- int 2ah
- pop ax
- jmp gr1
-
- gr2: mov cs:srvx_waiting,0
- cmp cs:srvx_killed,0
- jz gr3
- stc
- ret
- gr3: mov cs:cs:srvx_lock,al ;no locked so lock for us
- sti
- PUSHM <es,ds,bp,di,si,dx,cx,bx>
- push ds
- push ax
- mov ax,seg DGROUP
- mov ds,ax
- assume ds:DGROUP
- pop _srvx_eventcode ;what caused wakeup
- pop WO _srvx_smb+2
- mov WO _srvx_smb,di ;save smb ptr in global var
- mov _srvx_smbmax,cx ;save smb max len in global
- mov WO _srvx_ncb,bx
- mov WO _srvx_ncb+2,es
- mov _srvx_ses,dx
-
- assume ds:nothing
-
- mov u_sp,sp ;save user sp
- mov u_ss,ss
- cli
- mov ss,x_ss ;restore srvx's stack
- mov sp,x_sp
- sti
-
- mov di,OTX u_ctxt ;save user's context
- call save_context
- mov si,OTX x_ctxt ;restore srvx's context
- call restore_context
-
- ;set up a trap on server's int 21 functions
- DOS 3521h
- mov WO cs:i21_passon,bx
- mov WO cs:i21_passon+2,es
- mov dx,OTX i21_trap
- mov ax,cs
- mov ds,ax
- DOS 2521h
-
-
- POPM <ds,si,di,bp> ;restore C regs
- retf
-
-
- ;--------------------------------------------------------------------
- ;save_context
- ;--------------------------------------------------------------------
- ;utility used to save current context
- ;in:
- ; cs:di = save area
- ;out:
- ; ax,di,si,ds,es destroyed
- ;
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public save_context
- endif
-
- save_context:
- cld
- mov cx,cs
- mov es,cx ;es:di -> save
- xor cx,cx
- mov ds,cx
- mov si,1bh*4 ;get int 1b vect
- cld
- movsw
- movsw
- mov si,23h*4 ;get ints 23,24 vects
- movsw
- movsw
- movsw
- movsw
-
- lds si,cs:dos_state
- mov cx,cs:dctx_szsmall
- shr cx,1
- rep movsw
- jnc sst1
- movsb
- sst1:
- ret
-
- ;--------------------------------------------------------------------
- ;restore_context
- ;--------------------------------------------------------------------
- ;utility used to save current context
- ;in:
- ; cs:si = save area
- ;out:
- ; cx,di,si,es,ds destroyed
- ;
- ;--------------------------------------------------------------------
-
- ifdef DEBUG
- public restore_context
- endif
-
- restore_context:
- cld
- mov ax,cs
- mov ds,ax ;ds:si -> save area
- xor ax,ax
- mov es,cx
- 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
- les di,cs:dos_state
- mov cx,cs:dctx_szsmall
- shr cx,1
- rep movsw
- jnc rst1
- movsb
- rst1:
- 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
-
-
- ;--------------------------------------------------------------------
- ; srvx_init
- ;--------------------------------------------------------------------
- ;
- ;srvx_init(name, mid)
- ; char far *name; /* name of srvx process, 8 chars long */
- ; int mid; /* our ID on mux (int 2fh) chain
- ;
- ;
- ;assumes srvx_preinit() has been called to verify system ready
- ;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.
- ;--------------------------------------------------------------------
-
- ;this routine gets control on first call to srvx_wait(). It
- ;sets up this code as a resident program.
-
- ifdef DEBUG
- public got_req
- endif
-
- go_tsr:
- cli
- DOS 3100h
-
- __name = 6
- __mid = 10
-
- public _srvx_init
- _srvx_init proc far
- push bp
- mov bp,sp
- push di
- push si
-
- assume ds:DGROUP
-
- ;cut off mem alloc
- call fxalloc
-
-
- 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
-
- ;copy name to static buffer
-
-
- push cs
- pop es
- mov di,OTX srvx_name
- lds si,DWO [bp+__name]
- cld
- mov cx,8/2
- rep movsw
-
-
- ; copy current context to user context save
- ; (the first "user" is us, going tsr on first call to srvx_wait())
-
- mov di,OTX u_ctxt
- call save_context
-
- push cs
- pop ds
-
- ; turn off break checking
-
- mov dl,0
- DOS 3301h
-
-
- ;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
-
- ;set up a trap on server's int 21 functions
- DOS 3521h
- mov WO cs:i21_passon,bx
- mov WO cs:i21_passon+2,es
- mov dx,OTX i21_trap
- mov ax,cs
- mov ds,ax
- DOS 2521h
-
- ; set mux int trap
-
- mov ax,[bp+__mid]
- mov cs:srvx_mid,al
-
- DOS 352fh
- mov WO cs:i2f_passon,bx
- mov WO cs:i2f_passon+2,es
- mov dx,OTX i2f_trap
- DOS 252fh
-
- ; set server extension trap
- mov ax,0b803h
- int 2fh
- mov WO cs:upost_passon,bx
- mov WO cs:upost_passon+2,es
- push cs
- pop es
- mov bx,OTX srvx_trap
- mov ax,0b804h
- int 2fh
-
- ; 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
-
- pop ds
- assume ds:nothing
- itxit:
- pop si
- pop di
- pop bp
- ret
- _srvx_init endp
-
-
- ;--------------------------------------------------------------------
- ;UCOUNT srvx_preinit(muxid)
- ;--------------------------------------------------------------------
- ;--------------------------------------------------------------------
-
- __midi = 6
-
- public _srvx_preinit
- _srvx_preinit proc far
- push bp
- mov bp,sp
- push di
- push si
- ; check dos version
-
- DOS 30h
- cmp al,3
- jz tpi1
- mov ax,1 ;return 1 for bad dos ver
- jmp tpi2
- tpi1:
- mov ax,0b800h ;test for server installed
- int 2fh
- or al,al
- mov ax,2
- jz tpi2 ;ret 2 if not installed
- test bx,40h
- mov ax,3
- jz tpi2 ;ret 3 if not server
- mov ax,[bp+__midi]
- mov ah,al
- mov al,0
- int 2fh
- or al,al
- mov ax,4
- jnz tpi2 ;ret 4 if srvx already installed
-
- ;get addr and size of DOS data for context sw
- 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 ;(this not used)
-
- xor ax,ax ;ret 0 if all ok
-
- tpi2: pop si
- pop di
- pop bp
- ret
- _srvx_preinit 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
-
- ;--------------------------------------------------------------------
- ;farcpybuf(far *dest, far * src, count)
- ;--------------------------------------------------------------------
- ;so that c code can be any model
- ;--------------------------------------------------------------------
- public _farcpybuf
- _farcpybuf proc far
- push bp
- mov bp,sp
- PUSHM <si,di,ds>
- les di,DWO [bp+6]
- lds si,DWO [bp+10]
- mov cx,[bp+14]
- shr cx,1
- jz fcp1
- rep movsw
- fcp1: jnc fcp2
- movsb
- fcp2: POPM <ds,di,si>
- pop bp
- ret
- _farcpybuf endp
-
- END_MOD
- end
-
-
-
-
-
-
-
-
-
-
-