MTX VIDEO MEMORY MAPPING. 1.1 Terms used: VRAM - Video ram. VDP - Video Display Processor. CPU - Central Processing Unit. MBB - Most Significant Bit LSB - Least Significant Bit In using MSB and LSB, I have made the assumption that MSB is the left-most bit of any byte, and LSB is the right-most bit. In my notation MSB = Bit 7. LSB - Bit 0. MTX Vram memory architecture. 1.2 VRAM on the MTX is managed by the VDP chip, which contains its own autoincrementing address pointer.
After the address set up has been made, data bytes can either be input or output along port 1, and because the VRAM is managed by an auto-incrementing register, sequential transfers of data bytes can be performed without having to re-set the address pointer on the VDP chip. If you wish to perform alternate input and output of data bytes to VRAM you must reset the addressing mode as appropriate. Address set ups and data transfers require a certain minimum a of time between sequential processes.
1000 REM POKE DATA BYTE HELD IN VDATA UNTO SCREEN POINTED TO BY VADDRESS 1010 LET TEMP2=INT(VADDRESS/256): LET TEMP1=VADDRESS - (TEMP2*256) 1020 OUT (2),TEMP1 1030 LET TEMP2=TEMP2 OR 64 : LET TEMP2=TEMP2 AND 127 1040 OUT (2),TEMP2 1050 OUT (1),VDATA 1060 RETURN 2000 REM PEEK DATA BYTE ON SCREEN POINTED TO BY VADDRESS, AND RETURN RESULT IN VDATA 2010 LET TEMP2 = INT(VADDRESS/256):LET TEMP1=VADDRESS-(TEMP2*256) 1020 OUT (2),TEMP1 1030 LET TEMP2=TEMP2 AND 63 1040 OUT (2),TEMP2 1050 LET VDATA=INP(1) 1060 RETURN
AND OUT POP RET 127 (2),A AF ;SET 'WRITE TO VRAM MODE' ;OUTPUT HIGH BYTE ADDRESS ;GET OLD ACC ; ;VSETRD - SET UP VRAM ADDRESS POINTER FOR DATA INPUT DEPENDENT ON ADDRESS HELD IN DE ON ENTRY ; VSETRD: PUSH AF ;SAVE ACC LD A, E OUT (2),A ;OUTPUT LOW BYTE ADDRESS LD A, D AND 63 ;SET 'READ FROM VRAM MODE' OUT (2),A ;OUTPUT HIGH BYTE ADDRESS POP AF ;GET OLD ACC RET ; ;VD0UTP-OUTPUT DATA BYTE HELD IN C TO ADDRESS POINTED TO BY AUTOINCREMENTING REGISTER ON-BOARD THE VDP ; VDOUTP: PUSH AF ;SAVE ACC LD A, C OUT (
ASSEM 10 where 10 is the BASIC line number at which the code will appear. On pressing the return key the screen will clear and the prompt : Assemble > Will appear at the bottom of the screen. You are now in assemble mode ! The MTX will no longer respond to BASIC commands such as LIST or RUN but instead expects one of the assembler commands: L. - List T - Top of program E - Edit Insert (by default) Creating a Program. To start writing your program press the RET key.
4007 LD HL,DATA 400A LD DE,COPY 400D LD BC,5 4010 LDIR 4012 RET 4013 DATA: DB 12,£34,"LOW'' 4010 COPY:DS 5 4011 RET Symbols.. DATA 4013 COPY 4018 Suppose we wanted to modify the program to transfer only the first two bytes. We would change the line at 400D from LD BC,5 to LD BC,2. To do this type E £400D and RET. This will put us in edit mode and display the line to be edited.
and then carriage return to get into the code line and summon the assembler followed by CLS and RET to leave it again. This will re-assemble the code for its current location. To get around this problem it is wise to put your code lines as near the start of the BASIC program as possible. eg: 10 GOTO 100 100 CODE 4007 LD HL,DATA 400A LD DE,DATA1 etc. Symbols. DATA 4013 COPY 4018 20 RETURN 100 REM START OF BASIC PROGRAM Number Representation.
Type ASSEM 10 - Carriage return - CLS -Carriage return The program can now be "RUN". The number in brackets in the USR function is the address of the machine code, and needs to be re-calculated if the code is moved. USR returns with the value of the BC register pair, which it.) this case, is assigned to X. BC will be zero after execution of the routine. Assembler Commands. The assembler has only 4 different commands, L,E,T and an insert command which works by default.
NB:- Using a label will generate an out of range error, but ignoring this error leaves the low byte of the label in memory. 2) DW - Define word. DW allocates a value to word ie two bytes. The number is stored low byte first, making it compatible with Z80 word instructions. Eg:-
The 512 has 64k of memory starting at 4000 hex and finishing at FFFF hex, with an additional page of 16k switched out between 3000 hex and C000 hex. This additional memory is switched in and out automatically and provided the code line does not pass over its boundary the user is unaware of the paging system which is maintained in hardware by a ULA. It is possible to trick an MTX 512 into acting like a 500.
Graphics 2 mode is an enhancement of Graphics 1 mode providing more complex colour and pattern displays and 32 sprites. The video display consists of 35 planes, numbered from 34 down to 0. Working from the 'back' of the screen to the 'front' these are listed below.
It can be seen that bits 7 and 6 MUST be set to 1 and 0 respectively. These are the active control bits in this byte and tell the VDP that the previously transmitted data byte is to be directed into one of the write-only registers. Bits 5,4,3 MUST be set to zeroes. The number of the destination register is indicated by bits 2,1,0. Both data transfers and control bytes directed to the VDP write-only registers must be output via port 2. Example 1.
BASIC sets up the VRAM tables as shown in Appendix A. The data bytes which are used, and the routine to perform this set-up are listed in the example below. The routine is called VRGINI (VDP Registers Initialisation Routine). It needs no register setup on input, and affects none on output. It uses a table called VRGTAB which has 18 elements, and the routine VOUTRG, which must be present.
Register Number MSB 7 0 0 1 4/16K 2 0 5 4 3 2 1 0 0 0 0 0 M3 EV IE M1 M2 0 SIZE MAG 0 0 BLANK 0 3 NAME TABLE BASE ADDRESS COLOUR TABLE BASE ADDRESS 4 0 5 0 6 0 7 LSB 0 6 0 0 0 0 PG BASE ADDRESS SPRITE ATTRIBUTE TABLE BASE ADDRESS 0 0 TEXT COLOUR ONE 0 0 SPG BASE ADDRESS TEXT COLOUR ZERO/BACKDROP Register 0 This contains two VDP option control bits. All other bits are reserved for future use and must be zeroes.
M1 M2 M3 0 0 0 1 0 0 1 0 0 1 0 0 Bit 2 Bit 1 Reserved and must be zero. SIZE selects Sprite Size 1 selects size 1 sprites (16 times 16 bits). 0 selects size 0 sprites (8 times 8 bits). MAG is the magnification option for sprites. 1 selects MAG1 sprites (SIZE times 2). 0 selects MAG0 sprites (SIZE times 1).
If you wish to locate the colour table at address 0K then bit 7 of register 3 must be set to 0. If you wish to locate the colour table at address 8k then bit 7 of register 3 must be set to 1. In both cases bits 6 to 0 must be set to 1's. This set-up is also shown in the table below. Locate colour table at VRAM address Load register 3 with data byte OK - £0000 – 0 Decimal 127 Dec - £7F Hex BK – £2000 – 8192 Dec 255 Dec - £FF Hex The colour table is 6144 bytes long in graphic mode.
The pat gen table is 6144 bytes long in graphic 2 mode. Graphic 2 mode pattern generator creation is described in much greater depth in section 2.4. Register 5 SPRITE ATTRIBUTE TABLE BASE ADDRESS is the start address for a 128 byte block which contains position, colour and shape information, for each of the 32 sprites which it is possible to enable. The sprites are active in all modes except text mode. This register value occupies 7 bits and therefore has a range of 0 to 127. Bit 7 must be set to 0.
Register 7 This register is split into two nibbles ie two 4 bit values. The upper 4 bits 7,6,5 and 4, contain the colour code of the ink colour for characters in text mode. The lower 4 bits 3,2,1 and 0, contain the colour code of the paper colour for characters in text mode and the backdrop (border) colour in all modes. Graphics Mode 2 2.4 Graphics 2 mode is the normal BASIC graphics mode. The features which it provides are summarised in the table below.
Address to decimal 0000 - start of pattern generator table 6143 - end of pattern generator table 6144 - free space (see below) 8191 - end free space.
Allocating 1K bytes for the sprite generator table as BASIC does is a compromise. The VRAM set up as BASIC creates, it means that to switch from text mode to graphics 2 mode and vice versa it is only necessary to change two VDP write-only registers, a process which takes a little over 20 micro-seconds (20 1/100 thousandths of a second). This is how you can switch from one mode to the other without affecting the integrity of either screen in any way.
; ; INISCR ; ; ; ; INISCR: ; INISC1: INITIALISE PATTERN NAME TABLE (DISPLAY SCREEN) NO PARAMETERS REQUIRED ON ENTRY NO REGISTERS AFFECTED ON EXIT PUSH PUSH PUSH PUSH LD AF BC DE HL HL,768 ;Save Acc and flags ;Save BC register pair ;Save DE register pair ;Save HL register pair ;Set up loop counter to equal ;768 – This is the size of the ;display screen ;Set byte to be output to each ;sequential screen position to zero ;Load DE with start address of screen ;Set VDP write to VRAM pointer ;to point to start
The VDP is in text mode, when mode bits M1 = 1, M2 = 0 and M3 = 0 (see section 2.2 register 1 bits 3 and 4). When the VDP is first initialised into text mode the VRAM is organised as shown in the table below. VRAM sub-block Pattern generator table Pattern name table Length in bytes 2048 960 Text mode VRAM arrangement in BASIC has already been discussed in section 2.4, because in BASIC it has been designed to be an integral part of the tabling for graphic mode 2.
The ascii values of the characters we wish to output will provide the correct pattern number to be loaded into the text display screen area to extract the correct pattern shape.
The graphics pattern display colours can be any two of 16 (including transparent) sectioned into groups of 8 characters. The backdrop or border colour can be any one of 16 (including transparent). The character patterns can be dynamically changed to give any number of character patterns limited by the amount of storage space in Z80 RAM for the extra pattern libraries. Sprites are available up to a maximum of 32. The VDP is in Graphics 1 mode, when mode bits M1 = 0, M2 = 0 and M3 = 0 (see section 2.
The mapping arrangement for pattern generator character shapes to the appropriate colour bytes is shown in the table below.
; ;GRAFIK-CLEAR SCREEN USING PATTERN NUMBER 0 ; DRAW BRODER USING PATTERN NUMBER 8 ; FOR USE WITH GRAPHICS 1 MODE SCREEN ; ; ASSUMPTIONS DESCRIBED ABOVE ; ALSO ASSUME THAT VDP WRITE-ONLY REIGSTERS ; HAVE ALREADY BEEN SET-UP ; ; NO PARAMETERS REQUIRED ON ENTRY ; NO REGISTERS AFFECTED ON EXIT ; GRAFIK: PUSH AF ;Save old Acc and flags PUSH BC ;Save BC register pair PUSH DE ;Save DE register pair PUSH HL ;Save HL Register pair CALL CLRSCR ;Clear the screen CALL BORDER ;Draw the border POP HL ;Get old HL registe
‘address held in DE HL number of ;times: ;Return to calling routine RET ; BOTTOM LD CALL DE,£EA1 VSETOT LD C,8 LD CALL HL,32 OUTBLK RET ; SIDES: SIDES1: SIDES2: ; OUTBLK: LD DE,£C20 LD PUSH CALL B,22 BC VSETOT LD CALL C,8 VDOUTP LD ADD EX CALL HL,31 HL,DE DE,HL VSETOT CALL VDOUTP INC DE POP DJNZ BC SIDES1 RET CALL VDOUTP DEC LD HL A,H ;Set the VDP write to VRAM ;pointer to the start of the bottom ;line of the graphics display screen ;Load the border character into the output reg
OUTBL1: OR JR RET L NZ,OUTBLK ;OUTBLK else drop through to ;to OUTBL1 ;Return to calling routine Multicolour Mode 2.7 Multicolour mode is not normally allowed from BASIC, but like graphics 1 mode it can be enabled with ease in assembler. Although I cannot see much use for it, it is available on the machine and so I will attempt to describe it.
Byte Number Bits 7 6 5 4 Bits 3 2 1 0 8 PIXELS 1 2 COLOUR A COLOUR C COLOUR B COLOUR D 8 PIXELS **** *AB* *CD* **** ^(Illus 4 – ABCD diagrammed from above) The location of the two bytes within the eight byte segment of the pattern generator table pointed to by the character label value held in any one of the display screen character positions is dependent on the screen position in which the character label is held. This is also elaborated to some extent by the diagram below.
In most cases if you are doing anything that BASIC would not normally do you will have to use assembler. BASIC can easily be disabled by using a DI instruction at the start of your code, and an RETI instruction at the end. If you have modified the contents of the VDP registers drastically it would be far better to perform a JP £0000 as your last instruction as a warm boot back to BASIC.
Programming the CTC The Zilog CTC counter Timer Circuit handles all interrupts on the MTX including the Video Display Processor (VDP) interrupt. The following is intended only as brief outline concerning CTC operation. For more details refer to Zilog’s Z8430 CTC Counter/Timer Circuit product specifications. The CTC is capable of generating mode 2 interrupts from any of its 4 independently programmable channels. It is capable of acting as either a timer or counter, working on an external clock.
The interrupt vector word is identified by a zero in bit 0. The 5 most significant bits form the 5 most significant bits of the interrupt vector provided by the chip on interrupts (mode 2). Bits 1 and 2 are set according to the channel generating the interrupt and bit 0 is always zero. B2 B1 0 0 1 1 0 1 0 1 Channel 0 1 2 3 The interrupt vector table must lie on an 8 byte boundary. This table normally sits at FFF0 hex. A working example set up of an IM 2 vector table is detailed in section 3.
DJNZ KILLloop ;Decrement loop counter and if loop ;counter < > 0 then goto KILLloop else ;drop through to next section of code. It can be seen in the above code that the reset byte 3 is being written to the ctc chip twice. This is because the CTC may expect the next byte input to it to be a time constant therefore a re-write will eliminate these.
SETupINT: LD A,0C5H OUT (CTC),A LD A,1 OUT (CTC),A IN A,(VDPRGO) EI RETI ;Send CTC bytes to CTC chip to ;’wake’ it up and prepare CTC ;chip prior to beginning execution of ;VDP interrupts ;Clear VDP interrupt flag held in VDP ;read only register on port 2 ;Enable new interrupt system ;Return to calling routine and exit from ;interrupt set up routine.
RETI ; VDPout: ; DI ;Disable all interrupts (start of your routine) (you MUST save all registers which will be affected by the servicing routine at this point).
2. Every 1/50th of a second the variable ONE50 is set to one and can be used for delay loop timing. 3. By using a variable called CLRCLK you have the following: A) CLRCLK = 0 – No action taken B) CLRCLK = 1 – Clear CLOCK. Time is ’00 00 00’ C) CLRCLK = 2 – CLOCK is set to time contained within 6 byte table TIMSET. ; ;SEVCLK – INTERRUPT SERVICING ROUTINE SECTION ; IM 2 – POINTER TABLE IJTABLE SET UP USING CODE ; LISTED IN SECTION 3.
; SEVCL5: ; SEVC5A: ; SEVC5D: SEVCL6: ; SEVCL7: LD JP DEC DEC DJNZ JP (DE),A C,SEVCL7 DE HL SEVCL3 SEVCL7 CP JP 2 NZ,SEVC5D LD HL,TIMSET LD LD LDIR LD LD JP DE,CLOCK BC,7 A,0 (CLRCLK),A SEVCL7 ;Reset option select control ;variable to zero LD LD LD LD DJNZ LD LD HL,CLOCK A,30H B,7 (HL),A SEVCL6 A,0 (CLRCLK),A ;Clear clock option selected at ;this point here ;Fill table CLOCK with ASCII 0,s ;and then exit routine ;Goto routine exit at this point ;Has set a time option been ;selected at this
A point to note is that the random value contained within RND will only be autoupdated every 1/50th of a second. If this is too slow for some applications then it will do no harm to call the routine random independently of the interrupt routine using a standard Z80 ‘CALL RANDOM’ instruction. The assumption made is that prior to setting under the VDP interrupt routine a routine called SETRND is called. This is listed below. It sets up a random seed within an 8 byte table RNDMEM for use by the routine RANDOM.
RL RL RL RL RL DJNZ LD (IY+0) (IY+1) (IY+2) (IY+3) (IY+4) RAN0 A,(IY+0) LD (RND),A PDP IY PDP BC PDP AF (End of routine) ;Decrement loop counter and if ;loop counter < > 0 goto RAN0 ;else drop through to next ;statement and update value of RND ;Retrieve saved IY register pair ;Retrieve saved BC register pair ;Retrieve saved Acc and flags As mentioned in section 3.1, VDP interrupt routines can be used to create glitch free screen updates.
TEXMO2: TEXMO3: TEXMO4: LD CALL DEC LD OR JR DE,960 VDOUTP DE A,D E NZ,TEXMO2 LD A,255 LD (FILTEX),A (End of routine) ;into the write to VRAM output ;register ;Loop counter = 960 ;Output fill screen byte to screen ;Decrement loop counter and if ;loop counter <> 0 then goto TEXMO2 ;else drop through to TEXMO3 ;Reset fill screen byte to 255 Listed below is a section of code which demonstrates the use of the above routine.
; SPRIMP-SPRITE IMPACT DETECTION ROUTINE ; USES ROUTINE FROM SECTION 4 (IMPACT) ; AND VARIABLE IONOFF ; ; NO REGISTER SET UP REQUIRED ON ENTRY ; AF, BC, DE, HL REGISTERS AFFECTED ON EXIT ; IONOFF; DB 0 ;See description above ; SPRIMP: LD A,(IONOFF) ;If IONOFF = 0 then no action CP 0 ;taken – goto SPR99 and exit JP Z,SPRI99 ;else drop through to SPRI1 ; SPRI1; (Impact detection test routine from section 4) ; SPRI99: (End of routine) Appending programs to other programs 3.
8. 9. 10. 11. Now add the value obtained by subtracting the original value of VAZERO (which you noted down), from the original value of NBTOP, BASTOP and BASTBO. Set VAZERO to its original value Exit panel and return to BASIC Save the appended code At this point you will have an appended section of code saved on tape. Screen Output using RST 10 3.5 The ROM calls for screen output are all in the form of restart 10 calls. Following each of these calls is data which tells the ROM routine what to do.
The byte following the RST 10 is made up in the following way: RST 10 Control byte – Bit Format 7 1 6 0 5 C 4 3 2 1 0 Where bit 5 indicates that the routine should continue to interpret data after this instruction. n is the number of bytes in the string.
The routine reads the keyboard and echoes the typed characters on the screen. Control Codes and RST 10 In the ASCII character set there are 32 invisible characters before the first printable character (space). These invisible characters are called control characters. For example pressing both the control key and the ‘G’ key at the same time generates the bell code, character 7. These codes are extremely powerful in the MTX when used with RST 10.
21 22 23 25 27,65 27,89 27,90 27,67 insert key delete key back tab tab key attr p,state crvs n,t,x,y,w,h,s vs n gr$ x,y,b (result in work space) Printer Output All screen output can be redirected to either the RS232 or the centronics interface and hence the printer. To do this from basic type: POKE 64143,DEV – Where DEV is 0 1 2 for screen for Centronics for RS232 Option 2 sets the list device.
Essentially a sprite on the MTX can be defined as below: 1. It is a special animation pattern which can be moved one pixel at a time, either vertically or horizontally dependent on or independently of the pattern background. 2. It can be coloured in any one of the 15 colours plus transparent available of the MTX independently of the pattern background. 3.
The diagram below shows exactly how the four control bytes within each control block of the sprite attribute table are arranged. ^ (Illus 5 – Sprite attribute table control block) The first two bytes control the Y an X positions of the sprite onscreen. The first byte indicates the vertical distance from the top of the screen in pixels, and is defined such that a value of –1 (ie £FF Hex), places the sprite at the top of the screen touching the backdrop area.
Setting up the Sprite Attribute Table The start address in VRAM of the sprite attribute table is determined by the contents of VDP write only register 5, and is a fixed address. Given this fact and that there is a proportional relationship between any sprite number and its position in the sprite attribute table, it is easy to handle and manipulate sprites.
CALL RET DRWSPR ;Display two sprites on-screen ;Return to calling routine ; ;CLRSPR-CLEAR SPRITE ATTRIBUTE TABLE ; ; NO REGISTER SET UP REQUIRED ON ETRY ; ; VRAM START ADDRESS OF SPRITE ATTRIBUTE TABLE ; ASSUMED TO BE HELD IN TWO BYTE LOCATION SATSAD ; (SPRITE ATTRIBUTE TABLE START ADDRESS) ; SATSAD: ; CLRSPR: CLRSP1: DW 0 ;SATSAD is a two byte location ;which MUST hold the start ;address of the sprite attribute table LD CALL LD LD DE,(SATSAD) VSETOT B,32 C,192 CALL VDOUTP LD CALL CALL CALL C,
EX CALL DE,HL VSETOT LD CALL RET C,208 VDOUTP ;Set the write to VRAM pointer ;to give the correct VRAM ;address of the control block ;for the sprite which is to ;hold the locking off byte ;Output the locking off byte ;to VRAM ;Return to the calling routine ; ;DRWSPR-DISPLAY TWO SPRITES ON-SCREEN ; ; A YELLOW DIAMOND IN THE TOP LEFT HAND CORNER OF ; THE SCREEN ; A BLUE CIRCLE IN THE TOP RIGHT HAND CORNER OF THE ; SCREEN ; ; USES TABLE YDTL (YELLOW DIAMOND TOP LEFT) ; BCTR (BLUE CIRCLE TOP RIGHT) ; YDTL:
Sprite Generator Table 4.3 The sprite generator table holds a library of potential sprite patterns. It is a maximum of 2048 bytes long and starts on a 2K boundary (see section 2.2 Register 6). It is split into 256 blocks of 8 bytes each. When 8 times 8 bit sprites are being used there are 256 different possible patterns available for use at any one time.
An alternate solution which works quite well is to use a descending loop counter and then display a new pattern in the animation sequence each time the counter reaches zero. The pattern numbers to be displayed are held within a table marked by a delimiter such as £FF (Hex), 255 (Decimal).
; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ALCREV: ALCFS0: ASTFS0: SOTREV: SOTP: SPOLOC: ; ANIMAT: RESET VALUE FOR ALCFS0 HELD IN TWO BYTE LOCATION ALCREV – ANIMATION LOOP COUNTER REFERENCE VALUE ALSO USES TABLE ASTFS0 ANIMATION SEQUENCE TABLE FOR SPRITE 0 THE ROUTINE USES THE TWO BYTE POINTER SOTP TO KEEP TRACK OF THE POSITION OF THE CURRENTLY ACCESSED PATTERN NUMBER THE RESET REFERENCE VALUE FOR THIS POINTER IS HELD IN THE TWO BYTE LOCATION SOTREV THE TWO BYTE VARIABLE SPOLOC IS THE VRAM ADDRESS OF THE PATTER
CALL LD CALL RET VSETOT C,A VDOUTP ;address which contains sprite ;0 pattern number ;Write pattern number to VRAM ;updating previous pattern ;Return to calling routine This routine may animate a sprite too quickly or perhaps too slowly, in which case the speed of animation can be altered by changing the values contained in ALCREV and ALCFS0. A larger value will give a slower speed and a smaller value will give a faster speed. ALCREV and ALCFS0 must always be greater than one prior to calling the routine.
With an OFFSET value of 4 the routines below are designed to detect impact between 8 and 9 bit sprites within a central area of 4 pixels ; ; IMPACT-TEST FOR IMPACT BETWEEN SPRITE 0 ; AND ANY OTHER ON SCREEN SPRITES ; ; THE VRAM START ADDRESS OF THE SPRITE ; ATTRIBUTE TABLE IS HELD IN THE TWO BYTE LOCATION ; SATSAD (SPRITE ATTRIBUTE TABLE START ADDRESS) ; -; ; NO REGISTER SET UP REQUIRED ON ENTRY ; NO REGISTERS AFFECTED ON EXIT ; ; IF IMPACT TRUE THEN VARIABLE TRUFAL = 1 ; ELSE TRUFAL = 0 ; ; IF TRUFAL = 1
; IMPAC0: ; IMPAC1: ; IMPAC2: ; IMPAC3: LD CP JR LD CP RET A,E 192 NZ,IMPAC0 A,D 0 Z ;Check to see that sprite o ;is actually on screen ;and if condition true goto ;IMPAC0 ;else return to calling ;routine with variable ;TRUFAL = false CALL CALL LD VDINPT VDINPT B,31 ;Move read from VRAM pointer ;onto next sprite ;Set loop counter = 31 PUSH CALL BC VDINPT LD CP A,C 208 JR NZ,IMPAC2 POP BC JP IMPAC4 ;Save loop counter ;Read sprite Y coord from ;VRAM sprite attribute table ;and test to see
; IMPAC4: LD (IX+4),L CALL LD CALL LD LD SUB LD SLA SLA LD LD LD ADD VDINPT (IX+5),C VDINPT (IX+6),C A,32 B (IX+0),A A A E,A D,0 HL,(SATSAD) HL,DE LD (IX+1),L LD (IX+2),H POP POP POP POP POP RET IX HL DE BC AF ;= offending sprite X coord ;Byte 5 of table IMPSPR ;= offending sprite Y coord ;Byte 6 of table IMPSPR ;= offending sprite pattern number ;Byte 7 of table IMPSPR ;= offending sprite pattern colour ;Byte 1 of table IMPSPR ;= offending sprite number ;Determine actual VRAM ;address of offendi
COMTS1: ; COMTS2: ; COMTS3: LD CP JR LD CP RET A,L 192 NZ,COMTS2 A,H 0 Z ;Check to see that sprite ;is on-screen ;If condition true then goto ;COMTS2 else return to ;routine with TRUFAL = false LD ADD CP JR LD ADD CP JR LD ADD CP JR LD ADD CP JR LD LD RET A,(OFFSET) A,L E C,COMTS3 A,(OFFSET) A,E L C,COMTS3 A,(OFFSET) A,H D C,COMTS3 A,(OFFSET) A,D H C,COMTS3 A,1 (TRUFAL),A ;Perform impact true/false ;test on each of the four ;sides of the two active ;sprites ;If at any point the test ;routine shows t
If we are using the other option which is to set up three identical pattern libraries within the pattern generator table and to have a dynamically changing screen (Pattern name table), the routine will operate on the pattern name table and will return characters as results. This section of code is listed in Option 2. The relationship between both of these options and the sprites are shown in the diagram below.
2. There is an additional table BITTAB used by DOTSUB.
ADD HL, DE EX DE, HL POP PUSH HL DE LD AND LD LD LD ADD LD POP CALL CALL AND CP RET LD RET A,H 248 L,A H,0 DE,BITTAB HL,DE A,(HL) DE VSETRD VDINPT C 0 Z A,1 ;Add to relative address contained ;in HL to give true VRAM address ;of pattern generator byte to be ;examined – Result in DE ;Retrieve old sprite X/Y coords ;Save pattern generator byte ;address ;Perform bit test on extracted ;pattern generator byte ;using table BITTAB ;Read byte from pattern generator ;table ;If bit = 0 then exit routine ;Ac
; ; ; CENLTL: CENLTR: CENLBL: CENLBR: ; SPRP1: SPRP2: SPRP3: SPRP4: SPRP5: SPRP6: SPRP7: SPRP8: SPRP9: SPRP10: SPRP11: SPRP12: ; DOT: ; DOT1: ; DOT2: ; DOT3: NO OTHER REGISTER SET UP REQUIRED ON ENTRY NO REGISTERS AFFECTED ON EXIT DW DW DW DW 0 0 0 0 ;Screen address of byte in SPRP5 ;Screen address of byte in SPRP6 ;Screen address of byte in SPRP8 ;Screen address of byte in SPRP9 DB DB DB DB DB DB DB DB DB DB DB DB 0 0 0 0 0 0 0 0 0 0 0 0 ;Top left hand corner ;Top middle ;Top right hand corner ;Lef
; DOT4: ; DOT5: ; DOT6: ; DOT7: ; DOT8: LD ADD LD PUSH CALL POP LD A,L A,7 L,A HL DOTSUB HL (SPRP7),A ;Increment Y coord in register L ;by 7 to move onto right middle ;side of sprite ;Save HL register pair ;(See description in section DOT1) ;Retrieve saved HL register pair ;Store character value under right ;middle side of sprite in SPRP7 LD SUB LD PUSH CALL POP LD A,H 7 H,A HL DOTSUB HL (SPRP6),A ;Decrement X coord in register H ;by 7 to move onto the top right hand ;quadrant centre of sprite ;Sa
DOT9: INC PUSH CALL POP LD LD ; DOT10: ; DOT11: ; DOT12: H ;Increment X coord held in register H ;by 1 to move onto bottom right hand ;quadrant centre of sprite HL ;Save HL register pair DOTSUB ;(See description in section DOT1) HL ;Retrieve saved HL register pair (SPRP9),A ;Store character value under bottom ;right hand quadrant centre of sprite ;in SPRP9 (CENLBR),A ;Store character value under bottom ;right hand quadrant centre of sprite ;in SPRP9 DEC LD ADD LD PUSH CALL POP LD H A,L A,7 L,A HL
; ; ; ; ; ; ; TOPSCR: ; DOTSUB: ROUTINE USES TO BYTE VARIABLE TOPSCR WHICH MUST BE SET TO CONTAIN THE START ADDRESS OF THE TOP LEFT HAND CORNER OF THE SCREEN PRIOR TO ENTRY TO THIS ROUTINE DW £1800 ;(See description above) LD LD AND DE,0 A,L 248 LD SLA RL SLA RL LD SRL SRL SRL LD LD ADD E,A E D E D A,H A A A HL,0` L,A HL,DE ;Set DE to zero ;and mask off lowest three bits of Y ;coord held in register L ;this gives (Y coord DIV 8) * 8 ;Multiply above value by 4 LD ADD ;Screen Y position in DE ;Divi
CALL LD POP RET VDINPT H,C BC ;Read sprite X coord from VRAM and ;place into register H ;Retrieve old BC Register pair ;Return to calling routine Joystick and keyboard control – Introduction 5.1 On the MTX series computers, the joystick (left hand side), is mapped onto the cursor keys and home key as shown below.
Joystick Manipulation (BASIC) 5.2 This section describes the basic code which will perform a keyboard strobe on cursor left/right/up/down), and home.
GETHCHR: LD LD LD A,0 HL(KEYCHR) (HL),A ;Set KEYCHR to zero – no key ;pressed LD OUT IN CP JR SET A,223 (5+OFFSET),A A,(5+OFFSET) 127 NZ,GETLEF 4,(HL) ;Select strobe byte to scan ;fire key and output to port 5 ;Examine read lines and if fire ;key is not depressed then goto ;GETLEF else ;Site fire key bit (condition true) LD OUT IN CP JR SET A,247 (5+OFFSET),A A,(5+OFFSET) 127 NZ,GETRGT 0,(HL) ;Select strobe byte to scan ;cursor left key and output to ;port 5 – examine read lines and ;if cursor left
The result is returned in A and will be a standard ASCII value or a specific non-ASCII MTX keyboard value. If the zero flag is set then no key has been pressed If the zero flag is not set then a key has been pressed To access KBD perform the command ‘CALL £0079’ An important point to note concerning KBD is that it makes use of the variable LASTKEY to remove debouncing problems. KBD is normally used as part of BASIC and will therefore perform BASIC error and escape sequences.
Data Output/Input To/From Tape – Introduction 6.1 In some applications it may be desirable or even necessary to save and load variables or blocks of memory independently of your programme in files or discrete segments. For most people who have an MTX at this time the cost of a disk system may be too much to afford, and therefore the only logical alternative is to perform data file manipulation on tape.
PRESS PLAY AND RECORD ON TAPE AND HIT ANY KEY WHEN READY and will begin saving or loading data the moment it is executed. This means that any programmer who wishes to make use of this routine must write his or her own prompts.
References and Acknowledgements 7.8 References 1. 2. 3. 4. Texas TMS9929L Technical Handbook Zilog Z80 Handbook Zilog CTC Handbook Memotech customer enquiries Acknowledgements Many thanks to: 1. 2. 3. 4. David Fazackerley David Netherwood L R Whalley Jeff Wakeford (Artwork) And in particular all of Memotechs customers for the large amount of interest shown in the MTX. A guide for prospective software writers – Introduction 8.
Business and educational programs should have some form of validation to ensure that input is reasonable, eg range checks data type checks, format checks and any other reasonable precaution against entering invalid data by mistake. Programs should on the whole be simple to use, where this is not possible they should include help pages. All programs should have instructions included in them.
BASIC Programs 8.6 When writing business software and the like it is important to take great care over input and the ease of inputting data, as a rule BASICS own input facilities are not good enough Blended BASIC and Assembler Code Programs 8.7 Where a combination of assembler and basic is used all the assembly code should be contained in one line at the beginning of the program.
Technical/Commercial Enquiries 8.9 All technical enquiries should be directed to Technical Services at Memotech. Completed programs and commercial enquiries should be sent to: Mr T Spencer Software Co-ordinator Memotech Unit 23 Station Lane Whitney Oxon Appendix A 7.
The sprite coincidence flag, which detects impact of any two sprites will be 1 if impact has occurred, and 0 if it has not. However, the use of it requires caution because it will detect impact of zero sprites (that is the ones you are not using if the x/y coordinates match). You need some method of ‘locking off’ extra sprites, and this can be done by writing the decimal value 208 into the y coord position of the sprite number after the last sprite you wish to use. In diagram 1.
Appendix D 7.4 Keyboard Layout The diagram below is a logical map showing how the keyboard is laid out from the machine hardware point of view. Outputting the correct sense value via port 5 into the keyboard matrix and reading the correct value from port 5 as a scan byte is discussed in more detail in section 5. A table summary of the values is given in Appendix E. Lower case values are detected by looking at the shift key. (Illus 14 – Diagram of keyboard layout) Appendix E 7.
Q R S T U V W X Y Z £F7 £FB £EF £F7 £F7 £BF £FB £BF £FB £7F £FE £FB £FD £FB £F7 £FB £FD £FD £F7 £FE 0 1 2 3 4 5 6 7 8 9 £FD £FE £FD £FE £FD £FE £FD £FE £FD £FE £DF £FE £FD £FD £FB £FB £F7 £F7 £EF £FE £FB £BF £EF £F7 £DF £7F (see section 5.2 – 5.3) £7F £7F £7F £7F Cursor up Cursor down Cursor right Cursor left Home key Appendix F 7.6 Alternative KBD Routine Please refer to section 5.
;4 auto repeat on ;3 speed of auto ;0 international codes on alpha lock ; SENSE1 EQU 5 SENSE 2 EQU 6 DR EQU 5 ; ; KBFLAG: DB 40H LASTKY: DB 0 ; KBD: PUSH BC PUSH DE PUSH HL CALL SSS ;TEST ROUTINE AND A DB 0,0,0,0,0,0,0,0,0,0 EXIT: POP HL POP DE POP BC RET DEB: CALL DEB1 JR Z,0KI LD (LASTKY),A CP 128 RET C OKI: LD A,0 LD A, (LASTKY) CP B LD A,B RET SSS: CALL KBDSTA CALL DEB RET KBDSTA: LD A,251 OUT (DR),A IN A, (DR) BIT 0,A JR JZ,NORMAL CNTRL: CALL NORMAL LD B,A CP 128 JR Z,CN3 CP 136 JR NZ,CN2 CN3: CALL DEB
CN2: CN4: CN1: NOCONT: SWITCH: BITZ: SWEND: NORMAL: AUTO: ; ; NOTNP: CP 129 JR Z,CN4 CP 137 JR NZ,CN1 CALL DEB1 RET Z LD C,40H CALL SWITCH LD A,B RET LD A,B BIT 6,A JR Z,NOCONT BIT 7,A JR NZ,NOCONT AND 1FH RET LD, A,O RET LED A, (KBFLAG) LD D,A AND C JR Z,BITZ CPL AND D JR SWEND OR D OR C LD (KBFLAG),A RET CALL SHIF JR Z,NSHIFT CALL SCAN LD D,A LD BC,BASE CALL KBDLUK LD B,A LD A,9KBFLAG0 LD C,A BIT 7,A LD A,B JR Z,NCONT CP 32 JR C,NSH1 CP 64 RET C JR NZ,AU96 BIT O,C RET Z ADD A,32 RET ;GET FLAGS ;SAV
AUG96: CP 95 JR NC,NSH1 BIT 0,C RET Z ADD A,32 RET NSH1: LD A,D ;PAD ON SHIFT JR NSH2 NSHIFT: CALL SCAN NSH2: LD BC,UPPER CALL KBDLUK NCONT: LD B,A CP 144 JR NZ,NORM1 LD A,(KBFLAG) LAD C,A LD A,9 BIT 6,C RET Z INC A RET NORM1: CP 145 JR NZ,NORM2 CALL DEB1 RET \ LD C,128 CALL SWITCH LD A,145 RET NORM2: CP 28 ;28-SCROLL/PAGE RET NZ ;NORMAL CHAR LD 3,A ;save 28 CALL DEB1 RET Z LD A,29 LD A,(KBFLAG) BIT 5,A JR Z,NORM3 INC E NORM3: LD C,32 CALL SWITCH NORM4: LD A,E RET ;MATRIX SCAN SCAN: LD B,B ;B=8=DRIVE COUNT
CP OFFH JR Z,SCAN3 CHECK1: PUSH AF CH10: LD A,2 CP B JR NZ,CH11 POP AF SET 6,A JR CH13 CH11: LD A,6 CP B JR Z,CH12 POP AF JR VALID CH12: POP AF CH13: SET 0,A CH14: CP OFFH JR Z,SCAN3 ;VALID KEY FOUND VALID: POP DE LD C,0 CH15: RRCA JR NC,ENDSCAN INC C JR CH15 SCAN3 IN A, (SENSE 2) AND 03 CP 3 JR Z,SCAN4 CHECK2: AND A ADD A,7 LD C,A POP AF JR ENDSCAN SCAN4: POP AF DJNZ SCAN2 LD C,0 ENDSCAN: LD A,C SLA A SLA A SLA A ADD A,B AND A RET SHIF: LD A,191 OUT (DR), A IN A,(DR) BIT 6,A RET Z BIT 0,A RET ;IF FF THEN
KBDLUK: LD H,0 LD L,A ADD HL,BC LD A,(HL) RET ; BASE: DB 00 DB 122,0,97,145,113,0,27,49 DB 99,120,100,115,101,119,50,51 DB 98,118,103, 102,116,114,52,53 DB 109,110, 106,104,117,131,54,55 DB 46, 44,108,107,111,105,56,57 DB 95,47,58,59,64,112,48,45 DB 14,0,13,93,144,91,94,92 DB 12,10,26,25,8,11,5,28 DB 134,135,132,133,131,130,129,128 DB 32,0,0,0,17,9,8,3 UPPER: DB 0 DB 90,0,65,145,81 0,27,33 DB 67,88,68,83,69,87,34,35 DB 66,86,71,70,84,82,36,37 DB 77,78,74,72,85,89,38,39 DB 62,60,76,75,79,73,40,41 DB 95,63,
CASPORT EQU 3+OFFSET SNDPTI EQU 3+OFFSET DRIVE EQU 5+OFFSET SNDPT0 EQU 6+OFFSET SENSE2 EQU 6+OFFSET PORT EQU 8+OFFSET CASonOF EQU 1FH DELAY EQU 1500 ; ;********** VARIABLES THAT YOU WILL NEED ********** ; CASBAUD: DB 40H MIDVAL: DB 0B0H TYPE: DS 1 ; ;IJHIGH/IJLOW POINTERS TO START OF CASSET ROUTINE :(IE THE I/O POINT CASSET) ;USED BY CTC CHIP AND MUST BE ON AN 8 BYTE BOUNDARY ; ******* ; IJHIGH EQU (HIGH BYTE) IJLOW EQU (LOW BYTE) ; ;**************************************************************************
INBIT1: INBIT2: JR NC,INBIT 1 DEC A JP C,INBIT2 DI CP (IX+0) RET ;A bit faster ;IX = MIDVAL ; ; ; OUTBIT:: CALL BLIP LD A,0 JR C,HIGH ; ; ; ;Both LOW and HIGH entered with A = 0 ; LOW:: JR NC,LOW OUT (CASPORT),A L0W1: JR C,LOW1 INC A OUT (CASPORT),A RET ; ; ; HIGH:: JR C,HIGH HIGH1: JR NC,HIGH1 OUT (CASPORT),A HIGH2: JR C,HIGH2 HIGH3: JR NC,HIGH3 INC A OUT (CASPORT),A RET ; ; ; INBYTE:: LD B,B INBY1: CALL INBIT RR C DJNZ INBY1 RET ; ; ; OUTBYTE:: LD B,B OUTBY1: RR C CALL OUTBIT DJNZ OUTBY1 RET ; ;Preser
; ; INOUT:: LD A,D OR E RET Z CALL SETint EX AF,AF’ LD A,128+16 ;Return if size of block = 0 EX AF,AF JR Z,OUTBLOCK ; ; ; INBLOCK:: INBLK1: STBIT: INBLK2:: ; ; ; OUTBLOCK:: OTBLK1: DEL1: DEL2: OTBLK2: LD B,O CALL INBIT JR C,INBLOCK DJNZ INBLK1 EI XOR A CCF CALL INBIT2 JR NCSTBIT CALL INBYTE LD (HL),C INC HL DEC DE LD A,D OR E JR NZ,INBLK2 JR RESint ;Jump if saving ;Look for 50 low bits ;Set carry ;Find long pulse ;C = byte from tape ;Store byte LD BC, DELAY XOR A CALL LOW DEC BE LD A,B OR C JR
; ; RESint: CALL INJINIT LD A,55H OUT (CASonOFF),a RET ; ; ; ;Routine to set CTC interrupts going ;Routine Z if saving, NZ if loading/verifying ; SETint: CALL IJINIT PUSH HL LD HL,TOGGLE LD (IJTABLE+2),HL LD (IJTABLE+6),HL POP HL LD IX,MIDVAL LD A,0AAH OUT (CASonOFF),A LD C,PORT+3 LD B,0C5H ;Assume loading LD A,(TYPE) AND A JR NZ,SETin1 ;Jump if A = 1 ie loading LD C,PORT+1 LD A, (CASBAUD) SETin1: OUT (C),B OUT (C),A EI RETI ;Clear interrupts and return ; ;Init CTC and set all channels to ;disable interru
; ;**********END OF CASSETTE INTERFACE ************ ; DB 0,0 ;DUMMY PAD OUT BYTES ; INJTABLE:: DB “IJTABLE”