 
; SERVID - Serial video display using Ubicom SX microcontroller ; $Id servid.asm,v 1.34 2001/01/31 07 25 31 eric Exp $ ;**************************************************************** ; SX-KEY source mnenomics for SX18 device by Peter Verkaik ; This port uses the same oscillator frequency as the original source ; so it should run directly for NTSC. ; Do not contact the authors of the original source about this conversion ; Instead contact me: peterverkaik@boselectro.nl ;**************************************************************** ; ; Copyright 2000, 2001 Eric Smith <eric@brouhaha.com> ; ; Home page ; http //www.brouhaha.com/ubicom/servid/ ; ; This program is free software; you can redistribute it and/or modify ; it under the terms of the GNU General Public License version 2 as published ; by the Free Software Foundation. Note that permission is not granted ; to redistribute this program under the terms of any other version of the ; General Public License. ; ; This program is distributed in the hope that it will be useful, ; but WITHOUT ANY WARRANTY; without even the implied warranty of ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ; GNU General Public License for more details. ; ; You should have received a copy of the GNU General Public License ; along with this program; if not, write to the Free Software ; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. ; ; NOTE it is sometimes claimed that compliance with the GPL is ; awkward for commercial interests. Licenses for non-GPL use of this ; program may be negotiated with the author. ; ; This program is written to be assembled with the GPASM assembler, ; version 0.8.14 or newer ; http //gpasm.sourceforge.net/ ; NOTE there are references in this code to PAL and NTSC. Technically ; those are color standards. In most cases the references to PAL and NTSC ; are really intended to refer to 625/50 and 525/59.94 scanning, or (in ; non-interlaced mode) 312/25 and 262/29.97 scanning. device SX18L,oschs2,turbo,stackx_optionx,carryx ;sx device options freq 42_954_545 ;resonator frequency id '-SERVID-' ;code identification reset reset_entry ;set reset vector ;Features: ; ;serial input at 1200 bps 8N1 (eight data bits, no parity, one stop bit), MSB ignored ;monochrome displayo of four lines of twenty characaters ;1 volt peak-to-peak composite video ouptut into 75 ohm load ;ASCII character set, 95 displayable characters ;Subset of VT52 control characters and escape sequences ;Automatic scrolling ( no extra "4" characters when scrolling ) ;interlaced or non-interlaced video selectable by conditional assembly ;approximate RS-170 timing (525/60) ;approximate PAL timing (625/50) selectable by conditional assembly - maybe. ;PAL timing of an earlier version was only tested in a cursory fashion. ;Since then the line type table for PAL has been rewritten in an attempt to more ;closely meet PAL scanning specifications (e.g., 5 each equalization, vsync, ;equalization pulses per field). However, this newer code has not been tested ;in PAL mode at all. ;This is a preliminary release. As such, it basically works, ;but there are some known bugs (and probably a lot of unknown ones): ; ;some escape sequences are acting a bit flaky ;Supported control codes: ; ; $00 Null ; $07 Bell ; $08 Backspace ; $0A Line Feed ; $0C Form Feed - clear display and home cursor ; $0D Carriage Return ; $1B Escape - introduce escape sequence ; $7F Delete - ignored ; ; All unrecognized control characters are ignored. ;Supported escape sequences: ; ; ESC A - Cursor Up - wraparound rather than scroll ; ESC B - Cursor Down - wraparound rather than scroll ; ESC C - Cursor Left ; ESC D - Cursor Right ; ; ESC H - Cursor Home ; ESC I - Reverse Line Feed - may scroll ; ESC J - Erase to End of Screen ; ESC K - Erase to End of Line ; ; ESC Y- Direct cursor addressing, col and row offset by 32 ; ;Customization: ; ;SERVID is designed such that user application code may be added to (or replace) ;the serial character processing. In this release of the code there are 919 words ;of program memory free for a user application, and 21 bytes of RAM free. ;The video generation is entirely interrupt driven, so the user application code ;can run at non-interrupt time without any critical timing constraints. ; ;Software Requirements: ; ;As written, SERVID will only assemble with the GPASM assembler, version 0.8.14 ;or newer. GPASM is Free Software: ;http://gpasm.sourceforge.net/ ; ;Hardware Requirements: ; ;SERVID requires a processor clock of 42.954545 MHz (12 times the NTSC color burst frequency). ;Note that future versions of SERVID may change to a clock frequency of 57.272727 MHz ;(16 times the NTSC color burst frequency). Digikey offers suitable Epson oscillators ;which they program to customer spec; a suitable 8-pin DIP footprint (4 actual pin) part ;is part number SG-8002DC-PHB-ND. SERVID uses an 8-bit D/A converter on port B to generate ;the video output. A simple R-2R resistor ladder will suffice. ; ;The serial input should be fed into port RA0. If a conventional EIA-232 receiver ;(MC1489, MAX232, or the like) is used, the variable ft_ser_noninv near the top of ;the servid.asm source file should be set to 0. For a non-inverting serial input ;(such as the crude resistor-only method, see the file SCHEMATIC), ft_ser_noninv ;should be set to 1. ; ;Bill of Materials ;All parts but the microcontroller are available from Digikey. ;Digikey part numbers are given except for the microcontroller, ;for which a Mouser part number is given. ; ;http://www.digikey.com/ ;http://www.mouser.com/ ; ; Vendor Distributor ;Q. Vendor Part Part Number Description ;-- ------ --------- ------------- ---------------------------------------- ; 1 Ubicom SX18AC/DP 619-SX18AC/DP microcontroller, 18-pin plastic DIP ; 1 Epson SG-8002DC-PHB preprogrammed oscillator, 42.9545454 MHz ; 1 CTS 761-3-R220 8 * 220 ohm DIP resistor network ; 2 CTS 770-103-R120 5 * 120 ohm SIP res. network, isolated ; ; 1 15 ohm 1/8 watt resistor ; 1 33K ohm 1/8 watt resistor ; 1 180K ohm 1/8 watt resistor ; 1 0.1 uF ceramic capacitor ; ; 1 BNC or RCA jack for video output ; 1 DB25 connector for serial input ; 1 5V regulated DC power supply ; ;Schematic ;Schematic for SERVID ;$Id: SCHEMATIC,v 1.4 2001/01/04 23:52:55 eric Exp $ ; ;Copyright 2001 Richard Ottosen ; ; ; +5V ; | ; +---------------+ ; | | ; 0.1 uF | ; | | 1.25V p-p ; | ---------------- Video into ; V | | 75 ohms ; | Ubicom / | ; | SX18AC | 7 |--- 220 ohm ---+--------+--- 15 ohm ---> ; | | | | | ; +5V --| MCLR | | 120 ohm 120 ohm +---> ; | | | | | | ;---------- | | 6 |--- 220 ohm ---+ | | ;|42.954545 | | | | | V V ;| MHz |-----| OSC1 | | 120 ohm ;|Oscillator| | | | | ; ---------- NC--| OSC2 | 5 |--- 220 ohm ---+ ; | | | | ; | | | 120 ohm ; +------| RTCC | | | ; | | / 4 |--- 220 ohm ---+ ; V | | | | ; | Port B < | 120 ohm ; | | | | ; NC--| PA3 \ 3 |--- 220 ohm ---+ ; | | | | ; NC--| PA2 | | 120 ohm ; | | | | ; +------| PA1 | 2 |--- 220 ohm ---+ ; | | | | | ; -- | | | 120 ohm ; piezo [] ))) | | | | ; -- | | 1 |--- 220 ohm ---+ ; | | | | | ; | | | | 120 ohm ; V | | | | ;IA-232 | | 0 |--- 220 ohm ---+ ;Input | \ | | ;<----+--- 33K ---| PA0 | 120 ohm ; | | | | ; 180K ---------------- | ; | | 120 ohm ;<----+ | | ; | | | ; V V V ;--------------------------------------------------------------------------- ; feature test switches ;--------------------------------------------------------------------------- ft_pal_video equ 0 ; 0 for NTSC 525/60, 1 for PAL 625/50 ; (approximate timing only) ; (not well tested) ft_interlace equ 1 ; 1 for interlaced video ft_color equ 0 ; 1 for color burst (NTSC only) ft_serial_input equ 1 ; 1 for normal serial input, ; 0 to omit (when replaced with user ; application code) ft_ser_noninv equ 1 ; 0 for "normal" TTL-level serial, ; mark = low, space = high ; 1 for non-inverted serial (the ; crude resistor-only method) ; mark = high, space = low ft_splash equ 1 ; 1 for splash screen ;============================================================================== ; ; This program is available from ; ; Rho Enterprises ; 4100 W. Colfax Ave. ; Box 33 ; Denver, CO 80204 ; ; Phone 720-359-1467 Email info@rhoent.com ; ; http //www.rhoent.com/ ; ;============================================================================== ; ;SXDEFS.INC by Loren Blaney and Richard Ottosen 14-FEB-2000 ; ;Scenix SX Definitions for Microchip MPASM. ; ;REVISIONS ;FEB-23-98, Released. ;MAR-21-98, Added ID label. Corrected XT & HS defs by swapping them. ; Removed ASCII defs. New STATUS defs. ;MAR-27-98, Added PAGEA, BANKA, FCALL, FGOTO, SKIP. ;APR-13-98, Added CSA, CSBE (etc.) macros. Enclose all arguments in parentheses. ; Indent macros. ;APR-23-98, Changed some comments. ;OCT-4-98, Removed "RADIX DEC", added processor type based on SX FUSEX bits, ; added Trim bits to FUSEX and other cleanup. R.O. ;OCT-14-98 BOSC defaults to a "1". ;NOV-4-98, Revised Pins, Trim bits and BOSC in DEVICE equates, removed some ; inversions. R.O. ;SEP-11-99, Added warnings and messages to BANK and PAGE macros. R.O. ;9-JAN-2000, Changed ID bytes to leave unused bits as ones. R.O. ;12-JAN-2000, Made variables in macros local. R.O. ;14-FEB-2000, Cleanup. R.O. ;Define special function registers ;INDF equ 00h ;used for indirects thru fsr ;RTCC equ 01h ;real time clock/counter ;PCL equ 02h ;low 8 bits of PC ;STATUS equ 03h ;status bits ;FSR equ 04h ;file select register ;PORTA equ 05h ;I/O ports ;PORTB equ 06h ;supports multi-input wake-up (MIWU) ;PORTC equ 07h ;Define STATUS register bits CF equ 0 ;carry DCF equ 1 ;digit carry ZF equ 2 ;zero PDF equ 3 ;sleep power down (true low) TOF equ 4 ;watchdog time out (true low) ;PA0 equ 5 ;page select (LSB) ;PA1 equ 6 ;page select ;PA2 equ 7 ;page select (MSB) ;Define port control registers ;TRISX equ 0Fh ;tristate (1=input, 0=output) ;PLP equ 0Eh ;pullup (1=none, 0=20k) ;LVL equ 0Dh ;level (1=TTL, 0=CMOS) ;ST equ 0Ch ;Schmitt trigger (1=disabled, 0=enabled) ;WKEN equ 0Bh ;wake up (1=disabled, 0=enabled) ;WKED equ 0Ah ;wake up edge (1=falling, 0=rising) ;WKPND equ 09h ;wake up pending (1=pending, 0=none) ;CMP equ 08h ;comparator bit 0=result, 6=output, 7=enabled ;Define device symbols for configuration words (FUSE & FUSEX) ;OSCRC equ %00 ;external RC network (default, inverted) ;OSCHS equ %01 ;high speed external crystal/resonator ;OSCXT equ %10 ;normal external crystal/resonator ;OSCLP equ %11 ;low power external crystal/resonator ;WATCHDOG equ 1 << 2 ;watchdog timer enabled ; default to disabled ;PROTECT equ 1 << 3 ;code protect enabled (inverted) ; default is to disable code protect ;OSC4MHZ equ %1000 << 4 ;internal 4MHz ;OSC2MHZ equ %1001 << 4 ;internal 2MHz ;OSC1MHZ equ %1010 << 4 ;internal 1MHz ;OSC500KHZ equ %1011 << 4 ;internal 500KHz ;OSC250KHZ equ %1100 << 4 ;internal 250KHz ;OSC125KHZ equ %1101 << 4 ;internal 125KHz ;OSC62KHZ equ %1110 << 4 ;internal 62.5KHz ;OSC31KHZ equ %1111 << 4 ;internal 31.25KHz ;STACKX equ 1 << 8 ;stack is extended to 8 levels (inverted) ; default to 2 levels ;OPTIONX equ 1 << 9 ;extend option register to 8 bits (inverted) ; default to 6 bits ;SYNC equ 1 << 10 ;input syncing enabled (inverted) ; default to disabled ;TURBO equ 1 << 11 ;turbo mode enabled (inverted) ; default to disabled ;PAGES1 equ %00 << 12 ;default ;PAGES2 equ %01 << 12 ;PAGES4 equ %10 << 12 ;PAGES8 equ %11 << 12 ;BANKS1 equ %00 << 14 ;default ;BANKS2 equ %01 << 14 ;BANKS4 equ %10 << 14 ;BANKS8 equ %11 << 14 ;BOR40 equ %11 << 16 ;4.0V brownout reset ;BOR25 equ %10 << 16 ;2.5 ;BOR13 equ %01 << 16 ;1.3 ;BOR00 equ %00 << 16 ;disabled (default, inverted) ;CARRYX equ 1 << 18 ;ADDWF & SUBWF use carry input (inverted) ; default is to ignore carry in ;PRE7 equ 1 << 19 ;for changing the preset FUSEX bit 7 (inverted) ; default is no change ;for modifying factory IRC calibration ;TRIM0 equ %0000 << 20 ;highest frequency ;TRIM3 equ %0001 << 20 ;TRIM6 equ %0010 << 20 ;TRIM9 equ %0011 << 20 ; about 3% per step ;TRIM12 equ %1000 << 20 ;TRIM15 equ %1001 << 20 ;TRIM18 equ %1010 << 20 ;TRIM21 equ %1011 << 20 ;lowest frequency (default) ;PINS18 equ %0 << 22 ;default to 18 pin ;PINS28 equ %1 << 22 int_off equ $c3 ; RTCC internal clock, prescale by 16, ; RTCC interrupt off, WDT disabled int_on equ $83 ; RTCC internal clock, prescale by 16, ; RTCC interrupt on, WDT disabled ;--------------------------------------------------------------------------- ; other includes ;--------------------------------------------------------------------------- ; ASCII character definitions for serial video display ; $Id ascii.inc,v 1.1 2001/01/03 20 06 47 eric Exp $ ; ; Copyright 2000, 2001 Eric Smith <eric@brouhaha.com> ; ; This program is free software; you can redistribute it and/or modify ; it under the terms of the GNU General Public License version 2 as published ; by the Free Software Foundation. Note that permission is not granted ; to redistribute this program under the terms of any other version of the ; General Public License. ; ; This program is distributed in the hope that it will be useful, ; but WITHOUT ANY WARRANTY; without even the implied warranty of ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ; GNU General Public License for more details. ; ; You should have received a copy of the GNU General Public License ; along with this program; if not, write to the Free Software ; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. ; ; Licenses for non-GPL use may be negotiated with the author. asc_nul equ 00h asc_bel equ 07h asc_bs equ 08h asc_ht equ 09h asc_lf equ 0ah asc_ff equ 0ch asc_cr equ 0dh asc_so equ 0eh asc_si equ 0fh asc_esc equ 1ah asc_del equ 7fh ;--------------------------------------------------------------------------- ; video definitions ;--------------------------------------------------------------------------- ; Display size in characters. Note that simply changing these definitions ; won't have the desired effect. rows equ 4 columns equ 20 ; osc = 42,954,545 Hz = 12 * color burst ; tCYC = 23.2804 ns ; theoretical total width = 12 * 227.5 = 2730 cycles = 2 * 3 * 5 * 91 = 15 * 182 ; ; The RTCC prescaler can only be set for powers of two, and we need the ; count to be a little under 256, so we use a prescaler of 16 and a divisor ; of 171, for an actual scan line width of 2736 cycles (63.7 us). int_period equ 171 ; used by interrupt_done h equ 2736 ; 63.7 us hsync_pulse_width equ 201 ; 4.7 us equalization_pulse_width equ 98 ; 2.3 us serration_pulse_width equ 201 ; 4.7 us vsync_pulse_width equ (h/2)-serration_pulse_width front_porch_width equ 64 ; 1.5 us back_porch_width equ 193 ; 4.5 us ; safe area = 40 us = 1718 cycles ; ; 20 chars wide * (5+2) = 139 pixels wide, 12.4 cycles per pixel ; ("rounded" up to 13) ; ; for 4 3 aspect ratio, display should be 90 pixels tall, so make ; a pixel be 3 scan lines. scan_lines_per_vpixel equ 3 vpixels_per_char equ 10 chars_per_row equ 20 if ft_pal_video total_active_lines equ 287 else total_active_lines equ 242 endif active_video_lines equ rows*vpixels_per_char*scan_lines_per_vpixel top_border equ (total_active_lines-active_video_lines)/2 bottom_border equ total_active_lines-(top_border+active_video_lines) ;--------------------------------------------------------------------------- ; composite video definitions ;--------------------------------------------------------------------------- vid_port equ rb ; D/A converter ; DAC 0 = ground (sync tip), 255 = 1.25V into 75 ohm load ; one DAC step = 1.25/255 V = 4.902 mV ; there are 140 IRE units to 1.0V, so an IRE unit is 7.143 mV = 1.457 DAC steps vid_sync equ 0 ; -40 IRE vid_blank equ 58 ; 58.29 = 0 IRE vid_black equ 69 ; 69.21 = 7.5 IRE vid_white equ 204 ; 204.00 = 100 IRE vid_max_chroma equ 249 ; 249.17 = 131 IRE burst_amplitude equ 58 ; 58.29 = 40 IREs ;--------------------------------------------------------------------------- ; I/O port definitions ;--------------------------------------------------------------------------- rxd_bit equ 0 pzt_bit equ 1 txd_bit equ 2 ; not used mode_button_bit equ 3 ; not used rxd equ ra.rxd_bit pzt equ ra.pzt_bit txd equ ra.txd_bit mode_button equ ra.mode_button_bit trisa equ $01 ; RxD is our only input inita equ $00 trisb equ $00 ; all outputs initb equ vid_sync ;--------------------------------------------------------------------------- ; bell definitions ;--------------------------------------------------------------------------- ; The bell tone is nominally around 500 Hz for 200 ms (100 cycles). ; This works out to a period of 32 scan lines. bell_half_period equ 16 ; lines bell_duration equ 200 ; half-periods ;--------------------------------------------------------------------------- ; serial definitions ;--------------------------------------------------------------------------- ; While serial line idle, sample every scan line. Once start bit is ; detected, delay 6 scan lines, then sample every 13. This results ; in a 1208 bps rate, 0.6% fast. lines_per_serial_sample equ 13 skip_on_ser_rx_mark macro noexpand if ft_ser_noninv expand sb rxd noexpand else expand snb rxd noexpand endif endm skip_on_ser_rx_space macro noexpand if ft_ser_noninv expand snb rxd noexpand else expand sb rxd noexpand endif endm ;--------------------------------------------------------------------------- ; memory utilization ;--------------------------------------------------------------------------- rambase equ 08h ; start of RAM rombase equ 0000h ; beginning of program romsize equ 0800h chargen equ romsize-384 intvec equ 0000h ; interrupt vector main_page equ 0000h int_page equ 0200h ;--------------------------------------------------------------------------- ; shared variables ;--------------------------------------------------------------------------- org rambase ; start of RAM g_field_count ds 1 ; field down-counter g_mtemp ds 1 ; global temp for main ; "DelM" uses "DelMCnt" in the interupt. Do NOT use DelM or DelMCnt in main! DelMCnt ds 1 ; counter used for cycle delays Five ds 1 Fifteen ds 1 ;--------------------------------------------------------------------------- ; variables for main ;--------------------------------------------------------------------------- org 010h main_vars temp ds 3 char ds 1 ; character being processed escape_state ds 1 ; 0 = normal ; 1 = ESC seen, waiting for 2nd char ; 2 = ESC-Y seen, waiting for <col> ; 3 = ESC-Y <col> seen, waiting for <row> esc_Y_col ds 1 ; cursor cursor_col ds 1 cursor_row ds 1 cursor_loc ds 1 ; for scrolling src_addr equ temp dest_addr equ temp+1 move_count equ temp+2 ;--------------------------------------------------------------------------- ; variables for interrupt ;--------------------------------------------------------------------------- org 030h int_vars line_type ds 1 ; type of scan line we're working on ; 2 * [0 .. line_types-1] line_count ds 1 ; how many lines of this type to do if ft_color burst_phase ds 1 ; LSB used for burst phase int_temp ds 1 ; general use in interrupt endif line_start ds 1 ; start buffer loc of currently displayed line char_ptr ds 1 ; pointer to currently displayed character chargen_ptr ds 2 ; pointer into character generator inverse_flag ds 1 ; bit 7 indicates current char inverse vpix_cnt ds 1 ; vertical pixel counter scanline_cnt ds 1 ; vertical scan line counter (per pixel) char_cnt ds 1 pixels ds 1 ; pixels of current char ; bell bell_half_cyc ds 1 ; bell half-cycle in lines bell_line_cnt ds 1 ; bell half-cycle down-counter bell_dur_cnt ds 1 ; bell duration ;--------------------------------------------------------------------------- ; variables for serial receive ;--------------------------------------------------------------------------- if ft_serial_input org 050h ser_vars ser_rx_state ds 1 ser_rx_byte ds 1 ser_rx_samp_cnt ds 1 ser_rx_bit_cnt ds 1 ser_rx_char ds 1 ser_rx_flag ds 1 endif ;--------------------------------------------------------------------------- ; video buffer ;--------------------------------------------------------------------------- ; NOTE subtract offset of 20h (space) before storing characters into ; video buffer video_buffer equ 070h ; 80 characters, uses last five banks ; *must* start on a bank boundary ; reserve RAM, skipping over banks as needed res_bank_ram macro 1 ;res_bank_ram count noexpand local1 = \1 rept local1 expand ds 1 noexpand if ($ & 010h)=0 expand org $+010h noexpand endif endr endm org video_buffer line_0 res_bank_ram columns line_1 res_bank_ram columns line_2 res_bank_ram columns-1 line_2_end res_bank_ram 1 line_3 res_bank_ram columns-1 line_3_end res_bank_ram 1 org rombase page interrupt ; 0 jmp interrupt ; 1 escape_state_table mov W, escape_state add PC, W jmp esc_not_seen jmp esc_seen jmp esc_Y_col_seen jmp esc_Y_row_seen control_char_table mov W, char add PC, W jmp null ; 00 - NUL - null - don't do anything jmp null ; 01 - jmp null ; 02 - jmp null ; 03 - jmp null ; 04 - jmp null ; 05 - jmp null ; 06 - jmp bell ; 07 - BEL - bell jmp backspace ; 08 - BS - backspace jmp null ; 09 - jmp line_feed ; 0a - LF - line feed jmp null ; 0b - jmp form_feed ; 0c - FF - form feed - clear screen jmp carriage_return ; 0d - CR - carriage return jmp null ; 0e jmp null ; 0f jmp null ; 10 jmp null ; 11 jmp null ; 12 jmp null ; 13 jmp null ; 14 jmp null ; 15 jmp null ; 16 jmp null ; 17 jmp null ; 18 jmp null ; 19 jmp null ; 1a jmp escape ; 1b - ESC - escape jmp null ; 1c jmp null ; 1d jmp null ; 1e jmp null ; 1f esc_char_table add PC, W jmp bad_escape ; 40 - @ jmp cursor_up ; 41 - A - cursor up jmp cursor_down ; 42 - B - cursor down jmp cursor_left ; 43 - C - cursor left jmp cursor_right ; 44 - D - cursor right jmp bad_escape ; 45 - E jmp bad_escape ; 46 - F jmp bad_escape ; 47 - G jmp home_cursor ; 48 - H - cursor home jmp rev_line_feed ; 49 - I - reverse line feed (can scroll) jmp clear_eop ; 4A - J - clear to end of screen jmp clear_eol ; 4B - K - clear to end of line jmp bad_escape ; 4C - L jmp bad_escape ; 4D - M jmp bad_escape ; 4E - N jmp bad_escape ; 4F - O jmp bad_escape ; 50 - P jmp bad_escape ; 51 - Q jmp bad_escape ; 52 - R jmp bad_escape ; 53 - S jmp bad_escape ; 54 - T jmp bad_escape ; 55 - U jmp bad_escape ; 56 - V jmp bad_escape ; 57 - W jmp bad_escape ; 58 - X jmp esc_Y ; 59 - Y - cursor positioning jmp bad_escape ; 5A - Z jmp bad_escape ; 5B - [ jmp bad_escape ; 5C - jmp bad_escape ; 5D - ] jmp bad_escape ; 5E - ^ jmp bad_escape ; 5F - _ show_cursor mov W, cursor_loc mov fsr, W setb indf.7 bank main_vars ret hide_cursor mov W, cursor_loc mov fsr, W clrb indf.7 bank main_vars ret ; delay until either the number of fields specified in W have been ; displayed (zero flag set), or a serial character is received ; (zero flag clear) delay_fields bank ser_vars mov g_field_count, W df_loop if ft_serial_input test ser_rx_flag ; check serial receive flag sb status.zf ; character received? jmp df_return ; yes, return to caller endif test g_field_count ; has field count decremented to zero? sb status.zf jmp df_loop ; no, keep looping df_return bank main_vars ret home_cursor clr cursor_row carriage_return clr cursor_col compute_cursor_loc mov W, cursor_row ; cursor_loc = 20 * cursor_row mov cursor_loc, W clrb status.cf rl cursor_loc rl cursor_loc mov W, <>cursor_row add cursor_loc, W mov W, cursor_col ; cursor_loc += cursor_col add cursor_loc, W mov W, cursor_loc ; shift high nibble left one bit and W, #0f0h add cursor_loc, W mov W, #video_buffer ; add in base address add cursor_loc, W null ret ; output a character from W to the display output_char and W, #07fh ; strip MSB (parity?) and save mov char, W jmp escape_state_table ; process character esc_not_seen mov W, char and W, #060h ; is it a control character? snb status.zf jmp control_char_table ; yes, process and return mov W, char ; is it a DEL xor W, #asc_del snb status.zf ret ; yes, do nothing mov W, char ; fall into printable_char printable_char mov g_mtemp, W ; save character mov W, #-' ' ; remove offset add g_mtemp, W mov W, cursor_loc ; store character mov fsr, W mov W, g_mtemp mov indf, W bank main_vars ; fall into cursor_advance cursor_advance inc cursor_col mov W, cursor_col xor W, #columns sb status.zf jmp compute_cursor_loc crlf clr cursor_col line_feed inc cursor_row mov W, cursor_row xor W, #rows sb status.zf jmp compute_cursor_loc dec cursor_row ; restore call compute_cursor_loc scroll_up mov W, #line_1 mov src_addr, W mov W, #line_0 mov dest_addr, W mov W, #(rows-1)*columns mov move_count, W call block_move_up mov W, #line_3 ; clear freed space mov temp+1, W mov W, #columns mov temp, W jmp clear_chars block_move_up mov W, src_addr mov fsr, W mov W, indf mov g_mtemp, W bank main_vars inc src_addr setb src_addr.4 mov W, dest_addr mov fsr, W mov W, g_mtemp mov indf, W bank main_vars inc dest_addr setb dest_addr.4 decsz move_count jmp block_move_up ret backspace dec cursor_col sb cursor_col.7 jmp compute_cursor_loc mov W, #columns-1 mov cursor_col, W rev_line_feed dec cursor_row sb cursor_row.7 jmp compute_cursor_loc inc cursor_row ; restore call compute_cursor_loc scroll_down mov W, #line_2_end mov src_addr, W mov W, #line_3_end mov dest_addr, W mov W, #(rows-1)*columns mov move_count, W call block_move_down mov W, #line_0 ; clear freed space mov temp+1, W mov W, #columns mov temp, W jmp clear_chars block_move_down mov W, src_addr mov fsr, W mov W, indf mov g_mtemp, W bank main_vars dec src_addr snb src_addr.4 jmp bmd_1 mov W, #010h sub src_addr, W bmd_1 mov W, dest_addr mov fsr, W mov W, g_mtemp mov indf, W bank main_vars dec dest_addr snb dest_addr.4 jmp bmd_2 mov W, #010h sub dest_addr, W bmd_2 decsz move_count jmp block_move_down ret clear_eol mov W, #columns ; compute number of chars to clear mov temp, W ; temp = columns - cursor_col mov W, cursor_col sub temp, W mov W, cursor_loc mov temp+1, W ; clear temp chars starting at loc temp+1 clear_chars mov W, #' '-020h mov g_mtemp, W ; fill temp chars starting at loc temp+1 to value temp+2 fill_chars mov W, temp+1 mov fsr, W mov W, g_mtemp mov indf, W bank main_vars inc temp+1 setb temp+1.4 decsz temp jmp fill_chars ret form_feed call home_cursor clear_eop call clear_eol ; clear to end of current line mov W, #rows-1 ; compute additional rows to clear mov temp, W ; temp = (rows - 1) - cursor_row mov W, cursor_row sub temp, W snb status.zf ; any rows to clear? ret ; no clrb status.cf ; multiply temp by 20 to get char count rl temp clrb status.cf rl temp mov W, temp clrb status.cf rl temp clrb status.cf rl temp add temp, W jmp fill_chars cursor_up dec cursor_row mov W, #rows-1 snb cursor_row.7 mov cursor_row, W jmp compute_cursor_loc cursor_down inc cursor_row snb cursor_row.2 ; hard-coded for 4 rows clr cursor_row jmp compute_cursor_loc cursor_left dec cursor_col mov W, #columns-1 snb cursor_col.7 mov cursor_col, W jmp compute_cursor_loc cursor_right inc cursor_col mov W, cursor_col xor W, #columns snb status.zf clr cursor_row jmp compute_cursor_loc esc_Y mov W, #2 mov escape_state, W bad_escape ret esc_Y_col_seen mov W, #' ' mov W, char-w mov esc_Y_col, W inc escape_state ret escape inc escape_state ret esc_Y_row_seen mov W, #(256-' ')-rows ; range check the row (still has ' ' offset) add W, char snb status.cf jmp bad_row mov W, #' ' ; move cursor to specified column mov W, char-w mov cursor_row, W bad_row mov W, #256-columns ; range check the column add W, esc_Y_col snb status.cf jmp bad_col mov W, esc_Y_col ; move cursor to specified column mov cursor_col, W bad_col clr escape_state jmp compute_cursor_loc esc_seen clr escape_state ; assume only two-char sequence mov W, #$40 mov W, char-w mov temp, W and W, #060h ; check for range 40-5F sb status.zf jmp bad_escape mov W, temp jmp esc_char_table bell bank int_vars ; start a bell mov W, #bell_half_period mov bell_half_cyc, W mov bell_line_cnt, W mov W, #bell_duration mov bell_dur_cnt, W bank main_vars ret reset_entry mode 0fh ; paranoia mov W, #int_off mov !OPTION, W bank main_vars mov W, #inita mov Ra, W mov W, #trisa mov !ra,w mov W, #initb mov Rb, W mov W, #trisb mov !rb,w clr escape_state call form_feed bank int_vars mov W, #5 ; set up for DelM macro mov Five, W mov W, #15 mov Fifteen, W clr line_type mov W, ++line_type ; get initial line count page line_dispatch call line_dispatch page $ mov line_count, W if ft_serial_input bank ser_vars clr ser_rx_state mov W, #1 mov ser_rx_samp_cnt, W clr ser_rx_flag endif bank main_vars mov W, #int_on mov !OPTION, W if ft_splash page splash call splash endif ;call home_cursor main_loop call show_cursor if ft_pal_video mov W, #25 else mov W, #30 endif call delay_fields if ft_serial_input sb status.zf jmp got_char endif call hide_cursor if ft_pal_video mov W, #25 else mov W, #30 endif call delay_fields if ft_serial_input sb status.zf jmp got_char endif jmp main_loop if ft_serial_input got_char call hide_cursor ; hide cursor during character processing bank ser_vars ; get character and clear rx flag mov W, ser_rx_char clr ser_rx_flag bank main_vars call output_char jmp main_loop endif ;--------------------------------------------------------------------------- ; interrupt handler ;--------------------------------------------------------------------------- org 0200h ; 30-DEC-2000 Eric Smith ; changed for GPASM assembler ;6-JAN-2000 Richard Ottosen ;This routine is for the SX parts in Turbo mode only. It does not matter if the ; Carry fuse is set or clear. ; ;Macro to delay for M number of cycles from 0 through 65535. ; The macro includes paging for long calls. ; ;Uses the routine "DelW" to do the short delays and uses the variable "DelMCnt" ; as well for long delays. ;The constants 5 and 15 must be loaded into variables "Five" and "Fifteen" ; before DelM is used. ; ; DelM MACRO 1 ;DelM _MM noexpand local2 = \1 IF (local2 & $FF)=0 ;No delay at all ENDIF IF (local2 & $FF)=1 nop ;Delay 1 cycle inline ENDIF IF (local2 & $FF)=2 nop ;Delay 2 cycles inline nop ENDIF IF (local2 & $FF)=3 jmp $+1 ;Delay 3 cycles inline ENDIF IF (local2 & $FF)=4 jmp $+1 ;Delay 4 cycles inline nop ENDIF IF (local2 & $FF)=5 jmp $+1 ;Delay 5 cycles inline nop nop ENDIF IF (local2 & $FF)=6 jmp $+1 ;Delay 6 cycles inline jmp $+1 ENDIF IF (local2 & $FF)=7 PAGE Delay6 call Delay6 ;Delay 7 cycles ENDIF IF (local2 & $FF)=8 PAGE Delay7 call Delay7 ;Delay 8 cycles ENDIF IF (local2 & $FF)=9 PAGE Delay8 call Delay8 ;Delay 9 cycles ENDIF IF (local2 & $FF)=10 PAGE Delay9 call Delay9 ;Delay 10 cycles ENDIF IF (local2 & $FF)=11 PAGE Delay10 call Delay10 ;Delay 11 cycles ENDIF IF (local2 & $FF)=12 PAGE Delay11 call Delay11 ;Delay 12 cycles ENDIF IF (local2 & $FF)=13 PAGE Delay12 call Delay12 ;Delay 13 cycles ENDIF IF (local2 & $FF)=14 PAGE Delay13 call Delay13 ;Delay 14 cycles ENDIF IF (local2 & $FF)=15 PAGE Delay14 call Delay14 ;Delay 15 cycles ENDIF IF (local2 & $FF)=16 PAGE Delay15 call Delay15 ;Delay 16 cycles ENDIF IF (local2 & $FF)>16 mov W, #((local2-1) & $FF) PAGE DelW call DelW ;Delay for 17 thru 255 cycles ENDIF IF (local2 >> 8)<>0 mov W, #(local2 >> 8) ;Delay more for greater than 255 cycles mov DelMCnt, W ;_DelMLoop mov W, #251 PAGE DelW call DelW decsz DelMCnt jmp $-4 ;jmp _DelMLoop ENDIF ENDM ; original gpasm source macro by Eric Smith 7/8/96 Hacked by Richard Ottosen 8/8/99 ; converted to sx-key mnenomics by Peter Verkaik ;----------------------------------------------------------------------------- ;This version of DelW is for the Scenix parts in Turbo mode. It does not matter ;if the Carry fuse is set or clear. ; DelW delays W cycles, including call, return, and one cycle for the ; mov W, #instruction to set up the count in W ; range is 16..255 ; ; For example, the sequence ; mov W, #17 ; call DelW ; will take 17 cycles to execute ;----------------------------------------------------------------------------- ; W value on entry 16 17 18 19 20 21 22 23 ; Caller's instructions --- --- --- --- --- ----- ----- ----- ; mov W, #n 0 0 0 0 0 0 0 0 ; call DelW 1 1 1 1 1 1 1 1 DelW setb status.cf ; 4 4 4 4 4 4 4 4 mov W, Fifteen-w ; 5 5 5 5 5 5 5 5 _DelWLp add W, Five ; 6 6 6 6 6 6 11 7 11 7 11 sb status.cf ; 7 7 7 7 7 7 12 12 12 jmp _DelWLp ; 8 8 8 clrb status.cf ; 9 9 9 9 9 14 14 14 add PC, W ; 10 10 10 10 10 15 15 15 Delay10 nop ; 13 Delay9 nop ; 13 14 Delay8 nop ; 13 14 15 18 Delay7 nop ; 13 14 15 16 18 19 Delay6 retp ; 13 14 15 16 17 18 19 20 ; 16 17 18 19 20 21 22 23 Delay15 nop Delay14 nop Delay13 nop Delay12 nop Delay11 jmp Delay8 scanln macro 2 ;scanln count,function expand jmp \2 ;jmp function retw \1 ;retw count noexpand endm ; table of line type function pointers and counts ; when called for function, takes cycles 58-63 line_dispatch add PC, W ; 58 if ft_pal_video ; PAL lines scanln 2,equalization_line ; 624-625 scanln 2,vsync_line ; 1-2 scanln 1,vsync_eq_line ; 3 scanln 2,equalization_line ; 4-5 scanln 17,vblank_line ; 6-22 scanln 1,vblank_black_line ; 23 scanln top_border,black_video_line ; 24-106 scanln active_video_lines,active_video_line ; 107-226 scanln bottom_border-1,black_video_line ; 227-309 if ft_interlace scanln 1,black_video_line ; 310 scanln 2,equalization_line ; 311-312 scanln 1,eq_vsync_line ; 313 scanln 2,vsync_line ; 314-315 scanln 2,equalization_line ; 316-317 scanln 1,eq_vblank_line ; 318 scanln 17,vblank_line ; 319-335 scanln top_border,black_video_line ; 336-418 scanln active_video_lines,active_video_line ; 419-538 scanln bottom_border,black_video_line ; 539-622 endif scanln 1,black_eq_line ; 310 or 623 else ; NTSC lines scanln 3,equalization_line ; 1-3 scanln 3,vsync_line ; 4-6 scanln 3,equalization_line ; 7-9 scanln 11,vblank_line ; 10-20 scanln top_border,black_video_line ; 21-81 scanln active_video_lines,active_video_line ; 82-201 scanln bottom_border,black_video_line ; 202-262 if ft_interlace scanln 1,black_eq_line ; 263 scanln 2,equalization_line ; 264-265 scanln 1,eq_vsync_line ; 266 scanln 2,vsync_line ; 267-268 scanln 1,vsync_eq_line ; 269 scanln 2,equalization_line ; 270-271 scanln 1,eq_vblank_line ; 272 scanln 10,vblank_line ; 273-282 scanln 1,vblank_black_line ; 283 scanln top_border,black_video_line ; 284-344 scanln active_video_lines,active_video_line ; 345-464 scanln bottom_border,black_video_line ; 465-525 endif endif line_types equ (($-line_dispatch)-1)/2 if ft_serial_input ; serial input state machine dispatch serial_state_table mov W, ser_rx_state ; 12 add PC, W ; 13-15 jmp ser_idle ; 16-18 jmp ser_data_bit ; 16-18 jmp ser_stop_bit ; 16-18 endif bell_48 clrb pzt ; 48 delm 1 ; 49 bell_50 delm 1 ; 50 jmp bell_done ; 51-53 interrupt mov W, #vid_blank ; 4 start front porch mov vid_port, W ; 5 if ft_serial_input bank ser_vars ; 6 decsz ser_rx_samp_cnt ; 7 jmp skip_serial ; 8-10 call serial_state_table ; 9-11 jmp serial_done ; 39-41 skip_serial delm 31 ; 11-41 serial_done else delm 36 ; 6-41 endif bank int_vars ; 42 test bell_dur_cnt ; 43 - bell active? snb status.zf ; 44 jmp bell_48 ; 45-47 - no decsz bell_line_cnt ; 46 - time to toggle PZT? jmp bell_50 ; 47-49 - no mov W, #1<<pzt_bit ; 48 - toggle PZT xor Ra, W ; 49 dec bell_dur_cnt ; 50 - decrement duration mov W, bell_half_cyc ; 51 - reinit line count mov bell_line_cnt, W ; 52 delm 1 ; 53 bell_done mov W, line_type ; 54 call line_dispatch ; 55-57 decsz line_count ; any more lines of the current type? jmp interrupt_done ; no, done inc line_type ; advance to next line type inc line_type mov W, line_type ; end of field? xor W, #line_types*2 sb status.zf jmp get_line_count ; no clr line_type ; yes, start new field test g_field_count ; decrement field counter sb status.zf dec g_field_count get_line_count mov W, ++line_type ; new line type, how many lines? call line_dispatch mov line_count, W interrupt_done mov W, #256-int_period ; all done with this scan line retiw ; at some point within the frame before the first active video line, ; call this subroutine to initialize the pointers display_frame_setup mov W, #video_buffer mov line_start, W clr vpix_cnt mov W, #scan_lines_per_vpixel mov scanline_cnt, W ret if ft_color burst_l equ vid_blank-(burst_amplitude/2) burst_h equ vid_blank+(burst_amplitude/2) burst_x equ burst_l^burst_h ; burst starts at 228 cycles from horizontal reference point, ; which is 292 cycles from our start of back porch. color_burst delm 14 ; 270-283 ; $$$ actually, don't toggle burst phase, because our current ; line timing is an integral multiple of the color carrier mov W, #0 ; 284 - toggle burst phase xor burst_phase, W ; 285 mov W, #18 ; 286 - 18 half-cycles of burst mov int_temp, W ; 287 mov W, #burst_h ; 288 - assume leading edge high snb burst_phase.0 ; 289 mov W, #burst_l ; 290 burst_loop xor W, #burst_x ; 291 399 mov vid_port, W ; 292 400 decsz int_temp ; 293 401 jmp burst_loop ; 294-296 402 delm 2 ; 403 mov W, #vid_blank ; 405 mov vid_port, W ; 406 delm 48 ; 407 ret ; 455-457 else color_burst delm 185 ; 270-454 ret ; 455-457 endif equalization_line mov W, #vid_sync ; 64 - start equalizing pulse mov vid_port, W delm equalization_pulse_width-2 mov W, #vid_blank ; end equalizing pulse mov vid_port, W delm ((h/2)-equalization_pulse_width)-2 eq_second_half mov W, #vid_sync ; start equalizing pulse mov vid_port, W delm equalization_pulse_width-2 mov W, #vid_blank ; end equalizing pulse mov vid_port, W ret vsync_line mov W, #vid_sync ; 64 - start vsync pulse mov vid_port, W delm vsync_pulse_width-2 mov W, #vid_blank ; end vsync pulse - start serration mov vid_port, W delm serration_pulse_width-2 vsync_second_half mov W, #vid_sync ; start vsync pulse mov vid_port, W delm vsync_pulse_width-2 mov W, #vid_blank ; end vsync pulse - start serration mov vid_port, W ret vblank_line mov W, #vid_sync ; 64 - start hsync pulse mov vid_port, W ; 65 delm hsync_pulse_width-2 ; 66-264 mov W, #vid_blank ; 265 - end hsync pulse mov vid_port, W ; 266 call color_burst ; 267-269 ret black_video_line mov W, #vid_sync ; 64 - start hsync pulse mov vid_port, W ; 65 delm hsync_pulse_width-2 ; 66-264 mov W, #vid_blank ; 265 - end hsync pulse, start back porch mov vid_port, W ; 266 call color_burst ; 267-269 mov W, #vid_black ; 458 - end back porch, start active video mov vid_port, W ; 459 jmp display_frame_setup ; $$$ not the best place for this? ; ret if ft_interlace|ft_pal_video ; NTSC line 263, PAL line 623 (interlaced), PAL line 310 (non-interlaced) black_eq_line mov W, #vid_sync ; 64 - start hsync pulse mov vid_port, W ; 65 delm hsync_pulse_width-2 ; 66-264 mov W, #vid_blank ; 265 - end hsync pulse, start back porch mov vid_port, W ; 266 call color_burst ; 267-269 mov W, #vid_black ; 458 - end back porch, start active video mov vid_port, W ; 459 delm ((h/2)-(hsync_pulse_width+back_porch_width))-5 jmp eq_second_half endif if ft_interlace ; NTSC line 266, PAL line 313 eq_vsync_line mov W, #vid_sync ; 64 - start equalizing pulse mov vid_port, W delm equalization_pulse_width-2 mov W, #vid_blank ; end equalizing pulse mov vid_port, W delm ((h/2)-equalization_pulse_width)-5 jmp vsync_second_half endif if ft_interlace|ft_pal_video ; NTSC line 269, PAL line 3 vsync_eq_line mov W, #vid_sync ; 64 - start vsync pulse mov vid_port, W delm vsync_pulse_width-2 mov W, #vid_blank ; end vsync pulse - start serration mov vid_port, W delm serration_pulse_width-5 jmp eq_second_half endif if ft_interlace ; NTSC line 272 - like an equalization, but a full line with only one pulse ; PAL line 318 eq_vblank_line mov W, #vid_sync ; 64 - start equalizing pulse mov vid_port, W delm equalization_pulse_width-2 mov W, #vid_blank ; end equalizing pulse mov vid_port, W ret endif if ft_interlace|ft_pal_video ; NTSC line 283, PAL line 23 vblank_black_line mov W, #vid_sync ; 64 - start hsync pulse mov vid_port, W ; 65 delm hsync_pulse_width-2 ; 66-264 mov W, #vid_blank ; 265 - end hsync pulse mov vid_port, W ; 266 call color_burst ; 267-269 delm ((h/2)+front_porch_width)-458 ; 458-1431 mov W, #vid_black ; 1432 - start active video mov vid_port, W ret endif active_video_line mov W, #vid_sync ; 64 - start hsync pulse mov vid_port, W ; 65 delm hsync_pulse_width-2 ; 66-264 mov W, #vid_blank ; 265 - end hsync pulse, start back porch mov vid_port, W ; 266 call color_burst ; 267-269 mov W, #vid_black ; 458 - end back porch, start active video mov vid_port, W ; 459 snb vpix_cnt.3 ; vpixel >= 8? jmp active_video_line_done delm 100 mov W, line_start mov char_ptr, W mov W, #chars_per_row+1 mov char_cnt, W ; leading dummy character is always blank, allows us to fill ; the pixel pipeline clr pixels character ; pixel 0 mov W, #vid_black ; 0 snb pixels.0 ; 1 mov W, #vid_white ; 2 mov vid_port, W ; 3 mov W, char_ptr ; 4 - get next character mov fsr, W ; 5 mov W, indf ; 6 bank int_vars ; 7 mov inverse_flag, W ; 8 and W, #07fh ; 9 mov chargen_ptr, W ; 10 mov W, --char_cnt ; 11 - increment buffer pointer sb status.zf ; 12 - unless we're at end of line inc char_ptr ; 13 - (due to pipeline, we pass through setb char_ptr.4 ; 14 - here columns+1 times) ; pixel 1 mov W, #vid_black ; 0 snb pixels.1 ; 1 mov W, #vid_white ; 2 mov vid_port, W ; 3 mov W, #(chargen/4)&0ffh ; 4 - add low part of chargen base add chargen_ptr, W ; 5 mov W, #(chargen/4)>>8 ; 6 - add high part of chargen base mov chargen_ptr+1, W ; 7 snb status.cf ; 8 inc chargen_ptr+1 ; 9 clrb status.cf ; 10 - rotate high bit of vpix_cnt into snb vpix_cnt.2 ; 11 - table address setb status.cf ; 12 rl chargen_ptr ; 13 rl chargen_ptr+1 ; 14 ; pixel 2 mov W, #vid_black ; 0 snb pixels.2 ; 1 mov W, #vid_white ; 2 mov vid_port, W ; 3 clrb status.cf ; 4 - rotate next bit of vpix_cnt into snb vpix_cnt.1 ; 5 - table address setb status.cf ; 6 rl chargen_ptr ; 7 rl chargen_ptr+1 ; 8 delm 6 ; 9-14 ; pixel 3 mov W, #vid_black ; 0 snb pixels.3 ; 1 mov W, #vid_white ; 2 mov vid_port, W ; 3 DelM 11 ; 4-14 ; pixel 4 mov W, #vid_black ; 0 snb pixels.4 ; 1 mov W, #vid_white ; 2 mov vid_port, W ; 3 mov W, chargen_ptr+1 ; 4 mov m,w ; 5 mov W, chargen_ptr ; 6 iread ; 7-10 mov pixels, W ; 11 mov w,m ; 12 mode 0fh ; 13 mov chargen_ptr, W ; 14 - now use chargen_ptr as a temp ; intercharacter space snb vpix_cnt.0 ; 0 - get left four pixels into bits 0..3 swap pixels ; 1 mov W, #vid_black ; 2 mov vid_port, W ; 3 clrb pixels.4 ; 4 snb vpix_cnt.0 ; 5 - get rightmost pixel into bit 4 rr chargen_ptr ; 6 snb chargen_ptr.0 ; 7 setb pixels.4 ; 8 mov W, #01fh ; 9 - invert if needed snb inverse_flag.7 ; 10 xor pixels, W ; 11 ; $$$ add more inter-character spacing here? decsz char_cnt ; 12 jmp character ; 13-15 active_video_line_done decsz scanline_cnt ; more scan lines for this pixel row? ret mov W, #scan_lines_per_vpixel mov scanline_cnt, W inc vpix_cnt ; more pixels for this character row? mov W, vpix_cnt xor W, #vpixels_per_char sb status.zf ret clr vpix_cnt mov W, char_ptr ; advance buffer pointer to next character row mov line_start, W ret ;--------------------------------------------------------------------------- ; serial receive routine ;--------------------------------------------------------------------------- if ft_serial_input ser_idle mov W, #1 ; 19 - sample every line mov ser_rx_samp_cnt, W ; 20 skip_on_ser_rx_mark ; 21 - start bit detected? jmp ser_ret_25 ; 22-24 - no, return mov W, #lines_per_serial_sample * 3 / 2 ; 23 mov ser_rx_samp_cnt, W ; 24 - skip start bit and sample first data bit ; in middle of bit time mov W, #8 ; 25 - set up to receive 8 chars mov ser_rx_bit_cnt, W ; 26 clr ser_rx_byte ; 27 - not needed for 8-bit chars inc ser_rx_state ; 28 - advance to next state jmp ser_ret_32 ; 29-31 ser_data_bit clrb status.cf ; 19 - read a bit skip_on_ser_rx_mark ; 20 setb status.cf ; 21 rr ser_rx_byte ; 22 - rotate into byte mov W, #lines_per_serial_sample ; 23 - set up for next sample mov ser_rx_samp_cnt, W ; 24 decsz ser_rx_bit_cnt ; 25 - all data bits read? jmp ser_ret_29 ; 26-28 - no mov W, ser_rx_byte ; 27 - move char to buffer mov ser_rx_char, W ; 28 inc ser_rx_flag ; 29 - signal main mov W, #(lines_per_serial_sample * 11)/8 ; 30 - set up for stop bit mov ser_rx_samp_cnt, W ; 31 inc ser_rx_state ; 32 - advance to next state jmp ser_ret_36 ; 33-35 ser_stop_bit mov W, #1 ; 19 - sample every line mov ser_rx_samp_cnt, W ; 20 skip_on_ser_rx_mark ; 21 - line idle? clr ser_rx_state ; 22 - yes, back to idle ser_ret_23 delm 2 ; 23-24 ser_ret_25 delm 4 ; 25-28 ser_ret_29 delm 3 ; 29-31 ser_ret_32 delm 4 ; 32-35 ser_ret_36 ret ; 36-38 endif ;--------------------------------------------------------------------------- ; splash screen ;--------------------------------------------------------------------------- if ft_splash org 400h splash_table add PC, W dw asc_bel ; 01234567890123456789 dw 'SERVID 0.2 Copyright' dw '2001 Eric Smith and', asc_cr, asc_lf dw 'Richard Ottosen', asc_cr, asc_lf dw '(SXLIST challenge) ' dw 0 splash clr temp+2 splash_loop mov W, temp+2 call splash_table xor W, #0 snb status.zf retp page output_char call output_char ; $$$ change to end with retp? page $ inc temp+2 jmp splash_loop endif ;--------------------------------------------------------------------------- ; character generator macros ;--------------------------------------------------------------------------- org chargen cg_row1 macro 1 ;cg_row1 pixels noexpand char1 = \1 r1_bits = 0 rept 5 r1_bits = (r1_bits*2)+(char1//10) char1 = char1/10 endr endm cg_row2 macro 1 ;cg_row2 pixels noexpand char2 = \1 r2_bits = 0 rept 5 r2_bits = (r2_bits*2)+(char2//10) char2 = char2/10 endr expand dw ((r1_bits&010h)<<4)+(r1_bits&0fh)+((r2_bits&010h)<<5)+((r2_bits&0fh)<<4) noexpand endm ; SERVID character set ; $Id charset.inc,v 1.4 2001/01/04 04 58 40 eric Exp $ ; ; Copyright 2001 Richard Ottosen and Loren Blaney ; ; This program is free software; you can redistribute it and/or modify ; it under the terms of the GNU General Public License version 2 as published ; by the Free Software Foundation. Note that permission is not granted ; to redistribute this program under the terms of any other version of the ; General Public License. ; ; This program is distributed in the hope that it will be useful, ; but WITHOUT ANY WARRANTY; without even the implied warranty of ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ; GNU General Public License for more details. ; ; You should have received a copy of the GNU General Public License ; along with this program; if not, write to the Free Software ; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. ; ; Licenses for non-GPL use may be negotiated with the authors. ; ; originally from Bion as a vertical font ; used by Richard Ottosen's Whirlygig ; rotated to horizontal form by Loren Blaney ; munged for SERVID by Richard Ottosen cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;20h cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 cg_row1 00100 cg_row2 00000 ;21h cg_row1 01010 cg_row2 01010 cg_row1 01010 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;22h cg_row1 01010 cg_row2 01010 cg_row1 11111 cg_row2 01010 cg_row1 11111 cg_row2 01010 cg_row1 01010 cg_row2 00000 ;23h cg_row1 00100 cg_row2 01111 cg_row1 10100 cg_row2 01110 cg_row1 00101 cg_row2 11110 cg_row1 00100 cg_row2 00000 ;24h cg_row1 11000 cg_row2 11001 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 10011 cg_row1 00011 cg_row2 00000 ;25h cg_row1 01000 cg_row2 10100 cg_row1 10100 cg_row2 01000 cg_row1 10101 cg_row2 10010 cg_row1 01101 cg_row2 00000 ;26h cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;27h cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 01000 cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00000 ;28h cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00010 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 00000 ;29h cg_row1 00100 cg_row2 10101 cg_row1 01110 cg_row2 00100 cg_row1 01110 cg_row2 10101 cg_row1 00100 cg_row2 00000 ;2Ah cg_row1 00000 cg_row2 00100 cg_row1 00100 cg_row2 11111 cg_row1 00100 cg_row2 00100 cg_row1 00000 cg_row2 00000 ;2Bh cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00100 cg_row2 00100 cg_row1 01000 cg_row2 00000 ;2Ch cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 11111 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;2Dh cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00100 cg_row2 00000 ;2Eh cg_row1 00000 cg_row2 00001 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 10000 cg_row1 00000 cg_row2 00000 ;2Fh cg_row1 01110 cg_row2 10001 cg_row1 10011 cg_row2 10101 cg_row1 11001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;30h cg_row1 00100 cg_row2 01100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 01110 cg_row2 00000 ;31h cg_row1 01110 cg_row2 10001 cg_row1 00001 cg_row2 00110 cg_row1 01000 cg_row2 10000 cg_row1 11111 cg_row2 00000 ;32h cg_row1 11111 cg_row2 00001 cg_row1 00010 cg_row2 00110 cg_row1 00001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;33h cg_row1 00010 cg_row2 00110 cg_row1 01010 cg_row2 10010 cg_row1 11111 cg_row2 00010 cg_row1 00010 cg_row2 00000 ;34h cg_row1 11111 cg_row2 10000 cg_row1 11110 cg_row2 00001 cg_row1 00001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;35h cg_row1 00111 cg_row2 01000 cg_row1 10000 cg_row2 11110 cg_row1 10001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;36h cg_row1 11111 cg_row2 00001 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 01000 cg_row1 01000 cg_row2 00000 ;37h cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 01110 cg_row1 10001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;38h cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 01111 cg_row1 00001 cg_row2 00010 cg_row1 11100 cg_row2 00000 ;39h cg_row1 00000 cg_row2 00000 cg_row1 00100 cg_row2 00000 cg_row1 00100 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;3Ah cg_row1 00000 cg_row2 00000 cg_row1 00100 cg_row2 00000 cg_row1 00100 cg_row2 00100 cg_row1 01000 cg_row2 00000 ;3Bh cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 10000 cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00000 ;3Ch cg_row1 00000 cg_row2 00000 cg_row1 11111 cg_row2 00000 cg_row1 11111 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;3Dh cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00001 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 00000 ;3Eh cg_row1 01110 cg_row2 10001 cg_row1 00010 cg_row2 00100 cg_row1 00100 cg_row2 00000 cg_row1 00100 cg_row2 00000 ;3Fh cg_row1 01110 cg_row2 10001 cg_row1 10101 cg_row2 10111 cg_row1 10110 cg_row2 10000 cg_row1 01111 cg_row2 00000 ;40h cg_row1 00100 cg_row2 01010 cg_row1 10001 cg_row2 10001 cg_row1 11111 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;41h cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 11110 cg_row1 10001 cg_row2 10001 cg_row1 11110 cg_row2 00000 ;42h cg_row1 01110 cg_row2 10001 cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;43h cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 11110 cg_row2 00000 ;44h cg_row1 11111 cg_row2 10000 cg_row1 10000 cg_row2 11110 cg_row1 10000 cg_row2 10000 cg_row1 11111 cg_row2 00000 ;45h cg_row1 11111 cg_row2 10000 cg_row1 10000 cg_row2 11110 cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 00000 ;46h cg_row1 01111 cg_row2 10000 cg_row1 10000 cg_row2 10000 cg_row1 10011 cg_row2 10001 cg_row1 01111 cg_row2 00000 ;47h cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 11111 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;48h cg_row1 01110 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 01110 cg_row2 00000 ;49h cg_row1 00001 cg_row2 00001 cg_row1 00001 cg_row2 00001 cg_row1 00001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;4Ah cg_row1 10001 cg_row2 10010 cg_row1 10100 cg_row2 11000 cg_row1 10100 cg_row2 10010 cg_row1 10001 cg_row2 00000 ;4Bh cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 10000 cg_row1 11111 cg_row2 00000 ;4Ch cg_row1 10001 cg_row2 11011 cg_row1 10101 cg_row2 10101 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;4Dh cg_row1 10001 cg_row2 10001 cg_row1 11001 cg_row2 10101 cg_row1 10011 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;4Eh cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;4Fh cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 11110 cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 00000 ;50h cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10101 cg_row2 10010 cg_row1 01101 cg_row2 00000 ;51h cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 11110 cg_row1 10100 cg_row2 10010 cg_row1 10001 cg_row2 00000 ;52h cg_row1 01110 cg_row2 10001 cg_row1 10000 cg_row2 01110 cg_row1 00001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;53h cg_row1 11111 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 ;54h cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;55h cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 01010 cg_row1 00100 cg_row2 00000 ;56h cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10101 cg_row1 10101 cg_row2 11011 cg_row1 10001 cg_row2 00000 ;57h cg_row1 10001 cg_row2 10001 cg_row1 01010 cg_row2 00100 cg_row1 01010 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;58h cg_row1 10001 cg_row2 10001 cg_row1 01010 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 ;59h cg_row1 11111 cg_row2 00001 cg_row1 00010 cg_row2 00100 cg_row1 01000 cg_row2 10000 cg_row1 11111 cg_row2 00000 ;5Ah cg_row1 11111 cg_row2 11000 cg_row1 11000 cg_row2 11000 cg_row1 11000 cg_row2 11000 cg_row1 11111 cg_row2 00000 ;5Bh cg_row1 00000 cg_row2 10000 cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00001 cg_row1 00000 cg_row2 00000 ;5Ch cg_row1 11111 cg_row2 00011 cg_row1 00011 cg_row2 00011 cg_row1 00011 cg_row2 00011 cg_row1 11111 cg_row2 00000 ;5Dh cg_row1 00000 cg_row2 00000 cg_row1 00100 cg_row2 01010 cg_row1 10001 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;5Eh cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 11111 cg_row2 00000 ;5Fh cg_row1 01000 cg_row2 00100 cg_row1 00010 cg_row2 00000 cg_row1 00000 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;60h cg_row1 00000 cg_row2 00000 cg_row1 01110 cg_row2 00001 cg_row1 01111 cg_row2 10001 cg_row1 01111 cg_row2 00000 ;61h cg_row1 10000 cg_row2 10000 cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 11110 cg_row2 00000 ;62h cg_row1 00000 cg_row2 00000 cg_row1 01111 cg_row2 10000 cg_row1 10000 cg_row2 10000 cg_row1 01111 cg_row2 00000 ;63h cg_row1 00001 cg_row2 00001 cg_row1 01111 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 01111 cg_row2 00000 ;64h cg_row1 00000 cg_row2 00000 cg_row1 01110 cg_row2 10001 cg_row1 11111 cg_row2 10000 cg_row1 01111 cg_row2 00000 ;65h cg_row1 00110 cg_row2 01001 cg_row1 01000 cg_row2 11110 cg_row1 01000 cg_row2 01000 cg_row1 01000 cg_row2 00000 ;66h cg_row1 00000 cg_row2 00000 cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 01111 cg_row1 00001 cg_row2 01110 ;67h cg_row1 10000 cg_row2 10000 cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;68h cg_row1 00100 cg_row2 00000 cg_row1 01100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 01110 cg_row2 00000 ;69h cg_row1 00010 cg_row2 00000 cg_row1 00010 cg_row2 00010 cg_row1 00010 cg_row2 00010 cg_row1 10010 cg_row2 01100 ;6Ah cg_row1 10000 cg_row2 10000 cg_row1 10010 cg_row2 10100 cg_row1 11000 cg_row2 10100 cg_row1 10010 cg_row2 00000 ;6Bh cg_row1 01100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 01110 cg_row2 00000 ;6Ch cg_row1 00000 cg_row2 00000 cg_row1 11010 cg_row2 10101 cg_row1 10101 cg_row2 10101 cg_row1 10101 cg_row2 00000 ;6Dh cg_row1 00000 cg_row2 00000 cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 00000 ;6Eh cg_row1 00000 cg_row2 00000 cg_row1 01110 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 01110 cg_row2 00000 ;6Fh cg_row1 00000 cg_row2 00000 cg_row1 11110 cg_row2 10001 cg_row1 10001 cg_row2 11110 cg_row1 10000 cg_row2 10000 ;70h cg_row1 00000 cg_row2 00000 cg_row1 01111 cg_row2 10001 cg_row1 10001 cg_row2 01111 cg_row1 00001 cg_row2 00001 ;71h cg_row1 00000 cg_row2 00000 cg_row1 10110 cg_row2 11001 cg_row1 10000 cg_row2 10000 cg_row1 10000 cg_row2 00000 ;72h cg_row1 00000 cg_row2 00000 cg_row1 01111 cg_row2 10000 cg_row1 01110 cg_row2 00001 cg_row1 11110 cg_row2 00000 ;73h cg_row1 00100 cg_row2 00100 cg_row1 11111 cg_row2 00100 cg_row1 00100 cg_row2 00100 cg_row1 00011 cg_row2 00000 ;74h cg_row1 00000 cg_row2 00000 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 10001 cg_row1 01111 cg_row2 00000 ;75h cg_row1 00000 cg_row2 00000 cg_row1 10001 cg_row2 10001 cg_row1 10001 cg_row2 01010 cg_row1 00100 cg_row2 00000 ;76h cg_row1 00000 cg_row2 00000 cg_row1 10001 cg_row2 10101 cg_row1 10101 cg_row2 10101 cg_row1 01010 cg_row2 00000 ;77h cg_row1 00000 cg_row2 00000 cg_row1 10001 cg_row2 01010 cg_row1 00100 cg_row2 01010 cg_row1 10001 cg_row2 00000 ;78h cg_row1 00000 cg_row2 00000 cg_row1 10001 cg_row2 10001 cg_row1 01010 cg_row2 00100 cg_row1 01000 cg_row2 10000 ;79h cg_row1 00000 cg_row2 00000 cg_row1 11111 cg_row2 00010 cg_row1 00100 cg_row2 01000 cg_row1 11111 cg_row2 00000 ;7Ah cg_row1 00110 cg_row2 01000 cg_row1 01000 cg_row2 11000 cg_row1 01000 cg_row2 01000 cg_row1 00110 cg_row2 00000 ;7Bh cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 cg_row1 00100 cg_row2 00100 cg_row1 00100 cg_row2 00000 ;7Ch cg_row1 01100 cg_row2 00010 cg_row1 00010 cg_row2 00011 cg_row1 00010 cg_row2 00010 cg_row1 01100 cg_row2 00000 ;7Dh cg_row1 00000 cg_row2 00000 cg_row1 01000 cg_row2 10101 cg_row1 00010 cg_row2 00000 cg_row1 00000 cg_row2 00000 ;7Eh ;cg_row1 11111 ;cg_row2 11111 ;cg_row1 11111 ;cg_row2 11111 ;cg_row1 11111 ;cg_row2 11111 ;cg_row1 11111 ;cg_row2 11111 ;7Fh end
| file: /Techref/scenix/lib/io/dev/video/servid_sx.htm, 67KB, , updated: 2007/3/3 04:58, local time: 2025/10/25 22:17, 
owner: pv-bos-KA6, 
 
216.73.216.22,10-3-83-201:LOG IN | 
| ©2025 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions? <A HREF="http://www.piclist.com/Techref/scenix/lib/io/dev/video/servid_sx.htm"> Peter Verkaik's port of the MASM SERVID code to the SXKey</A> | 
| Did you find what you needed? | 
|  PICList 2025 contributors: o List host: MIT, Site host massmind.org, Top posters @none found - Page Editors: James Newton, David Cary, and YOU! * Roman Black of Black Robotics donates from sales of Linistep stepper controller kits. * Ashley Roll of Digital Nemesis donates from sales of RCL-1 RS232 to TTL converters. * Monthly Subscribers: Gregg Rew. on-going support is MOST appreciated! * Contributors: Richard Seriani, Sr. | 
| Welcome to www.piclist.com! | 
.