Changeset 4f508e6 in buchla-68k for vlib/vsplot4.s


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.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.