8086 Assembler (MS-DOS):
Routinensammlung für COM-Programme zur gefälligen Übernahme

Zur Verbesserung der Lesbarkeit ist die Programmauflistung maschinell in Kleinschrift umcodiert worden. Anschließend wurden manuell erforderliche Änderungen im Codeteil des Programmtextes vorgenommen. Ich hoffe, ich habe dabei keine Fehler gemacht!
Die Macro- und Unterprogrammsammlung enthält eine Laufzeitumgebung für .COM - Programme. Sie ist ausgerichtet auf die Übersetzung mit ML 6.11g oder ML 6.14. Sie ist für das MODEL TINY geschrieben.

Sollte die Macro- und Unterprogrammsammlung für das MODEL SMALL genutzt werden, empfiehlt sich eine Aufteilung in zwei Teile. Der erste Teil sollte ins DATA-Segment kopiert werden, der zweite Teil gehört ins CODE-Segment. Hinweise dazu sind in der Programmauflistung enthalten. Weiterhin wird beim Merkmal „attr” der Programmcode für das Bildschirmattributbyte geändert. Bei Verwendung für das MODEL SMALL ist dies Verfahren bedenklich. Soll es trotzdem bei anderen als dem MODEL TINY genutzt werden, muss in den sich auf das Attributbyte beziehenden Befehlen zusätzlich auf das Codesegment (CS) verwiesen werden.

Bei meinen älteren MODEL TINY - Programmen wird die Macro- und Unterprogrammsammlung mit „include firm.mac” eingebunden. Bei meinen neueren MODEL TINY - Programmen wird sie mit „include mac32.mac” gefolgt von „include firm32.mac” eingebunden. Bei meinen MODEL SMALL - Quellprogrammen steht „include mac32.mac” im DATA-Segment und „include firm32.mac” im CODE-Segment.

Die Programmauflistung enthält eine Fülle von Anregungen.

Für die Zeichenkettenverarbeitung besonders hervorzuheben sind:

Für Eingaben per Tastatur und Ausgaben auf dem Bildschirm sind besonders hervorzuheben:

Zur Programmbeendigung mit definiertem Rückgabewert werden drei Einsprünge angeboten:

Hinweis: Der Code der Umlaute des Quelltextes bei ucaseg und lcaseg wird hier auf der Webseite in einem anderen Zeichensatz dargestellt als im tatsächlichen Quelltext.

;Bei Verwendung mit dem MODEL SMALL beginnt hier der Teil fuer das
;DATA-Segment
;matthaei, 16.10.89,2.3.93,17.6.94,31.3.96, 21.1.2011, 11.3.2011
;makrosammlung
        .286c

;einzelne teile werden nur bei der
;festlegung xxx equ true im rahmenprogramm mit aufgenommen
;       xxx kann sein:
;       dump$   fuer     mdump,  rdump
;       prompt$ fuer     prompt, inkjn
;       intasc$ fuer     int2asc, asc2int
;       string$ fuer     cmpstr, lenstr, instrg, movstr, ucaseg, lcaseg

;false  equ    0         ;false und true ist im
;true   equ    not false ;rahmenprogramm definiert

w       equ     word ptr
b       equ     byte ptr

bs      equ     8
tab     equ     9
spc     equ     ' '
cr      equ     0dh
lf      equ     0ah
escp    equ     1bh
eof     equ     1ah     ;end of file

;kbd_int equ     9       ;tastaturinterrupt
kbd_int equ     16h     ;tastaturinterrupt
timer_int equ   1ah     ;echtzeituhr
user_int equ    1ch     ;wird vom timer aufgerufen
dos     equ     21h
video   equ     10h     ;bildschirmausgabe
break_int equ   23h     ;reaktion auf break

fcb     equ     005ch
lparm   equ     0080h   ;parameterlaenge
resflag equ     0072h   ;reset flag
;======

;sucht den anfang des parameters, der beim programmaufruf in der
;kommandozeile mitgegeben wurde. es kann ein label fuer
;den gefunden-fall angegeben werden.
getparm macro  gefunden
       local   getparm1,getparm99
       mov     si,lparm        ;parameterlaenge nach cx
       xor     ch,ch
       mov     cl,[si]

getparm1:
       inc     si              ;;adresszeiger
       cmp     b es:[si],spc   ;;igno leading spaces
       ifb     <gefunden>
       jne     getparm99
       else
       jne     gefunden
       endif
       cmp     b es:[si],cr    ;;cr ist absolutes parameterende
       je      getparm99
       loop    getparm1
getparm99:                     ;;si zeigt auf 1.zeichen parameter oder cr
        endm

endif                           ;if1

if1                             ;macros nur im 1.durchlauf
int21   macro   intnr
        ifnb    <intnr>
        ldreg   ah,intnr
        endif
        int     dos
        endm

; Das Macro JMPS ist ab MASM 6.1 nicht mehr erforderlich, da
; ab MASM 6.1 der Assembler die JMP-Verzweigungen selbststaendig
; optimiert.
jmps    macro   to      ;;kurzer sprung
        jmp     short to
        endm

jmpc    macro   to      ;;langer sprung bei gesetztem carry
        local   weiter
        jnc     weiter
        jmp     to
weiter:
        endm


ret_far macro
        db      0cbh
endm

ret_near macro
        db      0c3h
endm

pushreg macro   liste
        irp     reg,<liste>
        push    reg
        endm
        endm

popreg  macro   liste
        irp     reg,<liste>
        pop     reg
        endm
        endm

dbl     macro   text    ;;definiert eine zeile
        ifb     <text>
        db      cr
        else
        db      text,cr
        endif
        endm

dbz     macro   text    ;;definiert einen string mit 0 am ende
        ifb     <text>
        db      0
        else
        db      text,0
        endif
        endm

setint  macro   dxa,intn        ;;dxa = dx address  intn = int #
        lea     dx,dxa          ;;get execution address
        mov     al,intn         ;:interrupt level
        int21   25h             ;;set interrupt vector request
        endm

getint  macro   intn            ;:intn = int #
        mov     al,intn         ;;interrupt level
        int21   35h             ;;get interrupt vector request es:bx
        endm

;=====
;bios macros  (rs232 and video)

;ldreg is an "inner" macro to specify a register or a literal value
;as the arameter to the macro. it loads the specified register with
;the source, but ;no code will be generated if the two parameters are
;the same.

ldreg   macro   destreg,source
        ifdif   <destreg>,<source>
        mov     destreg,source
        endif
        endm

;tstnset will compare the value of two fields, if they are equal the
;third parameter will be or'd into al.

tstnset macro   src1,src2,orval
        ifidn   <src1>,<src2>
        or      al,orval
        endif
        endm

;irs232 will generate a call to bios to initialize the rs232 port
;it allows the fields to be specified that initialize the port

irs232  macro   baudrate,parity,stopbits,datalen,linenum
        ldreg   dx,linenum
        sub     ax,ax
        tstnset baudrate,150,00100000b
        tstnset baudrate,300,01000000b
        tstnset baudrate,600,01100000b
        tstnset baudrate,1200,10000000b
        tstnset baudrate,2400,10100000b
        tstnset baudrate,4800,11000000b
        tstnset baudrate,9600,11100000b
;;      tstnset parity,none,00000000b
        tstnset parity,odd,00001000b
        tstnset parity,even,00011000b
;;      tstnset stopbits,1,00000000b
        tstnset stopbits,2,00000100b
        tstnset datalen,7,00000010b
        tstnset datalen,8,00000011b
        int     14h
        endm

;sendchr sends a character over the rs232 line.
sendchr macro   char,linenum
        ldreg   dx,linenum
        ldreg   al,char
        mov     ah,1
        int     14h
        endm

;recvchr receives a character from the rs232 line.
recvchr macro   linenum
        ldreg   dx,linenum
        mov     ah,2
        int     14h
        endm

;comstat gets the status of the rs232 line.

comstat macro   linenum
        ldreg   dx,linenum
        mov     ah,3
        int     14h
        endm
;======
;loescht den bildschirm (allerdings bei text immer 25-zeilig)
clrcrt  macro   ;;init screen
        getvid  ;;al=video modus
        xor     ah,ah
        int     video
        endm

;getvid rueckgabewerte: al=videomodus, ah=anzahl zeichen / zeile, bh=seite
getvid  macro   ;;get video mode
        mov     ah,0fh
        int     video
        endm

;setcurtype will set the cursor type.
setcurtype macro start,end
        ldreg   ch,start
        ldreg   cl,end
        mov     ah,1
        int     video
        endm

;setcurpos will set the cursor position. row und col sind 0-basierend
setcurpos macro row,col,crtpage
        ldreg   dh,row
        ldreg   dl,col
        ifb     <crtpage>
        sub     bh,bh
        else
        ldreg   bh,crtpage
        endif
        mov     ah,2    ;;bios function select
        int     video   ;;invoke bios cursor positioning
        endm

;setcurcol setzt den cursor in der aktuellen zeile auf die angegebene position
;siehe weiter unten im codeteil

;getcurpos return: dh=zeile, dl=spalte, ch=anfangszeile-, cl=endzeile-cursor
getcurpos macro crtpage
        ldreg   bh,crtpage
        mov     ah,3
        int     video
        endm

;scroll will scroll the page up or down
scroll  macro   direction,lines,ulcrow,ulccol,lrcrow,lrccol,attr
        ldreg   al,lines
        ldreg   ch,ulcrow
        ldreg   cl,ulccol
        ldreg   dh,lrcrow
        ldreg   dl,lrccol
        ldreg   bh,attr
        ifidn   <direction>,<up>
        mov     ah,6
        endif
        ifidn   <direction>,<down>
        mov     ah,7
        endif
        int     video
        endm
;======

print_str macro string  ;;zeichenkette ueber ansi.sys zum bildschirm
        ifdif   <dx>,<string>
        mov     dx,offset string        ;;address of string ending with $
        endif
        int21   9
        endm

get_str macro string    ;;zeichenkette von tastatur holen
        ifdif   <dx>,<string>
        mov     dx,offset string        ;;address zielbereich
        endif
        int21   0ah
        endm

;eingaben von ganzzahlen und strings nach buffer (z.b.lparm)
;die maximale eingabelaenge wird in bl mitgegeben

inkstr  macro   prompt,length,buffer    ;;stringeingabe mit prompt
        prstr   <prompt>
        mov     di,offset buffer
        mov     bl,length
        inc     bl              ;;pufferlaenge=eingabelaenge+1
        mov     [di],bl         ;;eingabe ohne prompt
        get_str buffer
        endm

;zu keyread und keyget:
;for extended ascii codes two doscalls will be required, the first will return
;00 in al the second will return the extended code in al

keyread macro           ;;eingabe eines zeichens mit anzeige
        int21   1
        endm

keyget  macro           ;;eingabe eines zeichens ohne anzeige
        int21   8
        endm

;handle-dateibehandlung
;======
fopen   macro   fname,acode     ;;open file
        ifdif   <dx>,<fname>
        mov     dx,offset fname ;;address of file name
        endif
        ldreg   al,acode        ;;access code 0=read, 1=write, 2=read and write
        int21   3dh             ;;returns fhandle in ax
        endm

fcrat   macro   fname,attrb     ;;create a file (eine alte datei
        ifdif   <dx>,<fname>    ;;gleichen namens wird dabei geloescht)
        mov     dx,offset fname ;;address of file name
        endif
        ldreg   cx,attrb        ;;attribute
        int21   3ch             ;;returns fhandle in ax
        endm

fwrit   macro   fhand,wbuff,count       ;;write to file
        ldreg   bx,fhand        ;;handle
        ldreg   cx,count        ;;attribute
        ifdif   <dx>,<wbuff>
        mov     dx,offset wbuff ;;address of write buffer
        endif
        int21   40h
        endm

fclose  macro   fhand           ;;close file
        ldreg   bx,fhand        ;;handle
        int21   3eh
        endm

fread   macro   fhand,rbuff,count       ;;read from file
        ldreg   bx,fhand        ;;handle
        ldreg   cx,count        ;;get this many byte(s)
        ifdif   <dx>,<rbuff>
        mov     dx,offset rbuff ;;address of read buffer
        endif
        int21   3fh
        endm
endif                           ;if1

;farbattribute  (fuer int video mit bh=0)
;(linkes nibble: hintergrund, rechtes nibble: vordergrund)
;bit 7 bestimmt blinken (1=ein, 0=aus)
;bit 3 bestimmt intensitaet (1=hell, 0=normal)

n_blck  equ     0       ;schwarz
n_blue  equ     1       ;blau
n_grn   equ     2       ;gruen
n_zyan  equ     3       ;zyan
n_red   equ     4       ;rot
n_viol  equ     5       ;violett
n_brwn  equ     6       ;braun
n_white equ     7       ;weiss
n_grey  equ     8       ;grau
n_lblue equ     9       ;hellblau
n_lgrn  equ     0ah     ;hellgruen
n_lzyan equ     0bh     ;hellzyan
n_lred  equ     0ch     ;hellrot
n_lviol equ     0dh     ;hellviolett
n_yell  equ     0eh     ;gelb
n_lwhite equ    0fh     ;hellweiss
;attribute (monochrom- und farbkarte mit schwarzem hintergrund))
ma_blinken equ  87h
ma_normal  equ  7
ma_hell    equ  0fh
ma_invers  equ  70h

;attribute (nur farbkarte mit blauem hintergrund)
a_blinken equ   16d*n_lblue+n_white
a_invers  equ   16d*n_white+n_blue
a_hell    equ   16d*n_blue+n_yell
a_normal  equ   16d*n_blue+n_white

if1                     ;macros nur im 1.durchlauf
;attribut-steuerzeichen fuer farbkarte
a_nm    macro   ;;normal
        db      escp,a_normal
        endm
a_he    macro   ;;hell
        db      escp,a_hell
        endm
a_re    macro   ;;reverse
        db      escp,a_invers
        endm
a_bl    macro   ;;blinken
        db      escp,a_blinken
        endm
endif                   ;if1
;Bei Verwendung mit dem MODEL SMALL endet hier der Teil fuer das
;DATA-Segment
;Der nachfolgende Teil gehoert dann in das CODE-Segment, weil er
;ausführbaren Programmcode erzeugt.
;------ beginn der codeerzeugung ------
;======
;unterprogrammsammlung
;======
;print message following call prmsg and ending with 0
prmsg:  pop     si
        push    ds              ;sichern ds
        push    cs
        pop     ds              ;ds zeigt nun auf das Codesegment
        call    printa
        pop     ds              ;nach Ausgabe ds wieder heretellen
        push    si      ;returnadr.
        ret

;druckt die mit si adressierte zeichenkette
;die zeichenkette darf keine steuerzeichen außer cr und attribute enthalten
;sie endet mit 0h
printa:
        push    ax
        cld

printa5:
        lodsb           ;zeichen
        cmp     al,escp  ;hiernach soll attribut folgen
        jne     printa_b9
        lodsb           ;attribut
        mov     b attr,al
        jmps    printa5 ;und string weiter einlesen

printa_b9:
        or      al,al   ;ob fertig ?
        jz      printa7 ;ja
        call    printchr
        jmps    printa5

printa7:
        pop     ax
        ret

;======
if1                     ;macros nur im 1.durchlauf
prstr   macro   texte    ;;print string
        call    prmsg
        dbz     <texte>
        endm
;======
print_crlf macro
        call    $print_crlf     ;;ausgabe cr lf
        endm            ;;zum bildschirm


print_chr macro char    ;;1 zeichen zum
        ifnb    <char>
        ldreg   al,char ;;bildschirm
        endif
        call    printchr
        endm
;======
;setcurcol setzt den cursor in der aktuellen zeile auf die
;angegebene position
setcurcol macro col
        ldreg   cl,col
        call    $setcurcol
        endm
endif                   ;if1

$setcurcol:
        push    cx      ;col (spalte)
        getvid          ;get video page
        push    bx
        getcurpos bh    ;get cursor position
        pop     bx
        pop     cx
        mov     dl,cl   ;col
        setcurpos dh,cl,bh      ;set cursor position
        ret

                ;======
;stringbehandlung
;fill: der ueber di adressierte speicher wird auf den in al
;mitgegebenen wert gesetzt. mit cld wird eine aufsteigende
;fuellrichtung erzwungen.
;======
if1
fill    macro   nach,byte,laenge
        ifdif   <di>,<nach>
        mov     di,offset nach
        endif
        ldreg   cx,laenge
        cld
        ldreg   al,<b byte>
        rep     stosb
        endm

;scans the string 'fld' for the byte 'data'
;for a length of 'lng'. if a match is found branch is taken to 'fnd'

scanbyte macro  fld,data,lng,fnd
        local   again
        ifdif   <di>,<fld>
        mov     di,offset fld
        endif
        ldreg   al, <b data>    ;;get byte to find
        ldreg   cx,lng          ;;set length
again   scasb
        jz      fnd             ;;branch if found
        loop    again           ;;keep going
        endm

;copy from addr to to addr for lng
copy    macro   from,to,lng
        ifdif   <si>,<from>
        mov     si,offset from
        endif
        ifdif   <di>,<to>
        mov     di,offset to
        endif
        ldreg   cx,lng          ;;set length
        rep     movsb           ;;copy the data
        endm
endif                           ;if1

        if      string$
;======
;stringbehandlung.
;ein string wird durch eine hex.0 am ende gekennzeichet.
;er kann max. 0ffffh bytes lang sein
;======
;vergleich der durch di u.si adressierten strings.
;laenge in cx
;return: zero-flag set if =, reset if <>
;       carry/borrow set if bereich [si]<[di]
;       di and si: adresse der beiden ersten ungleichen bytes falls <>
;======
;register: siehe comp

cmpstr: mov     al,[si]
        or      al,al
        jz      f39     ;ende 1.string
        cmp     al,[di]
        jnz     f40
        inc     si
        inc     di
        jmps    cmpstr

f39:    cmp     al,[di]
f40:    ret             ;fertig, moeglicherweise gleich


lenstr: xor     al,al   ;laenge des ueber di adressierten strings nach cx
        xor     cx,cx
f41:    cmp     al,[di]
        jz      f40     ;ende gefunden
        inc     cx
        inc     di
        jmps    f41
;======
;sucht im string [di] den kuerzeren string [si]. bei return:
;ax=relative startadr. im string [di], (1.byte=1)
;zero-flag gesetzt wenn nicht gefunden
;======
instrg:  push    di
        push    si
        call    lenstr  ;laenge string [di] nach dx
        mov     dx,cx
        mov     di,si
        call    lenstr  ;laenge string [si] nach cx
        pop     si
        pop     di
        or      cl,ch
        jz      f48     ;no match, if [si] empty

        mov     ax,dx   ;no match, if string[si] lonther than string [di]
        sub     ax,cx
        jnb     f42
        xor     ax,ax   ;no match
        ret

f42:    inc     ax      ;wurzel suchen
        mov     cx,ax   ;letzte vergl. stelle in di
        mov     dx,1    ;1.stelle di
        mov     al,[si]
f43:    cmp     al,[di]
        jz      f45     ;match 1.stelle
f44:    inc     dx      ;erhoehen pos.
        inc     di
        loop    f43     ;weiter suchen
        xor     ax,ax   ;kein match
        ret
f45:    push    si      ;vergl. rest des strings
        inc     si
        push    di
        push    ax
        call    f47
        pop     ax
        pop     di
        pop     si
        jnz     f44     ;no match

f46:    xor     ax,ax
        add     ax,dx   ;pos.nach a
        ret             ;mit ungesetzter zeroflag

f47:    mov     al,[si] ;wie cmpstr, aber laenge kann ungleich sein
        inc     si
        or      al,al
        jz      f48     ;gleich
        inc     di
        cmp     al,[di]
        jz      f47
f48:    ret             ;ungleich
;======
;movstr  string [si] nach string [di]
;======
movstr: mov     al,[si] ;string [si]->[di]
        inc     si
        mov     [di],al
        inc     di
        or      al,al   ;stringende ?
        jnz     movstr
        ret             ;stringende

;======
;bei den codewandlungen wird der string mit si adressiert.
;codwandlung string in upper case
;======
ucaseg: mov     dx,6120h        ;dh = 'a', dl = conversion factor
$convupper:
        mov     al,[si]
        or      al,al
        jz      $updone
        cmp     al,dh
        jb      $lu
        cmp     al,'z'
        ja      $lu
        sub     al,dl
        mov     [si],al
        jmps    $luraus
$lu:    cmp     al,'ä'
        jne     $luoe
        mov     [si],byte ptr 'Ä'
        jmps    $luraus
$luoe:  cmp     al,'ö'
        jne     $luue
        mov     [si],byte ptr 'Ö'
        jmps    $luraus
$luue:  cmp     al,'ü'
        jne     $luraus
        mov     [si],byte ptr 'Ü'
$luraus:
        inc     si
        jmps    $convupper
$updone:
        ret

;======
;codwandlung string in lower case
;======
lcaseg: mov     dx,4120h        ;dh = 'A', dl = conversion factor

$convlower:
        mov     al,[si]
        or      al,al
        jz      $lodone
        cmp     al,dh
        jb      $ul
        cmp     al,'Z'
        ja      $ul
        add     al,dl
        mov     [si],al
        jmps    $ulraus
$ul:    cmp     al,'Ä'
        jne     $uloe
        mov     [si],byte ptr 'ä'
        jmps    $ulraus
$uloe:  cmp     al,'Ö'
        jne     $ulue
        mov     [si],byte ptr 'ö'
        jmps    $ulraus
$ulue:  cmp     al,'Ü'
        jne     $ulraus
        mov     [si],byte ptr 'ü'

$ulraus:
        inc     si
        jmps    $convlower
$lodone:
        ret

        endif                   ;string$

;======
        if      prompt$
;eingabe der fortsetzungsaufforderung
prompt:  prstr   <'-',3eh>
        keyread
        ret

;eingabe j/n im dialog
;bei return: 3 wenn ctrl c, sonst j oder n
inkjn:  prstr   <' (J/N)',3eh>
        keyread

        cmp     al,3    ;ctrl c ?
        jne     $inkjn4
        ret
$inkjn4:
        and     al,5fh  ;wandlung in
        cmp     al,'Y'  ;grossschrift
        jne     $inkjn5
        mov     al,'j'
$inkjn5:
        cmp     al,'J'
        jne     $inkjn6
        ret
$inkjn6:
        cmp     al,'N'
        jne     inkjn   ;nicht jny, also neueingabe!
        ret

        endif                   ;prompt$
;======
       if      intasc$
;======
;konvertierungen speicherbereich mit ascii-zahl aus/nach dx:ax
;mit binaerzahl. alle zahlen im positiven bereich
;======
;erzeugt eine binaerzahl in dx:ax aus einer dezimalzahl im mit
;si adressierten speicherbereich. der speicherbereich muss mit
;einer dezimalzahl beginnen,
;space wird als ziffer 0 gewertet.
asc2int:
        xor     dx,dx           ;ziel (akku) loeschen
        xor     ax,ax
asc2int5:
        push    dx
        push    ax
        mov     bl,[si]
        cmp     bl,cr           ;war es ein return ?
        je      asc2int98       ;ja, dann eingabe beendet
        or      bl,bl           ;war es hexa 0 ?
        jz      asc2int98       ;ja, dann eingabe beenden

        pop     ax              ;zielakku *10
        pop     dx
        sal     ax,1            ;*2
        adc     dx,dx
        push    dx
        push    ax
        sal     ax,1            ;*4
        adc     dx,dx
        sal     ax,1            ;*8
        adc     dx,dx
        pop     bx              ;*10
        add     ax,bx
        pop     bx
        adc     dx,bx
        mov     bl,[si]         ;+neue ziffer
        cmp     bl,spc
        jnz     asc2int7        ;space wird als 0 gewertet
        mov     bl,'0'
asc2int7:
        sub     bl,48           ;zahl = ascii - 48
        jb      asc2int99       ;fertig, wenn nicht numerisch
        cmp     bl,10d
        jnb     asc2int99
        inc     si
        mov     bh,0
        add     ax,bx
        adc     dx,0
        jmps    asc2int5

asc2int98:
        pop     ax
        pop     dx
asc2int99:
        ret                     ;zahl in dx:ax

;======
int2asc:
        xchg    bp,dx           ;erzeugt aus binaerzahl in dx:ax
        mov     bx,0ah          ;dezimalzahl und baut sie rueckwaerts ab di
        mov     cl,30h  ;'0'    ;im speicher auf
                                ;verfahren: division mit 10d, rest -> speicher
int2asc2:
        or      bp,bp
        jz      int2asc4
        xchg    bp,ax
        xor     dx,dx
        div     bx
        xchg    bp,ax
        div     bx
        or      dl,cl
        mov     [di],dl
        dec     di
        jmps    int2asc2

int2asc4:
        xor     dx,dx           ;kurze zahl (dx war 0)
        div     bx
        or      dl,cl
        mov     [di],dl
        dec     di
        or      ax,ax
        jnz     int2asc4
        ret

        endif                   ;ifasc$
;======

        if      dump$
if1                     ;macros nur im 1.durchlauf

;testhilfe: minidump, aufruf mit: bx=adresse, cx=anzahl bytes
;angezeigt wird das Codesegment
mdump   macro   adresse,anzahl
        local   mdump11,mdump22,mdump33,mdump44,mdump99
        ldreg   <bx>,<adresse>
        ldreg   <cx>,anzahl
mdump11:                ;;ausgabe adresse
        call    mdump44


mdump22:                ;;ausgabe wert
        mov     al,bl
        and     al,0fh  ;;ausgabe neue zeile?
        jnz     mdump33 ;;nein
        call    mdump44 ;;ja


mdump33:                 ;;ausgabe hexa byte
        push    cx
        print_chr spc
        mov     al,cs:[bx]
        inc     bx
        call    hex_out
        pop     cx
        dec     cx
        jnz     mdump22
        print_crlf
        jmps    mdump99


mdump44:                ;;ausgabe neue zeile mit adresse
        push    cx
        print_crlf
        mov     al,bh
        call    hex_out
        mov     al,bl
        call    hex_out
        print_chr ':'
        pop     cx
        ret

mdump99:
        endm
endif                           ;if1

;testhilfe: registerdump, aufruf ohne parameter
rdump   macro
        local   rdump10,rdump11
        pushreg <ss,es,ds,cs,ax,bx,cx,dx,sp,bp,si,di>
 prstr   <cr,'di=  si=  bp=  sp=  dx=  cx=  bx=  ax=  cs=  ds=  es=  ss=',cr>

        mov     cx,12  ;;anzahl anzuzeigender register

rdump10:
        pop     ax
        xchg    al,ah        ;;register ax hexadezimal zum bildschirm
        push    ax
        call    hex_out
        pop     ax
        xchg    al,ah
        call    hex_out
        print_chr spc
        loop    rdump10

        print_crlf           ;;leerzeile wenn fertig

        endm
        endif   ;dump$
;======


;ausgabe 8 bit zahl (in al) in hexa
hex_out: push   ax
        shr     al,1
        shr     al,1
        shr     al,1
        shr     al,1
        call    conv
        pop     ax
conv:   and     al,0fh
        daa
        add     al,0f0h
        adc     al,40h

;ausgabe zeichen in al zum bildschirm
printchr:
        cmp     al,cr   ;cr?
        je      printchr8
        cmp     al,tab
        je      printtab
printchr1:
        push    cx
        push    bx
        mov     cx,1    ;1 zeichen
        mov     ah,9
        xor     bh,bh
        mov     bl,a_normal     ;attribut wird modifiziert. siehe
attr    equ     $-1             ;hinweis zum MODELL SMALL am seitenanfang!
        int     video   ;zeichenausgabe
        mov     ah,3    ;cursorposition ermitteln
        int     video
        inc     dl      ;x-position um 1 erhoehen
        mov     ah,2
        int     video
        pop     bx
        pop     cx
        ret

$print_crlf:
        mov     al,cr

printchr8:              ;ausgabe crlf
        mov     ah,0eh  ;funktion tty-ausgabe
        int     video
        mov     ax,0e00h+lf
        int     video
        ret

printtab:               ;spaces bis tabulator
        mov     al,spc
        call    printchr1
        mov     ah,3    ;cursorposition ermitteln
        int     video
        and     dl,7
        cmp     dl,0
        jnz     printtab
        ret

;programmbeendungen
ret0:   xor     al,al   ;ausgang fuer fehlerfrei
        jmps    raus

ret1:   mov     al,1
        jmps    raus

ret3:   mov     al,3

;programmende
raus:
        int21   4ch
Letztes Upload: 24.03.2023 um 11:35:16 • Impressum und Datenschutzerklärung