Digital Research
This commit is contained in:
2020-11-06 18:50:37 +01:00
parent 621ed8ccaf
commit 31738079c4
8481 changed files with 1888323 additions and 0 deletions

View File

@@ -0,0 +1,27 @@
include cpyright.def
;*****************************************************
;*
;* BDOS - Basic Disk Operating System
;*
;*****************************************************
eject ! include equ.bdo ; symbol definitions
eject ! include system.def
eject ! include pd.def
eject ! include err.def
eject ! include qd.def
eject ! include modfunc.def
eject ! include xioscb.def
eject ! include bdosif.bdo ; system initialization
eject ! include file1.bdo ; file system part 1
eject ! include file2.bdo ; file system part 2
eject ! include file3.bdo ; file system part 3
eject ! include file4.bdo ; file system part 4
eject ! include patch.cod
eject ! include uda.fmt ; User Data area
eject ! include sysdat.fmt
eject ! include data.bdo
end


View File

@@ -0,0 +1,514 @@
;*****************************************************
;*
;* BDOS Interface
;*
;*****************************************************
MPM equ true
CPM equ false
cseg
org 0
jmp init ;BDOS initialization
jmp entry ;inter module entry pt.
sysdat dw 0 ;seg address of sysdat
supervisor equ offset $
dw 3
dw 0 ;SUP segment
db 'COPYRIGHT (C) 1981,'
db ' DIGITAL RESEARCH '
serial db '654321'
;====
init:
;====
; initialize bdos/xios modules
; assume ds=system data area
; save sysdat segment
mov sysdat,ds
mov bx,offset supmod ! mov si,supervisor
mov ax,[bx] ! mov cs:[si],ax
mov ax,2[bx] ! mov cs:2[si],ax
; create disk mx queue
mov dx,offset mxdiskqd ! mov cx,f_qmake
call mpmif
; open mx disk queue
mov dx,offset mxdiskqpb ! mov cx,f_qopen
call mpmif
; write mx disk queue
mov dx,offset mxdiskqpb ! mov cx,f_qwrite
call mpmif
retf
;*****************************************************
;*
;* BDOS function table
;*
;*****************************************************
;
; format of entry in functab
;
btab_addr equ word ptr 0
btab_flag equ byte ptr (btab_addr + word)
btablen equ btab_flag + byte
bf_getmx equ 0001h ;get mxdisk queue
BF_CSHELL EQU 0002H ;CONDITIONAL SHELL FUNCTION
BF_TANDW EQU 0004H ;TEST & WRITE FUNCTION
BF_FCB36 EQU 0008H ;SHELL 36 BYTE FCB FLAG
;
; bdos function table
;
functab dw func13 ! db 1 ; 0: disk reset
dw func14 ! db 1 ; 1: select disk
dw func15 ! db 1 ; 2: open file
dw func16 ! db 1 ; 3: close file
dw func17 ! db 1 ; 4: search first
dw func18 ! db 1 ; 5: search next
dw func19 ! db 1 ; 6: delete file
dw func20 ! db 3 ; 7: read sequential
dw func21 ! db 3 ; 8: write sequential
dw func22 ! db 1 ; 9: make file
dw func23 ! db 1 ; 10: rename file
dw func24 ! db 0 ; 11: return login vector
dw func25 ! db 0 ; 12: return current disk
dw func26 ! db 0 ; 13: set dma address
dw func27 ! db 1 ; 14: get alloc addr
dw func28 ! db 1 ; 15: write protect disk
dw func29 ! db 0 ; 16: get r/o vector
dw func30 ! db 1 ; 17: set file attributes
dw func31 ! db 1 ; 18: get disk parm addr
dw func32 ! db 0 ; 19: set/get user code
RDRAN_OFF dw func33 ! db 11 ; 20: read random
WRRAN_OFF dw func34 ! db 11 ; 21: write random
dw func35 ! db 1 ; 22: compute file size
dw func36 ! db 1 ; 23: set random record
dw func37 ! db 1 ; 24: reset drive
dw func38 ! db 1 ; 25: access drive
dw func39 ! db 1 ; 26: free drive
dw func40 ! db 3 ; 27: write random w/zero fill
DW FUNC41 ! DB 13 ; 28: TEST & WRITE RECORD
DW FUNC42 ! DB 1 ; 29: LOCK RECORD
DW FUNC43 ! DB 1 ; 30: UNLOCK RECORD
DW FUNC44 ! DB 0 ; 31: SET MULTI-SECTOR COUNT
DW FUNC45 ! DB 0 ; 32: SET BDOS ERROR MODE
DW FUNC46 ! DB 1 ; 33: GET DISK FREE SPACE
DW FUNC47 ! DB 1 ; 34: CHAIN TO PROGRAM
DW FUNC48 ! DB 1 ; 35: FLUSH BUFFERS
dw func51 ! db 0 ; 36: set dma base
dw func52 ! db 0 ; 37: get dma base
DW FUNC100 ! DB 1 ; 38: SET DIRECTORY LABEL
DW FUNC101 ! DB 1 ; 39: RETURN DIRECTORY LABEL DATA
DW FUNC102 ! DB 1 ; 40: READ FILE XFCB
DW FUNC103 ! DB 1 ; 41: WRITE OR UPDATE FILE XFCB
DW FUNC104 ! DB 1 ; 42: SET CURRENT DATE AND TIME
DW FUNC105 ! DB 1 ; 43: GET CURRENT DATE AND TIME
DW FUNC106 ! DB 1 ; 44: SET DEFAULT PASSWORD
DW FUNC107 ! DB 0 ; 45: RETURN SERIAL NUMBER
DW PR_TERM ! DB 1 ; 46: TERMINATE PROCESS
;=====
entry:
;=====
mov ch,0 ! mov ax,btablen
push dx ! mul cx ! pop dx
mov si,offset functab ! add si,ax
TEST cs:btab_flag[si],bf_getmx ! jz nomx
call getdiskmx ! jmps exit
nomx: call cs:btab_addr[si]
exit: mov ax,bx ! retf
;=========
getdiskmx:
;=========
; si = address of functab entry
; dx = argument
push si! push dx
MOV CX,F_CONSTAT
CALL MPMIF
pop dx! pop si
;do not allow ctrl c while in bdos
mov bx,rlr
mov ax,p_flag[bx] ! and ax,pf_tempkeep
PUSH AX
or p_flag[bx],pf_tempkeep
push si! push dx
mov cx,f_qread ! mov dx,offset mxdiskqpb
call mpmif
pop dx ! pop si
mov bx,rlr! test p_flag[bx],pf_ctlc
jz $+5
jmp retmonx
;switch to internal bdos stack
pushf ! pop ax ! cli
mov sssave,ss
mov spsave,sp
mov ss,sysdat
mov sp,offset bdosstack
push ax ! popf
;initialize bdos data area for user
push si ! push dx
mov ax,u_wrkseg
mov parametersegment,ax
mov ax,u_retseg
mov returnseg,ax
mov bx,rlr ! MOV PDADDR,BX
;set default user code
mov al,p_user[bx] ! mov usrcode,al
;set default disk
mov dl,p_dsk[bx]
MOV SELDSK,DL
;set default dma
mov setbf,false
mov ax,u_dma_ofst
cmp ax,dmaad ! je nodmaoch
mov setbf,true
nodmaoch:
mov ax,u_dma_seg
cmp ax,dmabase ! je nodmabch
mov setbf,true
nodmabch:
;copy uda bdos vars to local area
push es ! push ds ! pop es ! pop ds
mov si,offset u_dma_ofst ! mov di,offset dmaad
mov cx,uda_ovl_len ! rep movs al,al
push es ! push ds ! pop es ! pop ds
TEST PDCNT,1! JZ PDCNT_OK ;RESET PDCNT IF LOW ORDER BIT SET
MOV AL,PDCNT! CALL INC_PDCNT
PDCNT_OK:
pop dx ! push dx
mov info,dx ;info=dx
mov linfo,dl ;linfo = low(info) - don't equ
call entryzero
;Set DMA buffer if needed
cmp setbf,true ! jne nsetbf
call setdata
nsetbf:
;ready to go to the function
pop dx ! pop si
PUSH ES! PUSH DS! POP ES
MOV AH,CS:BTABFLAG[SI]
TEST AH,BF_TANDW ! JNZ SHELL
CMP MULT_CNT,1 ! JE NOSHELL
TEST AH,BF_CSHELL ! JNZ SHELL
NOSHELL:
CALL CALL_BDOS
RETMON:
POP ES
mov si,offset dmaad ! mov di,offset u_dma_ofst
mov cx,uda_ovl_len
rep movs al,al
;setup return registers
mov dx,returnseg
mov u_retseg,dx
mov bx,aret
;switch back to user's stack
pushf ! pop dx ! cli
mov ss,sssave
mov sp,spsave
push dx ! popf
;release mxdisk queue
RETMONX:
push bx
mov cx,f_qwrite ! mov dx,offset mxdiskqpb
call mpmif
;see if control c occured
mov si,rlr
pop bx! pop ax! not ax
xor ax,pf_tempkeep! and p_flag[si],ax
test p_flag[si],pf_ctlc
jz mxdiskexit
mov cx,f_terminate ! push bx
sub dx,dx ! call mpmif
pop bx
mxdiskexit:
ret
;
SHELL:
MOV SHELL_SI,SI
MOV BX,DMAAD! MOV SHELL_DMA,BX
MOV BX,OFFSET SHELL_RTN! PUSH BX
TEST AH,BF_FCB36! JNZ SHELL01
CALL PARSAVE33! JMP SHELL02
SHELL01:
CALL PARSAVE36! CALL SAVE_RR
SHELL02:
MOV SHELL_FLAG,TRUE
TEST AH,BF_TANDW! JNZ TST_WRT
JMP MULTIO
;
CBDOS:
MOV SI,SHELL_SI
CBDOS1:
MOV DX,INFO
CALL CALL_BDOS! MOV AL,BYTE PTR ARET! RET
;
SHELL_ERR:
MOV BX,ARET
MOV DL,MULT_CNT! POP AX! SUB DL,AL
MOV CL,4! SHL DL,CL! OR BH,DL
RET
;
SHELL_RTN:
MOV ARET,BX
TEST AH,BF_FCB36! JZ $+5! CALL RESET_RR
MOV BX,SHELL_DMA! MOV DMAAD,BX! CALL SET_DATA
MOV SHELL_FLAG,FALSE! CALL PARUNSAVE
JMP RETMON
;
INCR_RR:
CALL GET_RRA
INC W[BX]! JNZ INCR_RR_RET
INC BX! INC BX! INC B[BX]
INCR_RR_RET:
RET
;
SAVE_RR:
CALL SAVE_RR2! XCHG BX,DX
SAVE_RR1:
MOV CL,3! JMP MOVE
SAVE_RR2:
CALL GET_RRA! MOV DX,OFFSET SHELL_RR! RET
;
RESET_RR:
CALL SAVE_RR2! JMP SAVE_RR1
;
TST_WRT:
MOV AL,MULT_CNT! PUSH AX
CALL SET_DIR! POP AX
TST_WRT1:
PUSH AX! MOV SI,OFFSET RDRAN_OFF! CALL CBDOS1
OR AL,AL! JNZ SHELL_ERR
CALL COMPARE_RECS
CALL INCR_RR
ADD DMAAD,80H
POP AX! DEC AL! JNZ TST_WRT1
PUSH AX! CALL SET_DATA
CALL RESET_RR
MOV SHELL_SI,OFFSET WRRAN_OFF
POP AX
;
MULT_IO:
MOV AL,MULT_CNT
MULT_IO1:
PUSH AX! CALL CBDOS
OR AL,AL! JZ $+5! JMP SHELL_ERR
POP AX! PUSH AX! TEST AH,BF_FCB36! JZ MULT_IO2
CALL INCR_RR
MULT_IO2:
ADD DMAAD,80H! CALL SET_DATA
POP AX! DEC AL! JNZ MULT_IO1
XOR BX,BX
RET
;
COMPARE_RECS:
PUSH ES! MOV ES,DMABASE! MOV DI,DMAAD
MOV SI,BUFFA! MOV CL,64
REP CMPS AX,AX
POP ES
JNZ $+3! RET
POP BX! MOV BX,7! JMP SHELL_ERR
;
CALL_BDOS:
MOV SAVESP,SP
call cs:btab_addr[si]
BDOS_RETURN:
MOV AL,SELDSK
cmp resel,0
JE RETMON5
CMP COMP_FCB_CKS,TRUE! JNE RETMON1
CALL SET_CHKSUM_FCB
RETMON1:
MOV AL,XFCB_READ_ONLY! OR AL,AL! JZ RETMON2
MOV BX,INFO! OR 7[BX],AL
RETMON2:
CALL GETEXTA! MOV AL,HIGHEXT! CMP AL,60H! JNE RETMON3
SUB BX,4! MOV AL,80H
RETMON3:
OR [BX],AL
MOV AL,ACTUAL_RC! OR AL,AL! JZ RETMON4
CALL GETRCNTA! OR [BX],AL
RETMON4:
MOV AL,SELDSK
mov cl,fcbdsk
mov bx,info ! mov [bx],cl
cmp cl,0 ! je RETMON5
mov al,olddsk
RETMON5:
cmp parcopfl,true
jne RETMON6
call parunsave
RETMON6:
;copy local vars to uda
RET
;
XCRLF: mov cx,F_CONPRINT
mov dx,offset crlfstr
XOR BX,BX
jmp mpmif
;
XPRINT: mov dx,cx ! mov cx,F_CONPRINT
XOR BX,BX
jmp mpmif
;
parsave: ;copy parameterblock from user segment to bdos segment
;cl-reg = lenght of parameter block
;
TEST SHELL_FLAG,TRUE
JNZ PARRET
push ds
push ax
mov parcopfl,true
mov parlg,cl
xor ch,ch
mov si,info
mov infosave,si
mov di,offset loc_par_area
mov info,di
mov ds,parametersegment
rep movs al,al
pop ax
pop ds
parret: ret
;
parsave33: ;copy 33 byte length parameterblock
push cx
mov cl,33
jmps pscommon
;
parsave36: ;copy 36 byte length parameterblock
push cx
mov cl,36
pscommon:
call parsave
pop cx
ret
;
parunsave: ;copy local parameter block to user segment
;
TEST SHELL_FLAG,TRUE
JNZ PARRET
push es
push ax
push cx
mov cl,parlg
xor ch,ch
mov es,parametersegment
mov si,offset loc_par_area
mov di,infosave
mov info,di
rep movs al,al
pop cx
pop ax
pop es
ret
;these functions taken out of the
;bdosio.a86 module
setlret1: mov al,1
staret: mov lret,al
funcret: ret
;these functions added for mpm interface
;=====
mpmif:
;=====
; call mpm function
MOV SI,RLR
PUSH ES
MOV ES,P_UDA[SI]
callf cs:dword ptr .supervisor
POP ES
ret
entryzero:
;---------
push cx ! push es
mov cx,ds ! mov es,cx
mov cx,zerolength ! mov al,0
mov di,offset fcbdsk
rep stos al
pop es ! pop cx
ret
;*****************************************************
;*
;* bdos - xios interface
;*
;*****************************************************
bootf:
wbootf: mov cx,f_terminate ! jmp mpmif
homef: mov al,io_home ! jmps xiosif
seldskf:mov al,io_seldsk ! jmps xiosif
settrkf:mov al,io_settrk ! jmps xiosif
setsecf:mov al,io_setsec ! jmps xiosif
setdmf: mov al,io_setdma ! jmps xiosif
setdmbf:mov al,io_setdmab ! jmps xiosif
readf: mov al,io_read ! jmps xiosif
writef: mov al,io_write ! jmps xiosif
sectran:mov al,io_sectran ! jmps xiosif
flush: mov al,io_flush ! jmps xiosif
;====== ========================
xiosif: ; xios interface routine
;====== ========================
; input: al = function number
; cx = argument 1
; dx = argument 2
; output: ax = bx = output
MOV SI,RLR! PUSH ES! MOV ES,P_UDA[SI]
callf dword ptr .xiosmod
CLD! POP ES
ret


View File

@@ -0,0 +1,30 @@
;*****************************************************
;*
;* M P / M - 8 6 I I
;* ===================
;*
;* Copyright (c) 1981
;*
;* Digital Research
;* P.O.Box 579
;* Pacific Grove, California 93950
;*
;* (408) 649-3896
;* TWX 9103605001
;*
;* All Information contained in this source listing is
;*
;* PROPRIETORY
;* ===========
;*
;* All rights reserved. No part of this document
;* may be reproduced, transmitted, stored in a
;* retrieval system, or translated into any language
;* or computer language, in any form or by any means
;* without the prior written permission of Digital
;* Research, P.O Box 579, Pacific Grove, California.
;*
;*****************************************************


View File

@@ -0,0 +1,404 @@
;*****************************************************
;*
;* BDOS Data Area
;*
;*****************************************************
if CPM
;
; 8086 variables that must reside in code segment
;
cseg $
;
axsave dw 0 ; register saves
SS_save dw 0
SP_save dw 0
stack_begin dw endstack
;
; Variables in data segment:
;
dseg cpmsegment
org bdosoffset+bdoscodesize
header rs 128
rs 72
pag0 dw 0 ;address of user's page zero
ip0 db 0 ;initial page value for IP register
;
; memory control block
;
umembase dw 0 ;user'sbase for memory request
umemlg dw 0 ;length of memory req
contf db 0 ;flag indicates added memory is avail
;
;
hold_info dw 0 ;save info
hold_spsave dw 0 ;save user SP during program load
hold_sssave dw 0 ;save user SS during program load
mod8080 db 0
;
; byte I/O variables:
;
compcol db 0 ;true if computing column position
strtcol db 0 ;starting column position after read
column db 0 ;column position
listcp db 0 ;listing toggle
kbchar db 0 ;initial key char = 00
endif
if MPM
DSEG
org 0c00h
endif
efcb db 0e5h ;0e5=avail dir entry
rodsk dw 0 ;read only disk vector
dlog dw 0 ;logged-in disks
if MPM
RLOG DW 0 ;REMOVEABLE LOGGED-IN DISKS
TLOG DW 0 ;REMOVEABLE DISK TEST LOGIN VECTOR
NTLOG DW 0 ;NEW TLOG VECTOR
REM_DRV DB 0 ;REMOVABLE DRIVE FLAG
;1 = REMOVABLE DRIVE
;0 = PERMANENT DRIVE
endif
;The following variables are set to zero upon entry to file system
fcbdsk db 0 ;disk named in fcb
parcopfl db 0 ;true if parameter block copied
resel db 0 ;reselection flag
aret dw 0 ;adr value to return
lret equ byte ptr aret ;low(aret)
COMP_FCB_CKS DB 0 ;COMPUTE FCB CHECKSUM FLAG
SEARCH_USER0 DB 0 ;SEARCH USER 0 FOR FILE (OPEN)
MAKE_XFCB DB 0 ;MAKE & SEARCH XFCB FLAG
FIND_XFCB DB 0 ;SEARCH FIND XFCB FLAG
usrcode db 0 ;curr user num
zerolength equ (offset usrcode)-(offset fcbdsk)
if CPM
curdsk db 0 ;curr disk num
endif
SELDSK DB 0 ;SELECTED DISK NUM
info dw 0 ;info adr
srcha dw 0 ;search adr
;The Following variable order is critical
;Variables copied from UDA for MP/M X
;Variables included in FCB checksum for MP/M and CP/M X
;Variables used to access System Lock List for MP/M X
dmaad dw 0 ;dma offset 1
dmabase dw 0 ;dma base 2
FX DB 0 ;BDOS FUNCTION # 3
srchl db 0 ;search len 4
if MPM
srchaofst dw 0 ;search adr ofst 5
srchabase dw 0 ;search adr base 6
endif
dcnt dw 0 ;directory counter 7
DBLK DW 0 ;DIRECTORY BLOCK 8
ERROR_MODE DB 0 ;BDOS ERROR MODE 9
MULT_CNT DB 0 ;BDOS MULTI-SECTOR CNT 10
DF_PASSWORD RB 8 ;PROCESS DEFAULT PW 11
if MPM
PD_CNT DB 0 ;BDOS PROCESS CNT 12 1
endif
HIGH_EXT DB 0 ;FCB HIGH EXTENT BITS 2
XFCB_READ_ONLY DB 0 ;XFCB READ ONLY FLAG 3
CURDSK DB 0FFH ;CURRENT DISK 4 1
if MPM
PACKED_DCNT DB 0 ;PACKED DBLK+DCNT 2
DB 0
DB 0
PDADDR DW 0 ;PROCESS DESCRIPTOR ADDR 3
endif
; curtrka - alloca are set upon disk select
; (data must be adjacent)
cdrmaxa dw 0 ;ptr to cur dir max val
DRVLBLA dw 0 ;DRIVE LABEL DATA BYTE ADDR
buffa dw 0 ;ptr to dir dma addr
dpbaddr dw 0 ;curr disk param block addr
checka dw 0 ;curr checksum vector addr
alloca dw 0 ;curr alloc vector addr
addlist EQU 8 ;"$-buffa" = addr list size
; sectpt - offset obtained from disk parm block at dpbaddr
; (data must be adjacent)
sectpt dw 0 ;sectors per track
blkshf db 0 ;block shift factor
blkmsk db 0 ;block mask
extmsk db 0 ;extent mask
maxall dw 0 ;max alloc num
dirmax dw 0 ;max dir num
dirblk dw 0 ;reserved alloc bits for dir
chksiz dw 0 ;size of checksum vector
offsetv dw 0 ;offset tracks at beginning
endlist rs 0 ;end of list
dpblist equ (offset endlist)-(offset sectpt)
;size
; local variables
COMMON_DMA RB 16 ;COPY OF USER'S DMA 1ST 16 BYTES
XDMAAD DW OFFSET COMMON_DMA
RETURN_FFFF DB 0 ;SEL ERR FLAG FOR FXS 27 & 31
MAKE_FLAG DB 0 ;MAKE FUNCTION FLAG
FCB_EXISTS DB 0 ;FCB EXISTS FLAG (MAKE)
ACTUAL_RC DB 0 ;DIRECTORY EXT RECORD COUNT
SAVE_XFCB DB 0 ;SEARCH XFCB SAVE FLAG
SAVE_MOD DB 0 ;OPEN_REEL MODULE SAVE FIELD
SAVE_EXT DB 0 ;OPEN_REEL EXTENT SAVE FIELD
ATTRIBUTES DB 0 ;FCB INTERFACE ATTRIBUTES HOLD BYTE
if MPM
CHK_OLIST_FLAG DB 0 ;CHECK | TEST OLIST FLAG
LOCK_SP DW 0 ;LOCK STACK PTR
LOCK_SHELL DB 0 ;LOCK SHELL FLAG
CHECK_FCB_RET DB 0 ;CHECK_FCB RETURN SWITCH
LOCK_UNLOCK DB 0 ;LOCK | UNLOCK FUNCTION FLAG
INCR_PDCNT DB 0 ;INCREMENT PROCESS_CNT FLAG ??
FREE_MODE DB 0 ;FREE LOCK LIST ENTRIES FLAG ??
;1=FREE ENTRIES FOR CURDSK
;0=FREE ALL ENTRIES
CUR_POS DW 0 ;CURRENT POSITION IN LOCK LIST
PRV_POS DW 0 ;PREVIOUS POSITION IN LOCK LIST
;SDCNT, SDBLK, SDCNT0, SDBLK0 order critical
SDCNT DW 0 ;SAVED DCNT OF FILE'S 1ST FCB
SDBLK DW 0 ;SAVED DBLK OF FILE'S 1ST FCB
SDCNT0 DW 0 ;SAVED DCNT (USER 0 PASS)
SDBLK0 DW 0 ;SAVED DBLK (USER 0 PASS)
DONT_CLOSE DB 0 ;INHIBIT ACTUAL CLOSE FLAG
OPEN_CNT DB 0 ;PROCESS OPEN FILE COUNT
LOCK_CNT DB 0 ;PROCESS LOCKED RECORD COUNT
FILE_ID DW 0 ;ADDRESS OF FILE' LOCK LIST ENTRY
DELETED_FILES DB 0 ;DELETED FILES FLAG
SET_RO_FLAG DB 0 ;SET DRIVE R/O FLAG
CHECK_DISK DB 0 ;DISK RESET OPEN FILE CHECK FLAG
FLUSHED DB 0 ;LOCK LIST OPEN FILE FLUSH FLAG
;FREE_ROOT, LOCK_MAX, OPEN_MAX INITIALIZED BY SYSGEN
DW OFFSET FREE_ROOT
OPEN_ROOT DW 0 ;LOCK LIST OPEN FILE LIST ROOT
LOCK_ROOT DW 0 ;LOCK LIST LOCKED RECORD LIST ROOT
endif
if CPM
CHAIN_FLAG DB 0 ;CHAIN FLAG ??
STAMP DB 0FFH,0FFH,0FFH,0FFH ??
endif
tranv dw 0 ;adr of translate vector
fcbcopied db 0 ;true if copy$fcb called
rmf db 0 ;read mode flag for open$reel
wflag db 0 ;XIOS/BIOS write flag
dirloc db 0 ;directory flag in rename, etc.
seqio db 0 ;1 if seq i/o
linfo db 0 ;low(info)
dminx db 0 ;local for diskwrite
tinfo dw 0 ;temp for info in "make"
single db 0 ;set true if single byte
;alloc map
olddsk db 0 ;disk on entry to bdos
rcount db 0 ;record count in curr fcb
extval db 0 ;extent num and extmsk
VRECORD DB 0 ;curr virtual record
arecord dw 0 ;curr actual record
DB 0 ;CURR ACTUAL RECORD HIGH BYTE
ablock dw 0 ;curr actual block# * blkmsk
; local variables for directory access
dptr db 0 ;directory pointer 0,1,2,3
ldcnt equ byte ptr dcnt ;low(dcnt)
XDCNT DW 0 ;EMPTY DIRECTORY DCNT
XDBLK DW 0 ;EMPTY DIRECTORY DBLK
USER_ZERO_PASS DB 0 ;SEARCH USER ZERO FLAG
; SHELL VARIABLES
SHELL_SI DW 0 ;BDOS COMMAND OFFSET
SHELL_DMA DW 0 ;DMAAD SAVE AREA
SHELL_FLAG DB 0 ;PARSAVE SHELL FLAG
SHELL_RR DB 0,0,0 ;R0,R1,R2 SAVE AREA
; Special 8086 variables:
infosave dw 0 ;save for FCB adr
parametersegment dw 0 ;user parameter segment
if MPM
returnseg dw 0 ;user return segment
endif
parlg db 0 ;len of parameter block
; error messages
dskmsg db 'Bdos Err On '
dskerr db ' : ',0
permsg db 'Bad Sector',0
selmsg db 'Select',0
rofmsg db 'File '
rodmsg db 'R/O',0
XERR_LIST:
DW XE3,XE4,XE5,XE6,XE7,XE8,XE9,XE10,XE11
XE3 DB 'File Opened in Read/Only Mode'
XE4 DB 0
XE5 DB 'File Currently Open',0
XE6 DB 'Close Checksum Error',0
XE7 DB 'Password Error',0
XE8 DB 'File Already Exists',0
XE9 DB 'Illegal ? in FCB',0
XE10 DB 'Open File Limit Exceeded',0
XE11 DB 'No Room in System Lock List',0
crlfstr db 13,10,0
PR_FX DB 'Bdos Function: '
PR_FX1 DB ' '
PR_FCB DB ' File: '
PR_FCB1 RS 12
DB 0
DENIEDMSG DB 13,13,'Disk reset denied, Drive '
DENIEDDRV DB 0,':'
DB ' Console '
DENIEDCNS DB 0
DB ' Program '
DENIEDPRC DB '12345678',0
; Local buffer area:
loc_par_area rb 258 ;local user parameter (FCB,...)
if MPM
; bdos stack switch variables and stack
; used for all bdos disk functions
SAVE_SP RW 1
sssave rw 1
spsave rw 1
; 60 word BDOS stack
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
dw 0cccch,0cccch,0cccch
bdosstack rw 0
setdf db 0 ;flag to see if disk needs set on entry
setbf db 0 ;flag to see if dma needs set on entry
pf_keepsav dw 0 ;save pf_keep flag
mxdiskqd dw 0 ;link
db 0,0 ;net,org
dw qf_mx ;flags (MX queue)
db 'MXdisk '
dw 0,1 ;msglen,nmsgs
dw 0,0 ;nq,dq
dw 0,0 ;msgcnt,out
dw 0 ;buffer ptr
mxdiskqpb db 0 ;flgs
db 0 ;net
dw 0 ;qaddr
dw 1 ;nmsgs
dw 0 ;buffer
db 'MXdisk '
endif
if CPM
;
; Special 8086 variables:
;
ioloc db 0 ;iobyte
user_parm_seg dw 0 ;holds user parameter seg during load
nallocmem db 0 ;no. of allocated memory segments
ncrmem db 0 ;no. of available memory segments
crmem dw 0,0 ;memory table (16 elements)
dw 0,0,0,0,0,0
dw 0,0,0,0,0,0,0,0
dw 0,0,0,0,0,0,0,0
dw 0,0,0,0,0,0,0,0
;
mem_stack_length equ 40
memstack rs mem_stack_length
;8 possible allocations
stbase equ word ptr 0
stlen equ word ptr 2
ccpflag equ byte ptr 4
nccpalloc db 0 ;number of current ccp allocations
mem_stk_ptr dw 0 ;current memory stack location
stackarea rw ssize ;stack size
endstack rb 0 ;top of stack
;
endif
org 0fffh
db 0
end


View File

@@ -0,0 +1,47 @@
;
; BDOS symbols:
;
on EQU 0ffffh
off EQU 00000h
testf EQU off
;
; Special 8086 symbols:
;
b equ byte ptr 0
w equ word ptr 0
;
; literal constants
;
enddir EQU 0ffffh ;end of directory
;
; file control block (fcb) constants
;
fcblen EQU 32 ;fcb length
empty EQU 0e5h ;empty directory entry
lstrec EQU 127 ;last record# in extent
recsiz EQU 128 ;record size
dirrec EQU recsiz/fcblen ;directory elts / record
dskshf EQU 2 ;log2(dirrec)
dskmsk EQU dirrec-1
fcbshf EQU 5 ;log2(fcblen)
extnum EQU 12 ;extent number field
maxext EQU 31 ;largest extent number
ubytes EQU 13 ;unfilled bytes field
modnum EQU 14 ;data module number
maxmod EQU 63 ;largest module number
fwfmsk EQU 80h ;file write flag is high
;order modnum
namlen EQU 15 ;name length
reccnt EQU 15 ;record count field
dskmap EQU 16 ;disk map field
lstfcb EQU fcblen-1
nxtrec EQU fcblen
ranrec EQU nxtrec+1 ;random record field (2 bytes)
;
; reserved file indicators
;
rofile EQU 9 ;high order of first type char
invis EQU 10 ;invisible file in dir command
ARCHIVE EQU 11 ;FILE HAS BEEN ARCHIVED ATTRIBUTE
;


View File

@@ -0,0 +1,41 @@
;*****************************************************
;*
;* Error definitions
;*
;*****************************************************
;e_not_implemented equ 1 ; not implemented
;e_bad_entry equ 2 ; illegal func. #
;e_no_memory equ 3 ; cant find memory
;e_ill_flag equ 4 ; illegal flag #
;e_flag_ovrrun equ 5 ; flag over run in
;e_flag_underrun equ 6 ; flag underrun in
;e_no_qd equ 7 ; no unused qd's
;e_no_qbuf equ 8 ; no free qbuffer
;e_no_queue equ 9 ; cant find que in
;e_q_inuse equ 10 ; queue in use
;e_q_notactive equ 11 ; queue not on qrl
;e_no_pd equ 12 ; no free pd's
;e_q_protected equ 13 ; no que access
;e_q_empty equ 14 ; empty queue
;e_q_full equ 15 ; full queue
;e_ncliq equ 16 ; Cli queue missing
;e_no_cqbuf equ 17 ; no que buff space
;e_no_umd equ 18 ; no unused MD's
;e_ill_cns equ 19 ; illegal cns num.
;e_no_pdname equ 20 ; no PD match
;e_no_cnsmatch equ 21 ; no cns match
;e_nclip equ 22 ; no cli process
;e_illdisk equ 23 ; illegal disk #
;e_badfname equ 24 ; illegal filename
;e_badftype equ 25 ; illegal filetype
;e_nochar equ 26 ; char not ready
;e_ill_md equ 27 ; illegal mem descriptor
;e_bad_load equ 28 ; bad ret. from BDOS load
;e_bad_read equ 29 ; bad ret. from BDOS read
;e_bad_open equ 30 ; bad ret. from BDOS open
;e_nullcmd equ 31 ; null command
;e_not_owner equ 32 ; not owner of resource
;e_no_cseg equ 33 ; no CSEG in load file


View File

@@ -0,0 +1,904 @@
;*****************************************************************
;*****************************************************************
;** **
;** b a s i c d i s k o p e r a t i n g s y s t e m **
;** **
;*****************************************************************
;*****************************************************************
;
;
; error message handlers
;
pererror:
;report permanent error
MOV BX,OFFSET PERMSG
MOV CH,1
JMPS GOERR
roderror:
;report read/only disk error
MOV BX,OFFSET RODMSG
MOV CH,2
JMPS GOERR
roferror:
;report read/only file error
MOV BX,OFFSET ROFMSG
MOV CH,3
JMPS GOERR
selerror:
;report select error
MOV BX,OFFSET SELMSG
MOV CH,4
goerr:
MOV CL,0FFH
MOV ARET,CX ;SET ARET
CMP ERROR_MODE,0FFH ;IF ERROR_MODE = 0FFH THEN
JE RTN_PHY_ERRS ;RETURN PHYSICAL ERROR TO USER
JMPS REPORT_ERR ;REPORT ERROR TO USER
RTN_PHY_ERRS:
MOV BX,OFFSET RETURN_FFFF ;IF RETURN_FFFF THEN ARET = 0FFFFH
TEST B[BX],TRUE
JNZ $+5
JMP GOBACK
MOV B[BX],FALSE
MOV ARET,0FFFFH
JMP GOBACK
REPORT_ERR:
PUSH BX ;SAVE ERROR MESSAGE OFFSET
CALL XCRLF ;PRINT CR,LF
MOV AL,SELDSK
ADD AL,'A'
MOV DSKERR,AL ;SET D: FIELD
MOV CX,OFFSET DSKMSG
CALL XPRINT ;PRINT "Bdos Err On D:"
POP CX
CALL XPRINT ;PRINT ERROR MESSAGE
MOV AL,FX ;CONVERT FUNCTION TO CHARACTER
MOV CH,30H
MOV BX,OFFSET PRFX1
CMP AL,100
JC RPT_ERR1
MOV B[BX],31H
INC BX
SUB AL,100
RPT_ERR1:
SUB AL,10
JC RPT_ERR2
INC CH
JMPS RPT_ERR1
RPT_ERR2:
MOV [BX],CH
INC BX
ADD AL,3AH
MOV [BX],AL
INC BX
MOV B[BX],20H
MOV BX,OFFSET PR_FCB ;0 = MESSAGE DELIMITER
MOV B[BX],0
TEST RESEL,TRUE ;WAS RESELECT CALLED?
JZ RPT_ERR3 ;NO - DON'T PRINT FCB
MOV B[BX],20H ;REMOVE DELIMITER
MOV DX,INFO
INC DX
MOV BX,OFFSET PR_FCB1
MOV CL,8
CALL MOVE ;MOVE FILE NAME TO MESSAGE
MOV BX,DI
MOV DX,SI
MOV B[BX],'.' ;MOVE '.' TO MESSAGE
INC BX
MOV CL,3 ;MOVE FILE TYPE TO MESSAGE
CALL MOVE
RPT_ERR3:
CALL XCRLF ;ADVANCE TO NEW LINE
MOV CX,OFFSET PR_FX
CALL XPRINT ;PRINT "Bdos Function : ### "
; + "File: FFFFFFFF.TTT"
CALL XCRLF
CMP ERROR_MODE,0FEH ;IS ERROR MODE PRINT &
; RETURN ERRORS?
JE RPT_ERR4 ;YES
MOV SI,RLR
OR PFLAG[SI],PF_CTLC ;SET PROCESS ^C FLAG
RPT_ERR4:
JMP RTN_PHY_ERRS
;
; local subroutines for bios interface
;
;
;
move:
;move data length of length cl from source dx to
;destination given by bx
push cx
mov ch,0
mov si,dx
mov di,bx
rep movs al,al
pop cx
ret
;
;
selectdisk:
;select the disk drive given by curdsk, and fill
;the base addresses curtrka - alloca, then fill
;the values of the disk parameter block
;
MOV CURDSK,0FFH
MOV CL,SELDSK ;current disk# to cl
;lsb of dl = 0 if not yet
;logged in
call seldskf ;bx filled by call
;bx = 0000 if error,
;otherwise disk headers
cmp bx,0
jz ret4 ;rz
mov dx,[bx]
add bx,2
mov cdrmaxa,bx
add bx,2
MOV DRVLBLA,BX
ADD BX,4
;dx still contains .tran
xchg bx,dx
mov tranv,bx ;.tran vector
mov bx,offset buffa ;dx= source for move, bx=dest
mov cl,addlist
call move ;addlist filled
;now fill the disk
;parameter block
mov dx,dpbaddr
mov bx,offset sectpt ;bx is destination
mov cl,dpblist
call move ;data filled
;set single/double map mode
mov al,byte ptr maxall+1 ;largest allocation number
MOV SINGLE,TRUE ;assume a=00
or al,al
jz retselect
;high order of maxall not
;zero, use double dm
MOV SINGLE,FALSE
retselect:
MOV AL,SELDSK
MOV CURDSK,AL
INC AL
ret4: ret ;select disk function ok
;
home:
;move to home position, then offset to start of dir
call homef
;first directory pos. selected
MOV DBLK,0
ret
;
PASS_ARECORD:
MOV DX,ARECORD
MOV CH,BYTE PTR ARECORD+2
RET
;
rdbuff:
;read buffer and check if ok
CALL PASS_ARECORD
call readf ;current drive, track,....
jmps diocomp ;check for i/o errors
;
wrbufflg:
mov cl,wflag
wrbuff:
;write buffer and check condition
;write type (wrtype) is in register cl
;wrtype = 0 => normal write operation
;wrtype = 1 => directory write operation
;wrtype = 2 => start of new block
CALL PASS_ARECORD
OR CL,REM_DRV
call writef ;current drive, track, ...
diocomp: ;check for disk errors
or al,al
jz ret4 ;rz
CMP AL,2
JZ $+5
jmp pererror
JMP RODERROR
;
seekdir:
;seek the record containing the current dir entry
MOV DX,0FFFFH! XOR AH,AH ; MASK = FFFF
MOV BX,DBLK! CMP BX,0! JZ SEEKDIR1
INC DX! MOV DL,BLKMSK
MOV CL,BLKSHF! MOV AL,BH
; AH+BX = SHL(DBLK,BLKSHF)
SHL BX,CL! SHL AX,CL
SEEKDIR1:
MOV SI,DCNT
MOV CL,DSKSHF! SHR SI,CL
; ARECORD = SHL(DBLK,BLKSHF) + SHR(DCNT,DSKSHF) & MASK
AND DX,SI
ADD BX,DX! ADC AH,0
MOV ARECORD,BX! MOV BYTE PTR ARECORD+2,AH
seek:
;seek the track given by arecord (actual record)
MOV AX,ARECORD ;COMPUTE TRACK/SECTOR
XOR DX,DX
MOV DL,BYTE PTR ARECORD+2
DIV SECTPT ;DX=SECTOR, AX=TRACK
PUSH DX! MOV CX,AX
ADD CX,OFFSETV
CALL SETTRKF ;SET BIOS/XIOS TRACK
POP CX! MOV DX,TRANV
CALL SECTRAN ;SET BIOS/XIOS SECTOR
MOV CX,BX
JMP SETSECF ;RET
;
; utility functions for file access
;
dmposition:
;compute disk map position for vrecord to bx
mov bx,offset blkshf
mov cl,[bx] ;shift count to cl
mov al,vrecord ;current virtual record to a
shr al,cl
;a = shr(vrecord,blkshf) = vrecord/2**(sect/block)
mov ch,al ;save it for later addition
mov cl,7
sub cl,[bx]
mov al,extval ;extent value ani extmsk
;
;blkshf = 3,4,5,6,7
;cl=4,3,2,1,0
;shift is 4,3,2,1,0
shl al,cl
;arrive here with a = shl(ext and extmsk,7-blkshf)
add al,ch ;add the previous
;shr(vrecord,blkshf) value
;al is one of the following
;values, depending upon alloc
;bks blkshf
;1k 3 v/8 + extval * 16
;2k 4 v/16+ extval * 8
;4k 5 v/32+ extval * 4
;8k 6 v/64+ extval * 2
;16k 7 v/128+extval * 1
ret ;with dm$position in a
;
GET_DMA: ;BX = .FCB(DSKMAP)
MOV BX,INFO
ADD BX,DSKMAP
RET
;
getdm:
;return disk map value from position given by cx
CALL GET_DMA
add bx,cx ;index by asingle byte value
cmp single,0 ;single byte/map entry?
jz getdmd ;get disk map single byte
mov bl,[bx]
mov bh,0
ret ;with bx=00bb
getdmd:
add bx,cx ;bx=.fcb(dm+1*2)
;return double precision value
mov bx,[bx]
ret
;
index:
;compute disk block number from current fcb
call dmposition ;0...15 in register al
mov cl,al
mov ch,0
call getdm ;value to bx
mov arecord,bx
ret
;
alloct:
;called following index to see if block allocated
mov bx,arecord
or bx,bx
ret
;
atran:
;compute actual record address, assuming index called
mov cl,blkshf ;shift count to reg al
mov bx,arecord
XOR AH,AH
MOV AL,BH
shl bx,cl
SHL AX,CL
mov ablock,bx ;save shifted block #
mov al,vrecord
and al,blkmsk ;masked value in al
or bl,al
mov arecord,bx ;arecord=bx or
;(vrecord and blkmsk)
MOV BYTE PTR ARECORD+2,AH
ret
;
GET_ATTS:
;GET INTERFACE ATTRIBUTES (F5' - F8') FROM FCB
;RETURN ATTRIBUTES LEFT SHIFTED IN AL
;ZERO INTERFACE ATTRIBUTE BITS IN FCB
MOV BX,INFO! ADD BX,5
MOV CL,4! MOV DX,01111111B
GET_ATTS_LOOP:
MOV AL,[BX]! MOV CH,AL
RCL AL,1! ADC DH,DH
AND CH,DL! MOV [BX],CH
INC BX! DEC CL! JNZ GET_ATTS_LOOP
MOV AL,DH! MOV CL,4! SHL AL,CL! RET
;
GET_S1: ;GET CURRENT S1 FIELD TO AL
CALL GETEXTA! INC BX! MOV AL,[BX]! RET
;
GET_RRA:
;GET CURRENT RAN REC FIELD ADDRES TO BX
MOV BX,INFO! ADD BX,RANREC! RET
;
GET_RCNTA:
;GET RECCNT ADDRES TO BX
MOV BX,INFO! ADD BX,RECCNT! RET
;
getexta:
;get current extent field address to al
mov bx,info
add bx,extnum ;bx=.fcb(extnum)
; mov al,[bx] ;*************** removed 7/14
ret
;
gtfcba:
;compute reccnt and nxtrec addresses for get/setfcb
mov dx,reccnt
add dx,info ;dx=.fcb(reccnt)
mov bx,(nxtrec-reccnt)
add bx,dx ;bx=.fcb(nxtrec)
ret
;
getfcb:
;set variables from currently addressed fcb
call gtfcba ;addresses in dx, bx
mov al,[bx]
mov vrecord,al ;vrecord=fcb(nxtrec)
xchg bx,dx
mov al,[bx]
mov rcount,al ;rcount=fcb(reccnt)
call getexta ;bx=.fcb(extnum)
mov al,extmsk ;extent mask to a
and al,[bx] ;fcb(extnum) and extmsk
mov extval,al
ret
;
setfcb:
;place values back into current fcb
call gtfcba ;addresses to dx, bx
mov al,seqio
cmp al,02
jnz setfc1
xor al,al ;check ranfill
setfc1:
;=1 if sequential i/o
add al,vrecord
mov [bx],al ;fcb(nxtrec)=vrecord+seqio
xchg bx,dx
mov al,rcount
mov [bx],al ;fcb(reccnt)=rcount
ret
;
;
cmpecs:
;compute checksum for current directory buffer
mov cx,recsiz ;size of directory buffer
mov bx,buffa ;current directory buffer
xor al,al ;clear checksum value
cmpec0:
add al,[bx]
inc bx
loop cmpec0
ret ;with checksum in a
;
CHKSUM_FCB: ;COMPUTE CHECKSUM FOR FCB
;ADD 1ST 12 BYTES OF FCB + CURDSK +
; HIGH_EXT + XFCB_READONLY + BBH
SUB AL,AL
if MPM
MOV BX,OFFSET PDCNT
MOV CX,4
endif
if CPM
MOV BX,OFFSET HIGH_EXT
MOV CX,3
endif
CALL CMPEC0
ADD AL,0BBH ;ADD BIAS
MOV BX,INFO ;ADD 1ST 12 BYTES OF FCB
MOV CX,12
CALL CMPEC0
INC BX ;SKIP EXTENT
ADD AL,[BX] ;ADD S1
ADD BX,3 ;SKIP MODNUM & RECCNT
MOV CX,16 ;CHECKSUM DISK MAP
CALL CMPEC0
OR AL,AL ;ZERO FLAG SET IF CHEKSUM VALID
RET
;
SET_CHKSUM_FCB:
CALL CHKSUM_FCB ;COMPUTE FCB CHECKSUM
JZ RET45 ;RETURN IF VALID
MOV AH,AL ;SAVE CURRENT CHECKSUM VALUE
CALL GETS1 ;GET S1 BYTE
SUB AH,AL ;SUBTRACT FROM CHECKSUM VALUE
NEG AH ;NEGATE RESULT
MOV [BX],AH ;RESTORE S1
RET45: RET
;
RESET_CHECKSUM_FCB:
MOV COMP_FCB_CKS,0
CALL CHKSUM_FCB ;COMPUTE FCB CHECKSUM
JNZ RET45 ;RETURN IF INVALID
CALL GETS1 ;INVALIDATE S1
INC B[BX]
RET
;
CHEK_FCB:
CMP HIGH_EXT,01100000B ;DOES HIGH_EXT = 60H
JNE CHKSUM_FCB ;NO
MOV BX,INFO ;YES - SET FCB(0) TO ZERO
MOV B[BX],0
JMP CHKSUM_FCB
;
CHECK_FCB:
if MPM
MOV CHECK_FCB_RET,FALSE
CHECK_FCB1:
endif
CALL CHEK_FCB ;COMPUTE FCB CHECKSUM
JZ RET45 ;VALID IF ZERO
if MPM
AND AL,0FH ;IS MOD(CHKSUM,16) = 0 ?
JNZ CHECK_FCB3 ;NO - INVALID CHECKSUM
CMP PD_CNT,0 ;IS PDCNT = 0 ?
JZ CHECK_FCB3 ;YES - INVALID CHECKSUM
MOV BYTE PTR SDCNT+1,0FFH
MOV DONT_CLOSE,TRUE
CALL CLOSE1 ;ATTEMPT PARTIAL CLOSE
MOV BX,OFFSET LRET
INC B[BX]
JZ CHECK_FCB3 ;PARTIAL CLOSE FAILED
MOV B[BX],0 ;ZERO LRET
CALL PACK_SDCNT ;LOOK FOR FILE IN LOCK LIST
MOV CH,5
CALL SEARCH_OLIST
JNZ CHECK_FCB3 ;NOT FOUND - INVALID CHECKSUM
RET ;FOUND - CHECKSUM OK
CHECK_FCB3:
endif
POP BX ;DISCARD RETURN ADDRESS
if MPM
CHECK_FCB4:
TEST CHECK_FCB_RET,TRUE
JNZ RET45
endif
MOV AL,10 ;10 = CHECKSUM ERROR
JMP STA_RET
setcdisk:
;set a "1" value in SELDSK position of cx
MOV AL,SELDSK
SET_CDISK1: ;SET A "1" VALUE IN AL POSITION OF CX
push cx ;save input parameter
MOV CL,AL
mov bx,1 ;number to shift
shl bx,cl ;bx = mask to integrate
pop cx ;original mask
or bx,cx ;bx = mask or rol(1,curdsk)
ret
;
nowrite:
;return true if dir checksum difference occurred
MOV DX,RODSK
TEST_VECTOR:
MOV CL,SELDSK
TEST_VECTOR1:
SHR DX,CL
AND DX,1
ret ;non zero if nowrite
;
setro:
;set current disk to read only
mov cx,rodsk
call setcdisk ;sets bit to 1
mov rodsk,bx
;high water mark in directory
;goes to max
mov dx,dirmax
inc dx
mov bx,cdrmaxa ;bx = .cdrmax
mov [bx],dx ;cdrmax = dirmax
ret
;
ckrodir:
;check current directory element for read/only status
call getdptra ;address of element
;
ckrofile:
;check current buff(dptr) or fcb(0) for r/o status
CALL RO_TEST
jae ret5 ;rnc
jmp roferror
RO_TEST:
ADD BX,ROFILE ;offset to r/o bit
mov al,[bx]
rcl al,1
RET
checkwrite:
;check for write protected disk
call nowrite
jz ret5 ;rz
jmp roderror
;
getdptra:
;compute the address of a directory element at
;positon dptr in the buffer
mov bx,buffa
mov al,dptr
addh:
;bx = bx + al
mov ah,0
add bx,ax
ret5: ret
;
;
getmodnum:
;compute the address of the module number
;bring module number to accumulator
;(high order bit is fwf (file write flag)
mov bx,info
add bx,modnum
mov al,[bx]
ret ;al=fcb(modnum)
;
clrmodnum:
;clear the module number field for user open/make
call getmodnum
mov b[bx],0 ;fcb(modnum)=0
ret
;
CLR_EXT:
CALL GETEXTA
AND B[BX],1FH
RET
;
setfwf:
call getmodnum ;bx=.fcb(modnum),
;al=fcb(modnum)
;set fwf(file write flag) to 1
or al,fwfmsk
mov [bx],al ;fcb(modnum)=fcb(modnum) + 80h
;also returns non zero
;in accumulator
ret
;
;
compcdr:
;return cy if cdrmax > dcnt
mov dx,dcnt ;dx = directory counter
mov bx,cdrmaxa ;bx=.cdrmax
cmp dx,[bx]
;condition dcnt - cdrmax
;produces cy if cdrmax>dcnt
ret6: ret
;
setcdr:
;if not (cdrmax > dcnt) then cdrmax = dcnt+1
call compcdr
jb ret6 ;return if cdrmax > dcnt
;otherwise, bx = .cdrmax+1,
;dx = dcnt
inc dx
mov [bx],dx
ret
;
subdh:
;compute bx = dx - bx
push dx
sub dx,bx
mov bx,dx
pop dx
ret
;
newchecksum:
;drop through to compute new checksum
mov cl,true
checksum:
;compute current checksum record and update the
;directory element if cl=true, or check for = if not
;drec < chksiz?
MOV DX,ARECORD
mov bx,chksiz
AND BH,7FH ;REMOVE PERMANENT DRIVE BIT
call subdh ;dx-bx
jae ret6 ;skip checksum if past
;checksum vector size
;drec < chksiz, so continue
push cx ;save init flag
call cmpecs ;check sum value to al
MOV BX,ARECORD ;value of ARECORD
add bx,checka ;bx=.check(ARECORD)
pop cx ;recall true or false to cl
inc cl ;true produces zero flag
jz initcs
if MPM
INC CL ;0FEH PRODUCES ZERO FLAG
JZ TEST_DIR_CS
endif
;not initializing, compare
cmp al,[bx] ;compute$cs=check(ARECORD)?
jz ret7 ;no message if ok
;checksum error, are we beyond
;the end of the disk?
call compcdr
jae ret7 ;no message if so
if MPM
CALL NOWRITE ;FLUSH FILES IF DRIVE IS NOT
JNZ RET7 ;READ/ONLY
CALL FLUSH_FILE0
endif
jmp setro ;read/only disk set
if MPM
TEST_DIR_CS:
CMP AL,[BX] ;COMPUTE_CS=CHECK(ARECORD)
JZ RET7
JMP FLUSH_FILES
endif
initcs:
;initializing the checksum
mov [bx],al
ret7: ret
;
;
wrdir:
;write the current directory entry, set checksum
CALL CHECK_WRITE ;VERIFY DISK IS READ/WRITE
call newchecksum ;initialize entry
call setdir ;directory dma
mov cl,1 ;indicates a write directory
call wrbuff ;write the buffer
jmp setdata ;to data dma address
;ret
;
rddirbuf:
;read a directory entry into the directory buffer
call setdir ;directory dma
call rdbuff ;directory record loaded
; jmp setdata
; ret
;
setdata:
;set data dma address
mov cx,dmabase
call setdmbf ;set disk i/o base
mov bx,offset dmaad
jmps setdma ;to complete the call
;
setdir:
;set directory dma address
mov cx,ds
call setdmbf ;set bios disk i/o base
mov bx,offset buffa ;jmp setdma to complete call
;
setdma:
;bx=.dma address to set (i.e., buffa or dmaad)
mov cx,[bx] ;parameter ready
jmp setdmf
;
;
dirtouser:
;copy the directory entry to the user buffer
;after call to search or searchn by user code
mov dx,buffa ;source is directory buffer
mov bx,dmaad ;destination is user dma addr.
mov cl,recsiz ;copy entire record
push es ;move to user segment
mov es,parametersegment
call move
pop es
ret
MAKE_FCB_INV:
;FLAG FCB AS INVALID
CALL SETFWF ;RESET FCB WRITE FLAG
INC BX
INC BX
MOV W[BX],0FFFFH
RET
CHK_INV_FCB:
;CHECK FOR INVALID FCB
CALL GETDMA
JMPS TEST_FFFF
TST_INV_FCB:
;TEST FOR INVALID FCB
CALL CHK_INV_FCB
JNZ RET8
POP BX
MOV AL,9
JMP STA_RET
endofdir:
;return zero flag if at end of director, non zero
;if not at end (end of dir if dcnt = 0ffffh)
mov bx,offset dcnt
TEST_FFFF:
CMP W[BX],0FFFFH
; mov al,[bx] ;may be 0ffh
; inc bx
; cmp al,[bx] ;low(dcnt) = high(dcnt)?
; jnz ret8 ;return non zero if different
; ;high and low the same,= 0ffh?
; inc al ;0ffh becomes 00 if so
ret8: ret
;
setenddir:
;set dcnt to the end of the directory
MOV DCNT,ENDDIR
ret
;
rddir:
;read next directory entry, with cl=true if initializing
mov dx,dirmax ;in preparation for subtract
mov bx,dcnt
inc bx
mov dcnt,bx ;dcnt=dcnt+1
;continue while dirmax >= dcnt
;(dirmax-dcnt no cy)
call subdh ;dx-bx
jae rddir0
;yes, set dcnt to end
;of directory
jmps setenddir
; ret
rddir0:
;not at end of directory, seek next element
;cl=initialization flag
mov al,ldcnt
and al,dskmsk ;low(dcnt) and dskmsk
push cx
mov cl,fcbshf ;to multiply by fcb size
shl al,cl
pop cx
;a = (low(dcnt) and dskmsk)
;shl fcbshf
mov dptr,al ;ready for next dir operation
or al,al
jnz ret71 ;return if not a new record
push cx ;save initialization flag cl
call seekdir ;seek proper record
call rddirbuf ;read the directory record
pop cx ;recall initialization flag
jmp checksum ;checksum the directory elt
;ret
;
;
getallocbit:
;given allocation vector
;position on cx, return byte
;containing cx shifted so that the least significant
;bit is in the low order accumulator position. bx is
;the address of the byte for
;possible replacement in
;memory upon return, and dh contains the number of shifts
;required to place the returned value back into position
;
mov dx,cx
and cl,111b
inc cl
mov ch,cl
;ch and cl both contain the
;number of bit positions to
;shift
mov cl,3
shr dx,cl ;shift bit address right 3 for byte address
;dx shr 3 to dx
mov bx,alloca ;base addr. of alloc. vector
add bx,dx
;byte to a, hl =
mov al,[bx] ;.alloc(cx shr 3)
;now move the bit to the
;low order position of al
mov cl,ch
rol al,cl
mov dx,cx
ret71: ret
;
;
setallocbit:
;cx is the bit position of alloc to set or reset. the
;value of the bit is in register dl.
push dx
call getallocbit ;shifted val al,count in dl
and al,11111110b ;mask low bit to zero
;(may be set)
pop cx
or al,cl ;low bit of cl masked into al
; jmp rotr
; ret
rotr:
;byte value from alloc is in register al, with shift count
;in register ch (to place bit back into position), and
;target alloc position in registers bx, rotate and replace
;
push cx
mov cl,dh
ror al,cl
mov [bx],al
pop cx
ret
;
;************* end bdos filesystem part 1 **************
end


File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@@ -0,0 +1,16 @@
; a86 bdos
gencmd bdos
era bdos.mpm
ren bdos.mpm=bdos.cmd
xref86 bdos
; era bdos.lst
vax bdos.xrf $$atn
; pip lst:=bdos.xrf
; era bdos.xrf
; era bdos.sym
; era bdos.h86
;
;
; MAKE BDOS.MPM COMPLETE
;


View File

@@ -0,0 +1,147 @@
;*****************************************************
;*
;* MP/M-86 Inter-Module Function Definitions
;*
;* Same calling conventions as User programs
;* except CX = function instead of CL
;* BX = 2nd parameter on entry
;* (CH=module, CL=function # in module)
;*
;*****************************************************
; Module definitions
user equ 0
sup equ 1
rtm equ 2
mem equ 3
cio equ 4
bdos equ 5
xios equ 6
net equ 7
; Bits that represent present modules
; in module_map
supmod_bit equ 001h
rtmmod_bit equ 002h
memmod_bit equ 004h
bdosmod_bit equ 008h
ciomod_bit equ 010h
xiosmod_bit equ 020h
netmod_bit equ 040h
; Supervisor Functions
;f_sysreset equ (user * 0100h) + 0
;f_conin equ (user * 0100h) + 1
;f_conout equ (user * 0100h) + 2
;f_rawconin equ (user * 0100h) + 3
;f_rawconout equ (user * 0100h) + 4
;f_lstout equ (user * 0100h) + 5
;f_rawconio equ (user * 0100h) + 6
;f_getiobyte equ (user * 0100h) + 7
;f_setiobyte equ (user * 0100h) + 8
f_conwrite equ (user * 0100h) + 9
f_conread equ (user * 0100h) + 10
f_constat equ (user * 0100h) + 11
;f_getversion equ (user * 0100h) + 12
;f_diskreset equ (user * 0100h) + 13
;f_diskselect equ (user * 0100h) + 14
;f_fopen equ (user * 0100h) + 15
;f_fclose equ (user * 0100h) + 16
;f_searchfirst equ (user * 0100h) + 17
;f_searchnext equ (user * 0100h) + 18
;f_fdelete equ (user * 0100h) + 19
;f_freadseq equ (user * 0100h) + 20
;f_fwriteseq equ (user * 0100h) + 21
;f_fmake equ (user * 0100h) + 22
;f_frename equ (user * 0100h) + 23
;f_loginvector equ (user * 0100h) + 24
;f_getdefdisk equ (user * 0100h) + 25
;f_setdma equ (user * 0100h) + 26
;f_getallocvec equ (user * 0100h) + 27
;f_writeprotect equ (user * 0100h) + 28
;f_getrovector equ (user * 0100h) + 29
;f_setfileattr equ (user * 0100h) + 30
;f_getdpb equ (user * 0100h) + 31
;f_usercode equ (user * 0100h) + 32
;f_freadrdm equ (user * 0100h) + 33
;f_fwriterdm equ (user * 0100h) + 34
;f_filesize equ (user * 0100h) + 35
;f_setrndrec equ (user * 0100h) + 36
;f_resetdrive equ (user * 0100h) + 37
;f_accessdrive equ (user * 0100h) + 38
;f_freedrive equ (user * 0100h) + 39
;f_writerndzero equ (user * 0100h) + 40
;f_callbios equ (user * 0100h) + 50
;f_setdmab equ (user * 0100h) + 51
;f_getdma equ (user * 0100h) + 52
;f_getmaxmem equ (user * 0100h) + 53
;f_getabsmaxmem equ (user * 0100h) + 54
;f_allocmem equ (user * 0100h) + 55
;f_allocabsmem equ (user * 0100h) + 56
;f_freemem equ (user * 0100h) + 57
;f_freeallmem equ (user * 0100h) + 58
;f_userload equ (user * 0100h) + 59
;f_malloc equ (user * 0100h) + 128
;f_memfree equ (user * 0100h) + 130
;f_polldev equ (user * 0100h) + 131
;f_flagwait equ (user * 0100h) + 132
;f_flagset equ (user * 0100h) + 133
f_qmake equ (user * 0100h) + 134
f_qopen equ (user * 0100h) + 135
;f_qdelete equ (user * 0100h) + 136
f_qread equ (user * 0100h) + 137
;f_cqread equ (user * 0100h) + 138
f_qwrite equ (user * 0100h) + 139
;f_cqwrite equ (user * 0100h) + 140
;f_delay equ (user * 0100h) + 141
;f_dispatch equ (user * 0100h) + 142
f_terminate equ (user * 0100h) + 143
;f_createproc equ (user * 0100h) + 144
;f_setprior equ (user * 0100h) + 145
;f_conattach equ (user * 0100h) + 146
;f_condetach equ (user * 0100h) + 147
;f_setdefcon equ (user * 0100h) + 148
;f_conassign equ (user * 0100h) + 149
;f_clicmd equ (user * 0100h) + 150
;f_callrsp equ (user * 0100h) + 151
;f_parsefilename equ (user * 0100h) + 152
;f_getdefcon equ (user * 0100h) + 153
;f_sdataddr equ (user * 0100h) + 154
;f_timeofday equ (user * 0100h) + 155
;f_pdaddress equ (user * 0100h) + 156
;f_abortprocess equ (user * 0100h) + 157
;f_lstattach equ (user * 0100h) + 158
;f_lstdetach equ (user * 0100h) + 159
;f_setdeflst equ (user * 0100h) + 160
;f_clstattch equ (user * 0100h) + 161
;f_cconattch equ (user * 0100h) + 162
;f_mpmvernum equ (user * 0100h) + 163
;f_getdeflst equ (user * 0100h) + 164
; Internal RTM functions
;f_sleep equ (rtm * 0100h) + 18
;f_wakeup equ (rtm * 0100h) + 19
;f_findpdname equ (rtm * 0100h) + 20
; Internal MEM functions
;f_share equ (mem * 0100h) + 8
;f_maualloc equ (mem * 0100h) + 9
;f_maufree equ (mem * 0100h) + 10
;f_mlalloc equ (mem * 0100h) + 11
;f_mlfree equ (mem * 0100h) + 12
; Internal SUP functions
;f_load equ (sup * 0100h) + 10
; Internal CIO functions
f_conprint equ (cio * 0100h) + 14


View File

@@ -0,0 +1,41 @@
;*****************************************************
;*
;* PATCH AREA -- 128 bytes long
;*
;*****************************************************
patch:
nop ! nop ! nop ! nop ! nop ! nop ;00-0f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;10-1f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;20-2f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;30-3f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;40-4f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;50-5f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;60-6f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop
nop ! nop ! nop ! nop ! nop ! nop ;70-7f
nop ! nop ! nop ! nop ! nop ! nop
nop ! nop ! nop ! nop


View File

@@ -0,0 +1,111 @@
;*****************************************************
;*
;* Process Descriptor - with the UDA associated
;* with the PD, describes the current
;* state of a Process under MP/M-86
;*
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 00| link | thread |stat |prior| flag |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 08| Name |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 10| uda | dsk | user| ldsk|luser| mem |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 18| dvract | wait | org | net | parent |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 20| cns |abort| cin |cout | lst | sf3 | sf4 | sf5 |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;* 28| reserved | pret | scratch |
;* +-----+-----+-----+-----+-----+-----+-----+-----+
;*
;* link - Used for placement into System Lists
;* thread - link field for Thread List
;* stat - Current Process activity
;* prior - priority
;* flag - process state flags
;* name - name of process
;* uda - Segment Adress of User Data Area
;* dsk - Current default disk
;* user - Current default user number
;* ldsk - Disk program loaded from
;* luser - User number loaded from
;* mem - pointer to MD list of memory owned
;* by this process
;* dvract - bit map of currently active drives
;* wait - parameter field while on System Lists
;* org - Network node that originated this process
;* net - Network node running this process
;* parent - process that created this process
;* cns - controlling console
;* abort - abort code
;* cin - standard file #0 (console input)
;* cout - standard file #1 (console output)
;* lst - standard file #2 (list output)
;* sf3 - standard file #3
;* sf4 - standard file #4
;* sf5 - standard file #5
;* reserved- not currently used
;* pret - return code at termination
;* scratch - scratch word
;*
;*****************************************************
p_link equ word ptr 0
p_thread equ word ptr p_link + word
p_stat equ byte ptr p_thread + word
p_prior equ byte ptr p_stat + byte
p_flag equ word ptr p_prior + byte
p_name equ byte ptr p_flag + word
p_uda equ word ptr p_name + pnamsiz
p_dsk equ byte ptr p_uda + word
p_user equ byte ptr p_dsk + byte
p_ldsk equ byte ptr p_user + byte
p_luser equ byte ptr p_ldsk + byte
p_mem equ word ptr p_luser + byte
p_dvract equ word ptr p_mem + word
p_wait equ word ptr p_dvract + word
p_org equ byte ptr p_wait + word
p_net equ byte ptr p_org + byte
p_parent equ word ptr p_net + byte
p_cns equ byte ptr p_parent + word
p_abort equ byte ptr p_cns + byte
p_cin equ byte ptr p_abort + byte
p_cout equ byte ptr p_cin + byte
p_lst equ byte ptr p_cout + byte
p_sf3 equ byte ptr p_lst + byte
p_sf4 equ byte ptr p_sf3 + byte
p_sf5 equ byte ptr p_sf4 + byte
p_reserved equ word ptr p_sf5 + byte
p_pret equ word ptr p_reserved + (2*word)
p_scratch equ byte ptr p_pret + word
p_wscrtch equ word ptr p_scratch
;
; Process descriptor pd_status values
;
ps_run equ 00 ; in ready list root
ps_poll equ 01 ; in poll list
ps_delay equ 02 ; in delay list
ps_swap equ 03 ; in swap list
ps_term equ 04 ; terminating
ps_sleep equ 05 ; sleep processing
ps_dq equ 06 ; in dq list
ps_nq equ 07 ; in nq list
ps_flagwait equ 08 ; in flag table
ps_ciowait equ 09 ; in c_queue list
;
; Process descriptor pd_flag bit values
;
pf_sys equ 00001h ; system process
pf_keep equ 00002h ; do not terminate
pf_kernal equ 00004h ; resident in kernal
pf_pure equ 00008h ; pure memory descibed
pf_table equ 00010h ; from pd table
pf_resource equ 00020h ; waiting for resource
pf_raw equ 00040h ; raw console i/o
pf_ctlc equ 00080h ; abort pending
pf_active equ 00100h ; active tty
pf_tempkeep equ 00200h ; don't terminate yet...
pf_ctld equ 00400h ; explicit detach occured


View File

@@ -0,0 +1,84 @@
;*****************************************************
;*
;* Queue Descriptor - This is structure is used
;* to create a queue. One is maintained
;* in the system data area for each queue
;*
;* +----+----+----+----+----+----+----+----+
;* 00 | link |net |org | flags | name...
;* +----+----+----+----+----+----+----+----+
;* 08 ...name | msglen |
;* +----+----+----+----+----+----+----+----+
;* 10 | nmsgs | dq | nq | msgcnt |
;* +----+----+----+----+----+----+----+----+
;* 18 | msgout | buffer |
;* +----+----+----+----+
;*
;* link - used to link QDs is system lists
;* net - which machine in the network
;* org - origin machine in the network
;* flags - Queue Flags
;* name - Name of Queue
;* msglen - # of bytes in one message
;* nmsgs - maximum # of messages in queue
;* dq - Root of PDs waiting to read
;* nq - Root of PDs list waiting to write
;* msgcnt - # of messages currently in queue
;* msgout - next message # to read
;* buf - pointer to queue message buffer
;* (for MX queues, owner of queue)
;*
;*****************************************************
q_link equ word ptr 0
q_net equ byte ptr q_link + word
q_org equ byte ptr q_net + byte
q_flags equ word ptr q_org + byte
q_name equ byte ptr q_flags + word
q_msglen equ word ptr q_name + qnamsiz
q_nmsgs equ word ptr q_msglen + word
q_dq equ word ptr q_nmsgs + word
q_nq equ word ptr q_dq + word
q_msgcnt equ word ptr q_nq + word
q_msgout equ word ptr q_msgcnt + word
q_buf equ word ptr q_msgout + word
qdlen equ q_buf + word
;
; Q_FLAGS values
;
qf_mx equ 001h ; Mutual Exclusion
qf_keep equ 002h ; NO DELETE
qf_hide equ 004h ; Not User writable
qf_rsp equ 008h ; rsp queue
qf_table equ 010h ; from qd table
qf_rpl equ 020h ; rpl queue
qf_dev equ 040h ; device queue
;*****************************************************
;*
;* QPB - Queue Parameter Block
;*
;* +----+----+----+----+----+----+----+----+
;* 00 |flgs|net | qaddr | nmsgs | buffptr |
;* +----+----+----+----+----+----+----+----+
;* 08 | name |
;* +----+----+----+----+----+----+----+----+
;*
;* flgs - unused
;* net - unused (which machine to use)
;* qaddr - Queue ID, address of QD
;* nmsgs - number of messages to read/write
;* buffptr - address to read/write into/from
;* name - name of queue (for open only)
;*
;*****************************************************
qpb_flgs equ byte ptr 0
qpb_net equ byte ptr qpb_flgs + byte
qpb_qaddr equ word ptr qpb_net + byte
qpb_nmsgs equ word ptr qpb_qaddr + word
qpb_buffptr equ word ptr qpb_nmsgs + word
qpb_name equ byte ptr qpb_buffptr + word
qpblen equ qpb_name + qnamsiz


View File

@@ -0,0 +1,190 @@
;*****************************************************
;*
;* System Data Area
;*
;*****************************************************
DSEG
org 0
;
;This data is initialized by GENSYS
;
;Module Table - contains the FAR CALL addresses
; of each module for their initialization
; and entry routines.
;
; +---+---+---+---+---+---+---+---+
; | entry | initialize |
; +---+---+---+---+---+---+---+---+
;
; entry init
; ----- ----
module_table equ dword ptr (offset $)
supmod equ (offset $)
rw 4
rtmmod equ (offset $)
rw 4
memmod equ (offset $)
rw 4
ciomod equ (offset $)
rw 4
bdosmod equ (offset $)
rw 4
xiosmod equ (offset $)
rw 4
netmod equ (offset $)
rw 4
dispatcher equ (offset $)
rw 2
rtm_pdisp equ (offset $)
rw 2
; location in memory of MP/M-86
mpmseg rw 1 ;1st parag. of MP/M
rspseg rw 1 ;segment of first RSP
endseg rw 1 ;1st parag. outside of MP/M
module_map rb 1 ;bit map of modules that exist
; in this system. low order bit
; corresponds to 1st module in
; module table. If bit is on,then
; module exists.
; some answers to GENSYS questions
ncns rb 1 ;# system console devices
nlst rb 1 ;# system list devices
nccb rb 1 ;# character control blocks
nflags rb 1 ;# flags
srchdisk rb 1 ;default search disk
mmp rw 1 ;Max Memory per process
nslaves rb 1 ;Number of Network requestors
dayfile rb 1 ;if 0ffh, display command info
tempdisk rb 1 ;Temporary Disk
tickspersec rb 1 ;number of ticks per second
; data lists created by GENSYS
free_root rw 1 ;locked unused list
ccb rw 1 ;addr. Console Ctrl Blk Table
flags rw 1 ;addr. Flag Table
mdul rw 1 ;Mem descr. Unused List
mfl rw 1 ;Memory Free List
pul rw 1 ;Proc. descr. Unused List
qul rw 1 ;QCB Unused List
qmau rw 4 ;MAU for queue buffer
;
;This data is initialized at Assembly time
;
rlr rw 1 ;Ready List Root
dlr rw 1 ;Delay List Root
drl rw 1 ;Dispatcher Ready List
plr rw 1 ;Poll List Root
slr rw 1 ;Swap List Root
thrdrt rw 1 ;Process Thread Root
qlr rw 1 ;Queue List Root
mal rw 1 ;Memory Alloc List
version rw 1 ;addr. version str in SUP code segment
vernum rw 1 ;MPM-86 w/BDOS v3.0
mpmvernum rw 1 ;MPM-86 Version 1.0
tod rb 5 ;Time of Day Structure
ncondev rb 1 ;# XIOS consoles
nlstdev rb 1 ;# XIOS list devices
nciodev rb 1 ;# character i/o devices
; supported by XIOS.
;syslrec
rw 1 ;Total Locked records
;syslfil
rw 1 ;Total Open files
lock_max rb 1 ;Max locked recs/process
rb 1
open_max rb 1 ;Max Open files/process
rb 1
;sysltot
rw 1 ;Total Locked List records
rw 8 ;Reserved
sysent rb 256*3
; System MX queues (preinitialized)
mxloadqd rb 28
mxloadqpb rb 16
mxcliqd rb 28
mxcliqpb rb 16
mxmemqd rb 28
mxmemqpb rb 16
; Data Used by Load Program
load_dma rb dskrecl
load_uda rw 1
load_lstk rw 1
load_basep rw 1
load_8080 rb 1
load_nrelsegs rb 1
load_nldtabents rw 1
load_pd rw 1
load_fcb rw 1
load_maxwanted rw 1
load_minwanted rw 1
load_indma rw 1
ldtab rb ldtabsiz
;
; Data Used by Send Cli Command
;
cli_dma rb dskrecl ;dma buffer
cli_net rb 1 ;net
cli_ppd rw 1 ;parent PD
cli_cmdtail rb 130 ;command sent
cli_fcb rb fcblen+1 ;internal FCB
cli_cuspqpb rb 16
cli_acb rb 12
cli_pcb rw 2
cli_pd rw 1 ;pd of load prog
cli_err rw 1 ;error return
cli_bpage rw 1
cli_lddsk rb 1 ;load disk
cli_cns rb 1 ;pd.p_cns save
cli_user rb 1 ;pd.p_dsk save
cli_dsk rb 1 ;pd.p_user save
cli_err_mode rb 1 ;u_error_mode save
;
;System Initialization Variables
;
;User Data Area of Init process
org ((offset $)+0fh) AND 0fff0h
inituda rb ulen
org ((offset $)+0fh) AND 0fff0h
idleuda rb ulen
org ((offset $)+0fh) AND 0fff0h
tickuda rb ulen
initpd rb pdlen
idlepd rb pdlen
tickpd rb pdlen
rw 21
idle_tos rw 3
rw 21
tick_tos rw 3
rw 39
init_tos rw 0
indisp rb 1 ;?currently in dispatch?
intflag rb 1 ;if 0, interrupts not enabled
rw 18
dsptchtos rw 0
es_sav rw 1
bx_sav rw 1
mxmemowner rw 1
mxmemcount rb 1


View File

@@ -0,0 +1,25 @@
;*****************************************************
;*
;* SYSTEM DEFINITIONS
;*
;*****************************************************
true equ 0ffffh ; value of TRUE
false equ 0 ; value of FALSE
unknown equ 0 ; value to be filled in
dskrecl equ 128 ; log. disk record len
pnamsiz equ 8 ; size of process name
qnamsiz equ pnamsiz ; size of queue name
fnamsiz equ pnamsiz ; size of file name
ftypsiz equ 3 ; size of file type
mpmint equ 224 ; int vec for mpm ent.
debugint equ mpmint+1 ; int vec for debuggers
ulen equ 0100h ; size of uda
pdlen equ 030h ; size of Process Descriptor
todlen equ 5 ; size of Time of Day struct
flag_tick equ 1 ; flag 0 = tick flag
flag_sec equ 2 ; flag 1 = second flag
flag_min equ 3 ; flag 2 = minute flag
ldtabsiz equ 0aah ; ldtablen=11, 10 entries


View File

@@ -0,0 +1,71 @@
;*****************************************************
;*
;* User Data Area - The User Data Area is an
;* extension of the process descriptor but it
;* travels with the user. It contains info
;* that is needed only while in context.
;*
;* While in the operating system, The Extra
;* Segment register points to the beginning
;* of the User Data Area.
;*
;*****************************************************
eseg
org 0
u_dparam rw 1 ; arg to dispatch
; this area overlays part of BDOS
u_dma_ofst rw 1 ; BDOS dma offset
u_dma_seg rw 1 ; BDOS dma segment
u_func rb 1 ; actual function number
u_searchl rb 1 ; BDOS search length
u_searcha rw 1 ; BDOS search FCB offset
u_searchabase rw 1 ; BDOS search user's segment
u_dcnt rw 1 ; BDOS directory count
u_dblk rw 1 ; BDOS directory block #
u_error_mode rb 1 ; BDOS error mode
u_mult_cnt rb 1 ; BDOS multi-sector count
u_df_password rb 8 ; BDOS default password
u_pd_cnt rb 1 ; BDOS process count
uda_ovl_len equ (offset $)-(offset u_dma_ofst)
; end of overlay area
u_in_int rb 1
u_sp rw 1 ; save register area
u_ss rw 1
u_ax rw 1
u_bx rw 1
u_cx rw 1
u_dx rw 1
u_di rw 1
u_si rw 1
u_bp rw 1
u_wrkseg rw 1 ; curr seg addr of buf
u_retseg rw 1 ; usr ES return
u_ds_sav rw 1 ;\
u_stack_sp rw 1 ; usr stack segment
u_stack_ss rw 1 ; usr stack pointer
u_ivectors rw 10 ; save int 0-4
u_es_sav rw 1 ; > Used during interrupts
u_flag_sav rw 1 ;/
u_initcs rw 1
u_initds rw 1
u_inites rw 1
u_initss rw 1
u_mpm_ip rw 1 ; MPM vec save
u_mpm_cs rw 1
u_debug_ip rw 1 ; RTS,Debug Vector Save
u_debug_cs rw 1
u_insys rb 1 ; # times through user_entry
org (ulen-(3*word))
u_rtm_ret rw 1
u_sup_user_ret rw 1
u_sup_cs rw 1


View File

@@ -0,0 +1,45 @@
;*****************************************************
;*
;* XIOS function jump table offsets
;*
;*****************************************************
io_const equ 0
io_conin equ 1
io_conout equ 2
io_list equ 3
;io_punch equ 4 ;not used
;io_reader equ 5 ;not used
io_home equ 6
io_seldsk equ 7
io_settrk equ 8
io_setsec equ 9
io_setdma equ 10
io_read equ 11
io_write equ 12
;io_listst equ 13 ;not used
io_sectran equ 14
io_setdmab equ 15
;io_getsegt equ 16 ;not used
io_polldev equ 17
io_strtclk equ 18
io_stopclk equ 19
io_maxconsole equ 20
io_maxlist equ 21
io_selmemory equ 22
io_idle equ 23
io_flush equ 24
nxiosfuncs equ io_idle
;*****************************************************
;*
;* XIOS Parameter Block for CALL XIOS functions
;*
;*****************************************************
xcb_func equ 0
xcb_cx equ word ptr xcb_func + byte
xcb_dx equ word ptr xcb_cx + word
xcblen equ xcb_dx + word