[BACK]Return to hrcgraph.asm CVS log [TXT][DIR] Up to [local] / OpenXM_contrib / gnuplot

Annotation of OpenXM_contrib/gnuplot/hrcgraph.asm, Revision 1.1.1.1

1.1       maekawa     1: TITLE  Hercules graphics module
                      2:
                      3: ;      Michael Gordon - 8-Dec-86
                      4: ;
                      5: ; Certain routines were taken from the Hercules BIOS of        Dave Tutelman - 8/86
                      6: ; Others came from pcgraph.asm included in GNUPLOT by Colin Kelley
                      7: ;
                      8: ; modified slightly by Colin Kelley - 22-Dec-86
                      9: ;      added header.mac, parameterized declarations
                     10: ; added dgroup: in HVmodem to reach HCh_Parms and HGr_Parms - 30-Jan-87
                     11: ; modified by Russell Lang 3 Jun 1988
                     12: ;      added H_init
                     13:
                     14: include header.mac
                     15:
                     16: if1
                     17: include lineproc.mac
                     18: endif
                     19:
                     20:
                     21: GPg1_Base equ 0B800h   ; Graphics page 1 base address
                     22:
                     23: _text  segment
                     24:
                     25:        public _H_line, _H_color, _H_mask, _HVmode, _H_puts
                     26:        public _H_init
                     27:
                     28: HCfg_Switch equ        03BFH   ; Configuration Switch - software switch
                     29:                        ; to select graphics card memory map
                     30:
                     31: beginproc _H_init
                     32:        mov al, 03H     ; allow graphics in b8000:bffff
                     33:        mov dx, HCfg_Switch
                     34:        out dx, al
                     35:        ret
                     36: _H_init endp
                     37:
                     38: hpixel proc near
                     39:        ror word ptr bmask,1
                     40:        jc cont
                     41:        ret
                     42: cont:
                     43:        push ax
                     44:        push bx
                     45:        push cx
                     46:        push dx
                     47:        push si
                     48:        mov cx,ax               ; x
                     49:        mov dx,bx               ; y
                     50: ;
                     51: ; [couldn't this be done faster with a lookup table? -cdk]
                     52: ;
                     53:        ; first compute the address of byte to be modified
                     54:        ; = 90*[row/4] + [col/8] + 2^D*[row/4] + 2^F*page
                     55:        mov     bh,cl           ; col (low order) in BH
                     56:        mov     bl,dl           ; row (low order) in BL
                     57:        and     bx,0703H        ; mask the col & row remainders
                     58: IFDEF iAPX286
                     59:        shr     cx,3            ; col / 8
                     60:        shr     dx,2            ; row / 4
                     61:        mov     al,90
                     62:        mul     dx              ; AX = 90*[ row/4 ]
                     63:        add     ax,cx           ;  ... + col/8
                     64:        shl     bl,5            ; align row remainder
                     65: ELSE                   ; same as above, obscure but fast for 8086
                     66:        shr     cx,1            ; divide col by 8
                     67:        shr     cx,1
                     68:        shr     cx,1
                     69:        shr     dx,1            ; divide row by 4
                     70:        shr     dx,1
                     71:        shl     dx,1            ; begin fast multiply by 90 (1011010 B)
                     72:        mov     ax,dx
                     73:        shl     dx,1
                     74:        shl     dx,1
                     75:        add     ax,dx
                     76:        shl     dx,1
                     77:        add     ax,dx
                     78:        shl     dx,1
                     79:        shl     dx,1
                     80:        add     ax,dx           ; end fast multiply by 90
                     81:        add     ax,cx           ; add on the col/8
                     82:        shl     bl,1            ; align row remainder
                     83:        shl     bl,1
                     84:        shl     bl,1
                     85:        shl     bl,1
                     86:        shl     bl,1
                     87: ENDIF
                     88:        add     ah,bl           ; use aligned row remainder
                     89: end_adr_calc:                  ; address of byte is now in AX
                     90:        mov     dx,GPg1_Base    ; base of pixel display to DX
                     91:        mov     es,dx           ; ...and thence to segment reg
                     92:        mov     si,ax           ; address of byte w/ pixel to index reg
                     93:        mov     cl,bh           ; bit addr in byte
                     94:        mov     al,80H          ; '1000 0000' in AL
                     95:        shr     al,cl           ; shift mask to line up with bit to read/write
                     96: set_pix:                       ; set the pixel
                     97:        or      es:[si],al      ; or the mask with the right byte
                     98:        pop si
                     99:        pop dx
                    100:        pop cx
                    101:        pop bx
                    102:        pop ax
                    103:        ret
                    104: hpixel endp
                    105:
                    106: lineproc _H_line, hpixel
                    107:
                    108: ;
                    109: ; clear - clear page 1 of the screen buffer to zero (effectively, blank
                    110: ;      the screen)
                    111: ;
                    112: clear   proc near
                    113:        push es
                    114:        push ax
                    115:        push cx
                    116:        push di
                    117:        mov ax, GPg1_Base
                    118:        mov es, ax
                    119:        xor di, di
                    120:        mov cx, 4000h
                    121:        xor ax, ax
                    122:        cld
                    123:        rep stosw                       ; zero out screen page
                    124:        pop di
                    125:        pop cx
                    126:        pop ax
                    127:        pop es
                    128:        ret
                    129: clear  endp
                    130:
                    131: beginproc _H_color
                    132:        push bp
                    133:        mov bp,sp
                    134:        mov al,[bp+X]                   ; color
                    135:        mov byte ptr color,al
                    136:        pop bp
                    137:        ret
                    138: _H_color endp
                    139:
                    140: beginproc _H_mask
                    141:        push bp
                    142:        mov bp,sp
                    143:        mov ax,[bp+X]                   ; mask
                    144:        mov word ptr bmask,ax
                    145:        pop bp
                    146:        ret
                    147: _H_mask endp
                    148:
                    149: HCtrl_Port     equ     03B8H   ; Hercules 6845 control port IO addr
                    150: HIndx_Port     equ     03B4H   ; Hercules 6845 index port IO addr
                    151: HScrn_Enable   equ     008h    ; Control port bit to enable video
                    152: HCh_Mode       equ     020h    ; Character output mode
                    153: HGr_Mode       equ     082h    ; Graphics output mode page 1
                    154:
                    155: parm_count equ 12
                    156:
                    157: beginproc _HVmode
                    158:        push bp
                    159:        mov bp, sp
                    160:        push si
                    161:        mov ax, [bp+X]
                    162:        or ah, al
                    163:        mov al, HCh_Mode                ; Assume character mode is wanted
                    164:        mov si, offset dgroup:HCh_Parms
                    165:        cmp ah, 0                       ; nonzero means switch to graphics
                    166:        jz vmode_ok
                    167:        call near ptr clear             ; clear the graphics page
                    168:        mov al, HGr_Mode
                    169:        mov si, offset dgroup:HGr_Parms
                    170: vmode_ok:
                    171:        mov dx, HCtrl_Port
                    172:        out dx, al                      ; Set Hercules board to proper mode
                    173:        call near ptr setParms          ; Set the 6845 parameters
                    174:        or al, HScrn_Enable             ; Enable the video output
                    175:        out dx, al
                    176:        pop si
                    177:        pop bp
                    178:        ret
                    179: _HVmode        endp
                    180:
                    181: setParms proc near             ; Send 6845 parms to Hercules board
                    182:        push ax
                    183:        push dx
                    184:        push si
                    185:        mov dx, HIndx_Port      ; Index port addr -> DX
                    186:        mov ah, 0               ; 0 -> parameter counter
                    187: sp_loop:
                    188:        mov al, ah
                    189:        out dx, al              ; output to 6845 addr register
                    190:        inc dx                  ; next output to data register
                    191:        mov al, [si]            ; next control byte -> al
                    192:        inc si
                    193:        out dx, al              ; output control byte
                    194:        dec dx                  ; 6845 index addr -> dx
                    195:        inc ah                  ; bump addr
                    196:        cmp ah, parm_count
                    197:        jnz sp_loop
                    198:        pop si
                    199:        pop dx
                    200:        pop ax
                    201:        ret
                    202: setParms endp
                    203:
                    204: ; H_puts - print text in graphics mode
                    205: ;
                    206: ;      cx = row
                    207: ;      bx = column
                    208: ;      si = address of string (null terminated) to print
                    209:
                    210: beginproc _H_puts
                    211:        push bp
                    212:        mov bp, sp
                    213:        push si
                    214:        push ds
                    215:        mov si, [bp+X]                  ; string offset
                    216:
                    217: ifdef LARGE_DATA
                    218:        mov ds, [bp+X+2]                ; string segment
                    219:        mov cx, [bp+X+4]                ; row
                    220:        mov bx, [bp+X+6]                ; col
                    221: else
                    222:        mov cx, [bp+X+2]                ; row
                    223:        mov bx, [bp+X+4]                ; col
                    224: endif
                    225:
                    226: ploop: lodsb                           ; get next char
                    227:        or      al, al                  ; end of display?
                    228:        je      pdone
                    229:        call near ptr display
                    230:        inc     bx                      ; bump to next column
                    231:        jmp     ploop
                    232: pdone: pop ds
                    233:        pop si
                    234:        pop bp
                    235:        ret
                    236: _H_puts        endp
                    237:
                    238: ;
                    239: ; display - output an 8x8 character from the IBM ROM to the Herc board
                    240: ;
                    241: ; AX = char, BX = column (0-89), CX = row(0-42)  ** all preserved **
                    242: ;
                    243: CON8   db      8
                    244: CON180 db      180
                    245: IBMROM equ     0F000h
                    246: CHARTAB        equ     0FA6Eh
                    247:
                    248: display        proc near
                    249:        push    ds                      ; save the lot
                    250:        push    es
                    251:        push    ax
                    252:        push    bx
                    253:        push    cx
                    254:        push    dx
                    255:        push    si
                    256:        push    di
                    257:
                    258: ; setup ds -> IBM ROM, and si -> index into IBM ROM character table located
                    259: ;      at 0fa6eh in the ROM
                    260:
                    261:        and     ax, 07fh
                    262:        mul     cs:CON8                 ; mult by 8 bytes of table per char
                    263:        mov     si, ax
                    264:        mov     ax, IBMROM
                    265:        mov     ds, ax
                    266:        assume  ds:nothing
                    267:        add     si, CHARTAB             ; add offset of character table
                    268:
                    269: ; compute index into Hercules screen memory for scan line 0.  The remaining
                    270: ;      seven scan lines are all at fixed offsets from the first.
                    271: ;
                    272: ;      Since graphics mode treats the screen as sets of 16x4 "characters",
                    273: ;      we need to map an 8x8 real character onto the front or back of
                    274: ;      a pair of graphics "characters".  The first four scan lines of our
                    275: ;      8x8 character will map to the top graphics "character", and the second
                    276: ;      four scan lines map to the graphics character on the "line" (4 scan
                    277: ;      lines high) below it.
                    278: ;
                    279: ;      For some exotic hardware reason (probably speed), all scan line 0
                    280: ;      bits (i.e. every fourth scan line) are stored in memory locations
                    281: ;      0-2000h in the screen buffer.  All scan line 1 bits are stored
                    282: ;      2000h-4000h.  Within these banks, they are stored by rows.  The first
                    283: ;      scan line on the screen (scan line 0 of graphics character row 0)
                    284: ;      is the first 45 words of memory in the screen buffer.  The next 45
                    285: ;      words are the first scan line graphics row 1, and since graphics
                    286: ;      "characters" are 4 bits high, this second scan line is physically
                    287: ;      the fifth scan line displayed on the screen.
                    288: ;
                    289: ;      SO, to display an 8x8 character, the 1st and 5th rows of dots are
                    290: ;      both scan line 0 of the graphics "character", the 2nd and 6th are
                    291: ;      scan line 1, and so on.
                    292: ;
                    293: ;      The column (0-89) tells which byte in a scan line we need to load.
                    294: ;      Since it takes two rows of graphics characters to hold one row of
                    295: ;      our characters, column+90 is a index to scan line 4 rows of pixels
                    296: ;      higher (n+4).  Thus 180 bytes of screen memory in any bank (0h, 2000h,
                    297: ;      4000h, 6000h) represent a row of 8x8 characters.
                    298: ;
                    299: ;      The starting location in screen memory for the first scan line of
                    300: ;      a character to be displayed will be:    (row*180)+column
                    301: ;      The 5th scan line will be at:           (row*180)+column+90
                    302: ;
                    303: ;      The second and 6th scan lines will be at the above offsets plus
                    304: ;      the bank offset of 2000h.  The third and 7th, add 4000h and finally
                    305: ;      the 4th and 8th, add 6000h.
                    306: ;
                    307:        mov     ax, GPg1_Base
                    308:        mov     es, ax                  ; es = hercules page 0
                    309:        mov     ax, cx                  ; get row
                    310:        mul     cs:CON180               ; mult by 180(10)
                    311:        mov     di, ax                  ; di = index reg
                    312:        cld                             ; insure right direction
                    313:
                    314: ;output 8 segments of character to video ram
                    315:
                    316:        lodsb                           ; line 0
                    317:        mov     es:[di+bx], al
                    318:        lodsb
                    319:        mov     es:[di+bx+2000h], al    ; line 1
                    320:        lodsb
                    321:        mov     es:[di+bx+4000h], al    ; line 2
                    322:        lodsb
                    323:        mov     es:[di+bx+6000h], al    ; line 3
                    324:        lodsb
                    325:        mov     es:[di+bx+90], al       ; line 4
                    326:        lodsb
                    327:        mov     es:[di+bx+2000h+90], al ; line 5
                    328:        lodsb
                    329:        mov     es:[di+bx+4000h+90], al ; line 6
                    330:        lodsb
                    331:        mov     es:[di+bx+6000h+90], al ; line 7
                    332:
                    333:        pop     di
                    334:        pop     si
                    335:        pop     dx
                    336:        pop     cx
                    337:        pop     bx
                    338:        pop     ax
                    339:        pop     es
                    340:        pop     ds
                    341:        ret
                    342: display        endp
                    343:
                    344: _text  ends
                    345:
                    346: _data  segment
                    347: bmask  dw -1
                    348: color  db 1
                    349: _data  ends
                    350:
                    351: const  segment
                    352: HCh_Parms db   61H, 50H, 52H, 0FH, 19H, 06H, 19H, 19H, 02H, 0DH, 0BH, 0CH
                    353: HGr_Parms db   35H, 2DH, 2EH, 07H, 5BH, 02H, 57H, 57H, 02H, 03H, 00H, 00H
                    354: const  ends
                    355:
                    356:        end
                    357:
                    358:

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>