⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 pcmif.a86

📁 一个dos操作系统DRDOS的源码
💻 A86
📖 第 1 页 / 共 3 页
字号:
	Public	inactive
inactive:
	push es ! push ax

	dec	active_cnt		; Decrement the count
	jnz	inactive_10		; Return if Non-Zero

	mov	ax,idle_max		; Get the default count value
	mov	active_cnt,ax		; and reset the internal count

	test	idle_flags,IDLE_DISABLE	; Has Idle Checking been enabled
	 jnz	inactive_10		; Skip if NO.
	mov	ax,PROC_IDLE		; Process is IDLE
	callf	idle_vec		; Call the IDLE Handler

inactive_10:
	pop ax ! pop es
	ret
;
;	This routine will reset the active count for functions which
;	are treated as INACTIVE but which have active sub-functions.
;
	Public	active
active:
	push	ax
	mov	ax,idle_max		; Get the default count value
	mov	active_cnt,ax		; and reset the internal count
	pop	ax
	ret
endif
;
;
;	This function is invoked for functions number above the last 
;	supported function number. It forces AL to zero and returns.
;	Just that and nothing more.
; 
ms_zero_AL:
	xor	ax,ax			; AL = 0 for return
	ret

eject
;	DOS_ENTRY is used to call DOS functions internally.
;	eg. Func4B (exec) calls MS_X_OPEN, MS_X_READ, MS_X_CLOSE etc.
;	It is the responsibilty of the caller to make sure that no side
;	effects exist if this entry point is used.
;	eg. critical error handling
;
;
	Public	dos_entry
dos_entry:
	clc
	cld
	pushf				; look like Int21 registers
	pushf ! pushf			; fake CS/IP positions
	push ds ! push es		; Save registers on the USER stack
	push bp				; no Stack Swap is executed and DS
	push di ! push si		; and ES are swapped.
	push dx ! push cx
	push bx ! push ax
	mov	bp,sp			; Initialise Stack Frame

	call	get_dseg		; Get our Data Area

	inc	internal_flag

	push	fdos_data+0*WORD	; save fdos pblk so we can
	push	fdos_data+1*WORD	;  be re-entrant(ish)
	push	fdos_data+2*WORD
	push	fdos_data+3*WORD
	push	fdos_data+4*WORD
	push	fdos_data+5*WORD
	push	fdos_data+6*WORD
	
	push	int21regs_off
	push	int21regs_seg

	mov	int21regs_off,bp
	mov	int21regs_seg,ss

	call	internal_func		; Execute the function
	mov	reg_AL[bp],al		; always return AL to caller

	pop	int21regs_seg
	pop	int21regs_off		; restore previous pointer user REGS

	pop	fdos_data+6*WORD
	pop	fdos_data+5*WORD
	pop	fdos_data+4*WORD
	pop	fdos_data+3*WORD
	pop	fdos_data+2*WORD
	pop	fdos_data+1*WORD
	pop	fdos_data+0*WORD	; restore fdos_pb for nested calls

	dec	internal_flag

	pop ax ! pop bx			; Update the registers then
	pop cx ! pop dx			; set the flags and return
	pop si ! pop di			; to the user
	pop bp
	pop es ! pop ds
	popf				; discard dos_IP
	popf				;  and dos_CS
	popf				; get result
	 jnc	dos_entry10
	neg	ax			; return using our negative error
	stc				; conventions
dos_entry10:
	ret

	Public	int21_func

int21_func:
;----------
; On Entry:
;	AX, CX, DX, SI, DI as per Int 21
;	BX = ??
;	BP = ??
;	DS = pcmode data
;	ES = ??
; On Exit:
;	(to client function)
;	All general purpose registers as per Int 21 entry
;	ES = dos_DS
;

	xor	bx,bx			; BH = 0
	mov	bl,ah			; BX = function number
	shl	bx,1			; make it a word offset
	push	pcmode_ft[bx]		; save address of Function
	les	bp,int21regs_ptr
	mov	bx,es:reg_BX[bp]	; reload from dos_BX,dos_BP,and dos_DS
	les	bp,es:dword ptr reg_BP[bp]
	ret


internal_func:
;-------------
; On Entry:
;	All registers as per Int 21 EXCEPT
;	DS = pcmode data
;	BP = dos_REGS stack frame
; On Exit:
;	(to client function)
;	ES = dos_DS
;
	mov	al,ah			; function number in AL
	cbw				; AH = 0
	xchg	ax,bx			; get subfunction in BX
	shl	bx,1			; make offset in the internal table
	push	pcmode_ft[bx]		; save address of Function
	xchg	ax,bx			; restore BX
	mov	ax,reg_AX[bp]		; recover function number
	mov	es,reg_DS[bp]		; ES = callers DS
	ret				; "jump" to handler

eject
;	INT25 and INT26 direct disk I/O interface
;
;Standard DOS 1.xx - 3.30 INT25/26 Interface
;===========================================
;
;	entry:	al = drive number
;		ds = DMA segment
;		bx = DMA offset
;		cx = number of sectors
;		dx = beginning relative sector
;
;
;Enhanced DOS 3.31 INT25/26 Interface
;====================================
;
;	If CX == 0FFFFh then the application is using the enhanced
;	INT25/INT26 interface which allows access to more than 64K
;	sectors.
;
;	entry:	al = drive number
;		bx = Parameter block Offset
;		ds = Parameter block Segment
;
;	Parameter Block Format
;DS:BX ->	DD	Starting Sector No.
;		DW	Number of Sectors
;		DD	Transfer Address
;
;
;	exit:	C flag = 0 if successful
;		       = 1 if unsuccessful
;		ax = error code(if CF = 1)
;		  ah physical error
;		  al logical error
;		Users orginal flags left on stack
;
;
eject
DDIO_INT13	equ     0
DDIO_READ_OP	equ     1
DDIO_WRITE_OP	equ     2

;	++++++++++++++++++++++++++++
;	Int 26 - Absolute Disk Write
;	++++++++++++++++++++++++++++
;
	Public	int26_entry
int26_entry:
	mov 	ah,DDIO_WRITE_OP	; This is a WRITE operation	
	jmps	int26_10


;	+++++++++++++++++++++++++++
;	Int 25 - Absolute Disk Read
;	+++++++++++++++++++++++++++
;
	Public	int25_entry
int25_entry:
	mov 	ah,DDIO_READ_OP		; This is a READ operation	
int26_10:				; Common Direct Disk I/O code
	cld
	push ds ! push es
	push	dx			; save DX for FLASHCARD
	push ds ! pop es		; ES = callers DS
	call	get_dseg		; Get PCMODE Data Segment
	inc	indos_flag		; Update the INDOS_FLAG
	mov	normal_stack+2,ss	; save users SS:SP
	mov	normal_stack,sp
	cli
	push ds ! pop ss		; use normal stack when in here
	mov	sp,offset normal_stack
	sti
	inc	cx			; CX = FFFF indicates this is
     jz int26_30       
; CHECK FOR PARITIONS > 32 MBytes...
	dec	cx			; CX restored
	push	es
	push	ax
	push	bx
	push	dx
	call	get_ddsc		; ES:BX -> DDSC_
	mov	di,0201h		; assume bad drive
	 jc	int26_20
	mov	di,0207h		; assume large media, and this error
if 0
; This code works out the total number of sectors on a drive
	mov	ax,es:DDSC_NCLSTRS[bx]	; get last cluster #
	dec	ax			;  make it # data clusters
	xor	dx,dx
	mov	dl,es:DDSC_CLMSK[bx]	; get sec/cluster -1
	inc	dx			; DX = sec/cluster
	mul	dx			; DX:AX = # data sectors
	add	ax,es:DDSC_DATADDR[bx]	; add in address of 1st data sector
	adc	dx,0
else
	mov	ax,es:DDSC_NCLSTRS[bx]	; get last cluster #
	xor	dx,dx
	mov	dl,es:DDSC_CLMSK[bx]	; get sec/cluster -1
	inc	dx			; DX = sec/cluster
	mul	dx			; DX:AX is vaguely the # sectors
	test	dx,dx			; close enough for bill
endif
	stc				; assume an error
	 jnz	int26_20
	xor	di,di			; DI = zero, no error
int26_20:
	pop	dx
	pop	bx
	pop	ax
	pop	es
	 jnc	int26_40
	xchg	ax,di			; AX = error code
	jmps	int26_60		; return it
int26_30:	
	mov	dx,es:word ptr 0[bx]	; Get Starting Sector Low
	mov	di,es:word ptr 2[bx]	; Get Starting Sector High
	mov	cx,es:word ptr 4[bx]	; Get No. of sectors to transfer
	les	bx,es:dword ptr 6[bx]	; Tranfer Address Offset
int26_40:
	mov	FD_DDIO_DRV_OP,ax	; save drive and operation
	mov	FD_DDIO_NSECTORS,cx	; No. of Sectors
	mov	FD_DDIO_STARTLOW,dx	; Starting Sector No.
	mov	FD_DDIO_STARTHIGH,di	; High Word of Sector Number
	mov 	FD_DDIO_DMAOFF,bx	; DMA Offset
	mov	FD_DDIO_DMASEG,es	; DMA Segment

	mov	FD_FUNC,FD_DDIO
	call	fdos_nocrit		; let the FDOS do the work
	neg	ax			; AX is DOS extended error
	 jz	int26_exit
	sub	al,-ED_PROTECT		; get AL to Int24 error format
	cmp	al,-(ED_GENFAIL-ED_PROTECT)
     jbe    int26_50       
	mov	al,-(ED_GENFAIL-ED_PROTECT)
int26_50:				; no, make it general failure
	mov	ah,al			; save error in AH
	mov	bx,offset int13_error
	xlat	int13_error		; convert error to int13 format
	xchg	al,ah			; get errors in correct registers
int26_60:
	stc				; Set the Carry Flag when an error
int26_exit:				; Occurs and return to the calling app.
	cli
	mov	ss,normal_stack+2	; back to user stack
	mov	sp,normal_stack
	sti
	dec	indos_flag		; Update the INDOS_FLAG
	sti
	pop	dx
	pop es ! pop ds			; restore callers registers
	retf				; leave flags on stack

int13_error	db	03h,02h,80h,01h,10h,02h,40h,02h,04h,02h,02h,02h,02h

eject
;	++++++++++++++++++++++++++++++++++++
;	Int 27 - Terminate but Stay Resident
;	++++++++++++++++++++++++++++++++++++
;
	Public	int27_entry
int27_entry:
	mov	ax,3100h	; Convert this to a DOS 'Terminate and 
	add	dx,15		; Stay Resident' function by converting the
	rcr	dx,1		; memory size in bytes to paragraphs.
	shr	dx,1		; On entry DX == memsize + 1 bytes therefore
	shr	dx,1		; round upto a paragraph boundary by adding
	shr	dx,1		; 15 then divide by 16
	jmp	int21_entry

eject
;
;	DO_INT24:
;	    On Entry:-
;			AH	Set for INT 24
;			AL	Drive Number (0 = A:)
;			DI	Error Code
;			ES:SI	Device Header Control Block
;
;	    On Exit:-
;			AL	Error Response Retry/Ignore/Fail
;
;	INT 24 Critical Error:-
;	On Entry:-	AH/7	0 = Disk Device
;			AH/5	0 = IGNORE is an Invalid Response
;			AH/4	0 = RETRY in an Invalid Response
;			AH/3	0 = FAIL is an Invalid Response
;			AH/2-1	00= DOS Area

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -