; M4H192/ASM CLEAR_TO_EOS EQU $ GET_CURSOR ;Get the cursor position CALL GET_RC_ADDR ;Get the real address R077 EQU $-2 PUSH HL ;Save the start for LDIR PUSH HL ;Copy it to BC POP BC LD HL,24*80+0F7FFH ;Get the last place to blank CLEAR_SPACE EQU $ OR A ;Reset the carry SBC HL,BC ;HL is now length of area PUSH HL ;Put it into BC and clear stack POP BC POP HL ;Get the starting address JR Z,NO_CLEAR ;Jump if no count PUSH HL ;Copy to DE POP DE INC DE ;Point DE one ahead PUSH BC ;Hide the cursor before PUSH DE PUSH HL LD A,15 ;Use *DO for this CALL CHAIN_IN R190 EQU $-2 POP HL ;Restore the stack POP DE POP BC SWAP_IN ;Swap screen into RAM LD (HL),' ' ;Store one blank SWAP_OUT CLR_LOOP LD A,30 ;One line max SWAP_IN ;Screen in LINE_LOOP PUSH AF ;Save the max counter LD A,B ;Check if done with all bytes OR C JR Z,END_CLEAR ;If done, exit POP AF ;Get the max count back LDI ;Blank one byte DEC A ;Decrement the max count JR NZ,LINE_LOOP ;If not done, do it again SWAP_OUT ;Swap the video out, and enable JR CLR_LOOP ;interrupts again, and loop. ; END_CLEAR POP AF ;Fix the stack SWAP_OUT ;Swap the video back out LD A,14 ;Turn the cursor back on JP CHAIN_IN R078 EQU $-2 NO_CLEAR EQU $ JP RETOUT R191 EQU $-2 ; CLEAR_TO_EOL EQU $ GET_CURSOR ;Get the cursor ROW/COL PUSH HL ;Save it CALL GET_RC_ADDR ;Get the ADDRESS equivilent R188 EQU $-2 EX (SP),HL ;Exchange for ROW/COL LD L,79 ;Point to end of this line CALL GET_RC_ADDR ;Get the RAM address R189 EQU $-2 POP BC ;Restore the beginning PUSH BC ;Save it LD A,C ;If C = L then at EOL CP L JR Z,NO_CLEAR ;So skip rest of operations JR CLEAR_SPACE ; DEL_CHAR EQU $ LD DE,SCR_BUFF ;Get the buffer address R079 EQU $-2 PUSH DE ;Save it for the store GET_CURSOR ;Get the row to retrieve PUSH HL ;Save the column for later store GET_LINE ;Get the line into the buffer LD A,79 ;Maximum characters to move SUB L ;Subtract the current position LD H,0 ;Set the column to zero ADD HL,DE ;HL is now the place to start at PUSH HL ;Get a copy in de POP DE OR A JR Z,NO_D_CHAR LD C,A ;Get the count in BC as 16 bits LD B,0 INC HL ;Move the source one forward LDIR ;Skoot it all backwards NO_D_CHAR EQU $ LD A,' ' ;Get a space character LD (DE),A ;Blank the last space on the line POP HL ;Get the row to store at POP DE ;Get the buffer address back PUT_LINE ;Put the line back on the screen JP RETOUT R080 EQU $-2 ; END_INSERT EQU $ XOR A LD (INSERT_FLAG),A ;End insert mode R081 EQU $-2 JP RETOUT R082 EQU $-2 ; BEGIN_INSERT LD A,1 LD (INSERT_FLAG),A ;Begin insert mode R083 EQU $-2 JP RETOUT R084 EQU $-2 ; STAND_END EQU $ LD A,17 ;End standout mode JP STORE_CHAIN R085 EQU $-2 ; STAND_OUT EQU $ LD A,16 JP STORE_CHAIN ;Begin standout mode R086 EQU $-2 ; ; At this point, there are still more characters to distinguish ; between sequences. So we set the next state to go to ; SET_ESC_2 EQU $ LD HL,ESCAPE_2 ;Get address of the next state R087 EQU $-2 LD (OLDSTATE),HL ;Save it R088 EQU $-2 LD A,(NEWCHAR) ;Get the character sent this time R089 EQU $-2 LD (CHAR_2),A ;Save the character R090 EQU $-2 JP RETOUT ;Skip the *do device and return R091 EQU $-2 ; ; Jump table for processing ESC-y-[123456789] and ESC-x-[123456789] ; sequences ; MODE_TABLE EQU $ DW ENABLE_25TH R153 EQU $-2 DW NO_KEY_CLICK R154 EQU $-2 DW HOLD_SCREEN R155 EQU $-2 DW BLOCK_CURSOR R156 EQU $-2 DW CURSOR_OFF R157 EQU $-2 DW KEYPAD_SHIFTED R158 EQU $-2 DW ALT_KEY_MODE R159 EQU $-2 DW AUTO_LF R160 EQU $-2 DW AUTO_CR R161 EQU $-2 DW DISABLE_25TH R162 EQU $-2 DW KEY_CLICK R163 EQU $-2 DW NO_HOLD_SCREEN R164 EQU $-2 DW LINE_CURSOR R165 EQU $-2 DW CURSOR_ON R166 EQU $-2 DW KEY_UNSHIFT R167 EQU $-2 DW EXIT_ALT_KEY R168 EQU $-2 DW NO_AUTO_LF R169 EQU $-2 DW NO_AUTO_CR R170 EQU $-2 ; ; Process third character in 3 character or more sequence ; ESCAPE_2 EQU $ LD A,(CHAR_2) ;Get the previous character R092 EQU $-2 CP 'x' ;Was it options on JR Z,OPTION_X ;Yep, go do it CP 'y' ;Was it options off? JR NZ,MOVE_CURSOR ;Jump if not LD C,18 ;Get the offset JR OPTIONS ;Join other code OPTION_X EQU $ LD C,0 ;Get offset at zero OPTIONS EQU $ LD A,(NEWCHAR) ;Get the character R130 EQU $-2 SUB '1' ;Zero base it CP 9 ;Check for too big JP NC,RETOUT ;Can't do this one R187 EQU $-2 CP 0 JP C,RETOUT R171 EQU $-2 SLA A ;Multiply by 2 ADD A,C ;Tack on offset LD C,A ;Make BC a 16 bit offset LD B,0 LD HL,MODE_TABLE ;Get the table R172 EQU $-2 ADD HL,BC LD E,(HL) ;Get the low order byte INC HL ;Point to MSB LD D,(HL) ;Get the MSB PUSH DE ;Put it on the stack RET ;Jump to it ; ; All of the following options are not implemented, so they are ; ignored ; ENABLE_25TH: NO_KEY_CLICK: HOLD_SCREEN: KEYPAD_SHIFTED: ALT_KEY_MODE: DISABLE_25TH: KEY_CLICK: NO_HOLD_SCREEN: EXIT_ALT_KEY: KEY_UNSHIFT: GOOUT EQU $ JP RETOUT R173 EQU $-2 ; AUTO_LF EQU $ LD A,(FVAL) R179 EQU $-2 OR 1 LD (FVAL),A R180 EQU $-2 JR GOOUT ; AUTO_CR EQU $ LD A,(FVAL) R181 EQU $-2 OR 2 LD (FVAL),A R182 EQU $-2 JR GOOUT ; NO_AUTO_LF EQU $ LD A,(FVAL) R183 EQU $-2 AND 0FEH LD (FVAL),A R184 EQU $-2 JR GOOUT ; NO_AUTO_CR EQU $ LD A,(FVAL) R185 EQU $-2 AND 0FDH LD (FVAL),A R186 EQU $-2 JR GOOUT ; BLOCK_CURSOR EQU $ LD HL,(VIDEO_START);Get the call out vector R093 EQU $-2 CHECK_JUMP LD A,H ;Check for valid OR L JP Z,RETOUT ;Jump if no address specified R094 EQU $-2 LD DE,RETOUT ;Push the return address R095 EQU $-2 PUSH DE JP (HL) ;Call the users routine CURSOR_ON EQU $ LD A,15 ;Cursor on to *DO JP STORE_CHAIN R151 EQU $-2 ; LINE_CURSOR EQU $ LD HL,(VIDEO_END) ;Get the vector R096 EQU $-2 JR CHECK_JUMP ; CURSOR_OFF EQU $ LD A,14 JP STORE_CHAIN R152 EQU $-2 ; MOVE_CURSOR EQU $ LD A,(NEWCHAR) R097 EQU $-2 SUB ' ' ;This should be the row JP C,RETOUT ;Abort if bad row R098 EQU $-2 CP 24 ;check for too big JP NC,RETOUT ;Abort on bad here too R099 EQU $-2 LD (GOTO_ROW),A ;Save the row R100 EQU $-2 ; ; Now we must wait for the column to get here, so set the state, ; LD HL,ESCAPE_3 ;Set the state for column R101 EQU $-2 LD (OLDSTATE),HL ;Store it R102 EQU $-2 CONTINUE EQU $ JP RETOUT ;Chain into any filters R103 EQU $-2 ; ; At this point, we are looking for the column of a cursor ; motion sequence. This is the longest sequence ; ESCAPE_3 LD A,(NEWCHAR) ;Get the character R104 EQU $-2 SUB ' ' ;Get rid of the bias JP C,RETOUT ;Abort if bad column R105 EQU $-2 CP 80 ;Check for too high JP NC,RETOUT ;Exit if over R106 EQU $-2 LD L,A ;Get the column in L LD A,(GOTO_ROW) ;Get the ROW from the save area R107 EQU $-2 LD H,A ;Put it in HL for PUT_CURSOR PUT_CURSOR ;Set the new cursor position JP RETOUT ;Return R108 EQU $-2 ; DEL_LINE LD A,1 ;Set the delete line flag JR LINE_OPS ; ADD_LINE XOR A ;Clear the flag ; ; The following code is somewhat shared by the INSERT and DELETE ; line code. This code accesses the video memory directly to get ; the fastest possible movement. Interrupts must be off while ; the screen is swapped in, so a compromise was made so that the ; interrupts were not off for too long. The movement of the ; screen is done one line at a time. Interrupts are turned back ; on in between lines, so that the UART can generate RECEIVED ; CHARACTER AVAILABLE interrupts. I have had reasonable behavior ; at 9600 BAUD with this idea... ; LINE_OPS LD (DEL_FLAG),A ;Store the flag value R109 EQU $-2 GET_CURSOR ;Get the current row and column LD A,23 ;Get the maximum possible SUB H ;Get the difference in rows JR Z,CLEAR_LINE ;Go clear the line if on the last PUSH IY PUSH HL ;Save HL from the call to *DO PUSH BC PUSH DE PUSH AF LD A,15 ;Turn the cursor off CALL CHAIN_IN ;Call *DO to do the work R129 EQU $-2 POP AF POP DE POP BC POP HL ;Restore the ROW/COL POP IY LD A,(DEL_FLAG) ;Get the flag R110 EQU $-2 OR A JR Z,INS_MODE ; ; Delete the line that the cursor is on ; PUSH HL ;Save the row and column LD L,0 ;Go to the first col of the line CALL GET_RC_ADDR ;Get the effective address in mem R111 EQU $-2 POP AF ;Get the row in A, ignoring F PUSH HL ;Move the address to DE POP DE LD BC,80 ;One row is this many characters ADD HL,BC ;Add one row to HL for the source DEL_LOOP EQU $ SWAP_IN ;Swap the screen into view PUSH BC LDIR ;Move one rows worth POP BC SWAP_OUT ;Swap the screen back out INC A ;Add one to the row CP 23 ;Are we at the end? JR NZ,DEL_LOOP ;Loop if not LD H,A ;Load H with the last row JR LINE_OPS_1 ;Join the other code ; INS_MODE EQU $ LD A,23 ;Max lines on a screen SUB H ;Minus current line = remaining LD HL,23*80+0F7FFH ;Source address for LDDR LD DE,24*80+0F7FFH ;Destination address for LDDR LD BC,80 ;Number of bytes to move INS_LOOP EQU $ SWAP_IN ;Swap the screen in PUSH BC LDDR ;Move one line POP BC SWAP_OUT ;Swap the screen out DEC A ;Decrement the line count JR NZ,INS_LOOP ;Loop until done CLEAR_LINE EQU $ GET_CURSOR ;Get the current row LINE_OPS_1 EQU $ PUSH HL ;Save the row LD DE,SCR_BUFF ;Get the buffer address R112 EQU $-2 PUSH DE ;Save the buffer address PUSH DE ;Copy the address into hl POP HL INC DE ;Plus one for the copy LD BC,79 ;Copy 79 times LD (HL),' ' ;Store one blank LDIR ;Copy in the rest POP DE ;Restore the buffer address POP HL ;Restore the row PUT_LINE ;Put the line back LD A,14 ;Turn the cursor back on JP CHAIN_IN R113 EQU $-2 ; ; Chain into any filters ; CHAIN EQU $ LD A,(NEWCHAR) ;Get the character sent to us R114 EQU $-2 CHAIN_IN EQU $ LD C,A ;Move the character to C for @PUT LD B,2 ;Signal @PUT for others in chain OR A ;Reset the carry CP A ;Set Z flag CHAIN_2 EQU $ PUSH IX ;Save the old DCB address LD IX,(MODDCB) ;Get the next in chain R115 EQU $-2 LD A,@CHNIO RST 28H POP IX ;Restore the old ; ; Return without knowldege of the call to *DO ; RETOUT EQU $ LD A,(NEWCHAR) ;Get the character sent R125 EQU $-2 CP A ;Set the Z flag RET ; ; Clear the screen ; CLEAR_SCREEN EQU $ LD HL,0 ;Put the cursor at the top PUT_CURSOR JP CLEAR_TO_EOS R126 EQU $-2 ; ; Put the character in A on the screen at the current screen ; position. If insert mode is active, then perform the shift ; of the line before chaining to *DO which will do the actual ; displaying for us. ; INSERT_A EQU $ PUSH AF ;Save the character GET_CURSOR ;Get the cursor position PUSH HL ;Save the cursor position LD A,(INSERT_FLAG) ;Get the insert mode flag R116 EQU $-2 OR A ;Is insert character mode on? JR Z,NO_MOVE ;Jump if no insert character mode LD DE,SCR_BUFF ;Get the buffer's address R117 EQU $-2 GET_LINE ;Get the line from the screen LD A,79 ;Get the maximum to move SUB L ;Compute the number to move LD C,A ;Make the byte, 16 bits in BC LD B,0 ;Zero the high byte for 16 bits OR A ;Check if count is already zero JR Z,NO_MOVE ;Skip if it is LD L,79 ;Get the end of the buffer LD H,0 ; by adding 79 to the address ADD HL,DE ;HL is now the end of the buffer PUSH DE ;Save the buffer address LD E,L ;Copy HL to DE LD D,H DEC HL ;Decrement the source address LDDR ;Skoot the line over POP DE ;Restore the buffer address POP HL ;Restore the row to restore PUT_LINE ;Put it on the screen PUSH HL ;Push something for the POP NO_MOVE EQU $ POP HL ;Restore the current row/col POP AF ;Restore the character to insert JP CHAIN ;Use *DO to display it R118 EQU $-2 ; ; The default visual begin command is to change the cursor ; to a block character ; VSTART EQU $ LD B,8 ;Change cursor character LD A,(VSCUR) ;Get the video start cursor R119 EQU $-2 LD C,A ;Special graphics block LD A,@VDCTL RST 28H RET ; ; This is the default call out for visual end. ; VEND EQU $ LD B,8 ;Set the normal cursor character LD A,(VECUR) ;Get the video end cursor R120 EQU $-2 LD C,A LD A,@VDCTL RST 28H RET ;Return ; ; ; Calculate address of Row and Column in HL ; GET_RC_ADDR PUSH BC PUSH AF PUSH DE PUSH HL ;Copy the Row and Column to DE POP DE LD HL,0F800H ;Get the start of the screen LD BC,80 ;One row is this long ADD_LOOP DEC D ;Decrement the row count JP M,NO_MORE ;If less than zero, no more rows R121 EQU $-2 ADD HL,BC ;Add one more Row's worth JR ADD_LOOP ;Go to the top of the loop NO_MORE LD D,0 ;Make it a 16 bit value ADD HL,DE ;Add it into the total POP DE POP AF POP BC RET ;Return to caller ; ; Calculate Row and Column based on address in HL ; GET_ADDR_RC PUSH BC ;Save the registers PUSH AF PUSH DE LD BC,0F800H ;Get the start of the screen OR A ;Reset the carry flag SBC HL,BC ;HL now is the offset into screen LD D,0 ;This is the counter LD BC,80 ;Get one rows worth SUB_LOOP OR A ;Reset the carry SBC HL,BC ;Subtract one rows worth JP C,NO_MORE_2 ;There are no more so leave R122 EQU $-2 INC D ;Add one to the row count JR SUB_LOOP ;Go to the top of the loop NO_MORE_2 ADD HL,BC ;Correct for the subtract LD H,D ;Get the row count, L has the ;Column already in it POP DE ;Restore the registers POP AF POP BC RET ;Return to the caller ; ; Data storage area ; LASTPUSH DW PUSHAREA ;Next place to push pos into R140 EQU $-2 PUSHAREA DS 20 ;Storage area ENDPUSH EQU $ ;End of storage OLDSTATE DW 0 ;Any preexisting state for ;special character sequences, ;actually, the address of the ;routine to execute the next time ;that a @PUT request is made. INSERT_FLAG DB 0 ;Insert character mode flag DEL_FLAG DB 0 ;Delete or Insert line direction CHAR_2 DB 0 ;Second character in a multiple ; ;character sequence. VIDEO_START DW VSTART ;Call out address for visual begin R123 EQU $-2 VIDEO_END DW VEND ;Call out address for visual end R124 EQU $-2 FLAG_ADDR DW 0 ;Address of flags area GOTO_ROW DB 0 ;Saved row for cursor motion SCR_BUFF DS 81 ;Space for put_line and get_line NEWCHAR DB 0 ;Character sent to @PUT request MODEND EQU $ ;End of the routine FLTR_LEN EQU MODEND-FILTER ;This is the length INTRO EQU $ DB 'H19 Emulator-filter for TRSDOS 6.2. ' DB 'Written by: Gregg Wonderly',29,26 DB 'Load address: ',3 INTRO2 DB ' Ending address: ',3 STRING DS 80 FIRST DW 0 ; ; Entry point of load routine. ; LOAD EQU $ LD (MODDCB),DE ;Save the DCB address LD A,@FLAGS ;Get the Flags area address RST 28H LD (FLAG_ADDR),IY ;Save it away LD HL,INTRO ;Print the intro message LD A,@DSPLY RST 28H LD HL,0 ;Get HIGH MEMORY pointer from DOS LD B,0 ;B=0 selects HIGH$ LD A,@HIGH$ RST 28H LD (OLDLOW),HL ;Save it for later restoral LD (FILTER+2),HL PUSH HL ; ; Since this filter accesses the video directly, we can not reside ; up where it does. Here we determine if there is suffient space ; used to put us below the screen, or that we must waist memory, ; and relocate to just below 0F400H. ; LD HL,0F3FEH ;Get the highest usable address POP BC ;Get the old HIGH memory OR A ;Reset the carry bit PUSH HL ;Save HL SBC HL,BC ;See if hl is less than bc POP HL ;Get HL back JR C,USE_HL ;If C, then use HL's address PUSH BC ;Move BC into HL POP HL USE_HL EQU $ INC HL ;Must increment for true value LD BC,FLTR_LEN ;Get the length of the filter OR A ;Reset the carry SBC HL,BC ;Compute the new high PUSH HL ;Save where to load at DEC HL ;One below that is new high LD (OLDHIGH),HL ;Save it for restore when removed LD B,0 ;Select HIGH$ LD A,@HIGH$ RST 28H RELOCATE EQU $ ; ; THIS ROUTINE WILL MOVE THE FILTER, UP INTO HIGH MEMORY AND ; RESET THE POINTER TO HIGH$ ; POP DE ;Get the load address LD (FIRST),DE ;Save it for later LD HL,STRING ;Get the scratch area PUSH HL ;Save the address for @DSPLY LD A,@HEX16 ;Convert DE to 4 HEX digits (HL) RST 28H LD (HL),3 ;Terminate with ETX POP HL ;Get the start LD A,@DSPLY ;Display it RST 28H LD HL,(FIRST) ;Get the starting reloc address LD BC,FILTER ;Calculate offset from source OR A ;Reset the carry PUSH HL ;Save it SBC HL,BC ;Offset now in HL LD (OFFSET),HL ;Save it for later reference POP HL ;Get the load address into hl LD BC,FLTR_LEN ;Calculate the end ADD HL,BC ;HL now has the ending address PUSH HL ;Save it for transfer to DE LD HL,INTRO2 ;Get the message string LD A,@DSPLY ;Display it RST 28H POP DE ;Get the ending address LD HL,STRING ;Get the string buffer PUSH HL ;Save the address for later LD A,@HEX16 ;Convert DE to 4 HEX digits (HL) RST 28H LD (HL),13 ;Put a carriage return on the end POP HL ;Get the starting address back LD A,@DSPLY ;Display the VALUE RST 28H LD IX,OFFTBL ;Get start of offset table ; ; LOOP TO ADD OFFSET TO ALL ADDRESSES NECESSARY ; MOVNXT EQU $ LD BC,(OFFSET) ;Put the offset into BC LD L,(IX) ;Get LSB of address to change INC IX ;POINT TO MSB LD H,(IX) ;GET IT INC IX ;POINT TO LSB OF NEXT, OR END PUSH IX ;Save pointer to table PUSH HL ;Put the address into IX POP IX LD L,(IX) ;Get the LSB for relocation LD H,(IX+1) ;Get the MSB ADD HL,BC ;Relocate it LD (IX),L ;Put it back LD (IX+1),H POP BC ;Get the table address in BC PUSH BC ;Copy it back into IX POP IX ;Restore the table address LD HL,OFFEND ;Get the end of the offset table OR A ;Reset the carry SBC HL,BC ;Compute the difference JR NZ,MOVNXT ;Loop, if not done ; LD BC,FLTR_LEN ;MOVE MODULE INTO HIGH MEMORY. LD DE,(FIRST) LD HL,FILTER ;Get the load address LDIR ;Move it into place LD IX,(MODDCB) ;Get the dcb address back LD DE,(FIRST) LD (IX),47H ;Say we are a filter LD (IX+1),E ;Tell where the filter starts LD (IX+2),D LD HL,0 CP A RET ; OFFTBL EQU $ DW R001 DW R002 DW R003 DW R004 DW R005 DW R006 DW R007 DW R008 DW R009 DW R010 DW R011 DW R012 DW R013 DW R014 DW R015 DW R016 DW R017 DW R018 DW R019 DW R020 DW R021 DW R022 DW R023 DW R024 DW R025 DW R026 DW R027 DW R028 DW R029 DW R030 DW R031 DW R032 DW R033 DW R034 DW R035 DW R036 DW R037 DW R038 DW R039 DW R040 DW R041 DW R042 DW R043 DW R044 DW R045 DW R046 DW R047 DW R048 DW R049 DW R050 DW R051 DW R052 DW R053 DW R054 DW R055 DW R056 DW R057 DW R058 DW R059 DW R060 DW R061 DW R062 DW R063 DW R064 DW R065 DW R066 DW R067 DW R068 DW R069 DW R070 DW R071 DW R072 DW R073 DW R074 DW R075 DW R076 DW R077 DW R078 DW R079 DW R080 DW R081 DW R082 DW R083 DW R084 DW R085 DW R086 DW R087 DW R088 DW R089 DW R090 DW R091 DW R092 DW R093 DW R094 DW R095 DW R096 DW R097 DW R098 DW R099 DW R100 DW R101 DW R102 DW R103 DW R104 DW R105 DW R106 DW R107 DW R108 DW R109 DW R110 DW R111 DW R112 DW R113 DW R114 DW R115 DW R116 DW R117 DW R118 DW R119 DW R120 DW R121 DW R122 DW R123 DW R124 DW R125 DW R126 DW R127 DW R128 DW R129 DW R130 DW R131 DW R132 DW R133 DW R134 DW R135 DW R136 DW R137 DW R138 DW R139 DW R140 DW R141 DW R142 DW R143 DW R144 DW R145 DW R146 DW R147 DW R148 DW R149 DW R150 DW R151 DW R152 DW R153 DW R154 DW R155 DW R156 DW R157 DW R158 DW R159 DW R160 DW R161 DW R162 DW R163 DW R164 DW R165 DW R166 DW R167 DW R168 DW R169 DW R170 DW R171 DW R172 DW R173 DW R174 DW R175 DW R176 DW R177 DW R178 DW R179 DW R180 DW R181 DW R182 DW R183 DW R184 DW R185 DW R186 DW R187 DW R188 DW R189 DW R190 DW R191 OFFEND EQU $