Changeset 4f508e6 in buchla-68k for vlib


Ignore:
Timestamp:
07/01/2017 02:34:46 PM (7 years ago)
Author:
Thomas Lopatic <thomas@…>
Branches:
master
Children:
08e1da1
Parents:
f40a309
Message:

Converted assembly language files.

Location:
vlib
Files:
18 edited

Legend:

Unmodified
Added
Removed
  • vlib/acctrl.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * acctrl.s -- VSDD access table control functions
    3 * Version 6 -- 1987-04-13 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       objclr(obj)
    8 *       unsigned int obj;
    9 *
    10 *               Clear bits in access table for object 'obj'.
    11 *               Disables object 'obj'.
    12 *
    13 *       objoff(obj, line, num)
    14 *       unsigned int obj, line, num;
    15 *
    16 *               Disable object obj at line thru line+num.
    17 *
    18 *       objon(obj, line, num)
    19 *       unsigned int obj, line, num;
    20 *
    21 *               Enable object obj at line thru line+num.
    22 *
    23 *
    24 *       Assumes VSDD is looking at bank 0.
    25 *       Assumes a screen height of 350 lines.
    26 *       No error checks are done, so beware.
    27 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| acctrl.s -- VSDD access table control functions
     3| Version 6 -- 1987-04-13 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       objclr(obj)
     8|       unsigned int obj;
     9
     10|               Clear bits in access table for object 'obj'.
     11|               Disables object 'obj'.
     12
     13|       objoff(obj, line, num)
     14|       unsigned int obj, line, num;
     15
     16|               Disable object obj at line thru line+num.
     17
     18|       objon(obj, line, num)
     19|       unsigned int obj, line, num;
     20
     21|               Enable object obj at line thru line+num.
     22
     23
     24|       Assumes VSDD is looking at bank 0.
     25|       Assumes a screen height of 350 lines.
     26|       No error checks are done, so beware.
     27| ------------------------------------------------------------------------------
    2828                .text
    29 *
     29
    3030                .xdef   _objclr,_objoff,_objon
    31 *
     31
    3232                .xref   _v_actab
    33 *
    34 SCSIZE          .equ    350             * Screen height
    35 *
    36 OBJ             .equ    8               * Object number argument offset
    37 LINE            .equ    10              * Beginning line argument offset
    38 NUM             .equ    12              * Object height argument offset
    39 * ------------------------------------------------------------------------------
     33
     34SCSIZE          =       350             | Screen height
     35
     36OBJ             =       8               | Object number argument offset
     37LINE            =       10              | Beginning line argument offset
     38NUM             =       12              | Object height argument offset
     39| ------------------------------------------------------------------------------
    4040                .page
    41 * ------------------------------------------------------------------------------
    42 *
    43 *       objclr(obj)
    44 *       unsigned int obj;
    45 *
    46 *               Disables object obj in access table by turning on
    47 *               its bit in all words of the access table.
    48 * ------------------------------------------------------------------------------
    49 _objclr:        link    a6,#0           * Link stack frames
    50                 move.w  OBJ(a6),d1      * Get object bit number in d1
    51                 lea     _v_actab,a0     * Get base of object table in a0
    52                 move.w  #SCSIZE-1,d2    * Put line count in d2
    53 *
    54 objclr1:        move.w  (a0),d0         * Get access table word
    55                 bset.l  d1,d0           * Set the bit
    56                 move.w  d0,(a0)+        * Update word in access table
    57                 dbf     d2,objclr1      * Loop until done
    58 *
    59                 unlk    a6              * Unlink stack frame
    60                 rts                     * Return to caller
    61 *
     41| ------------------------------------------------------------------------------
     42
     43|       objclr(obj)
     44|       unsigned int obj;
     45
     46|               Disables object obj in access table by turning on
     47|               its bit in all words of the access table.
     48| ------------------------------------------------------------------------------
     49_objclr:        link    a6,#0           | Link stack frames
     50                move.w  OBJ(a6),d1      | Get object bit number in d1
     51                lea     _v_actab,a0     | Get base of object table in a0
     52                move.w  #SCSIZE-1,d2    | Put line count in d2
     53
     54objclr1:        move.w  (a0),d0         | Get access table word
     55                bset.l  d1,d0           | Set the bit
     56                move.w  d0,(a0)+        | Update word in access table
     57                dbf     d2,objclr1      | Loop until done
     58
     59                unlk    a6              | Unlink stack frame
     60                rts                     | Return to caller
     61
    6262                .page
    63 * ------------------------------------------------------------------------------
    64 *       objoff(obj, line, num)
    65 *       unsigned int obj, line, num;
    66 *
    67 *               Turn on access table bits for object 'obj' at
    68 *               lines 'line' through 'line'+'num'.  Disables the object.
    69 *               Assumes object bits were set at those locations.
    70 * ------------------------------------------------------------------------------
    71 _objoff:        link    a6,#0           * Link stack frames
    72                 move.w  OBJ(a6),d1      * Get object bit number into d1
    73                 move.w  LINE(a6),d2     * Get top line number
    74                 add.w   d2,d2           * Convert to word offset
    75                 lea     _v_actab,a0     * Get base address of access table
    76                 move.w  0(a0,d2),d0     * Get top line access word
    77                 bset.l  d1,d0           * Set object bit
    78                 move.w  d0,0(a0,d2)     * Update word in access table
    79                 tst.w   NUM(a6)         * Number of lines = 0 ?
    80                 beq     objoff1         * Done if so
    81 *
    82                 move.w  NUM(a6),d2      * Get object depth
    83                 add.w   LINE(a6),d2     * Add to top line number
    84                 cmpi.w  #SCSIZE,d2      * Bottom line >= screen height ?
    85                 bge     objoff1         * Done if so
    86 *
    87                 add.w   d2,d2           * Convert to word offset
    88                 move.w  0(a0,d2),d0     * Get bottom line access word
    89                 bset.l  d1,d0           * Set object bit
    90                 move.w  d0,0(a0,d2)     * Update word in access table
    91 *
    92 objoff1:        unlk    a6              * Unlink stack frame
    93                 rts                     * Return to caller
    94 *
     63| ------------------------------------------------------------------------------
     64|       objoff(obj, line, num)
     65|       unsigned int obj, line, num;
     66
     67|               Turn on access table bits for object 'obj' at
     68|               lines 'line' through 'line'+'num'.  Disables the object.
     69|               Assumes object bits were set at those locations.
     70| ------------------------------------------------------------------------------
     71_objoff:        link    a6,#0           | Link stack frames
     72                move.w  OBJ(a6),d1      | Get object bit number into d1
     73                move.w  LINE(a6),d2     | Get top line number
     74                add.w   d2,d2           | Convert to word offset
     75                lea     _v_actab,a0     | Get base address of access table
     76                move.w  0(a0,d2),d0     | Get top line access word
     77                bset.l  d1,d0           | Set object bit
     78                move.w  d0,0(a0,d2)     | Update word in access table
     79                tst.w   NUM(a6)         | Number of lines = 0 ?
     80                beq     objoff1         | Done if so
     81
     82                move.w  NUM(a6),d2      | Get object depth
     83                add.w   LINE(a6),d2     | Add to top line number
     84                cmpi.w  #SCSIZE,d2      | Bottom line >= screen height ?
     85                bge     objoff1         | Done if so
     86
     87                add.w   d2,d2           | Convert to word offset
     88                move.w  0(a0,d2),d0     | Get bottom line access word
     89                bset.l  d1,d0           | Set object bit
     90                move.w  d0,0(a0,d2)     | Update word in access table
     91
     92objoff1:        unlk    a6              | Unlink stack frame
     93                rts                     | Return to caller
     94
    9595                .page
    96 * ------------------------------------------------------------------------------
    97 *       objon(obj, line, num)
    98 *       unsigned int obj, line, num;
    99 *
    100 *               Turn off access table bits for object 'obj'
    101 *               at 'line' thru 'line'+'num'.  Enables the object.
    102 * ------------------------------------------------------------------------------
    103 _objon:         link    a6,#0           * Link stack frames
    104                 move.w  OBJ(a6),d1      * Get object bit number into d1
    105                 move.w  LINE(a6),d2     * Get top line number
    106                 add.w   d2,d2           * Convert to word offset
    107                 lea     _v_actab,a0     * Get base address of access table
    108                 move.w  0(a0,d2),d0     * Get top line access word
    109                 bclr.l  d1,d0           * Clear object bit
    110                 move.w  d0,0(a0,d2)     * Update word in access table
    111                 tst.w   NUM(a6)         * Number of lines = 0 ?
    112                 beq     objon1          * Done if so
    113 *
    114                 move.w  NUM(a6),d2      * Get object depth
    115                 add.w   LINE(a6),d2     * Add top line number
    116                 cmpi.w  #SCSIZE,d2      * Bottom line >= screen height ?
    117                 bge     objon1          * Done if so
    118 *
    119                 add.w   d2,d2           * Convert to word offset
    120                 move.w  0(a0,d2),d0     * Get bottom line access word
    121                 bclr.l  d1,d0           * Clear object bit
    122                 move.w  d0,0(a0,d2)     * Update word in access table
    123 *
    124 objon1:         unlk    a6              * Unlink stack frame
    125                 rts                     * Return to caller
    126 *
     96| ------------------------------------------------------------------------------
     97|       objon(obj, line, num)
     98|       unsigned int obj, line, num;
     99
     100|               Turn off access table bits for object 'obj'
     101|               at 'line' thru 'line'+'num'.  Enables the object.
     102| ------------------------------------------------------------------------------
     103_objon:         link    a6,#0           | Link stack frames
     104                move.w  OBJ(a6),d1      | Get object bit number into d1
     105                move.w  LINE(a6),d2     | Get top line number
     106                add.w   d2,d2           | Convert to word offset
     107                lea     _v_actab,a0     | Get base address of access table
     108                move.w  0(a0,d2),d0     | Get top line access word
     109                bclr.l  d1,d0           | Clear object bit
     110                move.w  d0,0(a0,d2)     | Update word in access table
     111                tst.w   NUM(a6)         | Number of lines = 0 ?
     112                beq     objon1          | Done if so
     113
     114                move.w  NUM(a6),d2      | Get object depth
     115                add.w   LINE(a6),d2     | Add top line number
     116                cmpi.w  #SCSIZE,d2      | Bottom line >= screen height ?
     117                bge     objon1          | Done if so
     118
     119                add.w   d2,d2           | Convert to word offset
     120                move.w  0(a0,d2),d0     | Get bottom line access word
     121                bclr.l  d1,d0           | Clear object bit
     122                move.w  d0,0(a0,d2)     | Update word in access table
     123
     124objon1:         unlk    a6              | Unlink stack frame
     125                rts                     | Return to caller
     126
    127127                .end
  • vlib/glcplot.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * glcplot.s -- plot a pixel on the LCD display
    3 * Version 2 -- 1987-04-23 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 *
    6 *       GLCplot(x, y, val)
    7 *       unsigned x, y, val);
    8 *
    9 *               Plot a pixel at ('x', 'y') using lcdbase as the plane address
    10 *               in GLC RAM.  If 'val' is zero, the pixel is cleared,
    11 *               otherwise the pixel is cleared.  No error checking is done.
    12 *               Limits:  0 LE x LE 511,  0 LE y LE 63.
    13 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| glcplot.s -- plot a pixel on the LCD display
     3| Version 2 -- 1987-04-23 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5
     6|       GLCplot(x, y, val)
     7|       unsigned x, y, val);
     8
     9|               Plot a pixel at ('x', 'y') using lcdbase as the plane address
     10|               in GLC RAM.  If 'val' is zero, the pixel is cleared,
     11|               otherwise the pixel is cleared.  No error checking is done.
     12|               Limits:  0 LE x LE 511,  0 LE y LE 63.
     13| ------------------------------------------------------------------------------
    1414                .text
    15 *
     15
    1616                .xdef   _GLCplot
    1717                .xref   _lcd_a0,_lcd_a1,_lcdbase
    18 *
    19 XLOC            .equ    8                       * 'x' parameter offset
    20 YLOC            .equ    10                      * 'y' parameter offset
    21 VAL             .equ    12                      * 'val' parameter offset
    22 *
    23 G_CRSWR         .equ    $46                     * GLC set cursor command
    24 G_MWRITE        .equ    $42                     * GLC write command
    25 G_MREAD         .equ    $43                     * GLC read command
    26 *
     18
     19XLOC            =       8                       | 'x' parameter offset
     20YLOC            =       10                      | 'y' parameter offset
     21VAL             =       12                      | 'val' parameter offset
     22
     23G_CRSWR         =       0x46                    | GLC set cursor command
     24G_MWRITE        =       0x42                    | GLC write command
     25G_MREAD         =       0x43                    | GLC read command
     26
    2727                .page
    28 *
    29 _GLCplot:       link    a6,#0                   * Link stack frames
    30                 moveq   #63,d0                  * d0 = (63-y) * 85
    31                 sub.w   YLOC(a6),d0             * ...
    32                 mulu    #85,d0                  * ...
    33                 clr.l   d1                      * d1 = x/6
    34                 move.w  XLOC(a6),d1             * ...
    35                 divu    #6,d1                   * ...
    36                 add.w   d1,d0                   * d0 = (63-y)*85 + (x/6)
    37                 swap    d1                      * d2 = 7 - (x%6) % 8
    38                 moveq   #7,d2                   * ...
    39                 sub.w   d1,d2                   * ...
    40                 andi.w  #7,d2                   * ...
    41                 lsr.w   #3,d1                   * d1 = (x%6) / 8
    42                 add.w   d1,d0                   * d0 = cursor address
    43                 add.w   _lcdbase,d0             * ...
    44                 move.w  d0,d1                   * d1 = cursor address, too
    45                 move.b  #G_CRSWR,_lcd_a1        * Send cursor address to GLC
    46                 move.b  d0,_lcd_a0              * ...
    47                 lsr.w   #8,d0                   * ...
    48                 move.b  d0,_lcd_a0              * ...
    49                 move.b  #G_MREAD,_lcd_a1        * Read old pixel byte
    50                 move.b  _lcd_a1,d0              * ... into d0
    51                 tst.w   VAL(a6)                 * Check val for zero
    52                 beq     glcplt1                 * Jump if val EQ 0
    53 *
    54                 bset    d2,d0                   * Set the pixel to 1
    55                 bra     glcplt2                 * Go write pixel to GLC
    56 *
    57 glcplt1:        bclr    d2,d0                   * Clear the pixel to 0
    58 *
    59 glcplt2:        move.b  #G_CRSWR,_lcd_a1        * Send cursor address to GLC
    60                 move.b  d1,_lcd_a0              * ...
    61                 lsr.w   #8,d1                   * ...
    62                 move.b  d1,_lcd_a0              * ...
    63                 move.b  #G_MWRITE,_lcd_a1       * Setup GLC to write pixel
    64                 move.b  d0,_lcd_a0              * Write pixel
    65                 unlk    a6                      * Unlink stack frames
    66                 rts                             * Return to caller
    67 *
     28
     29_GLCplot:       link    a6,#0                   | Link stack frames
     30                moveq   #63,d0                  | d0 = (63-y) | 85
     31                sub.w   YLOC(a6),d0             | ...
     32                mulu    #85,d0                  | ...
     33                clr.l   d1                      | d1 = x/6
     34                move.w  XLOC(a6),d1             | ...
     35                divu    #6,d1                   | ...
     36                add.w   d1,d0                   | d0 = (63-y)|85 + (x/6)
     37                swap    d1                      | d2 = 7 - (x%6) % 8
     38                moveq   #7,d2                   | ...
     39                sub.w   d1,d2                   | ...
     40                andi.w  #7,d2                   | ...
     41                lsr.w   #3,d1                   | d1 = (x%6) / 8
     42                add.w   d1,d0                   | d0 = cursor address
     43                add.w   _lcdbase,d0             | ...
     44                move.w  d0,d1                   | d1 = cursor address, too
     45                move.b  #G_CRSWR,_lcd_a1        | Send cursor address to GLC
     46                move.b  d0,_lcd_a0              | ...
     47                lsr.w   #8,d0                   | ...
     48                move.b  d0,_lcd_a0              | ...
     49                move.b  #G_MREAD,_lcd_a1        | Read old pixel byte
     50                move.b  _lcd_a1,d0              | ... into d0
     51                tst.w   VAL(a6)                 | Check val for zero
     52                beq     glcplt1                 | Jump if val EQ 0
     53
     54                bset    d2,d0                   | Set the pixel to 1
     55                bra     glcplt2                 | Go write pixel to GLC
     56
     57glcplt1:        bclr    d2,d0                   | Clear the pixel to 0
     58
     59glcplt2:        move.b  #G_CRSWR,_lcd_a1        | Send cursor address to GLC
     60                move.b  d1,_lcd_a0              | ...
     61                lsr.w   #8,d1                   | ...
     62                move.b  d1,_lcd_a0              | ...
     63                move.b  #G_MWRITE,_lcd_a1       | Setup GLC to write pixel
     64                move.b  d0,_lcd_a0              | Write pixel
     65                unlk    a6                      | Unlink stack frames
     66                rts                             | Return to caller
     67
    6868                .end
  • vlib/tsplot4.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * tsplot4.s -- output characters to a 4-bit / pixel graphics window
    3 *    with variable vertical pitch
    4 * Version 1 -- 1987-08-04 -- D.N. Lynx Crowe
    5 * (c) Copyright 1987 -- D.N. Lynx Crowe
    6 * ------------------------------------------------------------------------------
    7 *
    8 *       tsplot4(obase, nw, fg, row, col, str. pitch)
    9 *       int *obase, nw, fg, row, col, pitch;
    10 *       char *str;
    11 *
    12 *               Outputs characters from the string at 'str' to an 'nw'
    13 *               character wide 4-bit per pixel graphics window at 'obase'
    14 *               at ('row','col'), using 'fg' as the foreground color.
    15 *               Uses cgtable[][256] as the VSDD formatted character
    16 *               generator table.  Assumes 12 bit high characters in the
    17 *               cgtable.  Uses 'pitch' as the vertical spacing between
    18 *               character rows.  No error checks are done.
    19 *               The string must fit the output area (no overlaps, single line).
    20 *
    21 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| tsplot4.s -- output characters to a 4-bit / pixel graphics window
     3|    with variable vertical pitch
     4| Version 1 -- 1987-08-04 -- D.N. Lynx Crowe
     5| (c) Copyright 1987 -- D.N. Lynx Crowe
     6| ------------------------------------------------------------------------------
     7
     8|       tsplot4(obase, nw, fg, row, col, str. pitch)
     9|       int |obase, nw, fg, row, col, pitch;
     10|       char |str;
     11
     12|               Outputs characters from the string at 'str' to an 'nw'
     13|               character wide 4-bit per pixel graphics window at 'obase'
     14|               at ('row','col'), using 'fg' as the foreground color.
     15|               Uses cgtable[][256] as the VSDD formatted character
     16|               generator table.  Assumes 12 bit high characters in the
     17|               cgtable.  Uses 'pitch' as the vertical spacing between
     18|               character rows.  No error checks are done.
     19|               The string must fit the output area (no overlaps, single line).
     20
     21| ------------------------------------------------------------------------------
    2222                .text
    23 *
     23
    2424                .xdef   _tsplot4
    25 *
     25
    2626                .xref   _cgtable
    27 *
    28 * Argument offsets from a6:
    29 *
    30 OBASE           .equ    8               * LONG - Output area base address
    31 NW              .equ    12              * WORD - Character width of output area
    32 FG              .equ    14              * WORD - Foreground color
    33 ROW             .equ    16              * WORD - Row
    34 COL             .equ    18              * WORD - Column
    35 STR             .equ    20              * LONG - String base address
    36 PITCH           .equ    24              * WORD - Vertical spacing between rows
    37 *
    38 * Program constant definitions:
    39 *
    40 HPIX            .equ    8               * Character width in pixels
    41 VPIX            .equ    12              * Character height in pixels
    42 HCW             .equ    4               * Horizontal character width (bytes)
    43 PSHIFT          .equ    12              * Pixel shift into MS bits
    44 HSHIFT          .equ    4               * Pixel right shift
    45 *
     27
     28| Argument offsets from a6:
     29
     30OBASE           =       8               | LONG - Output area base address
     31NW              =       12              | WORD - Character width of output area
     32FG              =       14              | WORD - Foreground color
     33ROW             =       16              | WORD - Row
     34COL             =       18              | WORD - Column
     35STR             =       20              | LONG - String base address
     36PITCH           =       24              | WORD - Vertical spacing between rows
     37
     38| Program constant definitions:
     39
     40HPIX            =       8               | Character width in pixels
     41VPIX            =       12              | Character height in pixels
     42HCW             =       4               | Horizontal character width (bytes)
     43PSHIFT          =       12              | Pixel shift into MS bits
     44HSHIFT          =       4               | Pixel right shift
     45
    4646                .page
    47 *
    48 * Register usage:
    49 *
    50 *       d0      output word and scratch
    51 *       d1      CG word and scratch
    52 *       d2      pixel counter
    53 *
    54 *       d3      foreground color (in the 4 ms bits)
    55 *       d4      background color (in the 4 ms bits)
    56 *       d5      width of the area in bytes
    57 *       d6      scan line counter
    58 *
    59 *       a0      CG table pointer
    60 *       a1      output area scan line pointer
    61 *       a2      input string character pointer
    62 *
    63 *       a3      output area character base pointer
    64 *
    65 *       a6      frame pointer
    66 *       a7      stack pointer
    67 *
     47
     48| Register usage:
     49
     50|       d0      output word and scratch
     51|       d1      CG word and scratch
     52|       d2      pixel counter
     53
     54|       d3      foreground color (in the 4 ms bits)
     55|       d4      background color (in the 4 ms bits)
     56|       d5      width of the area in bytes
     57|       d6      scan line counter
     58
     59|       a0      CG table pointer
     60|       a1      output area scan line pointer
     61|       a2      input string character pointer
     62
     63|       a3      output area character base pointer
     64
     65|       a6      frame pointer
     66|       a7      stack pointer
     67
    6868                .page
    69 *
    70 _tsplot4:       link    a6,#0           * Link stack frames
    71                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    72                 move.w  #PSHIFT,d1      * Set shift constant
    73                 move.w  FG(a6),d3       * Setup foreground color
    74                 lsl.w   d1,d3           * ... in ms 4 bits of d3.W
    75                 move.w  NW(a6),d5       * Get line width in d5.W
    76                 lsl.w   #2,d5           * Multiply width by 4 for offset
    77                 move.w  ROW(a6),d0      * Calculate output address
    78                 move.w  PITCH(a6),d1    * ... PITCH
    79                 mulu    d1,d0           * ... * ROW
    80                 add.w   #VPIX-1,d0      * ... + VPIX-1
    81                 mulu    d5,d0           * ... * NW
    82                 clr.l   d1              * ...
    83                 move.w  COL(a6),d1      * ... +
    84                 lsl.w   #2,d1           * ... COL * 4
    85                 add.l   d1,d0           * ...
    86                 add.l   OBASE(a6),d0    * ... + OBASE
    87                 movea.l d0,a3           * Leave output address in a3
    88                 movea.l STR(a6),a2      * Put string address in a2
    89 *
    90 cgl0:           clr.l   d0              * Clear out upper bits of d0
    91                 move.b  (a2)+,d0        * Get next character
    92                 beq     cgl5            * Done if character EQ 0
    93 *
    94                 movea.l a3,a1           * Establish output pointer in a1
    95                 adda.l  #HCW,a3         * Update output pointer for next char.
    96                 lea     _cgtable,a0     * Establish CG pointer in a0
    97                 lsl.w   #1,d0           * ... 2 * character
    98                 adda.w  d0,a0           * ... + _cgtable address
    99                 move.w  #VPIX-1,d6      * Set scan line counter in d6
    100 *
     69
     70_tsplot4:       link    a6,#0           | Link stack frames
     71                movem.l d3-d6/a3,-(a7)  | Save registers we use
     72                move.w  #PSHIFT,d1      | Set shift constant
     73                move.w  FG(a6),d3       | Setup foreground color
     74                lsl.w   d1,d3           | ... in ms 4 bits of d3.W
     75                move.w  NW(a6),d5       | Get line width in d5.W
     76                lsl.w   #2,d5           | Multiply width by 4 for offset
     77                move.w  ROW(a6),d0      | Calculate output address
     78                move.w  PITCH(a6),d1    | ... PITCH
     79                mulu    d1,d0           | ... | ROW
     80                add.w   #VPIX-1,d0      | ... + VPIX-1
     81                mulu    d5,d0           | ... | NW
     82                clr.l   d1              | ...
     83                move.w  COL(a6),d1      | ... +
     84                lsl.w   #2,d1           | ... COL | 4
     85                add.l   d1,d0           | ...
     86                add.l   OBASE(a6),d0    | ... + OBASE
     87                movea.l d0,a3           | Leave output address in a3
     88                movea.l STR(a6),a2      | Put string address in a2
     89
     90cgl0:           clr.l   d0              | Clear out upper bits of d0
     91                move.b  (a2)+,d0        | Get next character
     92                beq     cgl5            | Done if character EQ 0
     93
     94                movea.l a3,a1           | Establish output pointer in a1
     95                adda.l  #HCW,a3         | Update output pointer for next char.
     96                lea     _cgtable,a0     | Establish CG pointer in a0
     97                lsl.w   #1,d0           | ... 2 | character
     98                adda.w  d0,a0           | ... + _cgtable address
     99                move.w  #VPIX-1,d6      | Set scan line counter in d6
     100
    101101                .page
    102 cgl1:           move.w  (a0),d1         * Get character generator word in d1
    103                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    104                 clr.l   d4              * Get old output word as background
    105                 move.w  (a1),d4         * ...
    106                 swap    d4              * ...
    107 *
    108 cgl2:           lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    109                 lsr.l   #HSHIFT,d4      * Shift background word 1 pixel
    110                 andi.l  #$FFFFF000,d4   * Mask for upper 4 bits of d4.W
    111                 btst.l  #0,d1           * Check CG word ls bit
    112                 beq     cgl3            * Set background color if bit EQ 0
    113 *
    114                 or.w    d3,d0           * OR foreground color into output word
    115                 bra     cgl4            * Go update CG word
    116 *
    117 cgl3:           or.w    d4,d0           * OR background color into output word
    118 *
    119 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    120                 dbf     d2,cgl2         * Loop for first 4 pixels
    121 *
    122                 move.w  d0,(a1)+        * Store first output word in scan line
    123                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    124                 clr.l   d4              * Get old output word as background
    125                 move.w  (a1),d4         * ...
    126                 swap    d4              * ...
    127 *
    128 cgl2a:          lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    129                 lsr.l   #HSHIFT,d4      * Shift background word 1 pixel
    130                 andi.l  #$FFFFF000,d4   * Mask for upper bits of d4.W
    131                 btst.l  #0,d1           * Check CG word ls bit
    132                 beq     cgl3a           * Set background color if bit EQ 0
    133 *
    134                 or.w    d3,d0           * OR foreground color into output word
    135                 bra     cgl4a           * Go update CG word
    136 *
    137 cgl3a:          or.w    d4,d0           * OR background color into output word
    138 *
    139 cgl4a:          lsr.w   #1,d1           * Shift CG word right 1 pixel
    140                 dbf     d2,cgl2a        * Loop for last 4 pixels
    141 *
    142                 move.w  d0,(a1)         * Store second output word in scan line
    143                 suba.w  d5,a1           * Update output pointer
    144                 suba.w  #2,a1           * ...
    145                 adda.l  #512,a0         * Update CG pointer for next scan line
    146                 dbf     d6,cgl1         * Loop for all scan lines
    147 *
    148                 bra     cgl0            * Loop for next character
    149 *
    150 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    151                 unlk    a6              * Unlink stack frames
    152                 rts                     * Return to caller
    153 *
     102cgl1:           move.w  (a0),d1         | Get character generator word in d1
     103                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     104                clr.l   d4              | Get old output word as background
     105                move.w  (a1),d4         | ...
     106                swap    d4              | ...
     107
     108cgl2:           lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     109                lsr.l   #HSHIFT,d4      | Shift background word 1 pixel
     110                andi.l  #0xFFFFF000,d4  | Mask for upper 4 bits of d4.W
     111                btst.l  #0,d1           | Check CG word ls bit
     112                beq     cgl3            | Set background color if bit EQ 0
     113
     114                or.w    d3,d0           | OR foreground color into output word
     115                bra     cgl4            | Go update CG word
     116
     117cgl3:           or.w    d4,d0           | OR background color into output word
     118
     119cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     120                dbf     d2,cgl2         | Loop for first 4 pixels
     121
     122                move.w  d0,(a1)+        | Store first output word in scan line
     123                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     124                clr.l   d4              | Get old output word as background
     125                move.w  (a1),d4         | ...
     126                swap    d4              | ...
     127
     128cgl2a:          lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     129                lsr.l   #HSHIFT,d4      | Shift background word 1 pixel
     130                andi.l  #0xFFFFF000,d4  | Mask for upper bits of d4.W
     131                btst.l  #0,d1           | Check CG word ls bit
     132                beq     cgl3a           | Set background color if bit EQ 0
     133
     134                or.w    d3,d0           | OR foreground color into output word
     135                bra     cgl4a           | Go update CG word
     136
     137cgl3a:          or.w    d4,d0           | OR background color into output word
     138
     139cgl4a:          lsr.w   #1,d1           | Shift CG word right 1 pixel
     140                dbf     d2,cgl2a        | Loop for last 4 pixels
     141
     142                move.w  d0,(a1)         | Store second output word in scan line
     143                suba.w  d5,a1           | Update output pointer
     144                suba.w  #2,a1           | ...
     145                adda.l  #512,a0         | Update CG pointer for next scan line
     146                dbf     d6,cgl1         | Loop for all scan lines
     147
     148                bra     cgl0            | Loop for next character
     149
     150cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     151                unlk    a6              | Unlink stack frames
     152                rts                     | Return to caller
     153
    154154                .end
  • vlib/vbank.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vbank.s -- VSDD bank switching control functions
    3 * Version 3 -- 1989-12-19 -- D.N. Lynx Crowe
    4 *
    5 *       unsigned
    6 *       vbank(b)
    7 *       unsigned b;
    8 *
    9 *               Set VSDD Data Segment bank to b.
    10 *               Return old bank select value.
    11 *
    12 *
    13 *       vfwait()
    14 *
    15 *               Wait for a FRAMESTOP update to transpire.
    16 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vbank.s -- VSDD bank switching control functions
     3| Version 3 -- 1989-12-19 -- D.N. Lynx Crowe
     4
     5|       unsigned
     6|       vbank(b)
     7|       unsigned b;
     8
     9|               Set VSDD Data Segment bank to b.
     10|               Return old bank select value.
     11
     12
     13|       vfwait()
     14
     15|               Wait for a FRAMESTOP update to transpire.
     16| ------------------------------------------------------------------------------
    1717                .xdef   _vbank
    1818                .xdef   _vfwait
    19 *
     19
    2020                .xref   _v_regs
    21 *
     21
    2222                .text
    23 *
    24 B               .equ    8
    25 *
    26 OLDB            .equ    d6
    27 NEWB            .equ    d7
    28 *
    29 VSDD_R5         .equ    10
    30 VSDD_R11        .equ    22
    31 *
    32 VT_BASE         .equ    128             * word offset of VSDD Access Table
    33 *
    34 VT_1            .equ    VT_BASE+300     * high time
    35 VT_2            .equ    VT_BASE+2       * low time
    36 *
     23
     24B               =       8
     25
     26OLDB            =       d6
     27NEWB            =       d7
     28
     29VSDD_R5         =       10
     30VSDD_R11        =       22
     31
     32VT_BASE         =       128             | word offset of VSDD Access Table
     33
     34VT_1            =       VT_BASE+300     | high time
     35VT_2            =       VT_BASE+2       | low time
     36
    3737                .page
    38 * ------------------------------------------------------------------------------
    39 *       vbank(b) -- change VSDD Data Segment bank to b.  Return old bank.
    40 *       Assumes a 128K byte window, sets S15..S11 to zero.
    41 * ------------------------------------------------------------------------------
    42 *
     38| ------------------------------------------------------------------------------
     39|       vbank(b) -- change VSDD Data Segment bank to b.  Return old bank.
     40|       Assumes a 128K byte window, sets S15..S11 to zero.
     41| ------------------------------------------------------------------------------
    4342
    44 _vbank:         link    a6,#0                   * link stack frames
    45                 movem.l d5-d7,-(sp)             * preserve registers
    46                 move.w  _v_regs+VSDD_R5,OLDB    * get v_regs[5]
    47                 lsr.w   #6,OLDB                 * extract BS bits
    48                 move.w  OLDB,d0                 * ...
    49                 andi.w  #2,d0                   * ...
    50                 move.w  OLDB,d1                 * ...
    51                 lsr.w   #2,d1                   * ...
    52                 andi.w  #1,d1                   * ...
    53                 or.w    d1,d0                   * ...
    54                 move.w  d0,OLDB                 * ...
    55                 cmp.w   B(a6),OLDB              * see if they're what we want
    56                 bne     L2                      * jump if not
    57 *
    58                 move.w  B(a6),d0                * setup to return b
     43
     44_vbank:         link    a6,#0                   | link stack frames
     45                movem.l d5-d7,-(sp)             | preserve registers
     46                move.w  _v_regs+VSDD_R5,OLDB    | get v_regs[5]
     47                lsr.w   #6,OLDB                 | extract BS bits
     48                move.w  OLDB,d0                 | ...
     49                andi.w  #2,d0                   | ...
     50                move.w  OLDB,d1                 | ...
     51                lsr.w   #2,d1                   | ...
     52                andi.w  #1,d1                   | ...
     53                or.w    d1,d0                   | ...
     54                move.w  d0,OLDB                 | ...
     55                cmp.w   B(a6),OLDB              | see if they're what we want
     56                bne     L2                      | jump if not
     57
     58                move.w  B(a6),d0                | setup to return b
    5959                bra     L1
    60 *
    61 L2:             move.w  B(a6),NEWB              * get bank bits from b
    62                 lsl.w   #6,NEWB                 * shift bits from b into BS bits
    63                 move.w  NEWB,d0                 * ...
    64                 andi.w  #128,d0                 * ...
    65                 lsl.w   #2,NEWB                 * ...
    66                 andi.w  #256,NEWB               * ...
    67                 or.w    NEWB,d0                 * ...
    68                 move.w  d0,_v_regs+VSDD_R5      * set v_regs[5] with new BS bits
    69 *
    70 vw1b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * wait for FRAMESTOP
    71                 bcc     vw1b                    * ...
    72 *
    73 vw2b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    74                 bcs     vw2b                    * ...
    75 *
    76 vw3b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    77                 bcc     vw3b                    * ...
    78 *
    79 vw4b:           cmp.w   #VT_2,_v_regs+VSDD_R11  * ...
    80                 bcs     vw4b                    * ...
    81 *
    82                 move.w  OLDB,d0                 * setup to return OLDB
    83 *
    84 L1:             tst.l   (sp)+                   * fixup stack
    85                 movem.l (sp)+,OLDB-NEWB         * restore registers
    86                 unlk    a6                      * unlink stack frames
    87                 rts                             * return to caller
    88 *
     60
     61L2:             move.w  B(a6),NEWB              | get bank bits from b
     62                lsl.w   #6,NEWB                 | shift bits from b into BS bits
     63                move.w  NEWB,d0                 | ...
     64                andi.w  #128,d0                 | ...
     65                lsl.w   #2,NEWB                 | ...
     66                andi.w  #256,NEWB               | ...
     67                or.w    NEWB,d0                 | ...
     68                move.w  d0,_v_regs+VSDD_R5      | set v_regs[5] with new BS bits
     69
     70vw1b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | wait for FRAMESTOP
     71                bcc     vw1b                    | ...
     72
     73vw2b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     74                bcs     vw2b                    | ...
     75
     76vw3b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     77                bcc     vw3b                    | ...
     78
     79vw4b:           cmp.w   #VT_2,_v_regs+VSDD_R11  | ...
     80                bcs     vw4b                    | ...
     81
     82                move.w  OLDB,d0                 | setup to return OLDB
     83
     84L1:             tst.l   (sp)+                   | fixup stack
     85                movem.l (sp)+,OLDB-NEWB         | restore registers
     86                unlk    a6                      | unlink stack frames
     87                rts                             | return to caller
     88
    8989                .page
    90 *
    91 * ------------------------------------------------------------------------------
    92 *       vfwait() -- Wait for a FRAMESTOP update to transpire.
    93 * ------------------------------------------------------------------------------
    94 *
    95 _vfwait:        link    a6,#0                   * link stack frames
    96 *
    97 vw1a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * wait for FRAMESTOP
    98                 bcc     vw1a                    * ...
    99 *
    100 vw2a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    101                 bcs     vw2a                    * ...
    102 *
    103 vw3a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    104                 bcc     vw3a                    * ...
    105 *
    106 vw4a:           cmp.w   #VT_2,_v_regs+VSDD_R11  * ...
    107                 bcs     vw4a                    * ...
    108 *
    109                 unlk    a6                      * unlink stack frames
    110                 rts                             * return to caller
    111 *
     90
     91| ------------------------------------------------------------------------------
     92|       vfwait() -- Wait for a FRAMESTOP update to transpire.
     93| ------------------------------------------------------------------------------
     94
     95_vfwait:        link    a6,#0                   | link stack frames
     96
     97vw1a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | wait for FRAMESTOP
     98                bcc     vw1a                    | ...
     99
     100vw2a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     101                bcs     vw2a                    | ...
     102
     103vw3a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     104                bcc     vw3a                    | ...
     105
     106vw4a:           cmp.w   #VT_2,_v_regs+VSDD_R11  | ...
     107                bcs     vw4a                    | ...
     108
     109                unlk    a6                      | unlink stack frames
     110                rts                             | return to caller
     111
    112112                .end
  • vlib/vclrav.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vclrav.s -- clear a character's attributes in video RAM
    3 * Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
    4 * (c) Copyright 1988 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vclrav(adr, row, col, atr, len)
    8 *       unsigned int *adr, row, col, atr, len;
    9 *
    10 *               Clears attribute 'atr' at ('row', 'col') in the
    11 *               full attribute text object at 'adr'
    12 *               using a line length of 'len'.
    13 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vclrav.s -- clear a character's attributes in video RAM
     3| Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
     4| (c) Copyright 1988 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vclrav(adr, row, col, atr, len)
     8|       unsigned int |adr, row, col, atr, len;
     9
     10|               Clears attribute 'atr' at ('row', 'col') in the
     11|               full attribute text object at 'adr'
     12|               using a line length of 'len'.
     13| ------------------------------------------------------------------------------
    1414                .text
    15 *
     15
    1616                .xdef   _vclrav
    17 *
    18 P_ADR           .equ    8
    19 P_ROW           .equ    12
    20 P_COL           .equ    14
    21 P_ATR           .equ    16
    22 P_LEN           .equ    18
    23 *
    24 _vclrav:        link    a6,#0           * Link stack frame pointer
    25                 move.w  P_ROW(a6),d0    * Get row
    26                 mulu    P_LEN(a6),d0    * Multiply by len
    27                 clr.l   d1              * Clear out d1
    28                 move.w  P_COL(a6),d1    * Get col
    29                 add.l   d1,d0           * Add col into d0 to get char. #
    30                 move.l  d0,d1           * Develop cw = (cn/2)*6 in d1
    31                 andi.l  #$FFFFFFFE,d1   * ...
    32                 move.l  d1,d2           * ...
    33                 add.l   d1,d1           * ...
    34                 add.l   d2,d1           * ...
    35                 add.l   P_ADR(a6),d1    * Add sbase to cw
    36                 movea.l d1,a0           * a0 points at the word with the char.
    37                 btst.l  #0,d0           * Odd char. location ?
    38                 bne     vclrav1         * Jump if so
    39 *
    40                 addq.l  #2,a0           * Point at the attribute word
    41                 bra     vclravx         * Go set attribute
    42 *
    43 vclrav1:        addq.l  #4,a0           * Point at the attribute word
    44 *
    45 vclravx:        move.w  P_ATR(a6),d0    * Get attribute mask
    46                 not.w   d0              * Complement the mask
    47                 and.w   d0,(a0)         * Clear attributes in video RAM
    48                 unlk    a6              * Unlink the stack frame
    49                 rts                     * Return to caller
    50 *
     17
     18P_ADR           =       8
     19P_ROW           =       12
     20P_COL           =       14
     21P_ATR           =       16
     22P_LEN           =       18
     23
     24_vclrav:        link    a6,#0           | Link stack frame pointer
     25                move.w  P_ROW(a6),d0    | Get row
     26                mulu    P_LEN(a6),d0    | Multiply by len
     27                clr.l   d1              | Clear out d1
     28                move.w  P_COL(a6),d1    | Get col
     29                add.l   d1,d0           | Add col into d0 to get char. #
     30                move.l  d0,d1           | Develop cw = (cn/2)|6 in d1
     31                andi.l  #0xFFFFFFFE,d1  | ...
     32                move.l  d1,d2           | ...
     33                add.l   d1,d1           | ...
     34                add.l   d2,d1           | ...
     35                add.l   P_ADR(a6),d1    | Add sbase to cw
     36                movea.l d1,a0           | a0 points at the word with the char.
     37                btst.l  #0,d0           | Odd char. location ?
     38                bne     vclrav1         | Jump if so
     39
     40                addq.l  #2,a0           | Point at the attribute word
     41                bra     vclravx         | Go set attribute
     42
     43vclrav1:        addq.l  #4,a0           | Point at the attribute word
     44
     45vclravx:        move.w  P_ATR(a6),d0    | Get attribute mask
     46                not.w   d0              | Complement the mask
     47                and.w   d0,(a0)         | Clear attributes in video RAM
     48                unlk    a6              | Unlink the stack frame
     49                rts                     | Return to caller
     50
    5151                .end
  • vlib/vcputs.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vcputs.s -- output a character string to a 4-bit per pixel graphics window
    3 * Version 3 -- 1987-07-31 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vcputs(obase, nw, fg, bg, row, col, str)
    8 *       int *obase, nw, fg, bg, row, col;
    9 *       char *str;
    10 *
    11 *               Outputs characters from the string at 'str' to an 'nw'
    12 *               character wide 4-bit per pixel graphics window at 'obase'
    13 *               at ('row','col'), using 'fg' as the foreground color, and
    14 *               'bg' as the background color.  Uses cgtable[][256] as the
    15 *               VSDD formatted character generator table.
    16 *               No error checks are done.
    17 *
    18 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vcputs.s -- output a character string to a 4-bit per pixel graphics window
     3| Version 3 -- 1987-07-31 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vcputs(obase, nw, fg, bg, row, col, str)
     8|       int |obase, nw, fg, bg, row, col;
     9|       char |str;
     10
     11|               Outputs characters from the string at 'str' to an 'nw'
     12|               character wide 4-bit per pixel graphics window at 'obase'
     13|               at ('row','col'), using 'fg' as the foreground color, and
     14|               'bg' as the background color.  Uses cgtable[][256] as the
     15|               VSDD formatted character generator table.
     16|               No error checks are done.
     17
     18| ------------------------------------------------------------------------------
    1919                .text
    20 *
     20
    2121                .xdef   _vcputs
    22 *
     22
    2323                .xref   _cgtable
    24 *
    25 * Argument offsets from a6:
    26 *
    27 OBASE           .equ    8               * Output area base address
    28 NW              .equ    12              * Character width of output area
    29 FG              .equ    14              * Foreground color
    30 BG              .equ    16              * Background color
    31 ROW             .equ    18              * Row
    32 COL             .equ    20              * Column
    33 STR             .equ    22              * String base address
    34 *
    35 * Program constant definitions:
    36 *
    37 HPIX            .equ    8               * Character width in pixels
    38 VPIX            .equ    12              * Character height in pixels
    39 HCW             .equ    4               * Horizontal character width (bytes)
    40 PSHIFT          .equ    12              * Pixel shift into MS bits
    41 HSHIFT          .equ    4               * Pixel right shift
    42 *
     24
     25| Argument offsets from a6:
     26
     27OBASE           =       8               | Output area base address
     28NW              =       12              | Character width of output area
     29FG              =       14              | Foreground color
     30BG              =       16              | Background color
     31ROW             =       18              | Row
     32COL             =       20              | Column
     33STR             =       22              | String base address
     34
     35| Program constant definitions:
     36
     37HPIX            =       8               | Character width in pixels
     38VPIX            =       12              | Character height in pixels
     39HCW             =       4               | Horizontal character width (bytes)
     40PSHIFT          =       12              | Pixel shift into MS bits
     41HSHIFT          =       4               | Pixel right shift
     42
    4343                .page
    44 *
    45 * Register usage:
    46 *
    47 *       d0      output word and scratch
    48 *       d1      CG word and scratch
    49 *       d2      pixel counter
    50 *
    51 *       d3      foreground color (in the 4 ms bits)
    52 *       d4      background color (in the 4 ms bits)
    53 *       d5      width of the area in bytes
    54 *       d6      scan line counter
    55 *
    56 *       a0      CG table pointer
    57 *       a1      output area scan line pointer
    58 *       a2      input string character pointer
    59 *
    60 *       a3      output area character base pointer
    61 *
     44
     45| Register usage:
     46
     47|       d0      output word and scratch
     48|       d1      CG word and scratch
     49|       d2      pixel counter
     50
     51|       d3      foreground color (in the 4 ms bits)
     52|       d4      background color (in the 4 ms bits)
     53|       d5      width of the area in bytes
     54|       d6      scan line counter
     55
     56|       a0      CG table pointer
     57|       a1      output area scan line pointer
     58|       a2      input string character pointer
     59
     60|       a3      output area character base pointer
     61
    6262                .page
    63 *
    64 _vcputs:        link    a6,#0           * Link stack frames
    65                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    66                 move.w  #PSHIFT,d1      * Set shift constant
    67                 move.w  FG(a6),d3       * Setup foreground color
    68                 lsl.w   d1,d3           * ... in ms 4 bits of d3.W
    69                 move.w  BG(a6),d4       * Setup background color
    70                 lsl.w   d1,d4           * ... in ms 4 bits of d4.W
    71                 move.w  NW(a6),d5       * Get line width in d5.W
    72                 lsl.w   #2,d5           * Multiply width by 4 for offset
    73                 move.w  ROW(a6),d0      * Calculate output address
    74                 move.w  #VPIX,d1        * ... VPIX
    75                 mulu    d1,d0           * ... * ROW
    76                 add.w   #VPIX-1,d0      * ... + VPIX-1
    77                 mulu    d5,d0           * ... * NW
    78                 clr.l   d1              * ...
    79                 move.w  COL(a6),d1      * ... +
    80                 lsl.w   #2,d1           * ... COL * 4
    81                 add.l   d1,d0           * ...
    82                 add.l   OBASE(a6),d0    * ... + OBASE
    83                 movea.l d0,a3           * Leave output address in a3
    84                 movea.l STR(a6),a2      * Put string address in a2
    85 *
    86 cgl0:           clr.l   d0              * Clear out upper bits of d0
    87                 move.b  (a2)+,d0        * Get next character
    88                 beq     cgl5            * Done if character EQ 0
    89 *
    90                 movea.l a3,a1           * Establish output pointer in a1
    91                 adda.l  #HCW,a3         * Update output pointer for next char.
    92                 lea     _cgtable,a0     * Establish CG pointer in a0
    93                 lsl.w   #1,d0           * ... 2 * character
    94                 adda.w  d0,a0           * ... + _cgtable address
    95                 move.w  #VPIX-1,d6      * Set scan line counter in d6
    96 *
     63
     64_vcputs:        link    a6,#0           | Link stack frames
     65                movem.l d3-d6/a3,-(a7)  | Save registers we use
     66                move.w  #PSHIFT,d1      | Set shift constant
     67                move.w  FG(a6),d3       | Setup foreground color
     68                lsl.w   d1,d3           | ... in ms 4 bits of d3.W
     69                move.w  BG(a6),d4       | Setup background color
     70                lsl.w   d1,d4           | ... in ms 4 bits of d4.W
     71                move.w  NW(a6),d5       | Get line width in d5.W
     72                lsl.w   #2,d5           | Multiply width by 4 for offset
     73                move.w  ROW(a6),d0      | Calculate output address
     74                move.w  #VPIX,d1        | ... VPIX
     75                mulu    d1,d0           | ... | ROW
     76                add.w   #VPIX-1,d0      | ... + VPIX-1
     77                mulu    d5,d0           | ... | NW
     78                clr.l   d1              | ...
     79                move.w  COL(a6),d1      | ... +
     80                lsl.w   #2,d1           | ... COL | 4
     81                add.l   d1,d0           | ...
     82                add.l   OBASE(a6),d0    | ... + OBASE
     83                movea.l d0,a3           | Leave output address in a3
     84                movea.l STR(a6),a2      | Put string address in a2
     85
     86cgl0:           clr.l   d0              | Clear out upper bits of d0
     87                move.b  (a2)+,d0        | Get next character
     88                beq     cgl5            | Done if character EQ 0
     89
     90                movea.l a3,a1           | Establish output pointer in a1
     91                adda.l  #HCW,a3         | Update output pointer for next char.
     92                lea     _cgtable,a0     | Establish CG pointer in a0
     93                lsl.w   #1,d0           | ... 2 | character
     94                adda.w  d0,a0           | ... + _cgtable address
     95                move.w  #VPIX-1,d6      | Set scan line counter in d6
     96
    9797                .page
    98 cgl1:           move.w  (a0),d1         * Get character generator word in d1
    99                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    100 *
    101 cgl2:           lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    102                 btst.l  #0,d1           * Check CG word ls bit
    103                 beq     cgl3            * Set background color if bit EQ 0
    104 *
    105                 or.w    d3,d0           * OR foreground color into output word
    106                 bra     cgl4            * Go update CG word
    107 *
    108 cgl3:           or.w    d4,d0           * OR background color into output word
    109 *
    110 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    111                 dbf     d2,cgl2         * Loop for first 4 pixels
    112 *
    113                 move.w  d0,(a1)+        * Store first output word in scan line
    114                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    115 *
    116 cgl2a:          lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    117                 btst.l  #0,d1           * Check CG word ls bit
    118                 beq     cgl3a           * Set background color if bit EQ 0
    119 *
    120                 or.w    d3,d0           * OR foreground color into output word
    121                 bra     cgl4a           * Go update CG word
    122 *
    123 cgl3a:          or.w    d4,d0           * OR background color into output word
    124 *
    125 cgl4a:          lsr.w   #1,d1           * Shift CG word right 1 pixel
    126                 dbf     d2,cgl2a        * Loop for last 4 pixels
    127 *
    128                 move.w  d0,(a1)         * Store second output word in scan line
    129                 suba.w  d5,a1           * Update output pointer
    130                 suba.w  #2,a1           * ...
    131                 adda.l  #512,a0         * Update CG pointer for next scan line
    132                 dbf     d6,cgl1         * Loop for all scan lines
    133 *
    134                 bra     cgl0            * Loop for next character
    135 *
    136 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    137                 unlk    a6              * Unlink stack frames
    138                 rts                     * Return to caller
    139 *
     98cgl1:           move.w  (a0),d1         | Get character generator word in d1
     99                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     100
     101cgl2:           lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     102                btst.l  #0,d1           | Check CG word ls bit
     103                beq     cgl3            | Set background color if bit EQ 0
     104
     105                or.w    d3,d0           | OR foreground color into output word
     106                bra     cgl4            | Go update CG word
     107
     108cgl3:           or.w    d4,d0           | OR background color into output word
     109
     110cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     111                dbf     d2,cgl2         | Loop for first 4 pixels
     112
     113                move.w  d0,(a1)+        | Store first output word in scan line
     114                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     115
     116cgl2a:          lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     117                btst.l  #0,d1           | Check CG word ls bit
     118                beq     cgl3a           | Set background color if bit EQ 0
     119
     120                or.w    d3,d0           | OR foreground color into output word
     121                bra     cgl4a           | Go update CG word
     122
     123cgl3a:          or.w    d4,d0           | OR background color into output word
     124
     125cgl4a:          lsr.w   #1,d1           | Shift CG word right 1 pixel
     126                dbf     d2,cgl2a        | Loop for last 4 pixels
     127
     128                move.w  d0,(a1)         | Store second output word in scan line
     129                suba.w  d5,a1           | Update output pointer
     130                suba.w  #2,a1           | ...
     131                adda.l  #512,a0         | Update CG pointer for next scan line
     132                dbf     d6,cgl1         | Loop for all scan lines
     133
     134                bra     cgl0            | Loop for next character
     135
     136cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     137                unlk    a6              | Unlink stack frames
     138                rts                     | Return to caller
     139
    140140                .end
  • vlib/vcputsv.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vcputsv.s -- output characters to a 4-bit / pixel graphics window
    3 * with variable vertical pitch
    4 * Version 2 -- 1987-08-03 -- D.N. Lynx Crowe
    5 * (c) Copyright 1987 -- D.N. Lynx Crowe
    6 * ------------------------------------------------------------------------------
    7 *
    8 *       vcputsv(obase, nw, fg, bg, row, col, str. pitch)
    9 *       int *obase, nw, fg, bg, row, col, pitch;
    10 *       char *str;
    11 *
    12 *               Outputs characters from the string at 'str' to an 'nw'
    13 *               character wide 4-bit per pixel graphics window at 'obase'
    14 *               at ('row','col'), using 'fg' as the foreground color, and
    15 *               'bg' as the background color.  Uses cgtable[][256] as the
    16 *               VSDD formatted character generator table.  Assumes 12 bit
    17 *               high characters in the cgtable.  Uses 'pitch' as the vertical
    18 *               spacing between character rows.  No error checks are done.
    19 *               The string must fit the output area (no overlaps, single line).
    20 *
    21 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vcputsv.s -- output characters to a 4-bit / pixel graphics window
     3| with variable vertical pitch
     4| Version 2 -- 1987-08-03 -- D.N. Lynx Crowe
     5| (c) Copyright 1987 -- D.N. Lynx Crowe
     6| ------------------------------------------------------------------------------
     7
     8|       vcputsv(obase, nw, fg, bg, row, col, str. pitch)
     9|       int |obase, nw, fg, bg, row, col, pitch;
     10|       char |str;
     11
     12|               Outputs characters from the string at 'str' to an 'nw'
     13|               character wide 4-bit per pixel graphics window at 'obase'
     14|               at ('row','col'), using 'fg' as the foreground color, and
     15|               'bg' as the background color.  Uses cgtable[][256] as the
     16|               VSDD formatted character generator table.  Assumes 12 bit
     17|               high characters in the cgtable.  Uses 'pitch' as the vertical
     18|               spacing between character rows.  No error checks are done.
     19|               The string must fit the output area (no overlaps, single line).
     20
     21| ------------------------------------------------------------------------------
    2222                .text
    23 *
     23
    2424                .xdef   _vcputsv
    25 *
     25
    2626                .xref   _cgtable
    27 *
    28 * Argument offsets from a6:
    29 *
    30 OBASE           .equ    8               * LONG - Output area base address
    31 NW              .equ    12              * WORD - Character width of output area
    32 FG              .equ    14              * WORD - Foreground color
    33 BG              .equ    16              * WORD - Background color
    34 ROW             .equ    18              * WORD - Row
    35 COL             .equ    20              * WORD - Column
    36 STR             .equ    22              * LONG - String base address
    37 PITCH           .equ    26              * WORD - Vertical spacing between rows
    38 *
    39 * Program constant definitions:
    40 *
    41 HPIX            .equ    8               * Character width in pixels
    42 VPIX            .equ    12              * Character height in pixels
    43 HCW             .equ    4               * Horizontal character width (bytes)
    44 PSHIFT          .equ    12              * Pixel shift into MS bits
    45 HSHIFT          .equ    4               * Pixel right shift
    46 *
     27
     28| Argument offsets from a6:
     29
     30OBASE           =       8               | LONG - Output area base address
     31NW              =       12              | WORD - Character width of output area
     32FG              =       14              | WORD - Foreground color
     33BG              =       16              | WORD - Background color
     34ROW             =       18              | WORD - Row
     35COL             =       20              | WORD - Column
     36STR             =       22              | LONG - String base address
     37PITCH           =       26              | WORD - Vertical spacing between rows
     38
     39| Program constant definitions:
     40
     41HPIX            =       8               | Character width in pixels
     42VPIX            =       12              | Character height in pixels
     43HCW             =       4               | Horizontal character width (bytes)
     44PSHIFT          =       12              | Pixel shift into MS bits
     45HSHIFT          =       4               | Pixel right shift
     46
    4747                .page
    48 *
    49 * Register usage:
    50 *
    51 *       d0      output word and scratch
    52 *       d1      CG word and scratch
    53 *       d2      pixel counter
    54 *
    55 *       d3      foreground color (in the 4 ms bits)
    56 *       d4      background color (in the 4 ms bits)
    57 *       d5      width of the area in bytes
    58 *       d6      scan line counter
    59 *
    60 *       a0      CG table pointer
    61 *       a1      output area scan line pointer
    62 *       a2      input string character pointer
    63 *
    64 *       a3      output area character base pointer
    65 *
    66 *       a6      frame pointer
    67 *       a7      stack pointer
    68 *
     48
     49| Register usage:
     50
     51|       d0      output word and scratch
     52|       d1      CG word and scratch
     53|       d2      pixel counter
     54
     55|       d3      foreground color (in the 4 ms bits)
     56|       d4      background color (in the 4 ms bits)
     57|       d5      width of the area in bytes
     58|       d6      scan line counter
     59
     60|       a0      CG table pointer
     61|       a1      output area scan line pointer
     62|       a2      input string character pointer
     63
     64|       a3      output area character base pointer
     65
     66|       a6      frame pointer
     67|       a7      stack pointer
     68
    6969                .page
    70 *
    71 _vcputsv:       link    a6,#0           * Link stack frames
    72                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    73                 move.w  #PSHIFT,d1      * Set shift constant
    74                 move.w  FG(a6),d3       * Setup foreground color
    75                 lsl.w   d1,d3           * ... in ms 4 bits of d3.W
    76                 move.w  BG(a6),d4       * Setup background color
    77                 lsl.w   d1,d4           * ... in ms 4 bits of d4.W
    78                 move.w  NW(a6),d5       * Get line width in d5.W
    79                 lsl.w   #2,d5           * Multiply width by 4 for offset
    80                 move.w  ROW(a6),d0      * Calculate output address
    81                 move.w  PITCH(a6),d1    * ... PITCH
    82                 mulu    d1,d0           * ... * ROW
    83                 add.w   #VPIX-1,d0      * ... + VPIX-1
    84                 mulu    d5,d0           * ... * NW
    85                 clr.l   d1              * ...
    86                 move.w  COL(a6),d1      * ... +
    87                 lsl.w   #2,d1           * ... COL * 4
    88                 add.l   d1,d0           * ...
    89                 add.l   OBASE(a6),d0    * ... + OBASE
    90                 movea.l d0,a3           * Leave output address in a3
    91                 movea.l STR(a6),a2      * Put string address in a2
    92 *
    93 cgl0:           clr.l   d0              * Clear out upper bits of d0
    94                 move.b  (a2)+,d0        * Get next character
    95                 beq     cgl5            * Done if character EQ 0
    96 *
    97                 movea.l a3,a1           * Establish output pointer in a1
    98                 adda.l  #HCW,a3         * Update output pointer for next char.
    99                 lea     _cgtable,a0     * Establish CG pointer in a0
    100                 lsl.w   #1,d0           * ... 2 * character
    101                 adda.w  d0,a0           * ... + _cgtable address
    102                 move.w  #VPIX-1,d6      * Set scan line counter in d6
    103 *
     70
     71_vcputsv:       link    a6,#0           | Link stack frames
     72                movem.l d3-d6/a3,-(a7)  | Save registers we use
     73                move.w  #PSHIFT,d1      | Set shift constant
     74                move.w  FG(a6),d3       | Setup foreground color
     75                lsl.w   d1,d3           | ... in ms 4 bits of d3.W
     76                move.w  BG(a6),d4       | Setup background color
     77                lsl.w   d1,d4           | ... in ms 4 bits of d4.W
     78                move.w  NW(a6),d5       | Get line width in d5.W
     79                lsl.w   #2,d5           | Multiply width by 4 for offset
     80                move.w  ROW(a6),d0      | Calculate output address
     81                move.w  PITCH(a6),d1    | ... PITCH
     82                mulu    d1,d0           | ... | ROW
     83                add.w   #VPIX-1,d0      | ... + VPIX-1
     84                mulu    d5,d0           | ... | NW
     85                clr.l   d1              | ...
     86                move.w  COL(a6),d1      | ... +
     87                lsl.w   #2,d1           | ... COL | 4
     88                add.l   d1,d0           | ...
     89                add.l   OBASE(a6),d0    | ... + OBASE
     90                movea.l d0,a3           | Leave output address in a3
     91                movea.l STR(a6),a2      | Put string address in a2
     92
     93cgl0:           clr.l   d0              | Clear out upper bits of d0
     94                move.b  (a2)+,d0        | Get next character
     95                beq     cgl5            | Done if character EQ 0
     96
     97                movea.l a3,a1           | Establish output pointer in a1
     98                adda.l  #HCW,a3         | Update output pointer for next char.
     99                lea     _cgtable,a0     | Establish CG pointer in a0
     100                lsl.w   #1,d0           | ... 2 | character
     101                adda.w  d0,a0           | ... + _cgtable address
     102                move.w  #VPIX-1,d6      | Set scan line counter in d6
     103
    104104                .page
    105 cgl1:           move.w  (a0),d1         * Get character generator word in d1
    106                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    107 *
    108 cgl2:           lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    109                 btst.l  #0,d1           * Check CG word ls bit
    110                 beq     cgl3            * Set background color if bit EQ 0
    111 *
    112                 or.w    d3,d0           * OR foreground color into output word
    113                 bra     cgl4            * Go update CG word
    114 *
    115 cgl3:           or.w    d4,d0           * OR background color into output word
    116 *
    117 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    118                 dbf     d2,cgl2         * Loop for first 4 pixels
    119 *
    120                 move.w  d0,(a1)+        * Store first output word in scan line
    121                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    122 *
    123 cgl2a:          lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    124                 btst.l  #0,d1           * Check CG word ls bit
    125                 beq     cgl3a           * Set background color if bit EQ 0
    126 *
    127                 or.w    d3,d0           * OR foreground color into output word
    128                 bra     cgl4a           * Go update CG word
    129 *
    130 cgl3a:          or.w    d4,d0           * OR background color into output word
    131 *
    132 cgl4a:          lsr.w   #1,d1           * Shift CG word right 1 pixel
    133                 dbf     d2,cgl2a        * Loop for last 4 pixels
    134 *
    135                 move.w  d0,(a1)         * Store second output word in scan line
    136                 suba.w  d5,a1           * Update output pointer
    137                 suba.w  #2,a1           * ...
    138                 adda.l  #512,a0         * Update CG pointer for next scan line
    139                 dbf     d6,cgl1         * Loop for all scan lines
    140 *
    141                 bra     cgl0            * Loop for next character
    142 *
    143 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    144                 unlk    a6              * Unlink stack frames
    145                 rts                     * Return to caller
    146 *
     105cgl1:           move.w  (a0),d1         | Get character generator word in d1
     106                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     107
     108cgl2:           lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     109                btst.l  #0,d1           | Check CG word ls bit
     110                beq     cgl3            | Set background color if bit EQ 0
     111
     112                or.w    d3,d0           | OR foreground color into output word
     113                bra     cgl4            | Go update CG word
     114
     115cgl3:           or.w    d4,d0           | OR background color into output word
     116
     117cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     118                dbf     d2,cgl2         | Loop for first 4 pixels
     119
     120                move.w  d0,(a1)+        | Store first output word in scan line
     121                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     122
     123cgl2a:          lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     124                btst.l  #0,d1           | Check CG word ls bit
     125                beq     cgl3a           | Set background color if bit EQ 0
     126
     127                or.w    d3,d0           | OR foreground color into output word
     128                bra     cgl4a           | Go update CG word
     129
     130cgl3a:          or.w    d4,d0           | OR background color into output word
     131
     132cgl4a:          lsr.w   #1,d1           | Shift CG word right 1 pixel
     133                dbf     d2,cgl2a        | Loop for last 4 pixels
     134
     135                move.w  d0,(a1)         | Store second output word in scan line
     136                suba.w  d5,a1           | Update output pointer
     137                suba.w  #2,a1           | ...
     138                adda.l  #512,a0         | Update CG pointer for next scan line
     139                dbf     d6,cgl1         | Loop for all scan lines
     140
     141                bra     cgl0            | Loop for next character
     142
     143cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     144                unlk    a6              | Unlink stack frames
     145                rts                     | Return to caller
     146
    147147                .end
  • vlib/viint.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * viint.s -- VSDD Vertical Interval interrupt handler for the Buchla 700
    3 * Version 17 -- 1989-12-19 -- D.N. Lynx Crowe
    4 *
    5 *       VIint
    6 *
    7 *               VSDD Vertical Interval interrupt handler.  Enables display of
    8 *               any object whose bit is set in vi_ctl.  Bit 0 = object 0, etc.
    9 *
    10 *               SetPri() uses BIOS(B_SETV, 25, VIint) to set the interrupt
    11 *               vector and lets VIint() enable the object.  If vi_dis
    12 *               is set, SetPri() won't enable the interrupt or set the vector
    13 *               so that several objects can be started up at once.
    14 *
    15 *               This routine also sets the base address and scroll offset
    16 *               for the score display object if vi_sadr is non-zero,
    17 *               after a delay for VSDD FRAMESTOP synchronization.
    18 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| viint.s -- VSDD Vertical Interval interrupt handler for the Buchla 700
     3| Version 17 -- 1989-12-19 -- D.N. Lynx Crowe
     4
     5|       VIint
     6
     7|               VSDD Vertical Interval interrupt handler.  Enables display of
     8|               any object whose bit is set in vi_ctl.  Bit 0 = object 0, etc.
     9
     10|               SetPri() uses BIOS(B_SETV, 25, VIint) to set the interrupt
     11|               vector and lets VIint() enable the object.  If vi_dis
     12|               is set, SetPri() won't enable the interrupt or set the vector
     13|               so that several objects can be started up at once.
     14
     15|               This routine also sets the base address and scroll offset
     16|               for the score display object if vi_sadr is non-zero,
     17|               after a delay for VSDD FRAMESTOP synchronization.
     18| ------------------------------------------------------------------------------
    1919                .text
    20 *
    21                 .xdef   _VIint                  * Vertical Interval int. handler
    22 *
    23                 .xdef   _vi_sadr                * score object base address
    24                 .xdef   _vi_scrl                * score object scroll offset
    25                 .xdef   lclsadr                 * local scroll address
    26                 .xdef   lclscrl                 * local scroll offset
    27                 .xdef   vdelay                  * VSDD scroll delay
    28 *
    29                 .xdef   VIct1                   * VSDD interrupt R11
    30                 .xdef   VIct2                   * VSDD interrupt R11
    31                 .xdef   VIct3                   * VSDD interrupt R11
    32                 .xdef   VIct4                   * VSDD interrupt R11
    33 *
    34                 .xref   _v_regs                 * VSDD registers
    35                 .xref   _v_odtab                * VSDD object descriptor table
    36 *
    37                 .xref   _vi_clk                 * scroll delay timer
    38                 .xref   _vi_ctl                 * unblank control word
    39                 .xref   _vi_tag                 * VSDD 'needs service' tag
    40 *
    41                 .page
    42 *
    43 * Miscellaneous equates:
    44 * ----------------------
    45 *
    46 DELAY           .equ    17                      * FRAMESTOP sync delay in Ms
    47 STACKSR         .equ    32                      * offset to sr on stack
    48 V_BLA           .equ    4                       * V_BLA (blank) bit number
    49 VSDD_R5         .equ    10                      * VSDD R5 byte offset in _v_regs
    50 VSDD_R11        .equ    22                      * VSDD R11 byte offset in _v_regs
    51 *
    52 VT_BASE         .equ    128                     * word offset of VSDD Access Table
    53 *
    54 VT_1            .equ    VT_BASE+300             * high time
    55 VT_2            .equ    VT_BASE+2               * low time
    56 * ------------------------------------------------------------------------------
    57 *
    58 * Stack picture after movem.l at entry:
    59 * -------------------------------------
    60 *
    61 *       LONG    PC      +34
    62 *       WORD    SR      +32     STACKSR
    63 *       LONG    A6      +28
    64 *       LONG    A2      +24
    65 *       LONG    A1      +20
    66 *       LONG    A0      +16
    67 *       LONG    D3      +12
    68 *       LONG    D2      +8
    69 *       LONG    D1      +4
    70 *       LONG    D0      +0
    71 *
    72 * ------------------------------------------------------------------------------
    73 *
    74                 .page
    75 *
    76 * _VIint -- Vertical interval interrupt handler
    77 * ------    -----------------------------------
    78 _VIint:         movem.l d0-d3/a0-a2/a6,-(a7)    * save registers
    79                 addi.w  #$0100,STACKSR(a7)      * raise IPL in sr on the stack
    80 *
    81                 move.w  _v_regs+VSDD_R11,VIct1  * save the VSDD R11 value
    82 *
    83                 tst.w   _vi_sadr                * see if we should scroll
    84                 beq     viunbl                  * jump if not
    85 *
    86 * ------------------------------------------------------------------------------
    87 * setup delayed scroll parameters
    88 * ------------------------------------------------------------------------------
    89                 move.w  _v_regs+VSDD_R5,d0      * get VSDD R5
    90                 move.w  d0,d1                   * save it for later
    91                 andi.w  #$0180,d0               * see if we're already in bank 0
    92                 beq     dlyscrl                 * jump if so
    93 *
    94                 clr.w   _v_regs+VSDD_R5         * set bank 0
    95 *
    96                 move.w  _v_regs+VSDD_R11,VIct2  * save the VSDD R11 value
    97 *
    98 vw1a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * wait for FRAMESTOP
    99                 bcc     vw1a                    * ...
    100 *
    101 vw2a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    102                 bcs     vw2a                    * ...
    103 *
    104 vw3a:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    105                 bcc     vw3a                    * ...
    106 *
    107 vw4a:           cmp.w   #VT_2,_v_regs+VSDD_R11  * ...
    108                 bcs     vw4a                    * ...
    109 *
    110 dlyscrl:        tst.w   _vi_tag                 * wait for previous scroll
    111                 bne     dlyscrl                 * ...
    112 *
    113                 move.w  _vi_sadr,lclsadr        * save address for timeint
    114                 move.w  _vi_scrl,lclscrl        * save offset for timeint
    115                 clr.w   _vi_sadr                * reset for next time
    116                 clr.w   _vi_scrl                * ...
    117                 move.w  vdelay,_vi_clk          * set the scroll delay timer
    118                 st      _vi_tag                 * set the 'need service' tag
    119 * ------------------------------------------------------------------------------
    120 * check for unblank requests
    121 * ------------------------------------------------------------------------------
    122                 move.w  _vi_ctl,d2              * get the unblank control word
    123                 beq     viexit                  * exit if nothing to unblank
    124 *
    125                 bra     unblnk                  * go unblank some objects
    126 *
    127 viunbl:         move.w  _vi_ctl,d2              * get the unblank control word
    128                 beq     vidone                  * exit if nothing to unblank
    129 *
    130                 move.w  _v_regs+VSDD_R5,d0      * get VSDD R5
    131                 move.w  d0,d1                   * save it for later
    132                 andi.w  #$0180,d0               * see if we're already in bank 0
    133                 beq     unblnk                  * jump if so
    134 *
    135                 clr.w   _v_regs+VSDD_R5         * set bank 0
    136 *
    137                 move.w  _v_regs+VSDD_R11,VIct3  * save the VSDD R11 value
    138 *
    139 vw1b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * wait for FRAMESTOP
    140                 bcc     vw1b                    * ...
    141 *
    142 vw2b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    143                 bcs     vw2b                    * ...
    144 *
    145 vw3b:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    146                 bcc     vw3b                    * ...
    147 *
    148 vw4b:           cmp.w   #VT_2,_v_regs+VSDD_R11  * ...
    149                 bcs     vw4b                    * ...
    150 *
    151                 .page
    152 *
    153 * ------------------------------------------------------------------------------
    154 * unblank objects indicated by contents of d2  (loaded earlier from _vi_ctl)
    155 * ------------------------------------------------------------------------------
    156 *
    157 unblnk:         clr.w   d3                      * clear the counter
    158                 clr.w   _vi_ctl                 * clear the unblank control word
    159                 lea     _v_odtab,a1             * point at first object
    160 *
    161 vicheck:        btst    d3,d2                   * check the object bit
    162                 beq     vinext                  * go check next one if not set
    163 *
    164                 move.w  (a1),d0                 * get v_odtab[obj][0]
    165                 bclr    #V_BLA,d0               * clear the blanking bit
    166                 move.w  d0,(a1)                 * set v_odtab[obj][0]
    167 *
    168 vinext:         cmpi.w  #15,d3                  * see if we're done
    169                 beq     viexit                  * jump if so
    170 *
    171                 addq.l  #8,a1                   * point at next object
    172                 addq.w  #1,d3                   * increment object counter
    173                 bra     vicheck                 * go check next object
    174 *
    175 * ------------------------------------------------------------------------------
    176 * switch back to the bank the interrupted code was using if we changed it
    177 * ------------------------------------------------------------------------------
    178 *
    179 viexit:         move.w  d1,d0                   * see if we were in bank 0
    180                 andi.w  #$0180,d0               * ...
    181                 beq     vidone                  * jump if so
    182 *
    183 viwait:         tst.w   _vi_tag                 * wait for timer to run out
    184                 bne     viwait                  * ... so timeint sees bank 0
    185 *
    186                 move.w  d1,_v_regs+VSDD_R5      * restore v_regs[5] to old bank
    187 *
    188                 move.w  _v_regs+VSDD_R11,VIct4  * save the VSDD R11 value
    189 *
    190 vw1c:           cmp.w   #VT_1,_v_regs+VSDD_R11  * wait for FRAMESTOP
    191                 bcc     vw1c                    * ...
    192 *
    193 vw2c:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    194                 bcs     vw2c                    * ...
    195 *
    196 vw3c:           cmp.w   #VT_1,_v_regs+VSDD_R11  * ...
    197                 bcc     vw3c                    * ...
    198 *
    199 vw4c:           cmp.w   #VT_2,_v_regs+VSDD_R11  * ...
    200                 bcs     vw4c                    * ...
    201 *
    202 * ------------------------------------------------------------------------------
    203 * restore registers and return to interrupted code
    204 * ------------------------------------------------------------------------------
    205 *
    206 vidone:         movem.l (a7)+,d0-d3/a0-a2/a6    * restore registers
    207                 rte                             * return from interrupt
    208 *
    209                 .page
    210 *
    211 * ------------------------------------------------------------------------------
     20
     21                .xdef   _VIint                  | Vertical Interval int. handler
     22
     23                .xdef   _vi_sadr                | score object base address
     24                .xdef   _vi_scrl                | score object scroll offset
     25                .xdef   lclsadr                 | local scroll address
     26                .xdef   lclscrl                 | local scroll offset
     27                .xdef   vdelay                  | VSDD scroll delay
     28
     29                .xdef   VIct1                   | VSDD interrupt R11
     30                .xdef   VIct2                   | VSDD interrupt R11
     31                .xdef   VIct3                   | VSDD interrupt R11
     32                .xdef   VIct4                   | VSDD interrupt R11
     33
     34                .xref   _v_regs                 | VSDD registers
     35                .xref   _v_odtab                | VSDD object descriptor table
     36
     37                .xref   _vi_clk                 | scroll delay timer
     38                .xref   _vi_ctl                 | unblank control word
     39                .xref   _vi_tag                 | VSDD 'needs service' tag
     40
     41                .page
     42
     43| Miscellaneous equates:
     44| ----------------------
     45
     46DELAY           =       17                      | FRAMESTOP sync delay in Ms
     47STACKSR         =       32                      | offset to sr on stack
     48V_BLA           =       4                       | V_BLA (blank) bit number
     49VSDD_R5         =       10                      | VSDD R5 byte offset in _v_regs
     50VSDD_R11        =       22                      | VSDD R11 byte offset in _v_regs
     51
     52VT_BASE         =       128                     | word offset of VSDD Access Table
     53
     54VT_1            =       VT_BASE+300             | high time
     55VT_2            =       VT_BASE+2               | low time
     56| ------------------------------------------------------------------------------
     57
     58| Stack picture after movem.l at entry:
     59| -------------------------------------
     60
     61|       LONG    PC      +34
     62|       WORD    SR      +32     STACKSR
     63|       LONG    A6      +28
     64|       LONG    A2      +24
     65|       LONG    A1      +20
     66|       LONG    A0      +16
     67|       LONG    D3      +12
     68|       LONG    D2      +8
     69|       LONG    D1      +4
     70|       LONG    D0      +0
     71
     72| ------------------------------------------------------------------------------
     73
     74                .page
     75
     76| _VIint -- Vertical interval interrupt handler
     77| ------    -----------------------------------
     78_VIint:         movem.l d0-d3/a0-a2/a6,-(a7)    | save registers
     79                addi.w  #0x0100,STACKSR(a7)     | raise IPL in sr on the stack
     80
     81                move.w  _v_regs+VSDD_R11,VIct1  | save the VSDD R11 value
     82
     83                tst.w   _vi_sadr                | see if we should scroll
     84                beq     viunbl                  | jump if not
     85
     86| ------------------------------------------------------------------------------
     87| setup delayed scroll parameters
     88| ------------------------------------------------------------------------------
     89                move.w  _v_regs+VSDD_R5,d0      | get VSDD R5
     90                move.w  d0,d1                   | save it for later
     91                andi.w  #0x0180,d0              | see if we're already in bank 0
     92                beq     dlyscrl                 | jump if so
     93
     94                clr.w   _v_regs+VSDD_R5         | set bank 0
     95
     96                move.w  _v_regs+VSDD_R11,VIct2  | save the VSDD R11 value
     97
     98vw1a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | wait for FRAMESTOP
     99                bcc     vw1a                    | ...
     100
     101vw2a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     102                bcs     vw2a                    | ...
     103
     104vw3a:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     105                bcc     vw3a                    | ...
     106
     107vw4a:           cmp.w   #VT_2,_v_regs+VSDD_R11  | ...
     108                bcs     vw4a                    | ...
     109
     110dlyscrl:        tst.w   _vi_tag                 | wait for previous scroll
     111                bne     dlyscrl                 | ...
     112
     113                move.w  _vi_sadr,lclsadr        | save address for timeint
     114                move.w  _vi_scrl,lclscrl        | save offset for timeint
     115                clr.w   _vi_sadr                | reset for next time
     116                clr.w   _vi_scrl                | ...
     117                move.w  vdelay,_vi_clk          | set the scroll delay timer
     118                st      _vi_tag                 | set the 'need service' tag
     119| ------------------------------------------------------------------------------
     120| check for unblank requests
     121| ------------------------------------------------------------------------------
     122                move.w  _vi_ctl,d2              | get the unblank control word
     123                beq     viexit                  | exit if nothing to unblank
     124
     125                bra     unblnk                  | go unblank some objects
     126
     127viunbl:         move.w  _vi_ctl,d2              | get the unblank control word
     128                beq     vidone                  | exit if nothing to unblank
     129
     130                move.w  _v_regs+VSDD_R5,d0      | get VSDD R5
     131                move.w  d0,d1                   | save it for later
     132                andi.w  #0x0180,d0              | see if we're already in bank 0
     133                beq     unblnk                  | jump if so
     134
     135                clr.w   _v_regs+VSDD_R5         | set bank 0
     136
     137                move.w  _v_regs+VSDD_R11,VIct3  | save the VSDD R11 value
     138
     139vw1b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | wait for FRAMESTOP
     140                bcc     vw1b                    | ...
     141
     142vw2b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     143                bcs     vw2b                    | ...
     144
     145vw3b:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     146                bcc     vw3b                    | ...
     147
     148vw4b:           cmp.w   #VT_2,_v_regs+VSDD_R11  | ...
     149                bcs     vw4b                    | ...
     150
     151                .page
     152
     153| ------------------------------------------------------------------------------
     154| unblank objects indicated by contents of d2  (loaded earlier from _vi_ctl)
     155| ------------------------------------------------------------------------------
     156
     157unblnk:         clr.w   d3                      | clear the counter
     158                clr.w   _vi_ctl                 | clear the unblank control word
     159                lea     _v_odtab,a1             | point at first object
     160
     161vicheck:        btst    d3,d2                   | check the object bit
     162                beq     vinext                  | go check next one if not set
     163
     164                move.w  (a1),d0                 | get v_odtab[obj][0]
     165                bclr    #V_BLA,d0               | clear the blanking bit
     166                move.w  d0,(a1)                 | set v_odtab[obj][0]
     167
     168vinext:         cmpi.w  #15,d3                  | see if we're done
     169                beq     viexit                  | jump if so
     170
     171                addq.l  #8,a1                   | point at next object
     172                addq.w  #1,d3                   | increment object counter
     173                bra     vicheck                 | go check next object
     174
     175| ------------------------------------------------------------------------------
     176| switch back to the bank the interrupted code was using if we changed it
     177| ------------------------------------------------------------------------------
     178
     179viexit:         move.w  d1,d0                   | see if we were in bank 0
     180                andi.w  #0x0180,d0              | ...
     181                beq     vidone                  | jump if so
     182
     183viwait:         tst.w   _vi_tag                 | wait for timer to run out
     184                bne     viwait                  | ... so timeint sees bank 0
     185
     186                move.w  d1,_v_regs+VSDD_R5      | restore v_regs[5] to old bank
     187
     188                move.w  _v_regs+VSDD_R11,VIct4  | save the VSDD R11 value
     189
     190vw1c:           cmp.w   #VT_1,_v_regs+VSDD_R11  | wait for FRAMESTOP
     191                bcc     vw1c                    | ...
     192
     193vw2c:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     194                bcs     vw2c                    | ...
     195
     196vw3c:           cmp.w   #VT_1,_v_regs+VSDD_R11  | ...
     197                bcc     vw3c                    | ...
     198
     199vw4c:           cmp.w   #VT_2,_v_regs+VSDD_R11  | ...
     200                bcs     vw4c                    | ...
     201
     202| ------------------------------------------------------------------------------
     203| restore registers and return to interrupted code
     204| ------------------------------------------------------------------------------
     205
     206vidone:         movem.l (a7)+,d0-d3/a0-a2/a6    | restore registers
     207                rte                             | return from interrupt
     208
     209                .page
     210
     211| ------------------------------------------------------------------------------
    212212                .data
    213 * ------------------------------------------------------------------------------
    214 *
    215 vdelay:         .dc.w   DELAY                   * VSDD scroll delay
    216 *
    217 * ------------------------------------------------------------------------------
     213| ------------------------------------------------------------------------------
     214
     215vdelay:         .dc.w   DELAY                   | VSDD scroll delay
     216
     217| ------------------------------------------------------------------------------
    218218                .bss
    219 * ------------------------------------------------------------------------------
    220 *
    221 _vi_sadr:       .ds.w   1                       * score object base address
    222 _vi_scrl:       .ds.w   1                       * score object scroll offset
    223 *
    224 lclsadr:        .ds.w   1                       * local copy of vi_sadr
    225 lclscrl:        .ds.w   1                       * local copy of vi_scrl
    226 *
    227 VIct1:          .ds.w   1                       * VSDD R11 value at interrupt
    228 VIct2:          .ds.w   1                       * VSDD R11 value at interrupt
    229 VIct3:          .ds.w   1                       * VSDD R11 value at interrupt
    230 VIct4:          .ds.w   1                       * VSDD R11 value at interrupt
    231 *
     219| ------------------------------------------------------------------------------
     220
     221_vi_sadr:       .ds.w   1                       | score object base address
     222_vi_scrl:       .ds.w   1                       | score object scroll offset
     223
     224lclsadr:        .ds.w   1                       | local copy of vi_sadr
     225lclscrl:        .ds.w   1                       | local copy of vi_scrl
     226
     227VIct1:          .ds.w   1                       | VSDD R11 value at interrupt
     228VIct2:          .ds.w   1                       | VSDD R11 value at interrupt
     229VIct3:          .ds.w   1                       | VSDD R11 value at interrupt
     230VIct4:          .ds.w   1                       | VSDD R11 value at interrupt
     231
    232232                .end
  • vlib/vputa.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vputa.s -- store character attributes in video RAM
    3 * Version 1 -- 1988-03-14 -- D.N. Lynx Crowe
    4 * (c) Copyright 1988 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vputa(sbase, row, col, attrib)
    8 *       unsigned int *sbase, row, col, attrib;
    9 *
    10 *               Stores attribute value 'attrib' for the character
    11 *               located at ('row','col') in VSDD RAM starting at 'sbase'.
    12 *               Assumes a 64 character line and full character attributes.
    13 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vputa.s -- store character attributes in video RAM
     3| Version 1 -- 1988-03-14 -- D.N. Lynx Crowe
     4| (c) Copyright 1988 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vputa(sbase, row, col, attrib)
     8|       unsigned int |sbase, row, col, attrib;
     9
     10|               Stores attribute value 'attrib' for the character
     11|               located at ('row','col') in VSDD RAM starting at 'sbase'.
     12|               Assumes a 64 character line and full character attributes.
     13| ------------------------------------------------------------------------------
    1414                .text
    15 *
     15
    1616                .xdef   _vputa
    17 *
    18 SBASE           .equ    8               * LONG - 'sbase'
    19 ROW             .equ    12              * WORD - 'row'
    20 COL             .equ    14              * WORD - 'col'
    21 ATTR            .equ    16              * WORD - 'attrib'
    22 *
    23 _vputa:         link    a6,#0           * Link stack frame pointer
    24                 clr.l   d0              * Clear out d0
    25                 move.w  ROW(a6),d0      * Get row
    26                 lsl.l   #6,d0           * Multiply by 64  (shift left 6)
    27                 move.w  COL(a6),d1      * Get col
    28                 andi.l  #$0000003F,d1   * Mask down to 6 bits
    29                 or.l    d1,d0           * OR into d0 to get char. #
    30                 move.w  d0,d1           * Develop cw = (cn/2)*6 in d1
    31                 andi.l  #$FFFFFFFE,d1   * ...
    32                 move.l  d1,d2           * ...
    33                 add.l   d1,d1           * ...
    34                 add.l   d2,d1           * ...
    35                 add.l   SBASE(a6),d1    * Add sbase to cw
    36                 movea.l d1,a0           * a0 points at the word with the char.
    37                 btst.l  #0,d0           * Odd char. location ?
    38                 bne     vputa1          * Jump if so
    39 *
    40                 move.w  ATTR(a6),2(a0)  * Store new attribute word in video RAM
    41 *
    42 vputax:         unlk    a6              * Unlink the stack frame
    43                 rts                     * Done -- return to caller
    44 *
    45 vputa1:         move.w  ATTR(a6),4(a0)  * Store new attribute word in video RAM
    46                 bra     vputax          * Done -- go return to caller
    47 *
     17
     18SBASE           =       8               | LONG - 'sbase'
     19ROW             =       12              | WORD - 'row'
     20COL             =       14              | WORD - 'col'
     21ATTR            =       16              | WORD - 'attrib'
     22
     23_vputa:         link    a6,#0           | Link stack frame pointer
     24                clr.l   d0              | Clear out d0
     25                move.w  ROW(a6),d0      | Get row
     26                lsl.l   #6,d0           | Multiply by 64  (shift left 6)
     27                move.w  COL(a6),d1      | Get col
     28                andi.l  #0x0000003F,d1  | Mask down to 6 bits
     29                or.l    d1,d0           | OR into d0 to get char. #
     30                move.w  d0,d1           | Develop cw = (cn/2)|6 in d1
     31                andi.l  #0xFFFFFFFE,d1  | ...
     32                move.l  d1,d2           | ...
     33                add.l   d1,d1           | ...
     34                add.l   d2,d1           | ...
     35                add.l   SBASE(a6),d1    | Add sbase to cw
     36                movea.l d1,a0           | a0 points at the word with the char.
     37                btst.l  #0,d0           | Odd char. location ?
     38                bne     vputa1          | Jump if so
     39
     40                move.w  ATTR(a6),2(a0)  | Store new attribute word in video RAM
     41
     42vputax:         unlk    a6              | Unlink the stack frame
     43                rts                     | Done -- return to caller
     44
     45vputa1:         move.w  ATTR(a6),4(a0)  | Store new attribute word in video RAM
     46                bra     vputax          | Done -- go return to caller
     47
    4848                .end
  • vlib/vputc.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vputc.s -- store a character and attributes in video RAM
    3 * Version 3 -- 1987-03-30 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vputc(sbase, row, col, c, attrib)
    8 *       unsigned int *sbase, row, col, c, attrib;
    9 *
    10 *               Stores character c at (row,col) in sbase with
    11 *               attribute value attrib.
    12 * ------------------------------------------------------------------------------
    13 *
     1| ------------------------------------------------------------------------------
     2| vputc.s -- store a character and attributes in video RAM
     3| Version 3 -- 1987-03-30 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vputc(sbase, row, col, c, attrib)
     8|       unsigned int |sbase, row, col, c, attrib;
     9
     10|               Stores character c at (row,col) in sbase with
     11|               attribute value attrib.
     12| ------------------------------------------------------------------------------
     13
    1414                .text
    15 *
     15
    1616                .xdef   _vputc
    17 *
    18 _vputc:         link    a6,#0           * Link stack frame pointer
    19                 clr.l   d0              * Clear out d0
    20                 move.w  12(a6),d0       * Get row
    21                 lsl.l   #6,d0           * Multiply by 64  (shift left 6)
    22                 move.w  14(a6),d1       * Get col
    23                 andi.l  #$0000003F,d1   * Mask down to 6 bits
    24                 or.l    d1,d0           * OR into d0 to get char. #
    25                 move.w  d0,d1           * Develop cw = (cn/2)*6 in d1
    26                 andi.l  #$FFFFFFFE,d1   * ...
    27                 move.l  d1,d2           * ...
    28                 lsl.l   #1,d1           * ...
    29                 add.l   d2,d1           * ...
    30                 add.l   8(a6),d1        * Add sbase to cw
    31                 movea.l d1,a0           * a0 points at the word with the char.
    32                 btst.l  #0,d0           * Odd char. location ?
    33                 bne     vputc1          * Jump if so
    34 *
    35                 move.w  16(a6),d0       * Get ch
    36                 andi.w  #$00FF,d0       * Mask off garbage bits
    37                 move.w  (a0),d1         * Get word from video RAM
    38                 andi.w  #$FF00,d1       * Mask off old even character
    39                 or.w    d0,d1           * OR in the new character
    40                 move.w  d1,(a0)+        * Store the updated word in video RAM
    41                 move.w  18(a6),(a0)     * Store new attribute word in video RAM
    42 *
    43 vputcx:         unlk    a6              * Unlink the stack frame
    44                 rts                     * Return to caller
    45 *
    46 vputc1:         move.w  16(a6),d0       * Get ch
    47                 lsl.w   #8,d0           * Shift to high (odd) byte
    48                 move.w  (a0),d1         * Get word from video RAM
    49                 andi.w  #$00FF,d1       * Mask off old odd character
    50                 or.w    d0,d1           * OR in the new character
    51                 move.w  d1,(a0)+        * Store the updated word in video RAM
    52                 addq.l  #2,a0           * Point at the attribute word
    53                 move.w  18(a6),(a0)     * Store new attributes in video RAM
    54                 bra     vputcx          * Done -- go return to caller
    55 *
     17
     18_vputc:         link    a6,#0           | Link stack frame pointer
     19                clr.l   d0              | Clear out d0
     20                move.w  12(a6),d0       | Get row
     21                lsl.l   #6,d0           | Multiply by 64  (shift left 6)
     22                move.w  14(a6),d1       | Get col
     23                andi.l  #0x0000003F,d1  | Mask down to 6 bits
     24                or.l    d1,d0           | OR into d0 to get char. #
     25                move.w  d0,d1           | Develop cw = (cn/2)|6 in d1
     26                andi.l  #0xFFFFFFFE,d1  | ...
     27                move.l  d1,d2           | ...
     28                lsl.l   #1,d1           | ...
     29                add.l   d2,d1           | ...
     30                add.l   8(a6),d1        | Add sbase to cw
     31                movea.l d1,a0           | a0 points at the word with the char.
     32                btst.l  #0,d0           | Odd char. location ?
     33                bne     vputc1          | Jump if so
     34
     35                move.w  16(a6),d0       | Get ch
     36                andi.w  #0x00FF,d0      | Mask off garbage bits
     37                move.w  (a0),d1         | Get word from video RAM
     38                andi.w  #0xFF00,d1      | Mask off old even character
     39                or.w    d0,d1           | OR in the new character
     40                move.w  d1,(a0)+        | Store the updated word in video RAM
     41                move.w  18(a6),(a0)     | Store new attribute word in video RAM
     42
     43vputcx:         unlk    a6              | Unlink the stack frame
     44                rts                     | Return to caller
     45
     46vputc1:         move.w  16(a6),d0       | Get ch
     47                lsl.w   #8,d0           | Shift to high (odd) byte
     48                move.w  (a0),d1         | Get word from video RAM
     49                andi.w  #0x00FF,d1      | Mask off old odd character
     50                or.w    d0,d1           | OR in the new character
     51                move.w  d1,(a0)+        | Store the updated word in video RAM
     52                addq.l  #2,a0           | Point at the attribute word
     53                move.w  18(a6),(a0)     | Store new attributes in video RAM
     54                bra     vputcx          | Done -- go return to caller
     55
    5656                .end
  • vlib/vputcv.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vputcv.s -- store a character and attributes in video RAM
    3 * Version 1 -- 1988-10-05 -- D.N. Lynx Crowe
    4 * (c) Copyright 1988 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vputcv(adr, row, col, chr, atr, cols)
    8 *       unsigned int *adr, row, col, chr, atr, cols;
    9 *
    10 *               Stores character 'chr' at ('row', 'col') in the
    11 *               full attribute text object at 'adr' with
    12 *               attribute value 'atr' using a line length of 'len'.
    13 * ------------------------------------------------------------------------------
    14 *
     1| ------------------------------------------------------------------------------
     2| vputcv.s -- store a character and attributes in video RAM
     3| Version 1 -- 1988-10-05 -- D.N. Lynx Crowe
     4| (c) Copyright 1988 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vputcv(adr, row, col, chr, atr, cols)
     8|       unsigned int |adr, row, col, chr, atr, cols;
     9
     10|               Stores character 'chr' at ('row', 'col') in the
     11|               full attribute text object at 'adr' with
     12|               attribute value 'atr' using a line length of 'len'.
     13| ------------------------------------------------------------------------------
     14
    1515                .text
    16 *
     16
    1717                .xdef   _vputcv
    18 *
    19 P_ADR           .equ    8
    20 P_ROW           .equ    12
    21 P_COL           .equ    14
    22 P_CHR           .equ    16
    23 P_ATR           .equ    18
    24 P_LEN           .equ    20
    25 *
     18
     19P_ADR           =       8
     20P_ROW           =       12
     21P_COL           =       14
     22P_CHR           =       16
     23P_ATR           =       18
     24P_LEN           =       20
     25
    2626                .page
    27 *
    28 _vputcv:        link    a6,#0           * Link stack frame pointer
    29                 move.w  P_ROW(a6),d0    * Get row
    30                 mulu    P_LEN(a6),d0    * Multiply by len
    31                 clr.l   d1              * Clear out d1
    32                 move.w  P_COL(a6),d1    * Get col
    33                 add.l   d1,d0           * Add col into d0 to get char. #
    34                 move.l  d0,d1           * Develop cw = (cn/2)*6 in d1
    35                 andi.l  #$FFFFFFFE,d1   * ...
    36                 move.l  d1,d2           * ...
    37                 add.l   d1,d1           * ...
    38                 add.l   d2,d1           * ...
    39                 add.l   P_ADR(a6),d1    * Add sbase to cw
    40                 movea.l d1,a0           * a0 points at the word with the char.
    41                 btst.l  #0,d0           * Odd char. location ?
    42                 bne     vputcv1         * Jump if so
    43 *
    44                 move.w  P_CHR(a6),d0    * Get chr
    45                 andi.w  #$00FF,d0       * Mask off garbage bits
    46                 move.w  (a0),d1         * Get word from video RAM
    47                 andi.w  #$FF00,d1       * Mask off old even character
    48                 or.w    d0,d1           * OR in the new character
    49                 move.w  d1,(a0)+        * Store the updated word in video RAM
    50                 bra     vputcvx         * Done -- go return to caller
    51 *
    52 vputcv1:        move.w  P_CHR(a6),d0    * Get chr
    53                 lsl.w   #8,d0           * Shift to high (odd) byte
    54                 move.w  (a0),d1         * Get word from video RAM
    55                 andi.w  #$00FF,d1       * Mask off old odd character
    56                 or.w    d0,d1           * OR in the new character
    57                 move.w  d1,(a0)+        * Store the updated word in video RAM
    58                 addq.l  #2,a0           * Point at the attribute word
    59 *
    60 vputcvx:        move.w  P_ATR(a6),(a0)  * Store new attributes in video RAM
    61                 unlk    a6              * Unlink the stack frame
    62                 rts                     * Return to caller
    63 *
     27
     28_vputcv:        link    a6,#0           | Link stack frame pointer
     29                move.w  P_ROW(a6),d0    | Get row
     30                mulu    P_LEN(a6),d0    | Multiply by len
     31                clr.l   d1              | Clear out d1
     32                move.w  P_COL(a6),d1    | Get col
     33                add.l   d1,d0           | Add col into d0 to get char. #
     34                move.l  d0,d1           | Develop cw = (cn/2)|6 in d1
     35                andi.l  #0xFFFFFFFE,d1  | ...
     36                move.l  d1,d2           | ...
     37                add.l   d1,d1           | ...
     38                add.l   d2,d1           | ...
     39                add.l   P_ADR(a6),d1    | Add sbase to cw
     40                movea.l d1,a0           | a0 points at the word with the char.
     41                btst.l  #0,d0           | Odd char. location ?
     42                bne     vputcv1         | Jump if so
     43
     44                move.w  P_CHR(a6),d0    | Get chr
     45                andi.w  #0x00FF,d0      | Mask off garbage bits
     46                move.w  (a0),d1         | Get word from video RAM
     47                andi.w  #0xFF00,d1      | Mask off old even character
     48                or.w    d0,d1           | OR in the new character
     49                move.w  d1,(a0)+        | Store the updated word in video RAM
     50                bra     vputcvx         | Done -- go return to caller
     51
     52vputcv1:        move.w  P_CHR(a6),d0    | Get chr
     53                lsl.w   #8,d0           | Shift to high (odd) byte
     54                move.w  (a0),d1         | Get word from video RAM
     55                andi.w  #0x00FF,d1      | Mask off old odd character
     56                or.w    d0,d1           | OR in the new character
     57                move.w  d1,(a0)+        | Store the updated word in video RAM
     58                addq.l  #2,a0           | Point at the attribute word
     59
     60vputcvx:        move.w  P_ATR(a6),(a0)  | Store new attributes in video RAM
     61                unlk    a6              | Unlink the stack frame
     62                rts                     | Return to caller
     63
    6464                .end
  • vlib/vputp.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vputp.s -- put a pixel into a 4-bit per pixel bitmap object
    3 * Version 4 -- 1987-08-04 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *       int
    7 *       vputp(octad, xloc, yloc, val)
    8 *       struct octent *octad;
    9 *       int xloc, yloc;
    10 *
    11 *               Puts the pixel value 'val' at ('xloc','yloc') in the
    12 *               4-bit per pixel bitmap object described by 'octad'.
    13 *
    14 *       -----
    15 *       struct octent {
    16 *
    17 *               uint    ysize,
    18 *                       xsize;
    19 *
    20 *               int     objx,
    21 *                       objy;
    22 *
    23 *               uint    *obase;
    24 *
    25 *               char    opri,
    26 *                       obank;
    27 *
    28 *               uint    odtw0,
    29 *                       odtw1;
    30 *       };
    31 *
     1| ------------------------------------------------------------------------------
     2| vputp.s -- put a pixel into a 4-bit per pixel bitmap object
     3| Version 4 -- 1987-08-04 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6|       int
     7|       vputp(octad, xloc, yloc, val)
     8|       struct octent |octad;
     9|       int xloc, yloc;
     10
     11|               Puts the pixel value 'val' at ('xloc','yloc') in the
     12|               4-bit per pixel bitmap object described by 'octad'.
     13
     14|       -----
     15|       struct octent {
     16
     17|               uint    ysize,
     18|                       xsize;
     19
     20|               int     objx,
     21|                       objy;
     22
     23|               uint    |obase;
     24
     25|               char    opri,
     26|                       obank;
     27
     28|               uint    odtw0,
     29|                       odtw1;
     30|       };
     31
    3232                .text
    33 *
     33
    3434                .xdef   _vputp
    35 *
    36 OCTAD           .equ    8
    37 XLOC            .equ    12
    38 YLOC            .equ    14
    39 VAL             .equ    16
    40 *
    41 YSIZE           .equ    0
    42 XSIZE           .equ    2
    43 OBJX            .equ    4
    44 OBJY            .equ    6
    45 OBASE           .equ    8
    46 OPRI            .equ    12
    47 OBANK           .equ    13
    48 ODTW0           .equ    14
    49 ODTW1           .equ    16
    50 *
     35
     36OCTAD           =       8
     37XLOC            =       12
     38YLOC            =       14
     39VAL             =       16
     40
     41YSIZE           =       0
     42XSIZE           =       2
     43OBJX            =       4
     44OBJY            =       6
     45OBASE           =       8
     46OPRI            =       12
     47OBANK           =       13
     48ODTW0           =       14
     49ODTW1           =       16
     50
    5151                .page
    52 *
    53 _vputp:         link    a6,#0                   * Link stack frames
    54                 movea.l OCTAD(a6),a1            * Get OCTAD base into a1
    55                 move.w  XLOC(a6),d0             * Get XLOC into d0
    56                 cmp.w   XSIZE(a1),d0            * Check XLOC range
    57                 bge     vputerr                 * ERROR if too large
    58 *
    59                 tst.w   d0                      * Check XLOC sign
    60                 bmi     vputerr                 * ERROR if negative
    61 *
    62                 move.w  YLOC(a6),d1             * Get YLOC into d1 to test
    63                 cmp.w   YSIZE(a1),d1            * Check YLOC range
    64                 bge     vputerr                 * ERROR if too large
    65 *
    66                 tst.w   d1                      * Check YLOC sign
    67                 bmi     vputerr                 * ERROR if negative
    68 *
    69                 lsr.w   #2,d0                   * Divide XLOC by 4
    70                 move.w  XSIZE(a1),d1            * Get width into d1
    71                 lsr.w   #2,d1                   * Divide width by 4
    72                 mulu    YLOC(a6),d1             * Multiply width/4 by YLOC
    73                 ext.l   d0                      * Extend XLOC/4 to a long
    74                 add.l   d0,d1                   * ... and add it to d1
    75                 lsl.l   #1,d1                   * Make d1 a word offset
    76                 add.l   OBASE(a1),d1            * Add OBASE to d1
    77                 movea.l d1,a0                   * Make a0 point at bitmap data
    78                 move.w  XLOC(a6),d0             * Get XLOC
    79                 andi.l  #$03,d0                 * Mask to low 2 bits
    80                 add.l   d0,d0                   * Multiply by 2 for word index
    81                 move.l  d0,d1                   * Save index in d1
    82                 add.l   #MTAB,d0                * Add mask table base
    83                 movea.l d0,a2                   * a2 points at mask
    84                 add.l   #STAB,d1                * Add shift table base to index
    85                 move.l  d1,a1                   * a1 points at shift count
    86                 move.w  (a1),d0                 * Get shift count in d0
    87                 move.w  VAL(a6),d1              * Get new pixel in d1
    88                 andi.w  #$0F,d1                 * Mask down to 4 bits
    89                 lsl.w   d0,d1                   * Shift into position for OR
    90                 move.w  (a0),d0                 * Get old bitmap word in d0
    91                 and.w   (a2),d0                 * Mask out old pixel
    92                 or.w    d1,d0                   * OR in new pixel
    93                 move.w  d0,(a0)                 * Store updated word in bitmap
    94                 clr.l   d0                      * Set return value = 0 = OK
    95 *
    96 vputexit:       unlk    a6                      * Unlink stack frame
    97                 rts                             * Return to caller
    98 *
    99 vputerr:        moveq.l #-1,d0                  * Set return value = -1 = ERROR
    100                 bra     vputexit                * Go unlink stack and return
    101 *
     52
     53_vputp:         link    a6,#0                   | Link stack frames
     54                movea.l OCTAD(a6),a1            | Get OCTAD base into a1
     55                move.w  XLOC(a6),d0             | Get XLOC into d0
     56                cmp.w   XSIZE(a1),d0            | Check XLOC range
     57                bge     vputerr                 | ERROR if too large
     58
     59                tst.w   d0                      | Check XLOC sign
     60                bmi     vputerr                 | ERROR if negative
     61
     62                move.w  YLOC(a6),d1             | Get YLOC into d1 to test
     63                cmp.w   YSIZE(a1),d1            | Check YLOC range
     64                bge     vputerr                 | ERROR if too large
     65
     66                tst.w   d1                      | Check YLOC sign
     67                bmi     vputerr                 | ERROR if negative
     68
     69                lsr.w   #2,d0                   | Divide XLOC by 4
     70                move.w  XSIZE(a1),d1            | Get width into d1
     71                lsr.w   #2,d1                   | Divide width by 4
     72                mulu    YLOC(a6),d1             | Multiply width/4 by YLOC
     73                ext.l   d0                      | Extend XLOC/4 to a long
     74                add.l   d0,d1                   | ... and add it to d1
     75                lsl.l   #1,d1                   | Make d1 a word offset
     76                add.l   OBASE(a1),d1            | Add OBASE to d1
     77                movea.l d1,a0                   | Make a0 point at bitmap data
     78                move.w  XLOC(a6),d0             | Get XLOC
     79                andi.l  #0x03,d0                | Mask to low 2 bits
     80                add.l   d0,d0                   | Multiply by 2 for word index
     81                move.l  d0,d1                   | Save index in d1
     82                add.l   #MTAB,d0                | Add mask table base
     83                movea.l d0,a2                   | a2 points at mask
     84                add.l   #STAB,d1                | Add shift table base to index
     85                move.l  d1,a1                   | a1 points at shift count
     86                move.w  (a1),d0                 | Get shift count in d0
     87                move.w  VAL(a6),d1              | Get new pixel in d1
     88                andi.w  #0x0F,d1                | Mask down to 4 bits
     89                lsl.w   d0,d1                   | Shift into position for OR
     90                move.w  (a0),d0                 | Get old bitmap word in d0
     91                and.w   (a2),d0                 | Mask out old pixel
     92                or.w    d1,d0                   | OR in new pixel
     93                move.w  d0,(a0)                 | Store updated word in bitmap
     94                clr.l   d0                      | Set return value = 0 = OK
     95
     96vputexit:       unlk    a6                      | Unlink stack frame
     97                rts                             | Return to caller
     98
     99vputerr:        moveq.l #-1,d0                  | Set return value = -1 = ERROR
     100                bra     vputexit                | Go unlink stack and return
     101
    102102                .page
    103 *
     103
    104104                .data
    105 *
    106 MTAB:           dc.w    $FFF0,$FF0F,$F0FF,$0FFF * Mask table
    107 STAB:           dc.w    0,4,8,12                * Shift table
    108 *
     105
     106MTAB:           dc.w    0xFFF0,0xFF0F,0xF0FF,0x0FFF     | Mask table
     107STAB:           dc.w    0,4,8,12                | Shift table
     108
    109109                .end
  • vlib/vsetav.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vsetav.s -- set a character's attributes in video RAM
    3 * Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
    4 * (c) Copyright 1988 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vsetav(adr, row, col, atr, len)
    8 *       unsigned int *adr, row, col, atr, len;
    9 *
    10 *               Sets attribute 'atr' at ('row', 'col') in the
    11 *               full attribute text object at 'adr'
    12 *               using a line length of 'len'.
    13 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vsetav.s -- set a character's attributes in video RAM
     3| Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
     4| (c) Copyright 1988 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vsetav(adr, row, col, atr, len)
     8|       unsigned int |adr, row, col, atr, len;
     9
     10|               Sets attribute 'atr' at ('row', 'col') in the
     11|               full attribute text object at 'adr'
     12|               using a line length of 'len'.
     13| ------------------------------------------------------------------------------
    1414                .text
    15 *
     15
    1616                .xdef   _vsetav
    17 *
    18 P_ADR           .equ    8
    19 P_ROW           .equ    12
    20 P_COL           .equ    14
    21 P_ATR           .equ    16
    22 P_LEN           .equ    18
    23 *
    24 _vsetav:        link    a6,#0           * Link stack frame pointer
    25                 move.w  P_ROW(a6),d0    * Get row
    26                 mulu    P_LEN(a6),d0    * Multiply by len
    27                 clr.l   d1              * Clear out d1
    28                 move.w  P_COL(a6),d1    * Get col
    29                 add.l   d1,d0           * Add col into d0 to get char. #
    30                 move.l  d0,d1           * Develop cw = (cn/2)*6 in d1
    31                 andi.l  #$FFFFFFFE,d1   * ...
    32                 move.l  d1,d2           * ...
    33                 add.l   d1,d1           * ...
    34                 add.l   d2,d1           * ...
    35                 add.l   P_ADR(a6),d1    * Add sbase to cw
    36                 movea.l d1,a0           * a0 points at the word with the char.
    37                 btst.l  #0,d0           * Odd char. location ?
    38                 bne     vsetav1         * Jump if so
    39 *
    40                 addq.l  #2,a0           * Point at the attribute word
    41                 bra     vsetavx         * Go set attribute
    42 *
    43 vsetav1:        addq.l  #4,a0           * Point at the attribute word
    44 *
    45 vsetavx:        move.w  P_ATR(a6),d0    * Get new attributes
    46                 or.w    d0,(a0)         * Set new attributes in video RAM
    47                 unlk    a6              * Unlink the stack frame
    48                 rts                     * Return to caller
    49 *
     17
     18P_ADR           =       8
     19P_ROW           =       12
     20P_COL           =       14
     21P_ATR           =       16
     22P_LEN           =       18
     23
     24_vsetav:        link    a6,#0           | Link stack frame pointer
     25                move.w  P_ROW(a6),d0    | Get row
     26                mulu    P_LEN(a6),d0    | Multiply by len
     27                clr.l   d1              | Clear out d1
     28                move.w  P_COL(a6),d1    | Get col
     29                add.l   d1,d0           | Add col into d0 to get char. #
     30                move.l  d0,d1           | Develop cw = (cn/2)|6 in d1
     31                andi.l  #0xFFFFFFFE,d1  | ...
     32                move.l  d1,d2           | ...
     33                add.l   d1,d1           | ...
     34                add.l   d2,d1           | ...
     35                add.l   P_ADR(a6),d1    | Add sbase to cw
     36                movea.l d1,a0           | a0 points at the word with the char.
     37                btst.l  #0,d0           | Odd char. location ?
     38                bne     vsetav1         | Jump if so
     39
     40                addq.l  #2,a0           | Point at the attribute word
     41                bra     vsetavx         | Go set attribute
     42
     43vsetav1:        addq.l  #4,a0           | Point at the attribute word
     44
     45vsetavx:        move.w  P_ATR(a6),d0    | Get new attributes
     46                or.w    d0,(a0)         | Set new attributes in video RAM
     47                unlk    a6              | Unlink the stack frame
     48                rts                     | Return to caller
     49
    5050                .end
  • vlib/vsetcv.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vsetcv.s -- set a character's colors in video RAM
    3 * Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
    4 * (c) Copyright 1988 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vsetcv(adr, row, col, cfb, len)
    8 *       unsigned int *adr, row, col, cfb, len;
    9 *
    10 *               Sets colors 'cfb' at ('row', 'col') in the
    11 *               full attribute text object at 'adr'
    12 *               using a line length of 'len'.
    13 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vsetcv.s -- set a character's colors in video RAM
     3| Version 1 -- 1988-10-11 -- D.N. Lynx Crowe
     4| (c) Copyright 1988 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vsetcv(adr, row, col, cfb, len)
     8|       unsigned int |adr, row, col, cfb, len;
     9
     10|               Sets colors 'cfb' at ('row', 'col') in the
     11|               full attribute text object at 'adr'
     12|               using a line length of 'len'.
     13| ------------------------------------------------------------------------------
    1414                .text
    15 *
     15
    1616                .xdef   _vsetcv
    17 *
    18 P_ADR           .equ    8
    19 P_ROW           .equ    12
    20 P_COL           .equ    14
    21 P_CFB           .equ    16
    22 P_LEN           .equ    18
    23 *
    24 _vsetcv:        link    a6,#0           * Link stack frame pointer
    25                 move.w  P_ROW(a6),d0    * Get row
    26                 mulu    P_LEN(a6),d0    * Multiply by len
    27                 clr.l   d1              * Clear out d1
    28                 move.w  P_COL(a6),d1    * Get col
    29                 add.l   d1,d0           * Add col into d0 to get char. #
    30                 move.l  d0,d1           * Develop cw = (cn/2)*6 in d1
    31                 andi.l  #$FFFFFFFE,d1   * ...
    32                 move.l  d1,d2           * ...
    33                 add.l   d1,d1           * ...
    34                 add.l   d2,d1           * ...
    35                 add.l   P_ADR(a6),d1    * Add sbase to cw
    36                 movea.l d1,a0           * a0 points at the word with the char.
    37                 btst.l  #0,d0           * Odd char. location ?
    38                 bne     vsetcv1         * Jump if so
    39 *
    40                 addq.l  #2,a0           * Point at the attribute word
    41                 bra     vsetcvx         * Go set attribute
    42 *
    43 vsetcv1:        addq.l  #4,a0           * Point at the attribute word
    44 *
    45 vsetcvx:        move.w  (a0),d0         * Get old attributes
    46                 andi.w  #$FF00,d0       * Remove old colors
    47                 or.w    P_CFB(a6),d0    * Get new colors
    48                 move.w  d0,(a0)         * Set new attributes in video RAM
    49                 unlk    a6              * Unlink the stack frame
    50                 rts                     * Return to caller
    51 *
     17
     18P_ADR           =       8
     19P_ROW           =       12
     20P_COL           =       14
     21P_CFB           =       16
     22P_LEN           =       18
     23
     24_vsetcv:        link    a6,#0           | Link stack frame pointer
     25                move.w  P_ROW(a6),d0    | Get row
     26                mulu    P_LEN(a6),d0    | Multiply by len
     27                clr.l   d1              | Clear out d1
     28                move.w  P_COL(a6),d1    | Get col
     29                add.l   d1,d0           | Add col into d0 to get char. #
     30                move.l  d0,d1           | Develop cw = (cn/2)|6 in d1
     31                andi.l  #0xFFFFFFFE,d1  | ...
     32                move.l  d1,d2           | ...
     33                add.l   d1,d1           | ...
     34                add.l   d2,d1           | ...
     35                add.l   P_ADR(a6),d1    | Add sbase to cw
     36                movea.l d1,a0           | a0 points at the word with the char.
     37                btst.l  #0,d0           | Odd char. location ?
     38                bne     vsetcv1         | Jump if so
     39
     40                addq.l  #2,a0           | Point at the attribute word
     41                bra     vsetcvx         | Go set attribute
     42
     43vsetcv1:        addq.l  #4,a0           | Point at the attribute word
     44
     45vsetcvx:        move.w  (a0),d0         | Get old attributes
     46                andi.w  #0xFF00,d0      | Remove old colors
     47                or.w    P_CFB(a6),d0    | Get new colors
     48                move.w  d0,(a0)         | Set new attributes in video RAM
     49                unlk    a6              | Unlink the stack frame
     50                rts                     | Return to caller
     51
    5252                .end
  • vlib/vsplot4.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vsplot4.s -- output characters to a 4-bit / pixel graphics window
    3 *    with variable vertical pitch, etc.
    4 * Version 1 -- 1988-10-07 -- D.N. Lynx Crowe
    5 * (c) Copyright 1988 -- D.N. Lynx Crowe
    6 * ------------------------------------------------------------------------------
    7 *
    8 *       vsplot4(obase, nw, fg, row, col, str, pitch, ht, cgtab)
    9 *       uint *obase, nw, fg, row, col, pitch, ht, cgtab[][256];
    10 *       char *str;
    11 *
    12 *               Outputs characters from the string at 'str' to an 'nw'
    13 *               character wide 4-bit per pixel graphics window at 'obase'
    14 *               at ('row','col'), using 'fg' as the foreground color.
    15 *               Uses cgtab[][256] as the VSDD formatted character
    16 *               generator table.  Assumes 'ht' bit high characters in the
    17 *               cgtable.  Uses 'pitch' as the vertical spacing between
    18 *               character rows.  No error checks are done.
    19 *               The string must fit the output area (no overlaps, single line).
    20 *               This function leaves the zero pixels alone and just sets the
    21 *               one pixels to the foreground color, allowing overlapping
    22 *               character cells.
    23 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vsplot4.s -- output characters to a 4-bit / pixel graphics window
     3|    with variable vertical pitch, etc.
     4| Version 1 -- 1988-10-07 -- D.N. Lynx Crowe
     5| (c) Copyright 1988 -- D.N. Lynx Crowe
     6| ------------------------------------------------------------------------------
     7
     8|       vsplot4(obase, nw, fg, row, col, str, pitch, ht, cgtab)
     9|       uint |obase, nw, fg, row, col, pitch, ht, cgtab[][256];
     10|       char |str;
     11
     12|               Outputs characters from the string at 'str' to an 'nw'
     13|               character wide 4-bit per pixel graphics window at 'obase'
     14|               at ('row','col'), using 'fg' as the foreground color.
     15|               Uses cgtab[][256] as the VSDD formatted character
     16|               generator table.  Assumes 'ht' bit high characters in the
     17|               cgtable.  Uses 'pitch' as the vertical spacing between
     18|               character rows.  No error checks are done.
     19|               The string must fit the output area (no overlaps, single line).
     20|               This function leaves the zero pixels alone and just sets the
     21|               one pixels to the foreground color, allowing overlapping
     22|               character cells.
     23| ------------------------------------------------------------------------------
    2424                .text
    25 *
     25
    2626                .xdef   _vsplot4
    27 *
    28 * Argument offsets from a6:
    29 *
    30 OBASE           .equ    8               * LONG - Output area base address
    31 NW              .equ    12              * WORD - Character width of output area
    32 FG              .equ    14              * WORD - Foreground color
    33 ROW             .equ    16              * WORD - Row
    34 COL             .equ    18              * WORD - Column
    35 STR             .equ    20              * LONG - String base address
    36 PITCH           .equ    24              * WORD - Vertical spacing between rows
    37 HT              .equ    26              * WORD - Character height
    38 CGTAB           .equ    28              * LONG - Character generator pionter
    39 *
    40 * Program constant definitions:
    41 *
    42 HPIX            .equ    8               * Character width in pixels
    43 HCW             .equ    4               * Horizontal character width (bytes)
    44 PSHIFT          .equ    12              * Pixel shift into MS bits
    45 HSHIFT          .equ    4               * Pixel right shift
    46 *
     27
     28| Argument offsets from a6:
     29
     30OBASE           =       8               | LONG - Output area base address
     31NW              =       12              | WORD - Character width of output area
     32FG              =       14              | WORD - Foreground color
     33ROW             =       16              | WORD - Row
     34COL             =       18              | WORD - Column
     35STR             =       20              | LONG - String base address
     36PITCH           =       24              | WORD - Vertical spacing between rows
     37HT              =       26              | WORD - Character height
     38CGTAB           =       28              | LONG - Character generator pionter
     39
     40| Program constant definitions:
     41
     42HPIX            =       8               | Character width in pixels
     43HCW             =       4               | Horizontal character width (bytes)
     44PSHIFT          =       12              | Pixel shift into MS bits
     45HSHIFT          =       4               | Pixel right shift
     46
    4747                .page
    48 *
    49 * Register usage:
    50 *
    51 *       d0      output word and scratch
    52 *       d1      CG word and scratch
    53 *       d2      pixel counter
    54 *
    55 *       d3      foreground color (in the 4 ms bits)
    56 *       d4      background color (in the 4 ms bits)
    57 *       d5      width of the area in bytes
    58 *       d6      scan line counter
    59 *
    60 *       a0      CG table pointer
    61 *       a1      output area scan line pointer
    62 *       a2      input string character pointer
    63 *
    64 *       a3      output area character base pointer
    65 *
    66 *       a6      frame pointer
    67 *       a7      stack pointer
    68 *
     48
     49| Register usage:
     50
     51|       d0      output word and scratch
     52|       d1      CG word and scratch
     53|       d2      pixel counter
     54
     55|       d3      foreground color (in the 4 ms bits)
     56|       d4      background color (in the 4 ms bits)
     57|       d5      width of the area in bytes
     58|       d6      scan line counter
     59
     60|       a0      CG table pointer
     61|       a1      output area scan line pointer
     62|       a2      input string character pointer
     63
     64|       a3      output area character base pointer
     65
     66|       a6      frame pointer
     67|       a7      stack pointer
     68
    6969                .page
    70 *
    71 _vsplot4:       link    a6,#0           * Link stack frames
    72                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    73                 move.w  #PSHIFT,d1      * Set shift constant
    74                 move.w  FG(a6),d3       * Setup foreground color
    75                 lsl.w   d1,d3           * ... in ms 4 bits of d3.W
    76                 move.w  NW(a6),d5       * Get line width in d5.W
    77                 lsl.w   #2,d5           * Multiply width by 4 for offset
    78                 move.w  ROW(a6),d0      * Calculate output address
    79                 move.w  PITCH(a6),d1    * ... PITCH
    80                 mulu    d1,d0           * ... * ROW
    81                 add.w   HT(a6),d0       * ... + HT-1
    82                 subq.w  #1,d0           * ...
    83                 mulu    d5,d0           * ... * NW
    84                 clr.l   d1              * ...
    85                 move.w  COL(a6),d1      * ... +
    86                 lsl.w   #2,d1           * ... COL * 4
    87                 add.l   d1,d0           * ...
    88                 add.l   OBASE(a6),d0    * ... + OBASE
    89                 movea.l d0,a3           * Leave output address in a3
    90                 movea.l STR(a6),a2      * Put string address in a2
    91 *
    92 cgl0:           clr.l   d0              * Clear out upper bits of d0
    93                 move.b  (a2)+,d0        * Get next character
    94                 beq     cgl5            * Done if character EQ 0
    95 *
    96                 movea.l a3,a1           * Establish output pointer in a1
    97                 adda.l  #HCW,a3         * Update output pointer for next char.
    98                 movea.l CGTAB(a6),a0    * Establish CG pointer in a0
    99                 lsl.w   #1,d0           * ... 2 * character
    100                 adda.w  d0,a0           * ... + cgtab address
    101                 move.w  HT(a6),d6       * Set scan line counter in d6
    102                 subq.w  #1,d6           * ...
    103 *
     70
     71_vsplot4:       link    a6,#0           | Link stack frames
     72                movem.l d3-d6/a3,-(a7)  | Save registers we use
     73                move.w  #PSHIFT,d1      | Set shift constant
     74                move.w  FG(a6),d3       | Setup foreground color
     75                lsl.w   d1,d3           | ... in ms 4 bits of d3.W
     76                move.w  NW(a6),d5       | Get line width in d5.W
     77                lsl.w   #2,d5           | Multiply width by 4 for offset
     78                move.w  ROW(a6),d0      | Calculate output address
     79                move.w  PITCH(a6),d1    | ... PITCH
     80                mulu    d1,d0           | ... | ROW
     81                add.w   HT(a6),d0       | ... + HT-1
     82                subq.w  #1,d0           | ...
     83                mulu    d5,d0           | ... | NW
     84                clr.l   d1              | ...
     85                move.w  COL(a6),d1      | ... +
     86                lsl.w   #2,d1           | ... COL | 4
     87                add.l   d1,d0           | ...
     88                add.l   OBASE(a6),d0    | ... + OBASE
     89                movea.l d0,a3           | Leave output address in a3
     90                movea.l STR(a6),a2      | Put string address in a2
     91
     92cgl0:           clr.l   d0              | Clear out upper bits of d0
     93                move.b  (a2)+,d0        | Get next character
     94                beq     cgl5            | Done if character EQ 0
     95
     96                movea.l a3,a1           | Establish output pointer in a1
     97                adda.l  #HCW,a3         | Update output pointer for next char.
     98                movea.l CGTAB(a6),a0    | Establish CG pointer in a0
     99                lsl.w   #1,d0           | ... 2 | character
     100                adda.w  d0,a0           | ... + cgtab address
     101                move.w  HT(a6),d6       | Set scan line counter in d6
     102                subq.w  #1,d6           | ...
     103
    104104                .page
    105 cgl1:           move.w  (a0),d1         * Get character generator word in d1
    106                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    107                 clr.l   d4              * Get old output word as background
    108                 move.w  (a1),d4         * ...
    109                 swap    d4              * ...
    110 *
    111 cgl2:           lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    112                 lsr.l   #HSHIFT,d4      * Shift background word 1 pixel
    113                 andi.l  #$FFFFF000,d4   * Mask for upper 4 bits of d4.W
    114                 btst.l  #0,d1           * Check CG word ls bit
    115                 beq     cgl3            * Set background color if bit EQ 0
    116 *
    117                 or.w    d3,d0           * OR foreground color into output word
    118                 bra     cgl4            * Go update CG word
    119 *
    120 cgl3:           or.w    d4,d0           * OR background color into output word
    121 *
    122 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    123                 dbf     d2,cgl2         * Loop for first 4 pixels
    124 *
    125                 move.w  d0,(a1)+        * Store first output word in scan line
    126                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    127                 clr.l   d4              * Get old output word as background
    128                 move.w  (a1),d4         * ...
    129                 swap    d4              * ...
    130 *
    131 cgl2a:          lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    132                 lsr.l   #HSHIFT,d4      * Shift background word 1 pixel
    133                 andi.l  #$FFFFF000,d4   * Mask for upper bits of d4.W
    134                 btst.l  #0,d1           * Check CG word ls bit
    135                 beq     cgl3a           * Set background color if bit EQ 0
    136 *
    137                 or.w    d3,d0           * OR foreground color into output word
    138                 bra     cgl4a           * Go update CG word
    139 *
    140 cgl3a:          or.w    d4,d0           * OR background color into output word
    141 *
    142 cgl4a:          lsr.w   #1,d1           * Shift CG word right 1 pixel
    143                 dbf     d2,cgl2a        * Loop for last 4 pixels
    144 *
    145                 move.w  d0,(a1)         * Store second output word in scan line
    146                 suba.w  d5,a1           * Update output pointer
    147                 suba.w  #2,a1           * ...
    148                 adda.l  #512,a0         * Update CG pointer for next scan line
    149                 dbf     d6,cgl1         * Loop for all scan lines
    150 *
    151                 bra     cgl0            * Loop for next character
    152 *
    153 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    154                 unlk    a6              * Unlink stack frames
    155                 rts                     * Return to caller
    156 *
     105cgl1:           move.w  (a0),d1         | Get character generator word in d1
     106                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     107                clr.l   d4              | Get old output word as background
     108                move.w  (a1),d4         | ...
     109                swap    d4              | ...
     110
     111cgl2:           lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     112                lsr.l   #HSHIFT,d4      | Shift background word 1 pixel
     113                andi.l  #0xFFFFF000,d4  | Mask for upper 4 bits of d4.W
     114                btst.l  #0,d1           | Check CG word ls bit
     115                beq     cgl3            | Set background color if bit EQ 0
     116
     117                or.w    d3,d0           | OR foreground color into output word
     118                bra     cgl4            | Go update CG word
     119
     120cgl3:           or.w    d4,d0           | OR background color into output word
     121
     122cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     123                dbf     d2,cgl2         | Loop for first 4 pixels
     124
     125                move.w  d0,(a1)+        | Store first output word in scan line
     126                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     127                clr.l   d4              | Get old output word as background
     128                move.w  (a1),d4         | ...
     129                swap    d4              | ...
     130
     131cgl2a:          lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     132                lsr.l   #HSHIFT,d4      | Shift background word 1 pixel
     133                andi.l  #0xFFFFF000,d4  | Mask for upper bits of d4.W
     134                btst.l  #0,d1           | Check CG word ls bit
     135                beq     cgl3a           | Set background color if bit EQ 0
     136
     137                or.w    d3,d0           | OR foreground color into output word
     138                bra     cgl4a           | Go update CG word
     139
     140cgl3a:          or.w    d4,d0           | OR background color into output word
     141
     142cgl4a:          lsr.w   #1,d1           | Shift CG word right 1 pixel
     143                dbf     d2,cgl2a        | Loop for last 4 pixels
     144
     145                move.w  d0,(a1)         | Store second output word in scan line
     146                suba.w  d5,a1           | Update output pointer
     147                suba.w  #2,a1           | ...
     148                adda.l  #512,a0         | Update CG pointer for next scan line
     149                dbf     d6,cgl1         | Loop for all scan lines
     150
     151                bra     cgl0            | Loop for next character
     152
     153cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     154                unlk    a6              | Unlink stack frames
     155                rts                     | Return to caller
     156
    157157                .end
  • vlib/vvputsv.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vvputsv.s -- output characters to a 4-bit / pixel graphics window
    3 * with variable vertical pitch
    4 * Version 1 -- 1988-10-07 -- D.N. Lynx Crowe
    5 * (c) Copyright 1988 -- D.N. Lynx Crowe
    6 * ------------------------------------------------------------------------------
    7 *
    8 *       vvputsv(obase, nw, fg, bg, row, col, str, pitch, ht, cgtab)
    9 *       uint *obase, nw, fg, bg, row, col, pitch, ht, cgtab[][256];
    10 *       char *str;
    11 *
    12 *               Outputs characters from the string at 'str' to an 'nw'
    13 *               character wide 4-bit per pixel graphics window at 'obase'
    14 *               at ('row','col'), using 'fg' as the foreground color, and
    15 *               'bg' as the background color.  Uses cgtab[][256] as the
    16 *               VSDD formatted character generator table.  Assumes 'ht' line
    17 *               high characters in the cg table.  Uses 'pitch' as the vertical
    18 *               spacing between character rows.  No error checks are done.
    19 *               The string must fit the output area (no overlaps, single line).
    20 *
    21 * ------------------------------------------------------------------------------
     1| ------------------------------------------------------------------------------
     2| vvputsv.s -- output characters to a 4-bit / pixel graphics window
     3| with variable vertical pitch
     4| Version 1 -- 1988-10-07 -- D.N. Lynx Crowe
     5| (c) Copyright 1988 -- D.N. Lynx Crowe
     6| ------------------------------------------------------------------------------
     7
     8|       vvputsv(obase, nw, fg, bg, row, col, str, pitch, ht, cgtab)
     9|       uint |obase, nw, fg, bg, row, col, pitch, ht, cgtab[][256];
     10|       char |str;
     11
     12|               Outputs characters from the string at 'str' to an 'nw'
     13|               character wide 4-bit per pixel graphics window at 'obase'
     14|               at ('row','col'), using 'fg' as the foreground color, and
     15|               'bg' as the background color.  Uses cgtab[][256] as the
     16|               VSDD formatted character generator table.  Assumes 'ht' line
     17|               high characters in the cg table.  Uses 'pitch' as the vertical
     18|               spacing between character rows.  No error checks are done.
     19|               The string must fit the output area (no overlaps, single line).
     20
     21| ------------------------------------------------------------------------------
    2222                .text
    23 *
     23
    2424                .xdef   _vvputsv
    25 *
    26 * Argument offsets from a6:
    27 *
    28 OBASE           .equ    8               * LONG - Output area base address
    29 NW              .equ    12              * WORD - Character width of output area
    30 FG              .equ    14              * WORD - Foreground color
    31 BG              .equ    16              * WORD - Background color
    32 ROW             .equ    18              * WORD - Row
    33 COL             .equ    20              * WORD - Column
    34 STR             .equ    22              * LONG - String base address
    35 PITCH           .equ    26              * WORD - Vertical spacing between rows
    36 HT              .equ    28              * WORD - Character height  (LE PITCH)
    37 CGTAB           .equ    30              * LONG - Character generator table
    38 *
    39 * Program constant definitions:
    40 *
    41 HPIX            .equ    8               * Character width in pixels
    42 HCW             .equ    4               * Horizontal character width (bytes)
    43 PSHIFT          .equ    12              * Pixel shift into MS bits
    44 HSHIFT          .equ    4               * Pixel right shift
    45 *
     25
     26| Argument offsets from a6:
     27
     28OBASE           =       8               | LONG - Output area base address
     29NW              =       12              | WORD - Character width of output area
     30FG              =       14              | WORD - Foreground color
     31BG              =       16              | WORD - Background color
     32ROW             =       18              | WORD - Row
     33COL             =       20              | WORD - Column
     34STR             =       22              | LONG - String base address
     35PITCH           =       26              | WORD - Vertical spacing between rows
     36HT              =       28              | WORD - Character height  (LE PITCH)
     37CGTAB           =       30              | LONG - Character generator table
     38
     39| Program constant definitions:
     40
     41HPIX            =       8               | Character width in pixels
     42HCW             =       4               | Horizontal character width (bytes)
     43PSHIFT          =       12              | Pixel shift into MS bits
     44HSHIFT          =       4               | Pixel right shift
     45
    4646                .page
    47 *
    48 * Register usage:
    49 *
    50 *       d0      output word and scratch
    51 *       d1      CG word and scratch
    52 *       d2      pixel counter
    53 *
    54 *       d3      foreground color (in the 4 ms bits)
    55 *       d4      background color (in the 4 ms bits)
    56 *       d5      width of the area in bytes
    57 *       d6      scan line counter
    58 *
    59 *       a0      CG table pointer
    60 *       a1      output area scan line pointer
    61 *       a2      input string character pointer
    62 *
    63 *       a3      output area character base pointer
    64 *
    65 *       a6      frame pointer
    66 *       a7      stack pointer
    67 *
     47
     48| Register usage:
     49
     50|       d0      output word and scratch
     51|       d1      CG word and scratch
     52|       d2      pixel counter
     53
     54|       d3      foreground color (in the 4 ms bits)
     55|       d4      background color (in the 4 ms bits)
     56|       d5      width of the area in bytes
     57|       d6      scan line counter
     58
     59|       a0      CG table pointer
     60|       a1      output area scan line pointer
     61|       a2      input string character pointer
     62
     63|       a3      output area character base pointer
     64
     65|       a6      frame pointer
     66|       a7      stack pointer
     67
    6868                .page
    69 *
    70 _vvputsv:       link    a6,#0           * Link stack frames
    71                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    72                 move.w  #PSHIFT,d1      * Set shift constant
    73                 move.w  FG(a6),d3       * Setup foreground color
    74                 lsl.w   d1,d3           * ... in ms 4 bits of d3.W
    75                 move.w  BG(a6),d4       * Setup background color
    76                 lsl.w   d1,d4           * ... in ms 4 bits of d4.W
    77                 move.w  NW(a6),d5       * Get line width in d5.W
    78                 lsl.w   #2,d5           * Multiply width by 4 for offset
    79                 move.w  ROW(a6),d0      * Calculate output address
    80                 move.w  PITCH(a6),d1    * ... PITCH
    81                 mulu    d1,d0           * ... * ROW
    82                 add.w   #HT(a6),d0      * ... + HT-1
    83                 subq.w  #1,d0           * ...
    84                 mulu    d5,d0           * ... * NW
    85                 clr.l   d1              * ...
    86                 move.w  COL(a6),d1      * ... +
    87                 lsl.w   #2,d1           * ... COL * 4
    88                 add.l   d1,d0           * ...
    89                 add.l   OBASE(a6),d0    * ... + OBASE
    90                 movea.l d0,a3           * Leave output address in a3
    91                 movea.l STR(a6),a2      * Put string address in a2
    92 *
    93 cgl0:           clr.l   d0              * Clear out upper bits of d0
    94                 move.b  (a2)+,d0        * Get next character
    95                 beq     cgl5            * Done if character EQ 0
    96 *
    97                 movea.l a3,a1           * Establish output pointer in a1
    98                 adda.l  #HCW,a3         * Update output pointer for next char.
    99                 movea.l CGTAB(a6),a0    * Establish CG pointer in a0
    100                 lsl.w   #1,d0           * ... 2 * character
    101                 adda.w  d0,a0           * ... + cg table address
    102                 move.w  HT(a6),d6       * Set scan line counter in d6
    103                 subq.w  #1,d6           * ... to HT-1
    104 *
     69
     70_vvputsv:       link    a6,#0           | Link stack frames
     71                movem.l d3-d6/a3,-(a7)  | Save registers we use
     72                move.w  #PSHIFT,d1      | Set shift constant
     73                move.w  FG(a6),d3       | Setup foreground color
     74                lsl.w   d1,d3           | ... in ms 4 bits of d3.W
     75                move.w  BG(a6),d4       | Setup background color
     76                lsl.w   d1,d4           | ... in ms 4 bits of d4.W
     77                move.w  NW(a6),d5       | Get line width in d5.W
     78                lsl.w   #2,d5           | Multiply width by 4 for offset
     79                move.w  ROW(a6),d0      | Calculate output address
     80                move.w  PITCH(a6),d1    | ... PITCH
     81                mulu    d1,d0           | ... | ROW
     82                add.w   HT(a6),d0       | ... + HT-1
     83                subq.w  #1,d0           | ...
     84                mulu    d5,d0           | ... | NW
     85                clr.l   d1              | ...
     86                move.w  COL(a6),d1      | ... +
     87                lsl.w   #2,d1           | ... COL | 4
     88                add.l   d1,d0           | ...
     89                add.l   OBASE(a6),d0    | ... + OBASE
     90                movea.l d0,a3           | Leave output address in a3
     91                movea.l STR(a6),a2      | Put string address in a2
     92
     93cgl0:           clr.l   d0              | Clear out upper bits of d0
     94                move.b  (a2)+,d0        | Get next character
     95                beq     cgl5            | Done if character EQ 0
     96
     97                movea.l a3,a1           | Establish output pointer in a1
     98                adda.l  #HCW,a3         | Update output pointer for next char.
     99                movea.l CGTAB(a6),a0    | Establish CG pointer in a0
     100                lsl.w   #1,d0           | ... 2 | character
     101                adda.w  d0,a0           | ... + cg table address
     102                move.w  HT(a6),d6       | Set scan line counter in d6
     103                subq.w  #1,d6           | ... to HT-1
     104
    105105                .page
    106 cgl1:           move.w  (a0),d1         * Get character generator word in d1
    107                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    108 *
    109 cgl2:           lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    110                 btst.l  #0,d1           * Check CG word ls bit
    111                 beq     cgl3            * Set background color if bit EQ 0
    112 *
    113                 or.w    d3,d0           * OR foreground color into output word
    114                 bra     cgl4            * Go update CG word
    115 *
    116 cgl3:           or.w    d4,d0           * OR background color into output word
    117 *
    118 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    119                 dbf     d2,cgl2         * Loop for first 4 pixels
    120 *
    121                 move.w  d0,(a1)+        * Store first output word in scan line
    122                 move.w  #(HPIX/2)-1,d2  * Set pixel counter in d2
    123 *
    124 cgl2a:          lsr.w   #HSHIFT,d0      * Shift output word right 1 pixel
    125                 btst.l  #0,d1           * Check CG word ls bit
    126                 beq     cgl3a           * Set background color if bit EQ 0
    127 *
    128                 or.w    d3,d0           * OR foreground color into output word
    129                 bra     cgl4a           * Go update CG word
    130 *
    131 cgl3a:          or.w    d4,d0           * OR background color into output word
    132 *
    133 cgl4a:          lsr.w   #1,d1           * Shift CG word right 1 pixel
    134                 dbf     d2,cgl2a        * Loop for last 4 pixels
    135 *
    136                 move.w  d0,(a1)         * Store second output word in scan line
    137                 suba.w  d5,a1           * Update output pointer
    138                 suba.w  #2,a1           * ...
    139                 adda.l  #512,a0         * Update CG pointer for next scan line
    140                 dbf     d6,cgl1         * Loop for all scan lines
    141 *
    142                 bra     cgl0            * Loop for next character
    143 *
    144 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    145                 unlk    a6              * Unlink stack frames
    146                 rts                     * Return to caller
    147 *
     106cgl1:           move.w  (a0),d1         | Get character generator word in d1
     107                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     108
     109cgl2:           lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     110                btst.l  #0,d1           | Check CG word ls bit
     111                beq     cgl3            | Set background color if bit EQ 0
     112
     113                or.w    d3,d0           | OR foreground color into output word
     114                bra     cgl4            | Go update CG word
     115
     116cgl3:           or.w    d4,d0           | OR background color into output word
     117
     118cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     119                dbf     d2,cgl2         | Loop for first 4 pixels
     120
     121                move.w  d0,(a1)+        | Store first output word in scan line
     122                move.w  #(HPIX/2)-1,d2  | Set pixel counter in d2
     123
     124cgl2a:          lsr.w   #HSHIFT,d0      | Shift output word right 1 pixel
     125                btst.l  #0,d1           | Check CG word ls bit
     126                beq     cgl3a           | Set background color if bit EQ 0
     127
     128                or.w    d3,d0           | OR foreground color into output word
     129                bra     cgl4a           | Go update CG word
     130
     131cgl3a:          or.w    d4,d0           | OR background color into output word
     132
     133cgl4a:          lsr.w   #1,d1           | Shift CG word right 1 pixel
     134                dbf     d2,cgl2a        | Loop for last 4 pixels
     135
     136                move.w  d0,(a1)         | Store second output word in scan line
     137                suba.w  d5,a1           | Update output pointer
     138                suba.w  #2,a1           | ...
     139                adda.l  #512,a0         | Update CG pointer for next scan line
     140                dbf     d6,cgl1         | Loop for all scan lines
     141
     142                bra     cgl0            | Loop for next character
     143
     144cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     145                unlk    a6              | Unlink stack frames
     146                rts                     | Return to caller
     147
    148148                .end
  • vlib/vwputp.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vwputp.s -- put a pixel into a 2-bit per pixel bitmap object
    3 * Version 2 -- 1987-04-14 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *       int
    7 *       vwputp(octad, xloc, yloc, val)
    8 *       struct octent *octad;
    9 *       int xloc, yloc;
    10 *
    11 *               Writes the pixel value 'val' into the 2-bit per pixel
    12 *               bitmap object described by 'octad' at ('xloc','yloc').
    13 *
    14 *       -----
    15 *
    16 *       struct octent {
    17 *
    18 *               uint    ysize,
    19 *                       xsize;
    20 *
    21 *               int     objx,
    22 *                       objy;
    23 *
    24 *               uint    *obase;
    25 *
    26 *               char    opri,
    27 *                       oflags;
    28 *
    29 *               uint    odtw0,
    30 *                       odtw1;
    31 *       };
    32 *
    33 *       Upper left corner of screen is (0,0) origin.
    34 *
     1| ------------------------------------------------------------------------------
     2| vwputp.s -- put a pixel into a 2-bit per pixel bitmap object
     3| Version 2 -- 1987-04-14 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6|       int
     7|       vwputp(octad, xloc, yloc, val)
     8|       struct octent |octad;
     9|       int xloc, yloc;
     10
     11|               Writes the pixel value 'val' into the 2-bit per pixel
     12|               bitmap object described by 'octad' at ('xloc','yloc').
     13
     14|       -----
     15
     16|       struct octent {
     17
     18|               uint    ysize,
     19|                       xsize;
     20
     21|               int     objx,
     22|                       objy;
     23
     24|               uint    |obase;
     25
     26|               char    opri,
     27|                       oflags;
     28
     29|               uint    odtw0,
     30|                       odtw1;
     31|       };
     32
     33|       Upper left corner of screen is (0,0) origin.
     34
    3535                .text
    36 *
     36
    3737                .xdef   _vputp
    38 *
    39 OCTAD           .equ    8
    40 XLOC            .equ    12
    41 YLOC            .equ    14
    42 VAL             .equ    16
    43 *
    44 YSIZE           .equ    0
    45 XSIZE           .equ    2
    46 OBJX            .equ    4
    47 OBJY            .equ    6
    48 OBASE           .equ    8
    49 OPRI            .equ    12
    50 OFLAGS          .equ    13
    51 ODTW0           .equ    14
    52 ODTW1           .equ    16
    53 *
     38
     39OCTAD           =       8
     40XLOC            =       12
     41YLOC            =       14
     42VAL             =       16
     43
     44YSIZE           =       0
     45XSIZE           =       2
     46OBJX            =       4
     47OBJY            =       6
     48OBASE           =       8
     49OPRI            =       12
     50OFLAGS          =       13
     51ODTW0           =       14
     52ODTW1           =       16
     53
    5454                .page
    55 *
    56 _vwputp:        link    a6,#0                   * Link stack frames
    57                 movea.l OCTAD(a6),a1            * Get OCTAD base into a1
    58                 move.w  XLOC(a6),d0             * Get XLOC into d0
    59                 cmp.w   XSIZE(a1),d0            * Check XLOC range
    60                 bge     vputerr                 * ERROR if too large
    61 *
    62                 tst.w   d0                      * Check XLOC sign
    63                 bmi     vputerr                 * ERROR if negative
    64 *
    65                 move.w  YLOC(a6),d1             * Get YLOC into d1 to test
    66                 cmp.w   YSIZE(a1),d1            * Check YLOC range
    67                 bge     vputerr                 * ERROR if too large
    68 *
    69                 tst.w   d1                      * Check YLOC sign
    70                 bmi     vputerr                 * ERROR if negative
    71 *
    72                 lsr.w   #3,d0                   * Divide XLOC by 8
    73                 move.w  XSIZE(a1),d1            * Get width into d1
    74                 lsr.w   #3,d1                   * Divide width by 8
    75                 mulu    YLOC(a6),d1             * Multiply width/8 by YLOC
    76                 ext.l   d0                      * Extend XLOC/8 to a long
    77                 add.l   d0,d1                   * ... and add it to d1
    78                 add.l   OBASE(a1),d1            * Add OBASE to d1
    79                 movea.l d1,a0                   * Make a0 point at bitmap data
    80                 move.w  XLOC(a6),d0             * Get XLOC
    81                 andi.l  #$07,d0                 * Mask to low 3 bits
    82                 add.l   d0,d0                   * Multiply by 2 for word index
    83                 move.l  d0,d1                   * Save index in d1
    84                 add.l   #MTAB,d0                * Add mask table base
    85                 movea.l d0,a2                   * a2 points at mask
    86                 add.l   #STAB,d1                * Add shift table base to index
    87                 move.l  d1,a1                   * a1 points at shift count
    88                 move.w  (a1),d0                 * Get shift count in d0
    89                 move.w  VAL(a6),d1              * Get new pixel in d1
    90                 andi.w  #$03,d1                 * Mask down to 2 bits
    91                 lsl.w   d0,d1                   * Shift into position for OR
    92                 move.w  (a0),d0                 * Get old bitmap word in d0
    93                 and.w   (a2),d0                 * Mask out old pixel
    94                 or.w    d1,d0                   * OR in new pixel
    95                 move.w  d0,(a0)                 * Store updated word in bitmap
    96                 clr.l   d0                      * Set return value = 0 = OK
    97 *
    98 vputexit:       unlk    a6                      * Unlink stack frame
    99                 rts                             * Return to caller
    100 *
    101 vputerr:        moveq.l #-1,d0                  * Set return value = -1 = ERROR
    102                 bra     vputexit                * Go unlink stack and return
    103 *
    104 MTAB:           dc.w    $FFFC,$FFF3,$FFCF,$FF3F * Mask table
    105                 dc.w    $FCFF,$F3FF,$CFFF,$3FFF
    106 STAB:           dc.w    0,2,4,6,8,10,12,14      * Shift table
    107 *
     55
     56_vwputp:        link    a6,#0                   | Link stack frames
     57                movea.l OCTAD(a6),a1            | Get OCTAD base into a1
     58                move.w  XLOC(a6),d0             | Get XLOC into d0
     59                cmp.w   XSIZE(a1),d0            | Check XLOC range
     60                bge     vputerr                 | ERROR if too large
     61
     62                tst.w   d0                      | Check XLOC sign
     63                bmi     vputerr                 | ERROR if negative
     64
     65                move.w  YLOC(a6),d1             | Get YLOC into d1 to test
     66                cmp.w   YSIZE(a1),d1            | Check YLOC range
     67                bge     vputerr                 | ERROR if too large
     68
     69                tst.w   d1                      | Check YLOC sign
     70                bmi     vputerr                 | ERROR if negative
     71
     72                lsr.w   #3,d0                   | Divide XLOC by 8
     73                move.w  XSIZE(a1),d1            | Get width into d1
     74                lsr.w   #3,d1                   | Divide width by 8
     75                mulu    YLOC(a6),d1             | Multiply width/8 by YLOC
     76                ext.l   d0                      | Extend XLOC/8 to a long
     77                add.l   d0,d1                   | ... and add it to d1
     78                add.l   OBASE(a1),d1            | Add OBASE to d1
     79                movea.l d1,a0                   | Make a0 point at bitmap data
     80                move.w  XLOC(a6),d0             | Get XLOC
     81                andi.l  #0x07,d0                | Mask to low 3 bits
     82                add.l   d0,d0                   | Multiply by 2 for word index
     83                move.l  d0,d1                   | Save index in d1
     84                add.l   #MTAB,d0                | Add mask table base
     85                movea.l d0,a2                   | a2 points at mask
     86                add.l   #STAB,d1                | Add shift table base to index
     87                move.l  d1,a1                   | a1 points at shift count
     88                move.w  (a1),d0                 | Get shift count in d0
     89                move.w  VAL(a6),d1              | Get new pixel in d1
     90                andi.w  #0x03,d1                | Mask down to 2 bits
     91                lsl.w   d0,d1                   | Shift into position for OR
     92                move.w  (a0),d0                 | Get old bitmap word in d0
     93                and.w   (a2),d0                 | Mask out old pixel
     94                or.w    d1,d0                   | OR in new pixel
     95                move.w  d0,(a0)                 | Store updated word in bitmap
     96                clr.l   d0                      | Set return value = 0 = OK
     97
     98vputexit:       unlk    a6                      | Unlink stack frame
     99                rts                             | Return to caller
     100
     101vputerr:        moveq.l #-1,d0                  | Set return value = -1 = ERROR
     102                bra     vputexit                | Go unlink stack and return
     103
     104MTAB:           dc.w    0xFFFC,0xFFF3,0xFFCF,0xFF3F     | Mask table
     105                dc.w    0xFCFF,0xF3FF,0xCFFF,0x3FFF
     106STAB:           dc.w    0,2,4,6,8,10,12,14      | Shift table
     107
    108108                .end
  • vlib/vwputs.s

    rf40a309 r4f508e6  
    1 * ------------------------------------------------------------------------------
    2 * vwputs.s -- output a character string to a 2-bit per pixel graphics window
    3 * Version 9 -- 1987-07-28 -- D.N. Lynx Crowe
    4 * (c) Copyright 1987 -- D.N. Lynx Crowe
    5 * ------------------------------------------------------------------------------
    6 *
    7 *       vwputs(obase, nw, fg, bg, row, col, str)
    8 *       int *obase, nw, fg, bg, row, col;
    9 *       char *str;
    10 *
    11 *               Outputs characters from the string at 'str' to an 'nw'
    12 *               character wide 2-bit per pixel graphics window at 'obase'
    13 *               at ('row','col'), using 'fg' as the foreground color, and
    14 *               'bg' as the background color.  Uses cgtable[][256] as the
    15 *               VSDD formatted character generator table.
    16 *               No error checks are done.
    17 * ------------------------------------------------------------------------------
    18 *
     1| ------------------------------------------------------------------------------
     2| vwputs.s -- output a character string to a 2-bit per pixel graphics window
     3| Version 9 -- 1987-07-28 -- D.N. Lynx Crowe
     4| (c) Copyright 1987 -- D.N. Lynx Crowe
     5| ------------------------------------------------------------------------------
     6
     7|       vwputs(obase, nw, fg, bg, row, col, str)
     8|       int |obase, nw, fg, bg, row, col;
     9|       char |str;
     10
     11|               Outputs characters from the string at 'str' to an 'nw'
     12|               character wide 2-bit per pixel graphics window at 'obase'
     13|               at ('row','col'), using 'fg' as the foreground color, and
     14|               'bg' as the background color.  Uses cgtable[][256] as the
     15|               VSDD formatted character generator table.
     16|               No error checks are done.
     17| ------------------------------------------------------------------------------
     18
    1919                .text
    2020                .xdef   _vwputs
    21 *
     21
    2222                .xref   _cgtable
    23 *
    24 * Argument offsets from a6:
    25 *
    26 OBASE           .equ    8               * L:  Output area base address
    27 NW              .equ    12              * W:  Character width of output area
    28 FG              .equ    14              * W:  Foreground color
    29 BG              .equ    16              * W:  Background color
    30 ROW             .equ    18              * W:  Row
    31 COL             .equ    20              * W:  Column
    32 STR             .equ    22              * L:  String base address
    33 *
    34 * Miscellaneous constants:
    35 *
    36 HPIX            .equ    8               * Horizontal pixels in the character
    37 *
    38 NVPIX           .equ    12              * Vertical pixels in the character
    39 VPITCH          .equ    12              * Vertical pitch between characters
    40 *
    41 * Register usage:
    42 *
    43 *       d0      output word and scratch
    44 *       d1      CG word and scratch
    45 *       d2      pixel counter
    46 *       d3      foreground color (in the 2 ms bits)
    47 *       d4      background color (in the 2 ms bits)
    48 *       d5      width of the area in bytes
    49 *       d6      scan line counter
    50 *
    51 *       a0      CG table pointer
    52 *       a1      output area scan line pointer
    53 *       a2      input character pointer
    54 *       a3      output area character pointer
    55 *
     23
     24| Argument offsets from a6:
     25
     26OBASE           =       8               | L:  Output area base address
     27NW              =       12              | W:  Character width of output area
     28FG              =       14              | W:  Foreground color
     29BG              =       16              | W:  Background color
     30ROW             =       18              | W:  Row
     31COL             =       20              | W:  Column
     32STR             =       22              | L:  String base address
     33
     34| Miscellaneous constants:
     35
     36HPIX            =       8               | Horizontal pixels in the character
     37
     38NVPIX           =       12              | Vertical pixels in the character
     39VPITCH          =       12              | Vertical pitch between characters
     40
     41| Register usage:
     42
     43|       d0      output word and scratch
     44|       d1      CG word and scratch
     45|       d2      pixel counter
     46|       d3      foreground color (in the 2 ms bits)
     47|       d4      background color (in the 2 ms bits)
     48|       d5      width of the area in bytes
     49|       d6      scan line counter
     50
     51|       a0      CG table pointer
     52|       a1      output area scan line pointer
     53|       a2      input character pointer
     54|       a3      output area character pointer
     55
    5656                .page
    57 *
    58 _vwputs:        link    a6,#0           * Link stack frames
    59                 movem.l d3-d6/a3,-(a7)  * Save registers we use
    60                 move.w  #14,d1          * Set shift constant
    61                 move.w  FG(a6),d3       * Setup foreground color
    62                 lsl.w   d1,d3           * ... in ms 2 bits of d3
    63                 move.w  BG(a6),d4       * Setup background color
    64                 lsl.w   d1,d4           * ... in ms 2 bits of d4
    65                 move.w  NW(a6),d5       * Get width in characters in d5
    66                 lsl.w   #1,d5           * ... make it words
    67                 move.w  ROW(a6),d0      * Calculate output address
    68                 move.w  #VPITCH,d1      * ...
    69                 mulu    d1,d0           * ... ROW * VPITCH
    70                 add.w   #NVPIX-1,d0     * ... + NVPIX-1
    71                 mulu    d5,d0           * ... * NW
    72                 clr.l   d1              * ...
    73                 move.w  COL(a6),d1      * ... + (COL * 2)
    74                 lsl.l   #1,d1           * ...
    75                 add.l   d1,d0           * ...
    76                 add.l   OBASE(a6),d0    * ... + OBASE
    77                 movea.l d0,a3           * Leave output address in a3
    78                 movea.l STR(a6),a2      * Put string address in a2
    79 *
     57
     58_vwputs:        link    a6,#0           | Link stack frames
     59                movem.l d3-d6/a3,-(a7)  | Save registers we use
     60                move.w  #14,d1          | Set shift constant
     61                move.w  FG(a6),d3       | Setup foreground color
     62                lsl.w   d1,d3           | ... in ms 2 bits of d3
     63                move.w  BG(a6),d4       | Setup background color
     64                lsl.w   d1,d4           | ... in ms 2 bits of d4
     65                move.w  NW(a6),d5       | Get width in characters in d5
     66                lsl.w   #1,d5           | ... make it words
     67                move.w  ROW(a6),d0      | Calculate output address
     68                move.w  #VPITCH,d1      | ...
     69                mulu    d1,d0           | ... ROW | VPITCH
     70                add.w   #NVPIX-1,d0     | ... + NVPIX-1
     71                mulu    d5,d0           | ... | NW
     72                clr.l   d1              | ...
     73                move.w  COL(a6),d1      | ... + (COL | 2)
     74                lsl.l   #1,d1           | ...
     75                add.l   d1,d0           | ...
     76                add.l   OBASE(a6),d0    | ... + OBASE
     77                movea.l d0,a3           | Leave output address in a3
     78                movea.l STR(a6),a2      | Put string address in a2
     79
    8080                .page
    81 cgl0:           clr.l   d0              * Clear out upper bits of d0
    82                 move.b  (a2)+,d0        * Get next character
    83                 beq     cgl5            * Done if character EQ 0
    84 *
    85                 movea.l a3,a1           * Establish output pointer in a1
    86                 adda.l  #2,a3           * Update output pointer for next char.
    87                 lea     _cgtable,a0     * Establish CG pointer in a0
    88                 lsl.w   #1,d0           * ... 2 * character
    89                 adda.w  d0,a0           * ... + _cgtable address
    90                 move.w  #NVPIX-1,d6     * Set scan line counter in d6
    91 *
    92 cgl1:           move.w  #HPIX-1,d2      * Set pixel counter in d2
    93                 move.w  (a0),d1         * Get character generator word in d1
    94 *
    95 cgl2:           lsr.w   #2,d0           * Shift output word right 1 pixel
    96                 btst.l  #0,d1           * Check CG word ls bit
    97                 beq     cgl3            * Set background color if bit EQ 0
    98 *
    99                 or.w    d3,d0           * OR foreground color into output word
    100                 bra     cgl4            * Go update CG word
    101 *
    102 cgl3:           or.w    d4,d0           * OR background color into  output word
    103 *
    104 cgl4:           lsr.w   #1,d1           * Shift CG word right 1 pixel
    105                 dbf     d2,cgl2         * Loop for all 8 pixels
    106 *
    107                 move.w  d0,(a1)         * Store output word in output bitmap
    108                 suba.w  d5,a1           * Update output pointer
    109                 adda.l  #512,a0         * Update CG pointer for next scan line
    110                 dbf     d6,cgl1         * Loop for all scan lines
    111 *
    112                 bra     cgl0            * Loop for next character
    113 *
    114 cgl5:           movem.l (a7)+,d3-d6/a3  * Restore registers
    115                 unlk    a6              * Unlink stack frames
    116                 rts                     * Return to caller
    117 *
     81cgl0:           clr.l   d0              | Clear out upper bits of d0
     82                move.b  (a2)+,d0        | Get next character
     83                beq     cgl5            | Done if character EQ 0
     84
     85                movea.l a3,a1           | Establish output pointer in a1
     86                adda.l  #2,a3           | Update output pointer for next char.
     87                lea     _cgtable,a0     | Establish CG pointer in a0
     88                lsl.w   #1,d0           | ... 2 | character
     89                adda.w  d0,a0           | ... + _cgtable address
     90                move.w  #NVPIX-1,d6     | Set scan line counter in d6
     91
     92cgl1:           move.w  #HPIX-1,d2      | Set pixel counter in d2
     93                move.w  (a0),d1         | Get character generator word in d1
     94
     95cgl2:           lsr.w   #2,d0           | Shift output word right 1 pixel
     96                btst.l  #0,d1           | Check CG word ls bit
     97                beq     cgl3            | Set background color if bit EQ 0
     98
     99                or.w    d3,d0           | OR foreground color into output word
     100                bra     cgl4            | Go update CG word
     101
     102cgl3:           or.w    d4,d0           | OR background color into  output word
     103
     104cgl4:           lsr.w   #1,d1           | Shift CG word right 1 pixel
     105                dbf     d2,cgl2         | Loop for all 8 pixels
     106
     107                move.w  d0,(a1)         | Store output word in output bitmap
     108                suba.w  d5,a1           | Update output pointer
     109                adda.l  #512,a0         | Update CG pointer for next scan line
     110                dbf     d6,cgl1         | Loop for all scan lines
     111
     112                bra     cgl0            | Loop for next character
     113
     114cgl5:           movem.l (a7)+,d3-d6/a3  | Restore registers
     115                unlk    a6              | Unlink stack frames
     116                rts                     | Return to caller
     117
    118118                .end
Note: See TracChangeset for help on using the changeset viewer.