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

📄 absasm21.bas

📁 如何在QBasic环境下实现和利用汇编
💻 BAS
📖 第 1 页 / 共 2 页
字号:
' -------------------------------------------------------------------------- '
' Absolute Assembly 2.1 by Petter Holmberg, -97.                             '
'                                                                            '
' I've found some bugs in Absolute Assembly 2.0, so here's a new version.    '
' For those of you who haven't used AbsAsm before, here's what it does:      '
'                                                                            '
' The program will let you choose a text file with Assembly source code,     '
' a destination file name and a string variable name. The result will be a   '
' set of commented BASIC string declaration lines in the destination file,   '
' ready to be executed with CALL ABSOLUTE.                                   '
' For example, you may have a text file looking like this:                   '
'                                                                            '
' ; A Useless Program example                                                '
'                                                                            '
'           XOR AX, AX    ; Set AX to 0                                      '
' Loopinit:                                                                  '
'           MOV CX, 4     ; Prepare for a loop                               '
' Increase: INC AX        ; Incease AX by 1                                  '
'           LOOP Increase ; Loop 8 times                                     '
'           CMP AX, 8     ; Is AX 8?                                         '
'           JNZ Loopinit  ; No. Go back to Loopinit                          '
'           RETF          ; Back to BASIC                                    '
'                                                                            '
' Run it through this program and you will get these lines moved into a      '
' selected BASIC program:                                                    '
'                                                                            '
' asm$ = ""                                                                  '
' asm$ = asm$ + CHR$(&H31) + CHR$(&HC0)            ' XOR AX,AX               '
' asm$ = asm$ + CHR$(&HB9) + CHR$(&H4) + CHR$(&H0) ' Loopinit: MOV CX,0004   '
' asm$ = asm$ + CHR$(&H40)                         ' Increase: INC AX        '
' asm$ = asm$ + CHR$(&HE2) + CHR$(&HFD)            ' LOOP Increase           '
' asm$ = asm$ + CHR$(&H3D) + CHR$(&H8) + CHR$(&H0) ' CMP AX,0008             '
' asm$ = asm$ + CHR$(&H75) + CHR$(&HF5)            ' JNZ Loopinit            '
' asm$ = asm$ + CHR$(&HCB)                         ' RETF                    '
'                                                                            '
' Absolute Assembly takes use of DEBUG, the program shipped with MS-DOS.     '
' DEBUG only supports 8088/8086 instructions, but it's still a good tool for '
' getting machine language out of Assembly instructions. And since QBASIC    '
'                                                                            '
' Absolute Assembly 2.1 features:                                            '
' * Support for blank lines and lines with just comments or lables.          '
' * Support for double Assembly commands, like REP STOSB.                    '
' * Option to automatically add CALL ABSOLUTE lines to output file.          '
' * All Assembly source lines printed to BASIC file in the same column.      '
' * Option to merge lines directly into a BASIC file.                        '
' * Auto-detection of QuickBASIC binary files to ensure safe merging.        '
' * Handling of errors and bugs in the sourcefile.                           '
'                                                                            '
' Notes:                                                                     '
' * Comments must start with a semicolon, (;).                               '
' * The maximum number of labels are 256. You shouldn't need half as much.   '
' * The maximum number of letters for a label are 16. It's easy to change    '
' * the program to accept a larger number, but it's probably not necessary.  '
' * A line label must be immediately followed by a colon, (:). Do NOT use a  '
'   colon after the label name in jump-instructions.                         '
' * Never use Assembly opcodes, numbers or single letters as labels.         '
' * Do not name labels so that the name includes the letters REP, REPE or    '
' * REPZ after each other, for example RepeatLoop:                           '
'   "Label:" and "label:" are processed as the same label.                   '
' * If no code string name is specified, it will be asm$ as default.         '
' * This program was made in QB45, but you should be able to run it in       '
'   QBASIC, PDS, VBDOS and PB as well.                                       '
' * If the program locks up, it's probably while running DEBUG. If this      '
'   happens, reboot your computer and check your source code for lines with  '
'   other things than Assembly instrucions, comments, labels or spaces.      '
' * You may use this program freely; distribute it, modify it, learn from it '
'   or erase it from your hard drive. ;) Just be sure to credit me in the    '
'   programs where you have used Absolute Assembly for some of the code.     '
' * If your computer gets damaged while using this program, don't blame me.  '
' * If you use Absolute Assembly in a program, please mail me and tell me    '
'   about it!                                                                '
' * Any comments/suggestions/bug reports etc. can be sent to:                '
'   petter.holmberg@usa.net                                                  '
' * Enjoy the program and have fun! Petter Holmberg, Sweden.                 '
' -------------------------------------------------------------------------- '

ON ERROR GOTO ErrorHandler

' -------------------------------------------------------------------------- '
' Declaration of constants and arrays:                                       '
' -------------------------------------------------------------------------- '

CONST rundebug$ = "C:\DOS\DEBUG.EXE" ' Change this if you have DEBUG on
				     ' another location.
CONST tempfile1$ = "TEMPFIL1.TXT"    ' Change this if the filename already
				     ' is in use.
CONST tempfile2$ = "TEMPFIL2.TXT"    ' Change this if the filename already
				     ' is in use.
CONST tempfile3$ = "TEMPFIL3.TXT"    ' Change this if the filename already
				     ' is in use.
CONST tempfile4$ = "TEMPFIL4.TXT"    ' Change this if the filename already
				     ' is in use.
CONST errorfile$ = "ERRORS.TXT"      ' Change this if the filename already
				     ' is in use.

TYPE labeltype                       ' Usertype for storing of labels.
  labelname AS STRING * 16           ' Change this if you want longer labels.
  labelpos AS STRING * 4
  labelnum AS INTEGER
END TYPE

DIM label(1 TO 256) AS labeltype     ' Array for storing of labels.

Start:

numlabels% = 0                       ' Label counter.
linecounter% = 1                     ' Line counter.
errorcounter% = 0                    ' Error counter.

' -------------------------------------------------------------------------- '
' Ask for settings:                                                          '
' -------------------------------------------------------------------------- '

CLS

PRINT "Absolute Assembly 2.1 by Petter Holmberg, -97."
PRINT

INPUT "Assembly source text file      : ", sourcefilename$
INPUT "BASIC destination file         : ", destfilename$
INPUT "Name of code string            : ", codestring$

codestring$ = LTRIM$(RTRIM$(codestring$))
IF codestring$ = "" THEN codestring$ = "asm$"
IF RIGHT$(codestring$, 1) <> "$" THEN codestring$ = codestring$ + "$"

PRINT "Append to destfile? (y/n)      : ";

DO
   kbd$ = INKEY$
   IF LCASE$(kbd$) = "n" THEN writemethod% = 0
   IF LCASE$(kbd$) = "y" THEN writemethod% = 1
LOOP UNTIL LCASE$(kbd$) = "n" OR LCASE$(kbd$) = "y"

PRINT LCASE$(kbd$)

PRINT "Add CALL ABSOLUTE lines? (y/n) : ";

DO
   kbd$ = INKEY$
   IF LCASE$(kbd$) = "n" THEN callabs% = 0
   IF LCASE$(kbd$) = "y" THEN callabs% = 1
LOOP UNTIL LCASE$(kbd$) = "n" OR LCASE$(kbd$) = "y"

PRINT LCASE$(kbd$)

PRINT

' -------------------------------------------------------------------------- '
' Warn the user if the BASIC destination file is a QuickBASIC binary file:   '
' -------------------------------------------------------------------------- '

IF writemethod% = 1 THEN
 DIM readstring AS STRING * 3

 OPEN destfilename$ FOR BINARY AS #1
 GET #1, , readstring

 IF readstring = CHR$(252) + CHR$(0) + CHR$(1) THEN
  PRINT "BASIC destination file is probably a QuickBASIC binary file"
  PRINT "Continue anyway? (y/n)         : "
 
  DO
     kbd$ = INKEY$
     IF UCASE$(kbd$) = "N" THEN END
  LOOP UNTIL UCASE$(kbd$) = "Y"
 END IF
 
 CLOSE #1
END IF

' -------------------------------------------------------------------------- '
' Get rid of blank lines, comments and double instructions in sourcefile:    '
' -------------------------------------------------------------------------- '

conversiontime! = TIMER

PRINT "Modifying source file..."

OPEN sourcefilename$ FOR INPUT AS #1
OPEN tempfile1$ FOR OUTPUT AS #2

DO
   LINE INPUT #1, readline$

   sourceline$ = sourceline$ + UCASE$(readline$)
  
   IF INSTR(sourceline$, ";") THEN
    sourceline$ = LEFT$(sourceline$, INSTR(sourceline$, ";") - 1)
   END IF

   sourceline$ = LTRIM$(RTRIM$(sourceline$))

   IF INSTR(sourceline$, "REPE") THEN
    PRINT #2, LEFT$(sourceline$, INSTR(sourceline$, "REPE") + 2) + "Z"
    sourceline$ = RIGHT$(sourceline$, LEN(sourceline$) - INSTR(sourceline$, "REPE") - 3)
    sourceline$ = LTRIM$(RTRIM$(sourceline$))
   ELSEIF INSTR(sourceline$, "REPZ") THEN
    PRINT #2, LEFT$(sourceline$, INSTR(sourceline$, "REPZ") + 3)
    sourceline$ = RIGHT$(sourceline$, LEN(sourceline$) - INSTR(sourceline$, "REPZ") - 3)
    sourceline$ = LTRIM$(RTRIM$(sourceline$))
   ELSEIF INSTR(sourceline$, "REP") THEN
    PRINT #2, LEFT$(sourceline$, INSTR(sourceline$, "REP") + 2) + "Z"
    sourceline$ = RIGHT$(sourceline$, LEN(sourceline$) - INSTR(sourceline$, "REP") - 2)
    sourceline$ = LTRIM$(RTRIM$(sourceline$))
   END IF

   IF RIGHT$(sourceline$, 1) <> ":" THEN
    IF LEN(sourceline$) > 0 THEN PRINT #2, sourceline$
    sourceline$ = ""
   END IF

LOOP UNTIL EOF(1)

CLOSE #2
CLOSE #1

' -------------------------------------------------------------------------- '
' Insert DEBUG instructions and Assembly source code into tempfile and take  '
' care of lables:                                                            '
' -------------------------------------------------------------------------- '

OPEN tempfile1$ FOR INPUT AS #1
OPEN tempfile2$ FOR OUTPUT AS #2

DO
   LINE INPUT #1, sourceline$

   IF INSTR(sourceline$, ":") THEN
    numlabels% = numlabels% + 1
    label(numlabels%).labelname = LEFT$(sourceline$, INSTR(sourceline$, ":") - 1)
    sourceline$ = MID$(sourceline$, INSTR(sourceline$, ":") + 1)
    label(numlabels%).labelnum = linecounter%
   END IF

   sourceline$ = LTRIM$(RTRIM$(sourceline$))
   PRINT #2, sourceline$

   linecounter% = linecounter% + 1
LOOP UNTIL EOF(1)

CLOSE #2
CLOSE #1

OPEN tempfile2$ FOR INPUT AS #1
OPEN tempfile3$ FOR OUTPUT AS #2

PRINT #2, "a"

DO
   LINE INPUT #1, sourceline$

   FOR labelscan% = 1 TO numlabels%
      IF INSTR(sourceline$, LTRIM$(RTRIM$(label(labelscan%).labelname))) THEN
       sourceline$ = LEFT$(sourceline$, INSTR(sourceline$, LTRIM$(RTRIM$(label(labelscan%).labelname))) - 1) + "100"
      END IF
   NEXT labelscan%

   PRINT #2, sourceline$
LOOP UNTIL EOF(1)

CLOSE #1

PRINT #2, ""
PRINT #2, "u 100, 100"
PRINT #2, "q"

CLOSE #2

' -------------------------------------------------------------------------- '
' Run DEBUG to find machine language code length in bytes and then update    '
' the tempfile with the correct byte length:                                 '
' All errors detected will be written to the file specified in errorfile$    '
' -------------------------------------------------------------------------- '

PRINT "Detecting machine language code length..."

SHELL rundebug$ + "<" + tempfile3$ + ">" + tempfile3$

OPEN tempfile3$ FOR INPUT AS #1
OPEN errorfile$ FOR OUTPUT AS #2

linecounter% = 0

DO
   oldline$ = midline$
   midline$ = newline$
   LINE INPUT #1, newline$
   SEEK #1, SEEK(1) + 2
   IF INSTR(newline$, "^") THEN
    PRINT
    PRINT "Error in line"; RTRIM$(STR$(linecounter% - 1)); ":"
    PRINT midline$
    PRINT newline$
    PRINT #2, "Error in line"; RTRIM$(STR$(linecounter% - 1)); ":"

⌨️ 快捷键说明

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