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

📄 disk3.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	mov	[DISK_FULL],1
	stc
	jmp	WRTERR		; go to disk full exit

SET_ACC_ERRW:
	transfer SET_ACC_ERR_DS

WRTLAST:
	MOV     AX,[BYTCNT2]
	OR      AX,AX
	JZ      FINWRT
	MOV     [BYTCNT1],AX
	invoke  NEXTSEC
	JC      SET_ACC_ERRW
	MOV     [BYTSECPOS],0
	invoke  BUFWRT
	JC      SET_ACC_ERRW
FINWRT:
	LES     DI,[THISSFT]
	Assert  ISSFT,<ES,DI>,"DiskWrite/FinWrt"
	MOV     AX,WORD PTR [GROWCNT]
	MOV     CX,WORD PTR [GROWCNT+2]
	OR      AX,AX
	JNZ     UPDATE_size
	JCXZ    SAMSIZ
Update_size:
	ADD     WORD PTR ES:[DI.sf_size],AX
	ADC     WORD PTR ES:[DI.sf_size+2],CX
;
; Make sure that all other SFT's see this growth also.
;
	MOV     AX,1
if installed
	call    JShare + 14 * 4
else
	Call    ShSU
endif
SAMSIZ:
	transfer SETCLUS                  ; ES:DI already points to SFT

WRTEOF:
	MOV     CX,AX
	OR      CX,DX
	JZ      KILLFIL
	SUB     AX,1
	SBB     DX,0

	PUSH    BX
	MOV     BX,ES:[BP.dpb_sector_size]    ;F.C. >32mb                       ;AN000;
	CALL    DIV32                         ;F.C. >32mb                       ;AN000;
	POP	BX			      ;F.C. >32mb			;AN000;
	MOV	DX,CX			      ;M039
        MOV     [HIGH_SECTOR],CX              ;M039: Probably extraneous, but not sure.
	CALL    SHR32                         ;F.C. >32mb                       ;AN000;

	MOV     CX,AX
	invoke  FNDCLUS
SET_ACC_ERRWJ2:
	JC      SET_ACC_ERRW


	JCXZ    RELFILE
	invoke  ALLOCATE
	JC      WRTERRJ              ;;;;;;;;; disk full
UPDATE:
	LES     DI,[THISSFT]
	Assert  ISSFT,<ES,DI>,"DiskWrite/update"
	MOV     AX,WORD PTR [BYTPOS]
	MOV     WORD PTR ES:[DI.sf_size],AX
	MOV     AX,WORD PTR [BYTPOS+2]
	MOV     WORD PTR ES:[DI.sf_size+2],AX
;
; Make sure that all other SFT's see this growth also.
;
	MOV     AX,2
if installed
	Call    JShare + 14 * 4
else
	Call    ShSU
endif
	XOR     CX,CX
	transfer ADDREC

WRTERRJ: JMP     WRTERR
;;;;;;;;;;;;;;;; 7/18/86
;;;;;;;;;;;;;;;;;
RELFILE:
	PUSH    ES                    ;AN002; BL   Reset Lstclus and cluspos to
	LES     DI,[THISSFT]          ;AN002; BL   beginning of file if current
	CMP     DX,ES:[DI.sf_cluspos] ;AN002; BL   cluspos is past EOF.
	JAE     SKIPRESET             ;AN002; BL
	MOV     ES:[DI.sf_cluspos],0  ;AN002; BL
	MOV     DX,ES:[DI.sf_firclus] ;AN002; BL
	MOV     ES:[DI.sf_lstclus],DX ;AN002; BL
SKIPRESET:                            ;AN002; BL
	POP     ES                    ;AN002; BL
;
	MOV     DX,0FFFFH
	invoke  RELBLKS
Set_Acc_ERRWJJ:
	JC      SET_ACC_ERRWJ2
	JMP     SHORT UPDATE

KILLFIL:
	XOR     BX,BX
	PUSH    ES
	LES     DI,[THISSFT]
	Assert  ISSFT,<ES,DI>,"DiskWrite/KillFil"
	MOV     ES:[DI.sf_cluspos],BX
	MOV     ES:[DI.sf_lstclus],BX
	XCHG    BX,ES:[DI.sf_firclus]
	POP     ES

	OR      BX,BX
	JZ      UPDATEJ
;; 10/23/86 FastOpen update
	PUSH    ES              ; since first cluster # is 0
	PUSH    BP              ; we must delete the old cache entry
	PUSH    AX
	PUSH    CX
	PUSH    DX
	LES     BP,[THISDPB]             ; get current DPB
	MOV     DL,ES:[BP.dpb_drive]     ; get current drive
	MOV     CX,BX                    ; first cluster #
	MOV     AH,2                     ; delete cache entry by drive:firclus
	invoke  FastOpen_Update          ; call fastopen
	POP     DX
	POP     CX
	POP     AX
	POP     BP
	POP     ES
;; 10/23/86 FastOpen update

	invoke  RELEASE
	JC      SET_ACC_ERRWJJ
UpDateJ:
	JMP     UPDATE
EndProc DISKWRITE



Break   <DskWrtBufPurge -- Disk Write Buffer Purge>
;----------------------------------------------------------------------------
;
; Procedure Name : DskWrtBufPurge
;
; Inputs:
;       CX = # of contiguous sectors to write. (These constitute a block of
;	     sectors, also termed an "Extent".)
;       [HIGH_SECTOR]:DX = physical sector # of first sector in extent.
;       ES:BP -> Drive Parameter Block (DPB).
;
; Function:
;       Purge the Buffer Queue and the Secondary Cache of any buffers which
;	are in Extent; they are being over-written.
;
; Outputs:
;       (Same as Input.)
; Uses:
;       All registers except DS,AX,SI,DI preserved.
;       SS override for all global variables.
;----------------------------------------------------------------------------
;M039: Created

procedure   DskWrtBufPurge,NEAR

ASSUME  DS:NOTHING

        SaveReg <bx,cx>
        mov	bx,[HIGH_SECTOR]	;BX:DX = Extent start (sector #).
        mov     si,bx
        add     cx,dx
        adc     si,0                    ;SI:CX = Extent end + 1.

	Assert  ISDPB,<ES,BP>,"DskWrtBufPurge"
	mov     al,es:[bp.dpb_drive]

;       BX:DX = Extent start.
;       SI:CX = Extent end + 1.
;          AL = Drive #

	cmp     [SC_CACHE_COUNT],0      ;Secondary cache in-use?
	je      nosc                    ; -no, jump.

;       If any of the sectors to be written are in the secondary cache (SC),
;       invalidate the entire SC. (This is an optimization; we really only
;	need to invalidate those sectors which intersect, but that's slower.)

        cmp     al,[CURSC_DRIVE]        ;Same drive?
        jne     nosc                    ; -no, jump.

        push    ax
        mov     ax,[CURSC_SECTOR]
        mov     di,[CURSC_SECTOR+2]     ;DI:AX = SC start.
        Cmp32   si,cx,di,ax             ;Extent end < SC start?
        jbe     sc5                     ; -yes, jump.
        add     ax,[SC_CACHE_COUNT]
        adc     di,0                    ;DI:AX = SC end + 1.
        Cmp32   bx,dx,di,ax             ;Extent start > SC end?
        jae     sc5                     ; -yes, jump.
        mov     [SC_STATUS],0           ;Extent intersects SC: invalidate SC.
sc5:	pop     ax

;       Free any buffered sectors which are in Extent; they are being over-
;       written.

nosc:	invoke  GETCURHEAD              ;DS:DI -> first buffer in queue.

bufq:   cmp     al,BYTE PTR [di.buf_ID] ;Same drive?
        jne     bufq5                   ; -no, jump.

        Cmp32   bx,dx,<WORD PTR [di.buf_sector+2]>,<WORD PTR [di.buf_sector]>
        ja	bufq5			;Jump if Extent start > buffer sector.
        Cmp32   si,cx,<WORD PTR [di.buf_sector+2]>,<WORD PTR [di.buf_sector]>
        jbe	bufq5                   ;Jump if Extent end < buffer sector.

;       Buffer's sector is in Extent, so free it; it is being over-written.

        testb   [di.buf_flags],buf_dirty ;Buffer dirty?
        jz      bufq2                    ; -no, jump.
        invoke  DEC_DIRTY_COUNT          ; -yes, decrement dirty count.
bufq2:  mov     WORD PTR [di.buf_ID],((buf_visit SHL 8) OR 0FFh)

        invoke  SCANPLACE
        jmp     short bufq6

bufq5:  mov     di,[di.buf_next]
bufq6:  cmp     di,[FIRST_BUFF_ADDR]    ;Scanned entire buffer queue?
        jne     bufq	                ; --no, go do next buffer.

        RestoreReg <cx,bx>
        return

EndProc DskWrtBufPurge


Break   <DIV32 -- PERFORM 32 BIT DIVIDE>
;----------------------------------------------------------------------------
;
; Procedure Name : DIV32
;
; Inputs:
;       DX:AX = 32 bit dividend   BX= divisor
; Function:
;       Perform 32 bit division:  DX:AX/BX = CX:AX + DX (rem.)
; Outputs:
;       CX:AX = quotient , DX= remainder
; Uses:
;       All registers except AX,CX,DX preserved.
;----------------------------------------------------------------------------
;M039: DIV32 optimized for divisor of 512 (common sector size).

procedure   DIV32,NEAR

        cmp     bx,512
        jne    	short div5

	mov     cx,dx
        mov     dx,ax           ; CX:AX = Dividend
        and     dx,(512-1)      ; DX = Remainder
        mov     al,ah
        mov     ah,cl
        mov     cl,ch
        xor     ch,ch
        shr     cx,1
        rcr     ax,1
        return

div5:	mov     cx,ax
        mov     ax,dx
        xor     dx,dx
        div     bx              ; 0:AX/BX
        xchg    cx,ax
        div     bx              ; DX:AX/BX
        return

EndProc DIV32

Break   <SHR32 -- PERFORM 32 BIT SHIFT RIGHT>
;----------------------------------------------------------------------------
;
; Proedure Name : SHR32
;
; Inputs:
;	DX:AX = 32 bit sector number
; Function:
;       Perform 32 bit shift right
; Outputs:
;	AX = cluster number
;	ZF = 1 if no error
;	   = 0 if error (cluster number > 64k)
; Uses:
;       DX,CX
;---------------------------------------------------------------------------
; M017	- SHR32 rewritten for better performance
; M039	- Additional optimization

procedure   SHR32,NEAR

	mov     cl,es:[bp.dpb_cluster_shift]
	xor	ch,ch	    ;ZF=1
	jcxz	norota

rotashft2:
	shr	dx,1	    ;ZF reflects state of DX.
	rcr	ax,1	    ;ZF not affected.
	loop	rotashft2

norota:
	return

EndProc SHR32

COMMENT @

;**RMFHFE** Remove File_Handle_Fail_Error support

;---------------------------------------------------------------------------
;
; Procedure Name : File_Handle_Fail_Error
;
; Issue File Handle Fail INT 24 Critical Error
; Input: Disk_Full=0  ok
;                  1  disk full or EOF
; Function: issue critical error for disk full or EOF error
;
; OutPut: carry clear , no I24
;         carry set, fail from I24
;---------------------------------------------------------------------------

procedure File_Handle_Fail_Error,NEAR                                           ;AN000;

;hkn; SS override for all variables in this procedure
										;AN000;
	CMP     [DISK_FULL],0    ;MS. disk full or EOF                          ;AN000;
	JZ      Fexit            ;MS. no                                        ;AN000;
	TESTB   [DOS34_FLAG],Disable_EOF_I24   ;MS. check input status ?        ;AN000;
	JNZ     Fexit            ;MS. yes                                       ;AN000;
										;AN000;
	LES     DI,[THISSFT]     ;MS. get current SFT                           ;AN000;
;       LES     DI,ES:[DI.sf_DEVPTR];MS. get device header                      ;AN000;
	TESTB   ES:[DI].SF_FLAGS,Handle_Fail_I24  ;MS. gen I24 ?                ;AN000;
	JZ      Fexit            ;MS. no                                        ;AN000;
	PUSH    DS               ;MS. save DS                                   ;AN000;
	test    AH,1                            ;MS. READ ?                     ;AN000;
	JZ      readeof                         ;MS. yes                        ;AN000;
	MOV     [EXTERR],error_Handle_Disk_Full ;MS. set extended error         ;AN000;
	JMP     SHORT errset                    ;MS. set extended error         ;AN000;
readeof:
	MOV     [EXTERR],error_Handle_EOF       ;MS. set extended error         ;AN000;
errset:
	MOV     [EXTERR_CLASS],errCLASS_OutRes  ;MS. set class                  ;AN000;
	MOV     [EXTERR_ACTION],errACT_Abort    ;MS. set action                 ;AN000;
	MOV     [EXTERR_LOCUS],errLOC_Unk       ;MS. set locus                  ;AN000;
	MOV     word ptr [EXITHOLD + 2],ES      ;MS. save es:bp in exithold     ;AN000;
	MOV     word ptr [EXITHOLD],BP          ;MS.                            ;AN000;
	TESTB   ES:[DI].SF_FLAGS,devid_device     ;MS. device  ?                ;AN000;
	JNZ     chardev2                          ;MS. yes                      ;AN000;
	LDS     SI,ES:[DI.sf_DEVPTR]              ;MS. get dpb                  ;AN000;
	LDS     SI,[SI.dpb_driver_addr]           ;MS. get drive device haeder  ;AN000;
	JMP     SHORT doi24                       ;MS. gen I24 ?                ;AN000;
chardev2:
	LDS     SI,ES:[DI.sf_DEVPTR]              ;MS. get chr dev header       ;AN000;
doi24:
	MOV     BP,DS                             ;MS. bp:si -> device header   ;AN000;
	MOV     DI,error_I24_gen_failure        ;MS. general error              ;AN000;
	invoke  NET_I24_ENTRY                   ;MS. issue I24                  ;AN000;
	STC                                     ;MS. must be fail               ;AN000;
	POP     DS                              ;MS. restore DS                 ;AN000;
	MOV     AX,[EXTERR]                     ;MS. set error                  ;AN000;
	JMP     SHORT Fend                      ;MS. exit                       ;AN000;
Fexit:                                                                          ;AN000;
	CLC                                     ;MS. clear carry                ;AN000;
Fend:                                                                           ;AN000;
	return                                  ;MS.                            ;AN000;
										;AN000;
EndProc File_Handle_Fail_Error                                                  ;AN000;

@       ;End COMMENT.

DOSCODE ENDS
	END

⌨️ 快捷键说明

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