home *** CD-ROM | disk | FTP | other *** search
- PAGE 59,132
- TITLE MAKEBAS - Create .BAS source to recreate a file
- ;----------------------------------------------------------------------
- ; MAKEBAS.ASM
- ;
- ; Author..: Salvatore P. Ricciardi
- ; Version.: 01.00
- ;
- ; Creates .BAS files to use when creating the PC Magazine utilities.
- ;----------------------------------------------------------------------
- page
- ;----------------------------------------------------------------------
- ;--- EQUATES, RECORDS and STRUCTURES
- ;----------------------------------------------------------------------
- LF EQU 0AH ;line feed
- CR EQU 0DH ;carriage return
- BYTES_LINE EQU 16D ;bytes per line of data
- LINE_INCR EQU 10D ;line number increment
- LASTBASIC EQU 260D ;last basic statement
- ;before data statements
- STACKSAVE EQU 200D ;stack requirement
-
- ;----------------------------------------------------------------------
- ;--- CODE
- ;----------------------------------------------------------------------
- CSEG SEGMENT PARA PUBLIC 'CODE'
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
-
- ORG 100h ;Starting offset for .COM files
- ENTRY: JMP START ;Jump to start
-
- COPYRIGHT DB "MAKEBAS 1.0 (C) 1988 Ziff Communications Co.",CR,LF
- DB "PC Magazine ",254," Salvatore P. Ricciardi",CR,LF
- DB CR,LF,"$"
- USAGE DB "Usage: MAKEBAS [d:][\path\]filename[.ext]",CR,LF,"$"
- DB 1AH
- BASIC_CODE DB "100 REM - BASIC PROGRAM TO CREATE "
- FLNAME DB 12 DUP(" "),CR,LF
- DB "110 CLS:PRINT ""Creating "
- FLNAME0 DB 12 DUP(" ")
- DB """: OPEN """
- FLNAME1 DB 12 DUP(" ")
- DB """ AS #1 LEN = 1",CR,LF
- DB "120 FIELD #1, 1 AS A$: CHECKSUM#=0",CR,LF
- DB "130 FOR I = 1 TO "
- LINECOUNT DB 5 DUP(" "),CR,LF
- DB "140 LINESUM#=0: LOCATE 2,3: "
- DB "PRINT ""Countdown: "" "
- COUNTDOWN DB 5 DUP(" ")," - I ;",CR,LF
- DB "150 FOR J = 1 TO "
- B_PER_LINE DB 3 DUP(" "),": READ BYTE$: "
- DB "CHECKSUM#=CHECKSUM#+VAL(""&H""+BYTE$)"
- DB CR,LF
- DB "160 LINESUM#=LINESUM#+VAL(""&H""+BYTE$)",CR,LF
- DB "170 IF (BYTE < 256) THEN LSET A$=CHR$"
- DB "(VAL(""&H""+BYTE$)): PUT #1",CR,LF
- DB "180 NEXT J",CR,LF
- DB "190 READ LINETOT$: LINECHECK# = VAL(""&H""+LINETOT$)"
- DB CR,LF
- DB "200 IF LINECHECK# = LINESUM# THEN GOTO 220",CR,LF
- DB "210 LOCATE 4,2: PRINT ""Error in line #"" ;"
- ALASTBAS DB 5 DUP(" ")," + "
- AINCR DB 3 DUP(" ")," * I: GOTO 260",CR,LF
- DB "220 NEXT I",CR,LF
- DB "230 CLOSE: READ FILETOT$ : FILECHECK# = VAL(FILETOT$)"
- DB CR,LF
- DB "240 IF CHECKSUM# <> FILECHECK# THEN GOTO 260",CR,LF
- DB "250 PRINT: PRINT """
- FLNAME2 DB 12 DUP(" ")
- DB " created successfully"": SYSTEM",CR,LF
- DB "260 PRINT: PRINT """
- FLNAME3 DB 12 DUP(" ")
- DB " is not valid!"": END",CR,LF
- BASICLEN EQU $-BASIC_CODE ;sum length of basic lines
-
- BASICDATA DB 5 DUP(" ") ;space for the line number
- DB " DATA " ;these are DATA statements
- BBUFFER DB ((BYTES_LINE*4)+7) DUP(" ")
- BASICDATAL EQU $-BASICDATA ;Length for the write
-
- ERRORLVL DB 0 ;Return code
- FNSTART DW 0 ;offset of filename on cmdline
- LINENUMBER DW 0 ;line number
-
- SRCFILE DB ".COM",0 ;default file extent
- SRCFLEN EQU $-SRCFILE ;length for mov
- SRCHANDLE DW ? ;file handle when opened
-
- BASFILE DB ".BAS",0 ;file extent for BAS file
- BASFLEN EQU $-BASFILE ;length for mov
- BASHANDLE DW 0 ;file handle when opened
-
- EXISTSMSG DB ".BAS file" ;message when file exists
- DB " already exists. Overwrite (y/n)? :","$"
- LINERROR DB "MAKEBAS: Error, line number too big",CR,LF,"$"
- SRCERROR DB "MAKEBAS: Source file error",CR,LF,"$"
- BASERROR DB "MAKEBAS: .BAS file error",CR,LF,"$"
- NOMEMORY DB "MAKEBAS: Not enough memory",CR,LF,"$"
- WORKING_MSG DB " Working...","$"
- DONE_MSG DB "Done",CR,LF,"$"
- CRLF_MSG DB CR,LF,"$"
-
- SRCCKSUM DD 0 ;dword for checksum
- ;
- ; Start of main code section
- ;
- START: MOV DX,OFFSET COPYRIGHT ;copyright message
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- ;
- ; Check and ensure that there is adequate memory
- ;
- CMP SP,(OFFSET BUFFER-OFFSET CSEG+BYTES_LINE+STACKSAVE)
- JA START1 ;yes, lets continue
- MOV AH,09H ;no, display message
- MOV DX,OFFSET NOMEMORY ;"not enough memory"
- INT 21H ;dos interrupt
- JMP RETURN_TO_DOS ;go end
-
- START1: CLD ;forward direction
- XOR AX,AX ;clear ax
- MOV AL,DS:[80H] ;get parm count
- CMP AL,1 ;is it more than one?
- JA GOTPARM ;yes, go handle
- JMP HELP ;no, display usage and quit
- ;
- ; Remove blanks or tabs from the end of the filespec by replacing
- ; them with binary zero. Skip leading spaces and tabs also.
- ;
- GOTPARM: MOV DI,AX ;use di
- INC AX ;start with count+1
- MOV CX,AX ;put in cx
- GOTPARM1: MOV BYTE PTR DS:[80H+DI+1],0 ;make asciiz
- DEC CX ;decrement cx
- JNZ GOTPARM3 ;not zero then continue
- JMP HELP ;none left, give usage message
- GOTPARM3: DEC DI ;back up one
- CMP BYTE PTR DS:[80H+DI+1]," " ;is last byte a space?
- JE GOTPARM1 ;yes, null it out
- CMP BYTE PTR DS:[80H+DI+1],09H ;is last byte a tab?
- JE GOTPARM1 ;yes, null it out
- GOTPARM4:
- MOV SI,80H ;set start
- GOTPARM5:
- INC SI ;skip spaces and tabs
- CMP BYTE PTR DS:[SI]," " ;a space?
- JNE GOTPARM6 ;no
- DEC CX ;back it out
- JMP GOTPARM5 ;yes
- GOTPARM6:
- CMP BYTE PTR DS:[SI],09H ;a tab?
- JNE GOTPARM7 ;no
- DEC CX ;back it out
- JMP GOTPARM5 ;yes
- GOTPARM7:
- MOV BYTE PTR DS:[80H],CL ;store adjusted length
- MOV FNSTART,SI ;save start of filename
- CALL STRUPPER ;make uppercase
- ;
- ; If no file extent is present, use .COM as the default
- ;
- CHECKCOM: MOV CL,BYTE PTR DS:[80H] ;get length
- MOV DI,SI ;set start
- MOV AL,"." ;look for start of extension
- REPNE SCASB ;is it there?
- MOV BX,DI ;save location in bx
- JNE MAKECOM ;no extent, use default
- DEC BX ;adjust to point to the "."
- JMP SHORT OPENSRC ;go open the file
-
- MAKECOM: MOV CX,SRCFLEN ;length of string
- MOV SI,OFFSET SRCFILE ;".COM,0"
- REP MOVSB ;move in the default
- ; ;extent (.COM)
- ; OPEN the source file for reading
- ;
- OPENSRC: MOV DX,FNSTART ;get start of filename
- MOV AX,3D00H ;open for reading
- INT 21H ;dos interrupt
- JNC OPENCOK ;no carry means success
- MOV ERRORLVL,2 ;set errorlevel
- MOV DX,OFFSET SRCERROR ;error message
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- JMP RETURN_TO_DOS ;carry means error
-
- OPENCOK: MOV SRCHANDLE,AX ;save handle
- ;
- ; Isolate the filename.ext portion of the pathspec
- ;
- MOV DI,FNSTART ;set for parsing
- CALL FILENAME ;look for filename.ext only
- ;
- ; Move the filename.ext into the appropriate places in the BASIC
- ; statements
- ;
- SAVNAME: MOV SI,DI ;get from position in si
- MOV AX,SI ;save move from position in ax
- MOV DX,CX ;save length in dx
- MOV DI,OFFSET FLNAME ;where to put filename
- REP MOVSB ;move in flname
- MOV SI,AX ;get back from position
- MOV CX,DX ;get back length
- MOV DI,OFFSET FLNAME0 ;where to put filename
- REP MOVSB ;move in flname1
- MOV SI,AX ;get back from position
- MOV CX,DX ;get back length
- MOV DI,OFFSET FLNAME1 ;where to put filename
- REP MOVSB ;move in flname1
- MOV SI,AX ;get back from position
- MOV CX,DX ;get back length
- MOV DI,OFFSET FLNAME2 ;where to put filename
- REP MOVSB ;move in flname2
- MOV SI,AX ;get back from position
- MOV CX,DX ;get back length
- MOV DI,OFFSET FLNAME3 ;where to put filename
- REP MOVSB ;move in flname3
- ;
- ; Now change file extent to .BAS and try to open for writing.
- ; If this works, a .BAS file with the same name already exists
- ;
- MAKEBAS: MOV CX,BASFLEN ;count in cx
- MOV DI,BX ;restore position of extent
- MOV SI,OFFSET BASFILE
- REP MOVSB ;move in .bas extent
- XOR BX,BX ;clear bx for later
-
- OPENBAS: MOV DX,FNSTART ;offset of filename
- MOV AX,3D01H ;open file for writing
- INT 21H ;dos interrupt
- JC CREATEBAS ;if this fails, go create file
- MOV BASHANDLE,AX ;save file handle
- ;
- ; If the .BAS file already exists, ask before overwriting
- ;
- MOV DX,OFFSET EXISTSMSG ;File exists, write over?
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
-
- GETANS: MOV AX,0100H ;DOS read kybd and echo
- INT 21H ;dos interrupt
- AND AL,0DFH ;make uppercase
- OR AL,AL ;is it extended key?
- JE GETANS ;go get the keycode
- PUSH AX ;save key
- MOV DX,OFFSET CRLF_MSG ;put out a CRLF combo
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- POP AX ;get back key
- CMP AL,"Y" ;is it yes?
- JE OVERWRITE ;yes, continue
- JMP CLOSFILES ;no, go quit
- ;
- ; To overwrite the existing file, close it and then create it using
- ; function 3CH
- ;
- OVERWRITE:
- MOV DX,OFFSET CRLF_MSG ;put out a CRLF combo
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- MOV AX,3E00H ;close file handle request
- MOV BX,BASHANDLE ;handle for .BAS file
- INT 21H ;close the file
- ;
- ; Create the .BAS file
- ;
- CREATEBAS: MOV DX,FNSTART ;offset of filename
- XOR CX,CX ;attribute normal
- MOV AX,3C00H ;create file
- INT 21H ;dos interrupt
- JNC CREATOK ;no carry means success
- MOV ERRORLVL,1 ;set errorlevel
- MOV DX,OFFSET BASERROR ;error message
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- MOV AX,3E00H ;close file handle request
- MOV BX,SRCHANDLE ;close the source file
- INT 21H ;dos interrupt
- JMP RETURN_TO_DOS ;go end
-
- CREATOK: MOV BASHANDLE,AX ;save file handle
- ;
- ; Display "Working" message
- ;
- MOV DX,OFFSET WORKING_MSG ;"Working" message
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- ;
- ; Calculate the number of DATA lines required
- ;
- NUMLINES: ;Get the file size in bytes
- MOV AX,4202H ;move file pointer
- MOV BX,SRCHANDLE ;file handle for com file
- XOR CX,CX ;seek to eof
- XOR DX,DX ;clear
- INT 21H ;dos interrupt
- JNC NUMLINES1 ;no carry means ok
- MOV ERRORLVL,5 ;set errorlevel
- MOV DX,OFFSET SRCERROR ;error message
- JMP ERROREXIT ;carry means error
-
- NUMLINES1: XOR BX,BX ;clear BX
- MOV BL,BYTES_LINE ;bytes per line
- DIV BX ;calculate number of lines
- OR DX,DX ;any remainder?
- JZ NUMLINES2 ;no, go ahead
- INC AX ;yes, one more line
- ;
- ; Convert values to ascii decimal and store in the BASIC statements
- ;
- NUMLINES2: MOV DI,OFFSET LINECOUNT ;store no. 1f lines in ascii
- XOR DX,DX ;high is zero, low in ax
- MOV BX,10D ;decimal radix
- MOV CX,5D ;width of output field
- CALL BTOA ;convert to ascii
-
- MOV DI,OFFSET COUNTDOWN ;store no. 1f lines in ascii
- MOV CX,5D ;width of output field
- CALL BTOA ;convert to ascii
-
- MOV DI,OFFSET B_PER_LINE ;store bytes per line in ascii
- MOV AX,BYTES_LINE ;low is bytes per line
- MOV CX,3D ;width of output field
- CALL BTOA ;convert to ascii
-
- MOV DI,OFFSET ALASTBAS ;store last line no. in ascii
- MOV AX,LASTBASIC ;low is bytes per line
- MOV CX,5D ;width of output field
- CALL BTOA ;convert to ascii
-
- MOV DI,OFFSET AINCR ;store line increment
- XOR AX,AX ;clear AX
- MOV AL,LINE_INCR ;low is bytes per line
- MOV CX,3D ;width of output field
- CALL BTOA ;convert to ascii
- ;
- ; Write everything except the DATA statements to the .BAS file
- ;
- WRITESOME: MOV DX,OFFSET BASIC_CODE ;start of text
- MOV CX,BASICLEN ;length of write
- MOV BX,BASHANDLE ;handle for basic file
- CALL WRITE_HANDLE ;write to handle
- JNC STARTDATA ;no carry means ok
- MOV ERRORLVL,4 ;set errorlevel
- MOV DX,OFFSET BASERROR ;error message
- JMP ERROREXIT ;carry means error
- ;
- ; Seek back to the beginning of the source file in order to create
- ; the DATA statements
- ;
- STARTDATA: MOV AX,4200H ;move file pointer
- MOV BX,SRCHANDLE ;file handle for com file
- XOR CX,CX ;seek to 0:0
- XOR DX,DX
- INT 21H ;dos interrupt
- JNC DATALOOP ;no carry means ok
- MOV ERRORLVL,5 ;set errorlevel
- MOV DX,OFFSET SRCERROR ;error message
- JMP ERROREXIT ;jump to error exit
- ;
- ; Create the DATA statements
- ;
- DATALOOP: MOV CX,BYTES_LINE ;read BYTES_LINE bytes
- CALL READDATA ;read into the buffer
- JNC DATALOOP1 ;no carry means ok
- MOV ERRORLVL,3 ;set errorlevel
- MOV DX,OFFSET SRCERROR ;error message
- JMP ERROREXIT ;jump to error exit
-
- DATALOOP1: OR AX,AX ;zero bytes read?
- JZ FINISHED ;yes, finished
- INC LINENUMBER ;increment line counter
- CALL LINENUM ;put out line number
- JNC DATALOOP2 ;no carry means ok
- MOV ERRORLVL,6 ;set errorlevel
- MOV DX,OFFSET LINERROR ;error message
- JMP ERROREXIT ;jump to error exit
-
- DATALOOP2: MOV CX,AX ;number of bytes from ax
- CALL MAKEDATA ;go make data statement
-
- MOV CX,BASICDATAL ;length of write
- CALL WRITEDATA ;write out data statement
- JNC DATALOOP ;go do some more
- MOV ERRORLVL,4 ;set errorlevel
- MOV DX,OFFSET BASERROR ;error message
- JMP ERROREXIT ;jump to error exit
- ;
- ; Convert the checksum to decimal ascii and store in the final data
- ; statement
- ;
- FINISHED: INC LINENUMBER ;increment line counter
- CALL LINENUM ;put out line number
-
- MOV DI,OFFSET BBUFFER ;store byte sum in ascii
- PUSH DI ;save a moment
- MOV DX,WORD PTR SRCCKSUM+2
- MOV AX,WORD PTR SRCCKSUM ;low in ax, high in dx
- MOV BX,10D ;decimal radix
- MOV CX,11D ;width of output field
- CALL BTOA ;convert to ascii
- MOV SI,DI ;get address in si
- POP DI ;restore buffer address
- REP MOVSB ;move flush left
- MOV AL,CR ;end of line
- STOSB ;store the byte
- MOV AL,LF ;end of line
- STOSB ;store the byte
- MOV CX,DI ;position in cx
- SUB CX,OFFSET BASICDATA ;calculate length
- FINISHED2:
- CALL WRITEDATA ;write out data statement
- JNC DISPDONE ;go do some more
- MOV ERRORLVL,4 ;set errorlevel
- MOV DX,OFFSET BASERROR ;error message
- JMP ERROREXIT ;jump to error exit
- ;
- ; Display "Done" message
- ;
- DISPDONE:
- MOV AH,09H ;display message
- MOV DX,OFFSET DONE_MSG ;"Done" message
- INT 21H ;dos interrupt
- ;
- ; Close both files
- ;
- CLOSFILES:
- MOV AX,3E00H ;close file handle request
- MOV BX,SRCHANDLE ;close the source file
- INT 21H ;dos interrupt
- MOV AX,3E00H ;close file handle request
- MOV BX,BASHANDLE ;close the source file
- INT 21H ;dos interrupt
- ;
- ; Set errorlevel and return to dos
- ;
- RETURN_TO_DOS:
- MOV AH,04CH ;terminate process
- MOV AL,ERRORLVL ;get return code
- INT 21H ;return to dos
- ;
- ; Error exit - display message, close files and terminate
- ;
- ERROREXIT:
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- JMP CLOSFILES ;go close and end
-
- HELP: MOV DX,OFFSET USAGE ;usage message
- MOV AH,09H ;display string
- INT 21H ;dos interrupt
- JMP RETURN_TO_DOS
-
- ;----------------------------------------------------------------------
- ; WRITEDATA - Write out a data statement. Entry: CX has bytecount.
- ; This routine removes leading blanks from the linenumbers.
- ;----------------------------------------------------------------------
- WRITEDATA PROC NEAR
- MOV SI,OFFSET BASICDATA ;start of data statement
- ;
- ; Scan past leading blanks...
- ;
- WRITED001: CMP BYTE PTR DS:[SI]," " ;is it a blank?
- JNE WRITED002 ;no, go write
- INC SI ;skip the blank
- DEC CX ;count - 1
- JMP WRITED001 ;check next char
-
- WRITED002: MOV DX,SI ;start position in DX
- MOV BX,BASHANDLE ;handle for basic file
- CALL WRITE_HANDLE ;write to handle
- RET
- WRITEDATA ENDP
-
- ;----------------------------------------------------------------------
- ; LINESUM - Convert line sum to ascii decimal and put in data
- ; statement followed by CR,LF. Entry: Line sum in BX
- ;----------------------------------------------------------------------
- LINESUM PROC NEAR ;create line checksum
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH DI ;save di
- MOV CX,5 ;blank fill first
- MOV AL," "
- REP STOSB
- POP DI ;restore di
- XOR DX,DX ;high is zero
- MOV AX,BX ;low is line sum
- OR AX,AX ;is it zero?
- JNZ LINESUM1 ;no, continue
-
- MOV AX," " ;lead with blanks
- STOSW
- STOSB
- MOV AX,"0 " ;put out zero
- STOSW
- JMP SHORT LINESUM2
-
- LINESUM1: ADD WORD PTR SRCCKSUM,AX ;add to the
- ADC WORD PTR SRCCKSUM+2,DX ;file checksum
- PUSH DI ;save it again
- MOV BX,16D ;hexadecimal radix
- MOV CX,5D ;width of buffer
- CALL BTOA ;go convert to ascii
- POP DI ;get it back
-
- ADD DI,5 ;point past line sum
- LINESUM2: MOV AL,CR ;end of line
- STOSB ;store the byte
- MOV AL,LF ;end of line
- STOSB ;store the byte
-
- RET
- LINESUM ENDP
-
- ;----------------------------------------------------------------------
- ; READDATA - Reads CX bytes from source file into buffer.
- ; Exit: AX contains number of bytes read
- ; If error occurred, carry set and AX contains error code
- ;----------------------------------------------------------------------
- READDATA PROC NEAR ;read BYTES_LINE bytes
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH BX ;save registers
- PUSH DX
- MOV AX,3F00H ;read from file handle
- MOV BX,SRCHANDLE ;handle for COM file
- MOV DX,OFFSET BUFFER ;address of buffer
- INT 21H ;get em from dos
- POP DX ;restore registers
- POP BX
- RET
- READDATA ENDP
-
- ;----------------------------------------------------------------------
- ; WRITE_HANDLE - Write to file handle.
- ; Input: DS:DX addresses buffer. CX has bytecount.
- ; BX has file handle.
- ; Exit: AX has count written unless carry is set, in which case
- ; an error code is in AX.
- ;----------------------------------------------------------------------
- WRITE_HANDLE PROC NEAR ;write to file handle
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH CX ;save just in case
- MOV AH,40H ;write to handle function
- INT 21H ;dos interrupt
- POP CX ;get back cx
- JC WRITE_HRET ;carry set, return immediately
- CMP AX,CX ;did we write them all?
- JE WRITE_HRET ;yes, go return
- STC ;no, set carry
- WRITE_HRET:
- RET
- WRITE_HANDLE ENDP
-
- ;----------------------------------------------------------------------
- ; MAKEDATA - Creates a BASIC data statement containing the next CX
- ; bytes in hexadecimal, followed by a line sum.
- ; Entry: CX - byte count.
- ;----------------------------------------------------------------------
- MAKEDATA PROC NEAR ;make a basic data statement
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- MOV BP,CX ;save byte count in bp
- MOV DI,OFFSET BBUFFER ;start of ascii buffer
- MOV SI,OFFSET BUFFER ;start of data buffer
- XOR AX,AX ;start with clear ax
- XOR BX,BX ;sixteen byte sum in bx
-
- MAKE00010: LODSB ;get byte in AL
- ADD BX,AX ;add to sum
- CALL PUTHEX ;put out al in hex
- MOV AX," ," ;need a comma and space
- STOSW ;store the byte
- XOR AH,AH ;clear AH
- LOOP MAKE00010 ;loop
-
- CMP BP,BYTES_LINE ;was this a complete line
- JE MAKE01000 ;yes, then go finish up
-
- MOV CX,BYTES_LINE ;calculate padding
- SUB CX,BP ;requirement
- MAKE00200: MOV AX,"0 " ;pad with zeros
- STOSW ;move them in
- MOV AX," ," ;comma and space
- STOSW ;move it in
- LOOP MAKE00200 ;continue until finished
-
- MAKE01000: CALL LINESUM ;convert and put out linesum
- ;and cr,lf
- RET
- MAKEDATA ENDP
-
- ;----------------------------------------------------------------------
- ; PUTHEX - Output AL in hexadecimal to ES:DI. Replace a leading zero
- ; with a space
- ;----------------------------------------------------------------------
- PUTHEX PROC NEAR ;output al in hex to es:di
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH AX ;save a moment
- SHR AL,1 ;isolate high nibble
- SHR AL,1
- SHR AL,1
- SHR AL,1
- JZ PUTHEX1 ;jump if zero
- ADD AL,90H ;convert al
- DAA ;to hex
- ADC AL,40H
- DAA
- STOSB ;store the byte
- JMP PUTHEX2
- PUTHEX1: MOV AL," " ;zero suppress
- STOSB ;store the byte
- PUTHEX2: POP AX ;get back original
- AND AL,0FH ;isolate low nibble
- ADD AL,90H ;convert al
- DAA ;to hex
- ADC AL,40H
- DAA
- STOSB ;store the byte
- RET
- PUTHEX ENDP
-
- ;----------------------------------------------------------------------
- ; LINENUM - Calculate a new line number for the data statement and
- ; move it in. Exit: Carry set if too many lines
- ;----------------------------------------------------------------------
- LINENUM PROC NEAR ;create line number
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH AX ;save ax
- PUSH DI ;save di
- PUSH CX ;and cx
- CLC ;clear carry
- MOV CX,LINENUMBER ;get current line number
- XOR DX,DX ;high is zero
- MOV AX,LINE_INCR ;multiply by line increment
- MUL CX
- JC LINENUME ;carry means too many
- ADD AX,LASTBASIC ;add last basic statement no.
- JC LINENUME ;carry means too many
- MOV DI,OFFSET BASICDATA ;where to put lineno
- XOR DX,DX ;clear high word, low is in ax
- MOV BX,10D ;radix is decimal
- MOV CX,5D ;width of field
- CALL BTOA ;convert to ascii
- CLC ;make sure carry is clear
- LINENUME: POP CX ;restore cx
- POP DI ;restore di
- POP AX ;restore ax
- RET
- LINENUM ENDP
-
- ;----------------------------------------------------------------------
- ; FILENAME - Find filename.ext in a full path specification.
- ; Entry: ES:DI points to asciiz full path specification.
- ; Exit: ES:DI points to the name.ext only.
- ; CX contains the length of the name.ext in bytes.
- ; Carry flag set if error occurs (ES:DI, CX not valid).
- ;----------------------------------------------------------------------
- FILENAME PROC NEAR ;find the name and extent
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH AX ;save AX
- XOR AX,AX ;zero out AX
- MOV CX,0FFFFH ;maximum search
- CLD ;set direction forward
- REPNE SCASB ;look for the terminating null
- JNE FILENAME7 ;error if not found
-
- DEC DI ;adjust DI to point to last
- DEC DI ;character
- NOT CX ;get length in CX
- DEC CX ;adjust the length
- XOR AX,AX ;clear ax again
- PUSH CX ;save CX temporarily
- STD ;reverse the direction
- MOV AL,"\" ;path seperator
- REPNE SCASB ;look for the \
- JNE FILENAME1 ;no \ found
-
- INC DI ;adjust DI
- INC DI
- POP AX ;get search length in AX
- SUB AX,CX ;back out CX
- MOV CX,AX ;get length in CX
- DEC CX ;adjust the length
- JMP SHORT FILENAME9 ;go return
-
- FILENAME1: INC DI ;adjust DI
- POP CX ;get search length in CX
- CMP CX,12D ;longer than 12 bytes?
- JLE FILENAME9 ;no, ok
-
- FILENAME7: STC ;set carry to indicate error
-
- FILENAME9: CLD ;set direction forward
- POP AX ;restore AX
- RET ;return to caller
- FILENAME ENDP
-
- ;----------------------------------------------------------------------
- ; BTOA - Unsigned binary to ascii conversion.
- ; Entry: DX:AX contains value to convert. ES:DI addresses the output
- ; buffer. BX contains radix (eg. 10d is decimal, 16d is hexadecimal).
- ; CX contains the size of the output buffer in bytes.
- ; Exit: ES:DI address the result. CX contains length in bytes.
- ;----------------------------------------------------------------------
- BTOA PROC NEAR ;unsigned binary to ascii conv
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH DX ;save DX
- PUSH AX ;and AX
- PUSH AX ;save AX for as moment
- MOV AL," " ;first blank fill
- REP STOSB ;the buffer
- POP AX ;get back AX
- DEC DI ;start at the last position
- PUSH DI ;save start address
-
- BTOA0010: MOV CX,DX ;get high in cx
- OR CX,AX ;is value zero?
- JZ BTOA9900 ;yes, jump out
-
- BTOA0020: PUSH AX ;save ax
- MOV AX,DX
- XOR DX,DX ;0:div-high/divisor
- DIV BX
- MOV CX,AX ;save quotient in cx
- POP AX ;restore ax
- DIV BX ;remainder:div-low/divisor
- XCHG CX,DX ;get first quotient in dx
- ;dx:ax=quotient, cx=remainder
- ADD CL,"0" ;make ascii
- CMP CL,"9" ;greater than 9 needs hex
- JBE BTOA1000 ;no, less than 9
- ADD CL,'A'-'9'-1 ;map to uppercase hex
-
- BTOA1000: MOV ES:[DI],CL ;store it
- DEC DI ;decrement destination
- MOV CX,DX ;get high in cx
- OR CX,AX ;is value zero?
- JZ BTOA9900 ;yes, jump out
- JMP BTOA0020 ;loop
-
- BTOA9900: POP CX ;original address
- SUB CX,DI ;back out current address
- INC DI ;point to start
- POP AX ;restore dx:ax
- POP DX
- RET
- BTOA ENDP
-
- ;----------------------------------------------------------------------
- ; STRUPPER - Convert asciiz string to uppercase.
- ; Entry: DS:SI addresses the string. String must end with binary 0.
- ;----------------------------------------------------------------------
- STRUPPER PROC NEAR ;uppercase asciiz string
- ASSUME CS:CSEG,DS:CSEG,ES:NOTHING,SS:NOTHING
- PUSH AX ;save ax
- PUSH SI ;save di
- STRUPPER1:
- LODSB ;get char in al
- OR AL,AL ;is it zero
- JZ STRUPPER2 ;yes, we are finished
- CMP AL,'a' ;less than 'a'
- JB STRUPPER1 ;yes, skip it
- CMP AL,'z' ;above 'z'
- JA STRUPPER1 ;yes, skip it
- AND AL,0DFH ;mask bit 5, make uppercase
- MOV BYTE PTR DS:[SI-1],AL ;replace
- JMP STRUPPER1 ;loop and get another
- STRUPPER2:
- POP SI ;restore di
- POP AX ;restore ax
- RET
- STRUPPER ENDP
-
- BUFFER LABEL BYTE ;Storage for i/o buffer
-
- CSEG ENDS
- END ENTRY