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

📄 format.asm

📁 msdos 3.30 source code
💻 ASM
📖 第 1 页 / 共 5 页
字号:
;               DS:SI == Command line text
;
;       Exit:
;               AX == Value
;               IF AX == 0 THEN Zero Flag == SET
;               IF ERROR   THEN Carry Flag == SET
;               BX,CX,DX == Garbage
;               DS:SI == Character after numeric value
;
;       Procs used:
;               ToDigit

Public MakeNum,CalcLoop
MakeNum:
        xor     BX,BX                           ; Initialize running cnt
        mov     CX,10                           ; and base of arithmetic
CalcLoop:                                       ; UNTIL no more digits
        call    ToDigit                         ;   AL := AL - '0'
        jc      BadNum                          ;   IF error EXIT with carry set

        xchg    ax,bx                           ;   AX := running_cnt * 10 +
        mul     cx                              ;                       digit
        add     ax,bx
        jc      BadNum                          ;   IF Overflow EXIT with carry

        xchg    ax,bx                           ;   BX := Running total

        LODSB                                   ;   Get Next Digit
        cmp     al,' '                          ;   IF ( ax = (' ',',',))
        je      RetVal                          ;      THEN return parsed value
        cmp     al,','
        je      RetVal

        cmp     al,'/'                          ;   IF (ax = ('/','cr'))
        je      BURetVal                        ;      THEN backup DS:SI and
        cmp     al,0dh                          ;       return parsed value
        je      BURetVal
        or      al,al
        jnz     CalcLoop                        ; END until

BURetVal:
        dec     SI
RetVal:
        mov     ax,bx
        or      ax,ax
        return

public Badnum
BadNum:
        xor     ax,ax
        stc
        return

; ToDigit:
;      Convert value in AX to decimal digit, range checking for valid values
;
public ToDigit
ToDigit:
        sub     al,'0'
        jb      NotDigit
        cmp     al,9
        ja      NotDigit
        clc
        return

NotDigit:
        stc
        return

;-------------------------------------------------------------------------------

ControlC_Handler:
        mov     ax, seg data
        mov     ds, ax
        lea     dx, msgInterrupt
        call    PrintString
        mov     ExitStatus, ExitCtrlC
        jmp     ExitProgram

;-------------------------------------------------------------------------------
; SaveNum
;       Save Number from switches into appropriate variable for later use
;       Some switches have upper and lower bounds for legal values and
;       these are checked for here
;
;       ENTRY:
;               cx == Switch just parsed
;               ax == value parsed
;
;       EXIT:
;               Value stored in appropriate variable
;               DS,DX == garbage
;

public SaveNum
SaveNum:
        mov     dx, seg data
        mov     ds, dx
        test    word ptr data:Switchmap, CX     ; IF already set THEN ignore
        jnz     done_ret

        test    CX,SWITCH_T
        jnz     Store_T

        test    CX,SWITCH_N
        jz      BadNum

Store_N:
        cmp     AX,0                            ; IF (value == 0) THEN ignore
        je      done_ret

        cmp     AX, MAX_SECTORS_IN_TRACK        ; IF (value > Max_sectors)
        jbe     short Store_N1                  ;   THEN issue error
        jmp     INVALID

Store_N1:
        mov     word ptr data:NumSectors  , AX

        jmp     short done_ret

Store_T:
        mov     word ptr data:TrackCnt, AX

Done_ret:
        ret
;-------------------------------------------------------------------------------

crlf:
        lea     dx, msgCRLF

PrintString:
        mov     printStringPointer, dx
        lea     dx, PrintStringPointer

std_printf:
        push    dx
        call    printf
        return

;-------------------------------------------------------------------------------

;*****************************************
; Process V switch if set

VOLID:
        TEST    [SWITCHMAP],SWITCH_V
        JNZ     DOVOL
VRET:   CLC
        return

DOVOL:
        PUSH    CX
        PUSH    SI
        PUSH    DI
        PUSH    ES
        PUSH    DS
        POP     ES
VOL_LOOP:
        MOV     AL,DRIVE
        INC     AL
        MOV     DS:BYTE PTR[VOLFCB+7],AL
        lea     dx, msgLabelPrompt
        call    PrintString
        CALL    USER_STRING
        call    crlf
        call    crlf
        MOV     CL,[INBUFF+1]
        OR      CL,CL
        JZ      VOLRET
        XOR     CH,CH
        MOV     SI,OFFSET INBUFF+2
        MOV     DI,SI
        ADD     DI,CX
        MOV     CX,11
        MOV     AL,' '
        REP     STOSB
        MOV     CX,5
        MOV     DI,OFFSET VOLNAM
        REP     MOVSW
        MOVSB
        MOV     DX,OFFSET VOLFCB
        MOV     AH,FCB_CREATE
        INT     21H
        OR      AL,AL
        JZ      GOOD_CREATE
        lea     dx, msgBadCharacters
        call    PrintString
        JMP     VOL_LOOP
GOOD_CREATE:
        MOV     DX,OFFSET VOLFCB
        MOV     AH,FCB_CLOSE
        INT     21H
        CALL    CRLF
VOLRET:
        POP     ES
        POP     DI
        POP     SI
        POP     CX
        return

;****************************************
;Copy IO.SYS, MSDOS.SYS and COMMAND.COM into data area.
; Carry set if problems

READDOS:
;       CALL    TESTSYSDISK             ; dcl 8/23/86
        call    Get_BIOS                ; dcl 8/23/86
        JNC     RDFILS
        return

RDFILS:
        MOV     BYTE PTR [FILSTAT],0
        MOV     BX,[bios.fileHandle]
        MOV     AX,[MSTART]
        MOV     DX,AX
        ADD     DX,[MSIZE]              ; CX first bad para
        MOV     [bios.fileStartSegment],AX
        MOV     CX,[bios.fileSizeInParagraphs]
        ADD     AX,CX
        CMP     AX,DX
        JBE     GOTBIOS
        MOV     BYTE PTR [FILSTAT],00000001B    ; Got part of BIOS
        MOV     SI,[MSIZE]
        XOR     DI,DI
        CALL    DISIX4
        push    ds
        MOV     DS,[bios.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data
        JC      CLSALL
        XOR     DX,DX
        MOV     CX,DX
        MOV     AX,(LSEEK SHL 8) OR 1
        INT     21H
        MOV     WORD PTR [bios.fileOffset],AX
        MOV     WORD PTR [bios.fileOffset+2],DX
FILESDONE:
        CLC
CLSALL:
        PUSHF
;       CALL    COMCLS                  ; dcl 8/23/86
        call    FILE_CLS                ; dcl 8/23/86
        POPF
        return

GOTBIOS:
        MOV     BYTE PTR [FILSTAT],00000010B    ; Got all of BIOS
        push    es
        LES     SI,[bios.fileSizeInBytes]
        MOV     DI,ES
        pop     es
        push    ds
        MOV     DS,[bios.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data
        JC      CLSALL

        push    ax                              ; dcl 8/23/86
        push    dx                              ; dcl 8/23/86
        call    File_Cls                        ; dcl 8/23/86
        call    Get_DOS                         ; dcl 8/23/86
        pop     dx                              ; dcl 8/23/86
        pop     ax                              ; dcl 8/23/86

        JNC     Found_MSDOS                     ;mt 12/8/86 P894
        return                                  ;mt 12/8/86

Found_MSDOS:                                    ;mt 12/8/86

        MOV     BX,[dos.fileHandle]
        MOV     [dos.fileStartSegment],AX
        CMP     AX,DX                   ; No room left?
        JZ      CLSALL                  ; Yes
        MOV     CX,[dos.fileSizeInParagraphs]
        ADD     AX,CX
        CMP     AX,DX
        JBE     GOTDOS
        OR      BYTE PTR [FILSTAT],00000100B    ; Got part of DOS
        SUB     DX,[dos.fileStartSegment]
        MOV     SI,DX
        XOR     DI,DI
        CALL    DISIX4
        push    ds
        MOV     DS,[dos.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data
        JC      CLSALL
        XOR     DX,DX
        MOV     CX,DX
        MOV     AX,(LSEEK SHL 8) OR 1
        INT     21H
        MOV     WORD PTR [dos.fileOffset],AX
        MOV     WORD PTR [dos.fileOffset+2],DX
        JMP     FILESDONE

GOTDOS:
        OR      BYTE PTR [FILSTAT],00001000B    ; Got all of DOS
        LES     SI,[dos.fileSizeInBytes]
        MOV     DI,ES
        push    ds
        MOV     DS,[dos.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data

CLSALLJ: JNC    NOTCLSALL               ;PTM P894  mt 12/8/86
         jmp    clsall                  ;

NotCLSALL:
        push    ax                      ; dcl 8/23/86

        push    dx                      ; dcl 8/23/86
        call    File_cls                ; dcl 8/23/86
        call    Get_COMMAND             ; dcl 8/23/86
        pop     dx                      ; dcl 8/23/86
        pop     ax                      ; dcl 8/23/86

        JNC     Found_COMMAND                   ;mt 12/8/86 P894
        return                                  ;mt 12/8/86

Found_COMMAND:                                  ;mt 12/8/86
        MOV     BX,[command.fileHandle]
        MOV     [command.fileStartSegment],AX
        CMP     AX,DX                   ; No room left?
        JZ      CLSALLJ                 ; Yes
        MOV     CX,[command.fileSizeInParagraphs]
        ADD     AX,CX
        CMP     AX,DX
        JBE     GOTCOM
        OR      BYTE PTR [FILSTAT],00010000B    ; Got part of COMMAND
        SUB     DX,[command.fileStartSegment]
        MOV     SI,DX
        XOR     DI,DI
        CALL    DISIX4
        push    ds
        MOV     DS,[command.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data
        JC      CLSALLJ
        XOR     DX,DX
        MOV     CX,DX
        MOV     AX,(LSEEK SHL 8) OR 1
        INT     21H
        MOV     WORD PTR [command.fileOffset],AX
        MOV     WORD PTR [command.fileOffset+2],DX
        JMP     FILESDONE

GOTCOM:
        OR      BYTE PTR [FILSTAT],00100000B    ; Got all of COMMAND
        LES     SI,[command.fileSizeInBytes]
        MOV     DI,ES
        push    ds
        MOV     DS,[command.fileStartSegment]
        assume  ds:nothing
        CALL    READFILE
        pop     ds
        assume  ds:data
        JMP     CLSALL

;**************************************************
;Write BIOS DOS COMMAND to the newly formatted disk.

ASSUME DS:DATA
WRITEDOS:
        MOV     CX,BiosAttributes
        MOV     DX,OFFSET BiosFile
        LES     SI,[bios.fileSizeInBytes]
        MOV     DI,ES
        CALL    MAKEFIL
        retc

        MOV     [TempHandle],BX
        TEST    BYTE PTR FILSTAT,00000010B
        JNZ     GOTALLBIO
        call    Get_BIOS                        ; dcl 8/23/86
        jnc     Got_WBIOS                       ;mt 12/8/86  P894
        ret

Got_WBIOS:

        LES     SI,[bios.fileOffset]
        MOV     DI,ES
        MOV     WORD PTR [IOCNT],SI
        MOV     WORD PTR [IOCNT+2],DI
        MOV     BP,OFFSET bios
        CALL    GOTTARG
        retc
        JMP     SHORT BIOSDONE

GOTALLBIO:
        LES     SI,[bios.fileSizeInBytes]
        MOV     DI,ES
        push    ds
        MOV     DS,[bios.fileStartSegment]
        assume  ds:nothing
        CALL    WRITEFILE
        pop     ds
        assume  ds:data
BIOSDONE:
        MOV     BX,[TempHandle]
        MOV     CX,bios.fileTime
        MOV     DX,bios.fileDate
        CALL    CLOSETARG
        MOV     CX,DosAttributes
        MOV     DX,OFFSET DosFile
        LES     SI,[dos.fileSizeInBytes]
        MOV     DI,ES
        CALL    MAKEFIL
        retc

GOTNDOS:
        MOV     [TempHandle],BX
        TEST    BYTE PTR FILSTAT,00001000B
        JNZ     GOTALLDOS
        call    Get_DOS                         ; dcl 8/23/86

⌨️ 快捷键说明

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