Home » CEEFAX disks » telesoftware15.adl » 08-04-89/T\TTX05

08-04-89/T\TTX05

This website contains an archive of files for the Acorn Electron, BBC Micro, Acorn Archimedes, Commodore 16 and Commodore 64 computers, which Dominic Ford has rescued from his private collection of floppy disks and cassettes.

Some of these files were originally commercial releases in the 1980s and 1990s, but they are now widely available online. I assume that copyright over them is no longer being asserted. If you own the copyright and would like files to be removed, please contact me.

Tape/disk: Home » CEEFAX disks » telesoftware15.adl
Filename: 08-04-89/T\TTX05
Read OK:
File size: 5BFF bytes
Load address: 0000
Exec address: FFFFFFFF
File contents
Interfacing with the Acorn Teletext Adaptor - by - Gordon Horsington
--------------------------------------------------------------------

Module 5. The Teletext Independent Data Packets, Channels 0 to 7, Part 1
------------------------------------------------------------------------

Packets 30 and 31 have been set aside for page independent data. These
packets are not associated with any Teletext magazine or page and can be
transmitted at any time. The MRAG of these packets is used to define 15
independent data channels. Because these packets are not associated with
paged data in any way the term magazine is not used with packets 30 and
31 and the term channel number is used instead. The channel number is the
(de-hammed) first byte of the MRAG. Channels 0 to 7 are equivalent to
packet 30, magazines 0 to 7 and channels 8 to 15 are equivalent to packet
31, magazines 0 to 7. It is still necessary to decode the MRAG to identify
the packet as being either 30 or 31.

The Television Service Data Packet (TSDP) is broadcast on independent data
channel 0 (ie. packet 30, magazine 0). This channel is sometimes referred
to as "Packet 8/30".

There are two types of TSDP format transmitted by the BBC. These are known
as type 0 and type 2 and both use independent data channel 0.  The ITV
network only uses the BBC format type 0.

Some of the information contained in the type 0 TSDP can be returned from
the ATS or TFS ROMs using Osword &7A. The information taken from the TSDP
by the ATS is made available as a 13 byte parameter block. There are,
however, 45 bytes broadcast in the TSDP, as there are in all Teletext
packets, and it is only possible to read and interpret all the information
in the TSDP if you bypass the ATS and read the adaptor directly.

German TV stations transmit a signal, which is not Teletext compatible, to
allow video recorders to be set to record a specific program, or type of
program, regardless of what time it actually starts and without
advertisements if required. The BBC has put forward a proposal to use a
version of the TSDP to carry similar information. This is known as the
type 2 TSDP format or "Packet 8/30 Format 2". The BBC type 2 format is
broadcast on both BBC 1 and BBC 2 and will be dealt with in detail in
module 6.


The type 0 TSDP
---------------

The table in figure 1 shows the complete format of the BBC type 0 TSDP.
The demonstration program associated with this module is used to read the
TSDP, and figure 1 also shows where this program stores the data it reads.
The byte number in the left hand column of figure 1 shows the order in
which the data are broadcast. The next column shows whether or not the
data are hamming coded (hc = hamming coded, blank = not coded), the third
column gives a brief description of the byte (or bits from the byte), the
next column shows where the byte (or bits from the byte) are stored by the
program TSDP0, and the last column describes the format in which the
program TSDP0 stores the data (blank = stored as read).


+-------+----+---------------------------+------------------+-----------+
|byte no|code| description               | stored in        | format    |
+-------+----+---------------------------+------------------+-----------+
|  1    |    | clock run-in              | (not read)       |           |
|  2    |    | clock run-in              | (not read)       |           |
|  3    |    | framing code              | (not stored)     |           |
|  4    | hc | channel number            | magazine         | de-hammed |
|  4    | hc | bit 0 of pack no in bit 3 | packet bit 0     | de-hammed |
|  5    | hc | packet number bits 1-4    | packet bits 1-4  | de-hammed |
|  6    | hc | TSDP type                 | buff?0           | de-hammed |
|  7    | hc | initial page, low nybble  | buff?1           | de-hammed |
|  8    | hc | initial page, high nybble | buff?2           | de-hammed |
|  9    | hc |init sub-page, low nybble  | buff?3           | de-hammed |
| 10    | hc | init subp nyb 1 in bit 0-2| buff?4 bits 0-2  | de-hammed |
| 10    | hc | bit 0 of init mag in bit 3| buff?4 bit 3     | de-hammed |
| 11    | hc |initial sub-page, nybble 2 | buff?5           | de-hammed |
| 12    | hc |init sub-page hi in bit 0-1| buff?6 bits 0-1  | de-hammed |
| 12    | hc | bit 1 of init mag in bit 2| buff?6 bit 2     | de-hammed |
| 12    | hc | bit 2 of init mag in bit 3| buff?6 bit 3     | de-hammed |
| 13    |    | channel number, low byte  | buff?7           |           |
| 14    |    | channel number, high byte | buff?8           |           |
| 15    |    | Time offset from UTC      | buff?9           |           |
| 16    |    | MJD 10000's               | buff?10          |           |
| 17    |    | MJD 1000's and 100's      | buff?11          |           |
| 18    |    | MJD 10's and 1's          | buff?12          |           |
| 19    |    | hours UTC                 | buff?13          |           |
| 20    |    | minutes UTC               | buff?14          |           |
| 21    |    | seconds UTC               | buff?15          |           |
| 22-25 |    | television programme label| buff?16 - buff?19|           |
| 26-45 |    | status display message    | buff?20 - buff?39|           |
+-------+----+---------------------------+------------------+-----------+

Figure 1. The data transmitted in the BBC type 0 TSDP
-----------------------------------------------------


If you compare table 1 with the output from Osword &7A:15 (page 36 of the
ATS User Guide) you will see that, although there is more information made
available by reading the TSDP directly, there is a lot more work to be
done in interpreting the data. The demonstration program uses a BASIC
foreground task to interpret the contents of the TSDP buffer and an
interrupt driven background task to read the data from the adaptor.
Interpreting the TSDPs is probably the only task that can be done in 'real
time' using BASIC. BASIC can just about keep up because the type 0 TSDP is
only broadcast once a second.

The first 5 bytes of the TSDP are in the same format as the first 5 bytes
of all Teletext packets. They are therefore read and decoded in the same
way as all packets. In the example program the magazine number is stored
in the memory location labelled 'magazine' and the packet number in the
memory location labelled 'packet'. The TSDP has a magazine number 0
(interpreted as 8) and a packet number 30, although these terms are not
usually applied to the page independent packets.

The TSDP type number is broadcast as byte number 6 and stored by the
demonstration program in the first byte of the buffer labelled 'buff'.

The initial magazine number, page number and sub-page numbers are spread
over bytes 7 to 12 and are stored by the program in buff?1 to buff?6 . Bit
0 of the initial magazine number is in bit 3 of (de-hammed) byte number
10, and is stored in buff?4. Bit 1 of the initial magazine number is in
bit 2 of (de-hammed) byte number 12, and is stored in buff?6. Bit 2 of the
initial magazine number is in bit 3 of (de-hammed) byte number 12, and is
stored in buff?6.

The low order nybble of the initial page number is in the (de-hammed) byte
number 7, and is stored in buff?1. The high order nybble of the initial
page number is in (de-hammed) byte number 8, and is stored in buff?2. The
initial magazine and page numbers are usually 100, 200 or 400.

The initial sub-page number can be extracted from the (de-hammed) 9th,
10th, 11th, and 12th bytes. The low order nybble is in the ninth byte and
is stored in buff?3. The (3 bit) nybble number 1 is in bits 0, 1 and 2 of
the tenth byte and is stored in buff?4. Nybble number 2 of the initial
sub-page is in the eleventh byte and stored in buff?5. The high order (2
bit) nybble is in bits 0 and 1 of the twelfth byte and stored in buff?6.
The initial sub-page numbers are usually either &0000, when only one
sub-page is broadcast, or &3F7F when any sub-page number will be accepted.
Decoding the initial magazine, page and sub-page numbers is performed in
lines 330 to 420 of the demonstration program.

Bytes 13 and 14 (stored in buff?7 and buff?8) combine to form the United
Kingdom Network Identity number of the TV station broadcasting the type 0
TSDP packet. Each television company has been allocated a unique number to
insert in these bytes of the TSDP. These numbers were generated by a
pseudo-random number generator which was 'seeded' with the number &0BBC. 
A full list of the British TV stations and their identity codes can be
found on page 52 of the ATS User Guide, but note that the entry for
Channel 4 should be &3F8B, not &3F88 as published. Each local ITV company
has been allocated an identity code although they all seem to use the TSDP
broadcast by the parent group and are thus identified as ITV Network. The
code &0000 means that the station is not identified.

The Modified Julian Date (MJD) is broadcast in bytes 16, 17 and 18 of the
type 0 TSDP and these bytes are stored in buff?10, buff?11 and buff?12 by
the demonstration program.

The MJD uses a strange, but internationally agreed, format. In 1582 a
French scholar, Joseph Scaliger, proposed a system of counting days within
a large period, rather than using the usual calendar. This would simplify
the measuring of time between astronomical observations, as differences
between the various calendars used in the past could be ignored. The
period chosen was 7980 (Julian) years. This is the product of 28, 19, and
15, being various astronomical cycles, and is called the 'Julian Period'
(after Scaliger's father, not Julius Caesar).

The beginning of the current Julian Period, that is, the last time that
all these cycles started together, was 4713 BC. As astronomers cannot
observe the skies during the daytime, it is convenient to change from one
day number to the next at midday, rather than midnight.  Noon on the 1st
January 4713 BC is therefore the starting point of this counting system.
The Julian Day number is a count of days since then. The Modified Julian
Day number is formed by subtracting 2,400,000.5 from the JD, thus giving a
five digit number that changes at midnight GMT, and was introduced to ease
calculations on machines of limited precision.

The three hexadecimal MJD bytes taken from the type 0 TSDP each produce a
two digit number giving a total of six hex digits. The first digit (stored
in buff?10) should be ignored, as it does not form part of the 5 digit
MJD. Each of the five remaining hex digits has been incremented by one
before transmission, and so must be lowered by one before use. The result
is a binary coded decimal MJD. This is printed in lines 490 to 540 of the
program TSDP0, and interpreted in lines 550 to 630.

The co-ordinated universal time (UTC) is broadcast in bytes 19, 20 and 21
of the type 0 TSDP and stored in buff?13, buff?14 and buff?15 by the
demonstration program. Each of these three bytes is used to produce a two
digit hexadecimal number and each of the six hex digits which make up the
three bytes has been incremented by one before transmission. The UTC is
extracted from these bytes by subtracting &11 from each one (lines 650 to
690) and printing the resultant binary coded decimal number. The time is
equivalent to GMT and relates to the following second.

Byte 15 (stored in buff?9) gives an offset to add to, or subtract from,
the UTC. Local time differences, such as British Summer Time, are provided
for using this offset. Each bit of the offset byte has the following
meaning:

Bits 0 and 7 are always set.

Bit 6 tells you whether to add or subtract the offset. 0 = add, 1=subtract

Bits 1 to 5 give the amount to add or subtract:

Bit 1 - half hour
Bit 2 - one hour
Bit 3 - two hours
Bit 4 - four hours
Bit 5 - eight hours

In Britain the offset is only ever zero or one hour. In winter, when GMT
is used, this byte has a value of &81 (ie. bits 0 and 7 set) meaning add
nothing. In summer, when BST is used, this value changes to &85 (bits 0,
2, and 7 are set) meaning add one hour. One would expect the TSDP
broadcast in other countries to use different offset values according to
the time difference applicable in their area.

During the summer of 1988, the IBA left the time offset byte at &81 (ie.
no offset) and changed the coded time to summer time. This did not conform
with the requirement to broadcast UTC (ie. GMT) and it will be interesting
to see what they broadcast in the future.

The television label in bytes 22 to 25 (buff?16 to buff?19) is a string of
7 bit ASCII characters with odd parity and contains either "BBC1", "BBC2"
or the rather unimaginative "PROG" on the ITV network stations. These 4
bytes are reserved to identify the television programme currently on air,
but the exact format has yet to be defined.

The status display message in bytes 26 to 45 (buff?20 to buff?39) is
another string of 7 bit ASCII characters with odd parity, and is currently
used to identify the Network in a human readable format. It is displayed
by the TFS after issuing the terminal mode tune command, Shift+f4, and by
some new televisions upon changing channels. This message is not displayed
by the ATS, but it is printed by the program TSDP0.

Chain the program TSDP0 and select one of the four channels when prompted.
You can halt the program at any time by pressing the Escape key.


   10 REM> TSDP0
   20 MODE7
   30 VDU23,1,0;0;0;0;
   40 DIM mcode &500 :REM: space for machine code
   50 DIM buff 40 :REM: TSDP buffer
   60 PROCmcode :REM: assemble machine code
   70 ttx$=CHR$(141)+CHR$(132)+CHR$(157)+CHR$(131)
      +"Television Service Data Packet 0  "+CHR$(156)
   80 PRINTTAB(0,1)ttx$
   90 PRINTTAB(0,2)ttx$
  100 INPUTTAB(10,5)"TV channel (1-4) = "answer$
  110 channel?0=EVAL("&"+LEFT$(answer$,1))+&1B
  120 IF channel?0 < &1C THEN channel?0 = &1C
  130 IF channel?0 > &1F THEN channel?0 = &1F
  140 PRINTTAB(5,9)"TSDP type ="
  150 PRINTTAB(5,10)"Initial page ="
  160 PRINTTAB(5,11)"Channel code = &"
  170 PRINTTAB(5,12)"Programme ="
  180 PRINTTAB(5,13)"Mod. Julian date ="
  190 PRINTTAB(5,14)"Day/Month/Year ="
  200 PRINTTAB(5,15)"Time ="
  210 PRINTTAB(5,16)"GMT"
  220 PRINTTAB(5,17)"Message ="
  230 CALL mcode :REM: enable TTX interrupts
  240 ONERROR GOTO 280
  250 REPEAT
  260 IF grabflag?0=0 PROCdisplay
  270 UNTIL FALSE
  280 CALL mcode :REM: disable TTX interrupts
  290 VDU31,0,21,23,1,1;0;0;0;
  300 END
  310 DEFPROCdisplay
  320 PRINTTAB(17,9);buff?0
  330 b0=((buff?4)AND8)<>0:REM: bit 0 of magazine number
  340 b1=((buff?6)AND4)<>0:REM: bit 1 of magazine number
  350 b2=((buff?6)AND8)<>0:REM: bit 2 of magazine number
  360 init=0:REM: initial magazine number
  370 IF b0 init=1
  380 IF b1 init=init+2
  390 IF b2 init=init+4
  400 PRINTTAB(20,10);~init;:REM: initial magazine
  410 PRINT;~buff?2;~buff?1;:REM: initial page
  420 PRINT;" ";~((buff?6)AND3);~buff?5;~((buff?4)AND7);~buff?3
      :REM: initial sub-page
  430 VDU31,21,11:PROChex(buff?7):REM: channel high byte
  440 PROChex(buff?8):REM: channel low byte
  450 VDU31,17,12 :REM: print programme
  460 FOR byte=16 TO 19
  470 VDU (buff?byte OR &80) :REM: set bit 7 for printing
  480 NEXT
  490 VDU31,24,13 :REM: modified Julian date
  500 PROChex(((buff?10)-&01)AND15):REM: 10000's
  510 full$=part$
  520 PROChex((buff?11)-&11):REM: 1000's and 100's
  530 full$=full$+part$
  540 PROChex((buff?12)-&11):REM: 10's and 1's
  550 full$=full$+part$
  560 J%=VAL(full$)
  570 Y%=(100*(J%-15078.2))DIV36525
  580 M%=INT((J%-14956.1-INT(365.25*Y%))/30.6001)
  590 D%=J%-14956-INT(365.25*Y%)-INT(30.6*M%) :REM: day
  600 IF M%<14 THEN K%=0 ELSE K%=1
  610 M%=M%-1-12*K% :REM: month
  620 Y%=Y%+K%+1900 :REM: year
  630 PRINTTAB(22,14);D%;"/";M%;"/";Y% :REM: day/month/year
  640 VDU31,12,15 :REM: print time
  650 PROChex((buff?13)-&11):REM: hours
  660 PRINT;":";
  670 PROChex((buff?14)-&11):REM: minutes
  680 PRINT;":";
  690 PROChex((buff?15)-&11):REM: seconds
  700 IF buff?9 = &85 PRINTTAB(5,16)"Add 1 hr for BST" :REM: &81=GMT
  710 VDU31,15,17 :REM: print message
  720 FOR byte=20 TO 39
  730 VDU (buff?byte OR &80) :REM: set bit 7 for printing
  740 NEXT
  750 VDU7
  760 grabflag?0=2 :REM: grabflag = searching
  770 ENDPROC
  780 DEFPROChex(N%):REM: print both nybbles of a hex. number
  790 L%=N% MOD 16
  800 H%=N% DIV 16
  810 PRINT;~H%;~L%;
  820 part$=STR$(H%)+STR$(L%)
  830 ENDPROC
  840 DEFPROCmcode
  850 packet=&70 :REM: row number of current packet
  860 magazine=&71 :REM: magazine number of current page
  870 grabflag=&72 :REM: page grabber flag
  880 channel=&73 :REM: TV channel
  890 savereg=&FC :REM: interrupt accumulator save register
  900 irq2v=&206 :REM: irq2 vector
  910 ttxcontrol=&FC10 :REM: TTX control register, write only
  920 ttxstatus=&FC10 :REM: TTX status register, read only
  930 rowreg=&FC11 :REM: TTX row register, write only
  940 datareg=&FC12 :REM: TTX data register, read & write
  950 statclr=&FC13 :REM: TTX clear status register, read & write
  960 FOR pass=0 TO 2 STEP 2
  970 P%=mcode
  980 [       OPT pass
  990         LDA #&02
 1000         STA grabflag  \ grabflag = searching
 1010         LDX irq2v     \ load secondary interrupt vector
 1020         LDY irq2v+1
 1030         CPY #interrupt DIV 256
 1040         BEQ disable
 1050         STX oldirq2v  \ save secondary interrupt vector
 1060         STY oldirq2v+1
 1070         LDX #interrupt MOD 256 \ install new interrupt routine
 1080         LDY #interrupt DIV 256
 1090         SEI           \ disable interrupts when altering vector
 1100         STX irq2v
 1110         STY irq2v+1
 1120         CLI           \ re-enable interrupts
 1130         LDA channel   \ load (channel number + #&1C)
 1140         STA ttxcontrol \ enable TTX
 1150         RTS           \ return to BASIC
 1160 .disable
 1170         LDA #&00
 1180         STA ttxcontrol \ disable TTX
 1190         LDX oldirq2v  \ load original vector
 1200         LDY oldirq2v+1
 1210         SEI           \ disable interrupts when altering vector
 1220         STX irq2v     \ restore original vector
 1230         STY irq2v+1
 1240         CLI           \ re-enable interrupts
 1250         RTS           \ return to BASIC
 1260 .interrupt
 1270         BIT ttxstatus \ poll TTX hardware
 1280         BMI ttxinter  \ branch if TTX interrupt
 1290         JMP (oldirq2v) \ not TTX interrupt
 1300 .ttxinter
 1310         LDA savereg   \ interrupt accumulator save register
 1320         PHA           \ push interrupt accumulator save register
 1330         TXA
 1340         PHA           \ push X
 1350         TYA
 1360         PHA           \ push Y
 1370         LDA grabflag  \ has TSDP been grabbed?
 1380         BEQ clearstatus \ clear status and RTI if TSDP grabbed
 1390         CLD           \ clear decimal flag
 1400         LDY #&00      \ start with row 0
 1410 .readttxt
 1420         STY rowreg    \ try rows 0 to 15
 1430         LDA datareg   \ load framing code (#&27)
 1440         BEQ emptyrow  \ if zero try next row
 1450         TYA
 1460         PHA           \ save row number
 1470         JSR readpacket
 1480         PLA
 1490         TAY           \ restore row number
 1500 .emptyrow
 1510         INY           \ increment row number
 1520         CPY #&10      \ try rows 0 - 15
 1530         BNE readttxt
 1540 .clearstatus
 1550         LDA #&00
 1560         LDY #&0F      \ clear 16 rows in adaptor
 1570 .clearloop
 1580         STY rowreg
 1590         STA datareg
 1600         DEY
 1610         BPL clearloop
 1620         STA statclr   \ clear status flags before returning
 1630         PLA
 1640         TAY           \ restore Y
 1650         PLA
 1660         TAX           \ restore X
 1670         PLA
 1680         STA savereg   \ restore interrupt accumulator save register
 1690         RTI           \ return from interrupt
 1700 .readpacket
 1710         LDA grabflag  \ just checking
 1720         BEQ return
 1730         LDY datareg   \ read magazine number
 1740         LDA hamtable,Y \ de-ham it
 1750         BMI return    \ stop loading if error
 1760         STA magazine  \ save magazine number
 1770         LDY datareg   \ read packet number
 1780         LDA hamtable,Y \ de-ham it
 1790         BMI return    \ stop loading if error
 1800         STA packet    \ save packet number
 1810         LDA magazine  \ load magazine number
 1820         CMP #&08      \ bit 3 of mag. number is bit 0 of packet
                            \ number
 1830         ROL packet    \ 5 bit packet number
 1840         AND #&07      \ use only bits 0-2
 1850         CMP #&00      \ is this magazine 0?
 1860         BNE return    \ return if not
 1870         LDA packet
 1880         CMP #&1E      \ look for TSDP
 1890         BNE return    \ ignore all other packets
 1900         LDY #&00      \ read bytes 0 - 39
 1910 .readmore
 1920         LDX datareg   \ read data register
 1930         LDA hamtable,X \ de-ham the byte
 1940         BMI return    \ return if error
 1950         STA buff,Y    \ store in buffer
 1960         INY           \ increment index
 1970         CPY #&07
 1980         BNE readmore  \ go back for more
 1990 .readagain
 2000         LDA datareg   \ read data register
 2010         STA buff,Y    \ store in buffer
 2020         INY           \ increment index
 2030         CPY #&28      \ decimal 40
 2040         BNE readagain \ go back for more
 2050         LDA buff      \ TSDP type byte
 2060         AND #&0E      \ %00001110
 2070         STA grabflag  \ grabflag = 0 or 2
 2080 .return
 2090         RTS
 2100 .oldirq2v
 2110         EQUW &00
 2120 .hamtable
 2130         EQUD &0101FF01 
 2140         EQUD &FF0100FF 
 2150         EQUD &FF0102FF 
 2160         EQUD &07FFFF0A
 2170         EQUD &FF0100FF 
 2180         EQUD &00FF0000 
 2190         EQUD &0BFFFF06 
 2200         EQUD &FF0300FF
 2210         EQUD &FF010CFF 
 2220         EQUD &07FFFF04 
 2230         EQUD &07FFFF06 
 2240         EQUD &070707FF
 2250         EQUD &05FFFF06 
 2260         EQUD &FF0D00FF 
 2270         EQUD &FF060606 
 2280         EQUD &07FFFF06
 2290         EQUD &FF0102FF 
 2300         EQUD &09FFFF04 
 2310         EQUD &02FF0202 
 2320         EQUD &FF0302FF
 2330         EQUD &05FFFF08 
 2340         EQUD &FF0300FF 
 2350         EQUD &FF0302FF 
 2360         EQUD &0303FF03
 2370         EQUD &05FFFF04 
 2380         EQUD &FF040404 
 2390         EQUD &FF0F02FF 
 2400         EQUD &07FFFF04
 2410         EQUD &050505FF 
 2420         EQUD &05FFFF04 
 2430         EQUD &05FFFF06 
 2440         EQUD &FF030EFF
 2450         EQUD &FF010CFF 
 2460         EQUD &09FFFF0A 
 2470         EQUD &0BFFFF0A 
 2480         EQUD &FF0A0A0A
 2490         EQUD &0BFFFF08 
 2500         EQUD &FF0D00FF 
 2510         EQUD &0B0B0BFF 
 2520         EQUD &0BFFFF0A
 2530         EQUD &0CFF0C0C 
 2540         EQUD &FF0D0CFF 
 2550         EQUD &FF0F0CFF 
 2560         EQUD &07FFFF0A
 2570         EQUD &FF0D0CFF 
 2580         EQUD &0D0DFF0D 
 2590         EQUD &0BFFFF06 
 2600         EQUD &FF0D0EFF
 2610         EQUD &09FFFF08 
 2620         EQUD &090909FF 
 2630         EQUD &FF0F02FF 
 2640         EQUD &09FFFF0A
 2650         EQUD &FF080808 
 2660         EQUD &09FFFF08 
 2670         EQUD &0BFFFF08 
 2680         EQUD &FF030EFF
 2690         EQUD &FF0F0CFF 
 2700         EQUD &09FFFF04 
 2710         EQUD &0F0FFF0F 
 2720         EQUD &FF0F0EFF
 2730         EQUD &05FFFF08 
 2740         EQUD &FF0D0EFF 
 2750         EQUD &FF0F0EFF 
 2760         EQUD &0EFF0E0E
 2770 ]
 2780 NEXT
 2790 ENDPROC
00000000  49 6e 74 65 72 66 61 63  69 6e 67 20 77 69 74 68  |Interfacing with|
00000010  20 74 68 65 20 41 63 6f  72 6e 20 54 65 6c 65 74  | the Acorn Telet|
00000020  65 78 74 20 41 64 61 70  74 6f 72 20 2d 20 62 79  |ext Adaptor - by|
00000030  20 2d 20 47 6f 72 64 6f  6e 20 48 6f 72 73 69 6e  | - Gordon Horsin|
00000040  67 74 6f 6e 0d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |gton.-----------|
00000050  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000080  2d 2d 2d 2d 2d 2d 2d 2d  2d 0d 0d 4d 6f 64 75 6c  |---------..Modul|
00000090  65 20 35 2e 20 54 68 65  20 54 65 6c 65 74 65 78  |e 5. The Teletex|
000000a0  74 20 49 6e 64 65 70 65  6e 64 65 6e 74 20 44 61  |t Independent Da|
000000b0  74 61 20 50 61 63 6b 65  74 73 2c 20 43 68 61 6e  |ta Packets, Chan|
000000c0  6e 65 6c 73 20 30 20 74  6f 20 37 2c 20 50 61 72  |nels 0 to 7, Par|
000000d0  74 20 31 0d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |t 1.------------|
000000e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000110  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 0d 0d 50 61  |------------..Pa|
00000120  63 6b 65 74 73 20 33 30  20 61 6e 64 20 33 31 20  |ckets 30 and 31 |
00000130  68 61 76 65 20 62 65 65  6e 20 73 65 74 20 61 73  |have been set as|
00000140  69 64 65 20 66 6f 72 20  70 61 67 65 20 69 6e 64  |ide for page ind|
00000150  65 70 65 6e 64 65 6e 74  20 64 61 74 61 2e 20 54  |ependent data. T|
00000160  68 65 73 65 0d 70 61 63  6b 65 74 73 20 61 72 65  |hese.packets are|
00000170  20 6e 6f 74 20 61 73 73  6f 63 69 61 74 65 64 20  | not associated |
00000180  77 69 74 68 20 61 6e 79  20 54 65 6c 65 74 65 78  |with any Teletex|
00000190  74 20 6d 61 67 61 7a 69  6e 65 20 6f 72 20 70 61  |t magazine or pa|
000001a0  67 65 20 61 6e 64 20 63  61 6e 20 62 65 0d 74 72  |ge and can be.tr|
000001b0  61 6e 73 6d 69 74 74 65  64 20 61 74 20 61 6e 79  |ansmitted at any|
000001c0  20 74 69 6d 65 2e 20 54  68 65 20 4d 52 41 47 20  | time. The MRAG |
000001d0  6f 66 20 74 68 65 73 65  20 70 61 63 6b 65 74 73  |of these packets|
000001e0  20 69 73 20 75 73 65 64  20 74 6f 20 64 65 66 69  | is used to defi|
000001f0  6e 65 20 31 35 0d 69 6e  64 65 70 65 6e 64 65 6e  |ne 15.independen|
00000200  74 20 64 61 74 61 20 63  68 61 6e 6e 65 6c 73 2e  |t data channels.|
00000210  20 42 65 63 61 75 73 65  20 74 68 65 73 65 20 70  | Because these p|
00000220  61 63 6b 65 74 73 20 61  72 65 20 6e 6f 74 20 61  |ackets are not a|
00000230  73 73 6f 63 69 61 74 65  64 20 77 69 74 68 0d 70  |ssociated with.p|
00000240  61 67 65 64 20 64 61 74  61 20 69 6e 20 61 6e 79  |aged data in any|
00000250  20 77 61 79 20 74 68 65  20 74 65 72 6d 20 6d 61  | way the term ma|
00000260  67 61 7a 69 6e 65 20 69  73 20 6e 6f 74 20 75 73  |gazine is not us|
00000270  65 64 20 77 69 74 68 20  70 61 63 6b 65 74 73 20  |ed with packets |
00000280  33 30 20 61 6e 64 0d 33  31 20 61 6e 64 20 74 68  |30 and.31 and th|
00000290  65 20 74 65 72 6d 20 63  68 61 6e 6e 65 6c 20 6e  |e term channel n|
000002a0  75 6d 62 65 72 20 69 73  20 75 73 65 64 20 69 6e  |umber is used in|
000002b0  73 74 65 61 64 2e 20 54  68 65 20 63 68 61 6e 6e  |stead. The chann|
000002c0  65 6c 20 6e 75 6d 62 65  72 20 69 73 20 74 68 65  |el number is the|
000002d0  0d 28 64 65 2d 68 61 6d  6d 65 64 29 20 66 69 72  |.(de-hammed) fir|
000002e0  73 74 20 62 79 74 65 20  6f 66 20 74 68 65 20 4d  |st byte of the M|
000002f0  52 41 47 2e 20 43 68 61  6e 6e 65 6c 73 20 30 20  |RAG. Channels 0 |
00000300  74 6f 20 37 20 61 72 65  20 65 71 75 69 76 61 6c  |to 7 are equival|
00000310  65 6e 74 20 74 6f 0d 70  61 63 6b 65 74 20 33 30  |ent to.packet 30|
00000320  2c 20 6d 61 67 61 7a 69  6e 65 73 20 30 20 74 6f  |, magazines 0 to|
00000330  20 37 20 61 6e 64 20 63  68 61 6e 6e 65 6c 73 20  | 7 and channels |
00000340  38 20 74 6f 20 31 35 20  61 72 65 20 65 71 75 69  |8 to 15 are equi|
00000350  76 61 6c 65 6e 74 20 74  6f 20 70 61 63 6b 65 74  |valent to packet|
00000360  0d 33 31 2c 20 6d 61 67  61 7a 69 6e 65 73 20 30  |.31, magazines 0|
00000370  20 74 6f 20 37 2e 20 49  74 20 69 73 20 73 74 69  | to 7. It is sti|
00000380  6c 6c 20 6e 65 63 65 73  73 61 72 79 20 74 6f 20  |ll necessary to |
00000390  64 65 63 6f 64 65 20 74  68 65 20 4d 52 41 47 20  |decode the MRAG |
000003a0  74 6f 20 69 64 65 6e 74  69 66 79 0d 74 68 65 20  |to identify.the |
000003b0  70 61 63 6b 65 74 20 61  73 20 62 65 69 6e 67 20  |packet as being |
000003c0  65 69 74 68 65 72 20 33  30 20 6f 72 20 33 31 2e  |either 30 or 31.|
000003d0  0d 0d 54 68 65 20 54 65  6c 65 76 69 73 69 6f 6e  |..The Television|
000003e0  20 53 65 72 76 69 63 65  20 44 61 74 61 20 50 61  | Service Data Pa|
000003f0  63 6b 65 74 20 28 54 53  44 50 29 20 69 73 20 62  |cket (TSDP) is b|
00000400  72 6f 61 64 63 61 73 74  20 6f 6e 20 69 6e 64 65  |roadcast on inde|
00000410  70 65 6e 64 65 6e 74 20  64 61 74 61 0d 63 68 61  |pendent data.cha|
00000420  6e 6e 65 6c 20 30 20 28  69 65 2e 20 70 61 63 6b  |nnel 0 (ie. pack|
00000430  65 74 20 33 30 2c 20 6d  61 67 61 7a 69 6e 65 20  |et 30, magazine |
00000440  30 29 2e 20 54 68 69 73  20 63 68 61 6e 6e 65 6c  |0). This channel|
00000450  20 69 73 20 73 6f 6d 65  74 69 6d 65 73 20 72 65  | is sometimes re|
00000460  66 65 72 72 65 64 0d 74  6f 20 61 73 20 22 50 61  |ferred.to as "Pa|
00000470  63 6b 65 74 20 38 2f 33  30 22 2e 0d 0d 54 68 65  |cket 8/30"...The|
00000480  72 65 20 61 72 65 20 74  77 6f 20 74 79 70 65 73  |re are two types|
00000490  20 6f 66 20 54 53 44 50  20 66 6f 72 6d 61 74 20  | of TSDP format |
000004a0  74 72 61 6e 73 6d 69 74  74 65 64 20 62 79 20 74  |transmitted by t|
000004b0  68 65 20 42 42 43 2e 20  54 68 65 73 65 20 61 72  |he BBC. These ar|
000004c0  65 20 6b 6e 6f 77 6e 0d  61 73 20 74 79 70 65 20  |e known.as type |
000004d0  30 20 61 6e 64 20 74 79  70 65 20 32 20 61 6e 64  |0 and type 2 and|
000004e0  20 62 6f 74 68 20 75 73  65 20 69 6e 64 65 70 65  | both use indepe|
000004f0  6e 64 65 6e 74 20 64 61  74 61 20 63 68 61 6e 6e  |ndent data chann|
00000500  65 6c 20 30 2e 20 20 54  68 65 20 49 54 56 0d 6e  |el 0.  The ITV.n|
00000510  65 74 77 6f 72 6b 20 6f  6e 6c 79 20 75 73 65 73  |etwork only uses|
00000520  20 74 68 65 20 42 42 43  20 66 6f 72 6d 61 74 20  | the BBC format |
00000530  74 79 70 65 20 30 2e 0d  0d 53 6f 6d 65 20 6f 66  |type 0...Some of|
00000540  20 74 68 65 20 69 6e 66  6f 72 6d 61 74 69 6f 6e  | the information|
00000550  20 63 6f 6e 74 61 69 6e  65 64 20 69 6e 20 74 68  | contained in th|
00000560  65 20 74 79 70 65 20 30  20 54 53 44 50 20 63 61  |e type 0 TSDP ca|
00000570  6e 20 62 65 20 72 65 74  75 72 6e 65 64 20 66 72  |n be returned fr|
00000580  6f 6d 0d 74 68 65 20 41  54 53 20 6f 72 20 54 46  |om.the ATS or TF|
00000590  53 20 52 4f 4d 73 20 75  73 69 6e 67 20 4f 73 77  |S ROMs using Osw|
000005a0  6f 72 64 20 26 37 41 2e  20 54 68 65 20 69 6e 66  |ord &7A. The inf|
000005b0  6f 72 6d 61 74 69 6f 6e  20 74 61 6b 65 6e 20 66  |ormation taken f|
000005c0  72 6f 6d 20 74 68 65 20  54 53 44 50 0d 62 79 20  |rom the TSDP.by |
000005d0  74 68 65 20 41 54 53 20  69 73 20 6d 61 64 65 20  |the ATS is made |
000005e0  61 76 61 69 6c 61 62 6c  65 20 61 73 20 61 20 31  |available as a 1|
000005f0  33 20 62 79 74 65 20 70  61 72 61 6d 65 74 65 72  |3 byte parameter|
00000600  20 62 6c 6f 63 6b 2e 20  54 68 65 72 65 20 61 72  | block. There ar|
00000610  65 2c 0d 68 6f 77 65 76  65 72 2c 20 34 35 20 62  |e,.however, 45 b|
00000620  79 74 65 73 20 62 72 6f  61 64 63 61 73 74 20 69  |ytes broadcast i|
00000630  6e 20 74 68 65 20 54 53  44 50 2c 20 61 73 20 74  |n the TSDP, as t|
00000640  68 65 72 65 20 61 72 65  20 69 6e 20 61 6c 6c 20  |here are in all |
00000650  54 65 6c 65 74 65 78 74  0d 70 61 63 6b 65 74 73  |Teletext.packets|
00000660  2c 20 61 6e 64 20 69 74  20 69 73 20 6f 6e 6c 79  |, and it is only|
00000670  20 70 6f 73 73 69 62 6c  65 20 74 6f 20 72 65 61  | possible to rea|
00000680  64 20 61 6e 64 20 69 6e  74 65 72 70 72 65 74 20  |d and interpret |
00000690  61 6c 6c 20 74 68 65 20  69 6e 66 6f 72 6d 61 74  |all the informat|
000006a0  69 6f 6e 0d 69 6e 20 74  68 65 20 54 53 44 50 20  |ion.in the TSDP |
000006b0  69 66 20 79 6f 75 20 62  79 70 61 73 73 20 74 68  |if you bypass th|
000006c0  65 20 41 54 53 20 61 6e  64 20 72 65 61 64 20 74  |e ATS and read t|
000006d0  68 65 20 61 64 61 70 74  6f 72 20 64 69 72 65 63  |he adaptor direc|
000006e0  74 6c 79 2e 0d 0d 47 65  72 6d 61 6e 20 54 56 20  |tly...German TV |
000006f0  73 74 61 74 69 6f 6e 73  20 74 72 61 6e 73 6d 69  |stations transmi|
00000700  74 20 61 20 73 69 67 6e  61 6c 2c 20 77 68 69 63  |t a signal, whic|
00000710  68 20 69 73 20 6e 6f 74  20 54 65 6c 65 74 65 78  |h is not Teletex|
00000720  74 20 63 6f 6d 70 61 74  69 62 6c 65 2c 20 74 6f  |t compatible, to|
00000730  0d 61 6c 6c 6f 77 20 76  69 64 65 6f 20 72 65 63  |.allow video rec|
00000740  6f 72 64 65 72 73 20 74  6f 20 62 65 20 73 65 74  |orders to be set|
00000750  20 74 6f 20 72 65 63 6f  72 64 20 61 20 73 70 65  | to record a spe|
00000760  63 69 66 69 63 20 70 72  6f 67 72 61 6d 2c 20 6f  |cific program, o|
00000770  72 20 74 79 70 65 20 6f  66 0d 70 72 6f 67 72 61  |r type of.progra|
00000780  6d 2c 20 72 65 67 61 72  64 6c 65 73 73 20 6f 66  |m, regardless of|
00000790  20 77 68 61 74 20 74 69  6d 65 20 69 74 20 61 63  | what time it ac|
000007a0  74 75 61 6c 6c 79 20 73  74 61 72 74 73 20 61 6e  |tually starts an|
000007b0  64 20 77 69 74 68 6f 75  74 0d 61 64 76 65 72 74  |d without.advert|
000007c0  69 73 65 6d 65 6e 74 73  20 69 66 20 72 65 71 75  |isements if requ|
000007d0  69 72 65 64 2e 20 54 68  65 20 42 42 43 20 68 61  |ired. The BBC ha|
000007e0  73 20 70 75 74 20 66 6f  72 77 61 72 64 20 61 20  |s put forward a |
000007f0  70 72 6f 70 6f 73 61 6c  20 74 6f 20 75 73 65 20  |proposal to use |
00000800  61 0d 76 65 72 73 69 6f  6e 20 6f 66 20 74 68 65  |a.version of the|
00000810  20 54 53 44 50 20 74 6f  20 63 61 72 72 79 20 73  | TSDP to carry s|
00000820  69 6d 69 6c 61 72 20 69  6e 66 6f 72 6d 61 74 69  |imilar informati|
00000830  6f 6e 2e 20 54 68 69 73  20 69 73 20 6b 6e 6f 77  |on. This is know|
00000840  6e 20 61 73 20 74 68 65  0d 74 79 70 65 20 32 20  |n as the.type 2 |
00000850  54 53 44 50 20 66 6f 72  6d 61 74 20 6f 72 20 22  |TSDP format or "|
00000860  50 61 63 6b 65 74 20 38  2f 33 30 20 46 6f 72 6d  |Packet 8/30 Form|
00000870  61 74 20 32 22 2e 20 54  68 65 20 42 42 43 20 74  |at 2". The BBC t|
00000880  79 70 65 20 32 20 66 6f  72 6d 61 74 20 69 73 0d  |ype 2 format is.|
00000890  62 72 6f 61 64 63 61 73  74 20 6f 6e 20 62 6f 74  |broadcast on bot|
000008a0  68 20 42 42 43 20 31 20  61 6e 64 20 42 42 43 20  |h BBC 1 and BBC |
000008b0  32 20 61 6e 64 20 77 69  6c 6c 20 62 65 20 64 65  |2 and will be de|
000008c0  61 6c 74 20 77 69 74 68  20 69 6e 20 64 65 74 61  |alt with in deta|
000008d0  69 6c 20 69 6e 0d 6d 6f  64 75 6c 65 20 36 2e 0d  |il in.module 6..|
000008e0  0d 0d 54 68 65 20 74 79  70 65 20 30 20 54 53 44  |..The type 0 TSD|
000008f0  50 0d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |P.--------------|
00000900  2d 0d 0d 54 68 65 20 74  61 62 6c 65 20 69 6e 20  |-..The table in |
00000910  66 69 67 75 72 65 20 31  20 73 68 6f 77 73 20 74  |figure 1 shows t|
00000920  68 65 20 63 6f 6d 70 6c  65 74 65 20 66 6f 72 6d  |he complete form|
00000930  61 74 20 6f 66 20 74 68  65 20 42 42 43 20 74 79  |at of the BBC ty|
00000940  70 65 20 30 20 54 53 44  50 2e 0d 54 68 65 20 64  |pe 0 TSDP..The d|
00000950  65 6d 6f 6e 73 74 72 61  74 69 6f 6e 20 70 72 6f  |emonstration pro|
00000960  67 72 61 6d 20 61 73 73  6f 63 69 61 74 65 64 20  |gram associated |
00000970  77 69 74 68 20 74 68 69  73 20 6d 6f 64 75 6c 65  |with this module|
00000980  20 69 73 20 75 73 65 64  20 74 6f 20 72 65 61 64  | is used to read|
00000990  20 74 68 65 0d 54 53 44  50 2c 20 61 6e 64 20 66  | the.TSDP, and f|
000009a0  69 67 75 72 65 20 31 20  61 6c 73 6f 20 73 68 6f  |igure 1 also sho|
000009b0  77 73 20 77 68 65 72 65  20 74 68 69 73 20 70 72  |ws where this pr|
000009c0  6f 67 72 61 6d 20 73 74  6f 72 65 73 20 74 68 65  |ogram stores the|
000009d0  20 64 61 74 61 20 69 74  20 72 65 61 64 73 2e 0d  | data it reads..|
000009e0  54 68 65 20 62 79 74 65  20 6e 75 6d 62 65 72 20  |The byte number |
000009f0  69 6e 20 74 68 65 20 6c  65 66 74 20 68 61 6e 64  |in the left hand|
00000a00  20 63 6f 6c 75 6d 6e 20  6f 66 20 66 69 67 75 72  | column of figur|
00000a10  65 20 31 20 73 68 6f 77  73 20 74 68 65 20 6f 72  |e 1 shows the or|
00000a20  64 65 72 20 69 6e 0d 77  68 69 63 68 20 74 68 65  |der in.which the|
00000a30  20 64 61 74 61 20 61 72  65 20 62 72 6f 61 64 63  | data are broadc|
00000a40  61 73 74 2e 20 54 68 65  20 6e 65 78 74 20 63 6f  |ast. The next co|
00000a50  6c 75 6d 6e 20 73 68 6f  77 73 20 77 68 65 74 68  |lumn shows wheth|
00000a60  65 72 20 6f 72 20 6e 6f  74 20 74 68 65 0d 64 61  |er or not the.da|
00000a70  74 61 20 61 72 65 20 68  61 6d 6d 69 6e 67 20 63  |ta are hamming c|
00000a80  6f 64 65 64 20 28 68 63  20 3d 20 68 61 6d 6d 69  |oded (hc = hammi|
00000a90  6e 67 20 63 6f 64 65 64  2c 20 62 6c 61 6e 6b 20  |ng coded, blank |
00000aa0  3d 20 6e 6f 74 20 63 6f  64 65 64 29 2c 20 74 68  |= not coded), th|
00000ab0  65 20 74 68 69 72 64 0d  63 6f 6c 75 6d 6e 20 67  |e third.column g|
00000ac0  69 76 65 73 20 61 20 62  72 69 65 66 20 64 65 73  |ives a brief des|
00000ad0  63 72 69 70 74 69 6f 6e  20 6f 66 20 74 68 65 20  |cription of the |
00000ae0  62 79 74 65 20 28 6f 72  20 62 69 74 73 20 66 72  |byte (or bits fr|
00000af0  6f 6d 20 74 68 65 20 62  79 74 65 29 2c 20 74 68  |om the byte), th|
00000b00  65 0d 6e 65 78 74 20 63  6f 6c 75 6d 6e 20 73 68  |e.next column sh|
00000b10  6f 77 73 20 77 68 65 72  65 20 74 68 65 20 62 79  |ows where the by|
00000b20  74 65 20 28 6f 72 20 62  69 74 73 20 66 72 6f 6d  |te (or bits from|
00000b30  20 74 68 65 20 62 79 74  65 29 20 61 72 65 20 73  | the byte) are s|
00000b40  74 6f 72 65 64 20 62 79  20 74 68 65 0d 70 72 6f  |tored by the.pro|
00000b50  67 72 61 6d 20 54 53 44  50 30 2c 20 61 6e 64 20  |gram TSDP0, and |
00000b60  74 68 65 20 6c 61 73 74  20 63 6f 6c 75 6d 6e 20  |the last column |
00000b70  64 65 73 63 72 69 62 65  73 20 74 68 65 20 66 6f  |describes the fo|
00000b80  72 6d 61 74 20 69 6e 20  77 68 69 63 68 20 74 68  |rmat in which th|
00000b90  65 0d 70 72 6f 67 72 61  6d 20 54 53 44 50 30 20  |e.program TSDP0 |
00000ba0  73 74 6f 72 65 73 20 74  68 65 20 64 61 74 61 20  |stores the data |
00000bb0  28 62 6c 61 6e 6b 20 3d  20 73 74 6f 72 65 64 20  |(blank = stored |
00000bc0  61 73 20 72 65 61 64 29  2e 0d 0d 0d 2b 2d 2d 2d  |as read)....+---|
00000bd0  2d 2d 2d 2d 2b 2d 2d 2d  2d 2b 2d 2d 2d 2d 2d 2d  |----+----+------|
00000be0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
00000bf0  2d 2d 2d 2d 2d 2b 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |-----+----------|
00000c00  2d 2d 2d 2d 2d 2d 2d 2d  2b 2d 2d 2d 2d 2d 2d 2d  |--------+-------|
00000c10  2d 2d 2d 2d 2b 0d 7c 62  79 74 65 20 6e 6f 7c 63  |----+.|byte no|c|
00000c20  6f 64 65 7c 20 64 65 73  63 72 69 70 74 69 6f 6e  |ode| description|
00000c30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 7c  |               ||
00000c40  20 73 74 6f 72 65 64 20  69 6e 20 20 20 20 20 20  | stored in      |
00000c50  20 20 7c 20 66 6f 72 6d  61 74 20 20 20 20 7c 0d  |  | format    |.|
00000c60  2b 2d 2d 2d 2d 2d 2d 2d  2b 2d 2d 2d 2d 2b 2d 2d  |+-------+----+--|
00000c70  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
00000c80  2d 2d 2d 2d 2d 2d 2d 2d  2d 2b 2d 2d 2d 2d 2d 2d  |---------+------|
00000c90  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2b 2d 2d 2d  |------------+---|
00000ca0  2d 2d 2d 2d 2d 2d 2d 2d  2b 0d 7c 20 20 31 20 20  |--------+.|  1  |
00000cb0  20 20 7c 20 20 20 20 7c  20 63 6c 6f 63 6b 20 72  |  |    | clock r|
00000cc0  75 6e 2d 69 6e 20 20 20  20 20 20 20 20 20 20 20  |un-in           |
00000cd0  20 20 20 7c 20 28 6e 6f  74 20 72 65 61 64 29 20  |   | (not read) |
00000ce0  20 20 20 20 20 20 7c 20  20 20 20 20 20 20 20 20  |      |         |
00000cf0  20 20 7c 0d 7c 20 20 32  20 20 20 20 7c 20 20 20  |  |.|  2    |   |
00000d00  20 7c 20 63 6c 6f 63 6b  20 72 75 6e 2d 69 6e 20  | | clock run-in |
00000d10  20 20 20 20 20 20 20 20  20 20 20 20 20 7c 20 28  |             | (|
00000d20  6e 6f 74 20 72 65 61 64  29 20 20 20 20 20 20 20  |not read)       |
00000d30  7c 20 20 20 20 20 20 20  20 20 20 20 7c 0d 7c 20  ||           |.| |
00000d40  20 33 20 20 20 20 7c 20  20 20 20 7c 20 66 72 61  | 3    |    | fra|
00000d50  6d 69 6e 67 20 63 6f 64  65 20 20 20 20 20 20 20  |ming code       |
00000d60  20 20 20 20 20 20 20 7c  20 28 6e 6f 74 20 73 74  |       | (not st|
00000d70  6f 72 65 64 29 20 20 20  20 20 7c 20 20 20 20 20  |ored)     |     |
00000d80  20 20 20 20 20 20 7c 0d  7c 20 20 34 20 20 20 20  |      |.|  4    |
00000d90  7c 20 68 63 20 7c 20 63  68 61 6e 6e 65 6c 20 6e  || hc | channel n|
00000da0  75 6d 62 65 72 20 20 20  20 20 20 20 20 20 20 20  |umber           |
00000db0  20 7c 20 6d 61 67 61 7a  69 6e 65 20 20 20 20 20  | | magazine     |
00000dc0  20 20 20 20 7c 20 64 65  2d 68 61 6d 6d 65 64 20  |    | de-hammed |
00000dd0  7c 0d 7c 20 20 34 20 20  20 20 7c 20 68 63 20 7c  ||.|  4    | hc ||
00000de0  20 62 69 74 20 30 20 6f  66 20 70 61 63 6b 20 6e  | bit 0 of pack n|
00000df0  6f 20 69 6e 20 62 69 74  20 33 20 7c 20 70 61 63  |o in bit 3 | pac|
00000e00  6b 65 74 20 62 69 74 20  30 20 20 20 20 20 7c 20  |ket bit 0     | |
00000e10  64 65 2d 68 61 6d 6d 65  64 20 7c 0d 7c 20 20 35  |de-hammed |.|  5|
00000e20  20 20 20 20 7c 20 68 63  20 7c 20 70 61 63 6b 65  |    | hc | packe|
00000e30  74 20 6e 75 6d 62 65 72  20 62 69 74 73 20 31 2d  |t number bits 1-|
00000e40  34 20 20 20 20 7c 20 70  61 63 6b 65 74 20 62 69  |4    | packet bi|
00000e50  74 73 20 31 2d 34 20 20  7c 20 64 65 2d 68 61 6d  |ts 1-4  | de-ham|
00000e60  6d 65 64 20 7c 0d 7c 20  20 36 20 20 20 20 7c 20  |med |.|  6    | |
00000e70  68 63 20 7c 20 54 53 44  50 20 74 79 70 65 20 20  |hc | TSDP type  |
00000e80  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 7c  |               ||
00000e90  20 62 75 66 66 3f 30 20  20 20 20 20 20 20 20 20  | buff?0         |
00000ea0  20 20 7c 20 64 65 2d 68  61 6d 6d 65 64 20 7c 0d  |  | de-hammed |.|
00000eb0  7c 20 20 37 20 20 20 20  7c 20 68 63 20 7c 20 69  ||  7    | hc | i|
00000ec0  6e 69 74 69 61 6c 20 70  61 67 65 2c 20 6c 6f 77  |nitial page, low|
00000ed0  20 6e 79 62 62 6c 65 20  20 7c 20 62 75 66 66 3f  | nybble  | buff?|
00000ee0  31 20 20 20 20 20 20 20  20 20 20 20 7c 20 64 65  |1           | de|
00000ef0  2d 68 61 6d 6d 65 64 20  7c 0d 7c 20 20 38 20 20  |-hammed |.|  8  |
00000f00  20 20 7c 20 68 63 20 7c  20 69 6e 69 74 69 61 6c  |  | hc | initial|
00000f10  20 70 61 67 65 2c 20 68  69 67 68 20 6e 79 62 62  | page, high nybb|
00000f20  6c 65 20 7c 20 62 75 66  66 3f 32 20 20 20 20 20  |le | buff?2     |
00000f30  20 20 20 20 20 20 7c 20  64 65 2d 68 61 6d 6d 65  |      | de-hamme|
00000f40  64 20 7c 0d 7c 20 20 39  20 20 20 20 7c 20 68 63  |d |.|  9    | hc|
00000f50  20 7c 69 6e 69 74 20 73  75 62 2d 70 61 67 65 2c  | |init sub-page,|
00000f60  20 6c 6f 77 20 6e 79 62  62 6c 65 20 20 7c 20 62  | low nybble  | b|
00000f70  75 66 66 3f 33 20 20 20  20 20 20 20 20 20 20 20  |uff?3           |
00000f80  7c 20 64 65 2d 68 61 6d  6d 65 64 20 7c 0d 7c 20  || de-hammed |.| |
00000f90  31 30 20 20 20 20 7c 20  68 63 20 7c 20 69 6e 69  |10    | hc | ini|
00000fa0  74 20 73 75 62 70 20 6e  79 62 20 31 20 69 6e 20  |t subp nyb 1 in |
00000fb0  62 69 74 20 30 2d 32 7c  20 62 75 66 66 3f 34 20  |bit 0-2| buff?4 |
00000fc0  62 69 74 73 20 30 2d 32  20 20 7c 20 64 65 2d 68  |bits 0-2  | de-h|
00000fd0  61 6d 6d 65 64 20 7c 0d  7c 20 31 30 20 20 20 20  |ammed |.| 10    |
00000fe0  7c 20 68 63 20 7c 20 62  69 74 20 30 20 6f 66 20  || hc | bit 0 of |
00000ff0  69 6e 69 74 20 6d 61 67  20 69 6e 20 62 69 74 20  |init mag in bit |
00001000  33 7c 20 62 75 66 66 3f  34 20 62 69 74 20 33 20  |3| buff?4 bit 3 |
00001010  20 20 20 20 7c 20 64 65  2d 68 61 6d 6d 65 64 20  |    | de-hammed |
00001020  7c 0d 7c 20 31 31 20 20  20 20 7c 20 68 63 20 7c  ||.| 11    | hc ||
00001030  69 6e 69 74 69 61 6c 20  73 75 62 2d 70 61 67 65  |initial sub-page|
00001040  2c 20 6e 79 62 62 6c 65  20 32 20 7c 20 62 75 66  |, nybble 2 | buf|
00001050  66 3f 35 20 20 20 20 20  20 20 20 20 20 20 7c 20  |f?5           | |
00001060  64 65 2d 68 61 6d 6d 65  64 20 7c 0d 7c 20 31 32  |de-hammed |.| 12|
00001070  20 20 20 20 7c 20 68 63  20 7c 69 6e 69 74 20 73  |    | hc |init s|
00001080  75 62 2d 70 61 67 65 20  68 69 20 69 6e 20 62 69  |ub-page hi in bi|
00001090  74 20 30 2d 31 7c 20 62  75 66 66 3f 36 20 62 69  |t 0-1| buff?6 bi|
000010a0  74 73 20 30 2d 31 20 20  7c 20 64 65 2d 68 61 6d  |ts 0-1  | de-ham|
000010b0  6d 65 64 20 7c 0d 7c 20  31 32 20 20 20 20 7c 20  |med |.| 12    | |
000010c0  68 63 20 7c 20 62 69 74  20 31 20 6f 66 20 69 6e  |hc | bit 1 of in|
000010d0  69 74 20 6d 61 67 20 69  6e 20 62 69 74 20 32 7c  |it mag in bit 2||
000010e0  20 62 75 66 66 3f 36 20  62 69 74 20 32 20 20 20  | buff?6 bit 2   |
000010f0  20 20 7c 20 64 65 2d 68  61 6d 6d 65 64 20 7c 0d  |  | de-hammed |.|
00001100  7c 20 31 32 20 20 20 20  7c 20 68 63 20 7c 20 62  || 12    | hc | b|
00001110  69 74 20 32 20 6f 66 20  69 6e 69 74 20 6d 61 67  |it 2 of init mag|
00001120  20 69 6e 20 62 69 74 20  33 7c 20 62 75 66 66 3f  | in bit 3| buff?|
00001130  36 20 62 69 74 20 33 20  20 20 20 20 7c 20 64 65  |6 bit 3     | de|
00001140  2d 68 61 6d 6d 65 64 20  7c 0d 7c 20 31 33 20 20  |-hammed |.| 13  |
00001150  20 20 7c 20 20 20 20 7c  20 63 68 61 6e 6e 65 6c  |  |    | channel|
00001160  20 6e 75 6d 62 65 72 2c  20 6c 6f 77 20 62 79 74  | number, low byt|
00001170  65 20 20 7c 20 62 75 66  66 3f 37 20 20 20 20 20  |e  | buff?7     |
00001180  20 20 20 20 20 20 7c 20  20 20 20 20 20 20 20 20  |      |         |
00001190  20 20 7c 0d 7c 20 31 34  20 20 20 20 7c 20 20 20  |  |.| 14    |   |
000011a0  20 7c 20 63 68 61 6e 6e  65 6c 20 6e 75 6d 62 65  | | channel numbe|
000011b0  72 2c 20 68 69 67 68 20  62 79 74 65 20 7c 20 62  |r, high byte | b|
000011c0  75 66 66 3f 38 20 20 20  20 20 20 20 20 20 20 20  |uff?8           |
000011d0  7c 20 20 20 20 20 20 20  20 20 20 20 7c 0d 7c 20  ||           |.| |
000011e0  31 35 20 20 20 20 7c 20  20 20 20 7c 20 54 69 6d  |15    |    | Tim|
000011f0  65 20 6f 66 66 73 65 74  20 66 72 6f 6d 20 55 54  |e offset from UT|
00001200  43 20 20 20 20 20 20 7c  20 62 75 66 66 3f 39 20  |C      | buff?9 |
00001210  20 20 20 20 20 20 20 20  20 20 7c 20 20 20 20 20  |          |     |
00001220  20 20 20 20 20 20 7c 0d  7c 20 31 36 20 20 20 20  |      |.| 16    |
00001230  7c 20 20 20 20 7c 20 4d  4a 44 20 31 30 30 30 30  ||    | MJD 10000|
00001240  27 73 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |'s              |
00001250  20 7c 20 62 75 66 66 3f  31 30 20 20 20 20 20 20  | | buff?10      |
00001260  20 20 20 20 7c 20 20 20  20 20 20 20 20 20 20 20  |    |           |
00001270  7c 0d 7c 20 31 37 20 20  20 20 7c 20 20 20 20 7c  ||.| 17    |    ||
00001280  20 4d 4a 44 20 31 30 30  30 27 73 20 61 6e 64 20  | MJD 1000's and |
00001290  31 30 30 27 73 20 20 20  20 20 20 7c 20 62 75 66  |100's      | buf|
000012a0  66 3f 31 31 20 20 20 20  20 20 20 20 20 20 7c 20  |f?11          | |
000012b0  20 20 20 20 20 20 20 20  20 20 7c 0d 7c 20 31 38  |          |.| 18|
000012c0  20 20 20 20 7c 20 20 20  20 7c 20 4d 4a 44 20 31  |    |    | MJD 1|
000012d0  30 27 73 20 61 6e 64 20  31 27 73 20 20 20 20 20  |0's and 1's     |
000012e0  20 20 20 20 20 7c 20 62  75 66 66 3f 31 32 20 20  |     | buff?12  |
000012f0  20 20 20 20 20 20 20 20  7c 20 20 20 20 20 20 20  |        |       |
00001300  20 20 20 20 7c 0d 7c 20  31 39 20 20 20 20 7c 20  |    |.| 19    | |
00001310  20 20 20 7c 20 68 6f 75  72 73 20 55 54 43 20 20  |   | hours UTC  |
00001320  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 7c  |               ||
00001330  20 62 75 66 66 3f 31 33  20 20 20 20 20 20 20 20  | buff?13        |
00001340  20 20 7c 20 20 20 20 20  20 20 20 20 20 20 7c 0d  |  |           |.|
00001350  7c 20 32 30 20 20 20 20  7c 20 20 20 20 7c 20 6d  || 20    |    | m|
00001360  69 6e 75 74 65 73 20 55  54 43 20 20 20 20 20 20  |inutes UTC      |
00001370  20 20 20 20 20 20 20 20  20 7c 20 62 75 66 66 3f  |         | buff?|
00001380  31 34 20 20 20 20 20 20  20 20 20 20 7c 20 20 20  |14          |   |
00001390  20 20 20 20 20 20 20 20  7c 0d 7c 20 32 31 20 20  |        |.| 21  |
000013a0  20 20 7c 20 20 20 20 7c  20 73 65 63 6f 6e 64 73  |  |    | seconds|
000013b0  20 55 54 43 20 20 20 20  20 20 20 20 20 20 20 20  | UTC            |
000013c0  20 20 20 7c 20 62 75 66  66 3f 31 35 20 20 20 20  |   | buff?15    |
000013d0  20 20 20 20 20 20 7c 20  20 20 20 20 20 20 20 20  |      |         |
000013e0  20 20 7c 0d 7c 20 32 32  2d 32 35 20 7c 20 20 20  |  |.| 22-25 |   |
000013f0  20 7c 20 74 65 6c 65 76  69 73 69 6f 6e 20 70 72  | | television pr|
00001400  6f 67 72 61 6d 6d 65 20  6c 61 62 65 6c 7c 20 62  |ogramme label| b|
00001410  75 66 66 3f 31 36 20 2d  20 62 75 66 66 3f 31 39  |uff?16 - buff?19|
00001420  7c 20 20 20 20 20 20 20  20 20 20 20 7c 0d 7c 20  ||           |.| |
00001430  32 36 2d 34 35 20 7c 20  20 20 20 7c 20 73 74 61  |26-45 |    | sta|
00001440  74 75 73 20 64 69 73 70  6c 61 79 20 6d 65 73 73  |tus display mess|
00001450  61 67 65 20 20 20 20 7c  20 62 75 66 66 3f 32 30  |age    | buff?20|
00001460  20 2d 20 62 75 66 66 3f  33 39 7c 20 20 20 20 20  | - buff?39|     |
00001470  20 20 20 20 20 20 7c 0d  2b 2d 2d 2d 2d 2d 2d 2d  |      |.+-------|
00001480  2b 2d 2d 2d 2d 2b 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |+----+----------|
00001490  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
000014a0  2d 2b 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |-+--------------|
000014b0  2d 2d 2d 2d 2b 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----+-----------|
000014c0  2b 0d 0d 46 69 67 75 72  65 20 31 2e 20 54 68 65  |+..Figure 1. The|
000014d0  20 64 61 74 61 20 74 72  61 6e 73 6d 69 74 74 65  | data transmitte|
000014e0  64 20 69 6e 20 74 68 65  20 42 42 43 20 74 79 70  |d in the BBC typ|
000014f0  65 20 30 20 54 53 44 50  0d 2d 2d 2d 2d 2d 2d 2d  |e 0 TSDP.-------|
00001500  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001520  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0d 0d  |--------------..|
00001530  0d 49 66 20 79 6f 75 20  63 6f 6d 70 61 72 65 20  |.If you compare |
00001540  74 61 62 6c 65 20 31 20  77 69 74 68 20 74 68 65  |table 1 with the|
00001550  20 6f 75 74 70 75 74 20  66 72 6f 6d 20 4f 73 77  | output from Osw|
00001560  6f 72 64 20 26 37 41 3a  31 35 20 28 70 61 67 65  |ord &7A:15 (page|
00001570  20 33 36 20 6f 66 20 74  68 65 0d 41 54 53 20 55  | 36 of the.ATS U|
00001580  73 65 72 20 47 75 69 64  65 29 20 79 6f 75 20 77  |ser Guide) you w|
00001590  69 6c 6c 20 73 65 65 20  74 68 61 74 2c 20 61 6c  |ill see that, al|
000015a0  74 68 6f 75 67 68 20 74  68 65 72 65 20 69 73 20  |though there is |
000015b0  6d 6f 72 65 20 69 6e 66  6f 72 6d 61 74 69 6f 6e  |more information|
000015c0  20 6d 61 64 65 0d 61 76  61 69 6c 61 62 6c 65 20  | made.available |
000015d0  62 79 20 72 65 61 64 69  6e 67 20 74 68 65 20 54  |by reading the T|
000015e0  53 44 50 20 64 69 72 65  63 74 6c 79 2c 20 74 68  |SDP directly, th|
000015f0  65 72 65 20 69 73 20 61  20 6c 6f 74 20 6d 6f 72  |ere is a lot mor|
00001600  65 20 77 6f 72 6b 20 74  6f 20 62 65 0d 64 6f 6e  |e work to be.don|
00001610  65 20 69 6e 20 69 6e 74  65 72 70 72 65 74 69 6e  |e in interpretin|
00001620  67 20 74 68 65 20 64 61  74 61 2e 20 54 68 65 20  |g the data. The |
00001630  64 65 6d 6f 6e 73 74 72  61 74 69 6f 6e 20 70 72  |demonstration pr|
00001640  6f 67 72 61 6d 20 75 73  65 73 20 61 20 42 41 53  |ogram uses a BAS|
00001650  49 43 0d 66 6f 72 65 67  72 6f 75 6e 64 20 74 61  |IC.foreground ta|
00001660  73 6b 20 74 6f 20 69 6e  74 65 72 70 72 65 74 20  |sk to interpret |
00001670  74 68 65 20 63 6f 6e 74  65 6e 74 73 20 6f 66 20  |the contents of |
00001680  74 68 65 20 54 53 44 50  20 62 75 66 66 65 72 20  |the TSDP buffer |
00001690  61 6e 64 20 61 6e 0d 69  6e 74 65 72 72 75 70 74  |and an.interrupt|
000016a0  20 64 72 69 76 65 6e 20  62 61 63 6b 67 72 6f 75  | driven backgrou|
000016b0  6e 64 20 74 61 73 6b 20  74 6f 20 72 65 61 64 20  |nd task to read |
000016c0  74 68 65 20 64 61 74 61  20 66 72 6f 6d 20 74 68  |the data from th|
000016d0  65 20 61 64 61 70 74 6f  72 2e 0d 49 6e 74 65 72  |e adaptor..Inter|
000016e0  70 72 65 74 69 6e 67 20  74 68 65 20 54 53 44 50  |preting the TSDP|
000016f0  73 20 69 73 20 70 72 6f  62 61 62 6c 79 20 74 68  |s is probably th|
00001700  65 20 6f 6e 6c 79 20 74  61 73 6b 20 74 68 61 74  |e only task that|
00001710  20 63 61 6e 20 62 65 20  64 6f 6e 65 20 69 6e 20  | can be done in |
00001720  27 72 65 61 6c 0d 74 69  6d 65 27 20 75 73 69 6e  |'real.time' usin|
00001730  67 20 42 41 53 49 43 2e  20 42 41 53 49 43 20 63  |g BASIC. BASIC c|
00001740  61 6e 20 6a 75 73 74 20  61 62 6f 75 74 20 6b 65  |an just about ke|
00001750  65 70 20 75 70 20 62 65  63 61 75 73 65 20 74 68  |ep up because th|
00001760  65 20 74 79 70 65 20 30  20 54 53 44 50 20 69 73  |e type 0 TSDP is|
00001770  0d 6f 6e 6c 79 20 62 72  6f 61 64 63 61 73 74 20  |.only broadcast |
00001780  6f 6e 63 65 20 61 20 73  65 63 6f 6e 64 2e 0d 0d  |once a second...|
00001790  54 68 65 20 66 69 72 73  74 20 35 20 62 79 74 65  |The first 5 byte|
000017a0  73 20 6f 66 20 74 68 65  20 54 53 44 50 20 61 72  |s of the TSDP ar|
000017b0  65 20 69 6e 20 74 68 65  20 73 61 6d 65 20 66 6f  |e in the same fo|
000017c0  72 6d 61 74 20 61 73 20  74 68 65 20 66 69 72 73  |rmat as the firs|
000017d0  74 20 35 20 62 79 74 65  73 0d 6f 66 20 61 6c 6c  |t 5 bytes.of all|
000017e0  20 54 65 6c 65 74 65 78  74 20 70 61 63 6b 65 74  | Teletext packet|
000017f0  73 2e 20 54 68 65 79 20  61 72 65 20 74 68 65 72  |s. They are ther|
00001800  65 66 6f 72 65 20 72 65  61 64 20 61 6e 64 20 64  |efore read and d|
00001810  65 63 6f 64 65 64 20 69  6e 20 74 68 65 20 73 61  |ecoded in the sa|
00001820  6d 65 0d 77 61 79 20 61  73 20 61 6c 6c 20 70 61  |me.way as all pa|
00001830  63 6b 65 74 73 2e 20 49  6e 20 74 68 65 20 65 78  |ckets. In the ex|
00001840  61 6d 70 6c 65 20 70 72  6f 67 72 61 6d 20 74 68  |ample program th|
00001850  65 20 6d 61 67 61 7a 69  6e 65 20 6e 75 6d 62 65  |e magazine numbe|
00001860  72 20 69 73 20 73 74 6f  72 65 64 0d 69 6e 20 74  |r is stored.in t|
00001870  68 65 20 6d 65 6d 6f 72  79 20 6c 6f 63 61 74 69  |he memory locati|
00001880  6f 6e 20 6c 61 62 65 6c  6c 65 64 20 27 6d 61 67  |on labelled 'mag|
00001890  61 7a 69 6e 65 27 20 61  6e 64 20 74 68 65 20 70  |azine' and the p|
000018a0  61 63 6b 65 74 20 6e 75  6d 62 65 72 20 69 6e 20  |acket number in |
000018b0  74 68 65 0d 6d 65 6d 6f  72 79 20 6c 6f 63 61 74  |the.memory locat|
000018c0  69 6f 6e 20 6c 61 62 65  6c 6c 65 64 20 27 70 61  |ion labelled 'pa|
000018d0  63 6b 65 74 27 2e 20 54  68 65 20 54 53 44 50 20  |cket'. The TSDP |
000018e0  68 61 73 20 61 20 6d 61  67 61 7a 69 6e 65 20 6e  |has a magazine n|
000018f0  75 6d 62 65 72 20 30 0d  28 69 6e 74 65 72 70 72  |umber 0.(interpr|
00001900  65 74 65 64 20 61 73 20  38 29 20 61 6e 64 20 61  |eted as 8) and a|
00001910  20 70 61 63 6b 65 74 20  6e 75 6d 62 65 72 20 33  | packet number 3|
00001920  30 2c 20 61 6c 74 68 6f  75 67 68 20 74 68 65 73  |0, although thes|
00001930  65 20 74 65 72 6d 73 20  61 72 65 20 6e 6f 74 0d  |e terms are not.|
00001940  75 73 75 61 6c 6c 79 20  61 70 70 6c 69 65 64 20  |usually applied |
00001950  74 6f 20 74 68 65 20 70  61 67 65 20 69 6e 64 65  |to the page inde|
00001960  70 65 6e 64 65 6e 74 20  70 61 63 6b 65 74 73 2e  |pendent packets.|
00001970  0d 0d 54 68 65 20 54 53  44 50 20 74 79 70 65 20  |..The TSDP type |
00001980  6e 75 6d 62 65 72 20 69  73 20 62 72 6f 61 64 63  |number is broadc|
00001990  61 73 74 20 61 73 20 62  79 74 65 20 6e 75 6d 62  |ast as byte numb|
000019a0  65 72 20 36 20 61 6e 64  20 73 74 6f 72 65 64 20  |er 6 and stored |
000019b0  62 79 20 74 68 65 0d 64  65 6d 6f 6e 73 74 72 61  |by the.demonstra|
000019c0  74 69 6f 6e 20 70 72 6f  67 72 61 6d 20 69 6e 20  |tion program in |
000019d0  74 68 65 20 66 69 72 73  74 20 62 79 74 65 20 6f  |the first byte o|
000019e0  66 20 74 68 65 20 62 75  66 66 65 72 20 6c 61 62  |f the buffer lab|
000019f0  65 6c 6c 65 64 20 27 62  75 66 66 27 2e 0d 0d 54  |elled 'buff'...T|
00001a00  68 65 20 69 6e 69 74 69  61 6c 20 6d 61 67 61 7a  |he initial magaz|
00001a10  69 6e 65 20 6e 75 6d 62  65 72 2c 20 70 61 67 65  |ine number, page|
00001a20  20 6e 75 6d 62 65 72 20  61 6e 64 20 73 75 62 2d  | number and sub-|
00001a30  70 61 67 65 20 6e 75 6d  62 65 72 73 20 61 72 65  |page numbers are|
00001a40  20 73 70 72 65 61 64 0d  6f 76 65 72 20 62 79 74  | spread.over byt|
00001a50  65 73 20 37 20 74 6f 20  31 32 20 61 6e 64 20 61  |es 7 to 12 and a|
00001a60  72 65 20 73 74 6f 72 65  64 20 62 79 20 74 68 65  |re stored by the|
00001a70  20 70 72 6f 67 72 61 6d  20 69 6e 20 62 75 66 66  | program in buff|
00001a80  3f 31 20 74 6f 20 62 75  66 66 3f 36 20 2e 20 42  |?1 to buff?6 . B|
00001a90  69 74 0d 30 20 6f 66 20  74 68 65 20 69 6e 69 74  |it.0 of the init|
00001aa0  69 61 6c 20 6d 61 67 61  7a 69 6e 65 20 6e 75 6d  |ial magazine num|
00001ab0  62 65 72 20 69 73 20 69  6e 20 62 69 74 20 33 20  |ber is in bit 3 |
00001ac0  6f 66 20 28 64 65 2d 68  61 6d 6d 65 64 29 20 62  |of (de-hammed) b|
00001ad0  79 74 65 20 6e 75 6d 62  65 72 0d 31 30 2c 20 61  |yte number.10, a|
00001ae0  6e 64 20 69 73 20 73 74  6f 72 65 64 20 69 6e 20  |nd is stored in |
00001af0  62 75 66 66 3f 34 2e 20  42 69 74 20 31 20 6f 66  |buff?4. Bit 1 of|
00001b00  20 74 68 65 20 69 6e 69  74 69 61 6c 20 6d 61 67  | the initial mag|
00001b10  61 7a 69 6e 65 20 6e 75  6d 62 65 72 20 69 73 20  |azine number is |
00001b20  69 6e 0d 62 69 74 20 32  20 6f 66 20 28 64 65 2d  |in.bit 2 of (de-|
00001b30  68 61 6d 6d 65 64 29 20  62 79 74 65 20 6e 75 6d  |hammed) byte num|
00001b40  62 65 72 20 31 32 2c 20  61 6e 64 20 69 73 20 73  |ber 12, and is s|
00001b50  74 6f 72 65 64 20 69 6e  20 62 75 66 66 3f 36 2e  |tored in buff?6.|
00001b60  20 42 69 74 20 32 20 6f  66 20 74 68 65 0d 69 6e  | Bit 2 of the.in|
00001b70  69 74 69 61 6c 20 6d 61  67 61 7a 69 6e 65 20 6e  |itial magazine n|
00001b80  75 6d 62 65 72 20 69 73  20 69 6e 20 62 69 74 20  |umber is in bit |
00001b90  33 20 6f 66 20 28 64 65  2d 68 61 6d 6d 65 64 29  |3 of (de-hammed)|
00001ba0  20 62 79 74 65 20 6e 75  6d 62 65 72 20 31 32 2c  | byte number 12,|
00001bb0  20 61 6e 64 20 69 73 0d  73 74 6f 72 65 64 20 69  | and is.stored i|
00001bc0  6e 20 62 75 66 66 3f 36  2e 0d 0d 54 68 65 20 6c  |n buff?6...The l|
00001bd0  6f 77 20 6f 72 64 65 72  20 6e 79 62 62 6c 65 20  |ow order nybble |
00001be0  6f 66 20 74 68 65 20 69  6e 69 74 69 61 6c 20 70  |of the initial p|
00001bf0  61 67 65 20 6e 75 6d 62  65 72 20 69 73 20 69 6e  |age number is in|
00001c00  20 74 68 65 20 28 64 65  2d 68 61 6d 6d 65 64 29  | the (de-hammed)|
00001c10  20 62 79 74 65 0d 6e 75  6d 62 65 72 20 37 2c 20  | byte.number 7, |
00001c20  61 6e 64 20 69 73 20 73  74 6f 72 65 64 20 69 6e  |and is stored in|
00001c30  20 62 75 66 66 3f 31 2e  20 54 68 65 20 68 69 67  | buff?1. The hig|
00001c40  68 20 6f 72 64 65 72 20  6e 79 62 62 6c 65 20 6f  |h order nybble o|
00001c50  66 20 74 68 65 20 69 6e  69 74 69 61 6c 0d 70 61  |f the initial.pa|
00001c60  67 65 20 6e 75 6d 62 65  72 20 69 73 20 69 6e 20  |ge number is in |
00001c70  28 64 65 2d 68 61 6d 6d  65 64 29 20 62 79 74 65  |(de-hammed) byte|
00001c80  20 6e 75 6d 62 65 72 20  38 2c 20 61 6e 64 20 69  | number 8, and i|
00001c90  73 20 73 74 6f 72 65 64  20 69 6e 20 62 75 66 66  |s stored in buff|
00001ca0  3f 32 2e 20 54 68 65 0d  69 6e 69 74 69 61 6c 20  |?2. The.initial |
00001cb0  6d 61 67 61 7a 69 6e 65  20 61 6e 64 20 70 61 67  |magazine and pag|
00001cc0  65 20 6e 75 6d 62 65 72  73 20 61 72 65 20 75 73  |e numbers are us|
00001cd0  75 61 6c 6c 79 20 31 30  30 2c 20 32 30 30 20 6f  |ually 100, 200 o|
00001ce0  72 20 34 30 30 2e 0d 0d  54 68 65 20 69 6e 69 74  |r 400...The init|
00001cf0  69 61 6c 20 73 75 62 2d  70 61 67 65 20 6e 75 6d  |ial sub-page num|
00001d00  62 65 72 20 63 61 6e 20  62 65 20 65 78 74 72 61  |ber can be extra|
00001d10  63 74 65 64 20 66 72 6f  6d 20 74 68 65 20 28 64  |cted from the (d|
00001d20  65 2d 68 61 6d 6d 65 64  29 20 39 74 68 2c 0d 31  |e-hammed) 9th,.1|
00001d30  30 74 68 2c 20 31 31 74  68 2c 20 61 6e 64 20 31  |0th, 11th, and 1|
00001d40  32 74 68 20 62 79 74 65  73 2e 20 54 68 65 20 6c  |2th bytes. The l|
00001d50  6f 77 20 6f 72 64 65 72  20 6e 79 62 62 6c 65 20  |ow order nybble |
00001d60  69 73 20 69 6e 20 74 68  65 20 6e 69 6e 74 68 20  |is in the ninth |
00001d70  62 79 74 65 20 61 6e 64  0d 69 73 20 73 74 6f 72  |byte and.is stor|
00001d80  65 64 20 69 6e 20 62 75  66 66 3f 33 2e 20 54 68  |ed in buff?3. Th|
00001d90  65 20 28 33 20 62 69 74  29 20 6e 79 62 62 6c 65  |e (3 bit) nybble|
00001da0  20 6e 75 6d 62 65 72 20  31 20 69 73 20 69 6e 20  | number 1 is in |
00001db0  62 69 74 73 20 30 2c 20  31 20 61 6e 64 20 32 20  |bits 0, 1 and 2 |
00001dc0  6f 66 0d 74 68 65 20 74  65 6e 74 68 20 62 79 74  |of.the tenth byt|
00001dd0  65 20 61 6e 64 20 69 73  20 73 74 6f 72 65 64 20  |e and is stored |
00001de0  69 6e 20 62 75 66 66 3f  34 2e 20 4e 79 62 62 6c  |in buff?4. Nybbl|
00001df0  65 20 6e 75 6d 62 65 72  20 32 20 6f 66 20 74 68  |e number 2 of th|
00001e00  65 20 69 6e 69 74 69 61  6c 0d 73 75 62 2d 70 61  |e initial.sub-pa|
00001e10  67 65 20 69 73 20 69 6e  20 74 68 65 20 65 6c 65  |ge is in the ele|
00001e20  76 65 6e 74 68 20 62 79  74 65 20 61 6e 64 20 73  |venth byte and s|
00001e30  74 6f 72 65 64 20 69 6e  20 62 75 66 66 3f 35 2e  |tored in buff?5.|
00001e40  20 54 68 65 20 68 69 67  68 20 6f 72 64 65 72 20  | The high order |
00001e50  28 32 0d 62 69 74 29 20  6e 79 62 62 6c 65 20 69  |(2.bit) nybble i|
00001e60  73 20 69 6e 20 62 69 74  73 20 30 20 61 6e 64 20  |s in bits 0 and |
00001e70  31 20 6f 66 20 74 68 65  20 74 77 65 6c 66 74 68  |1 of the twelfth|
00001e80  20 62 79 74 65 20 61 6e  64 20 73 74 6f 72 65 64  | byte and stored|
00001e90  20 69 6e 20 62 75 66 66  3f 36 2e 0d 54 68 65 20  | in buff?6..The |
00001ea0  69 6e 69 74 69 61 6c 20  73 75 62 2d 70 61 67 65  |initial sub-page|
00001eb0  20 6e 75 6d 62 65 72 73  20 61 72 65 20 75 73 75  | numbers are usu|
00001ec0  61 6c 6c 79 20 65 69 74  68 65 72 20 26 30 30 30  |ally either &000|
00001ed0  30 2c 20 77 68 65 6e 20  6f 6e 6c 79 20 6f 6e 65  |0, when only one|
00001ee0  0d 73 75 62 2d 70 61 67  65 20 69 73 20 62 72 6f  |.sub-page is bro|
00001ef0  61 64 63 61 73 74 2c 20  6f 72 20 26 33 46 37 46  |adcast, or &3F7F|
00001f00  20 77 68 65 6e 20 61 6e  79 20 73 75 62 2d 70 61  | when any sub-pa|
00001f10  67 65 20 6e 75 6d 62 65  72 20 77 69 6c 6c 20 62  |ge number will b|
00001f20  65 20 61 63 63 65 70 74  65 64 2e 0d 44 65 63 6f  |e accepted..Deco|
00001f30  64 69 6e 67 20 74 68 65  20 69 6e 69 74 69 61 6c  |ding the initial|
00001f40  20 6d 61 67 61 7a 69 6e  65 2c 20 70 61 67 65 20  | magazine, page |
00001f50  61 6e 64 20 73 75 62 2d  70 61 67 65 20 6e 75 6d  |and sub-page num|
00001f60  62 65 72 73 20 69 73 20  70 65 72 66 6f 72 6d 65  |bers is performe|
00001f70  64 20 69 6e 0d 6c 69 6e  65 73 20 33 33 30 20 74  |d in.lines 330 t|
00001f80  6f 20 34 32 30 20 6f 66  20 74 68 65 20 64 65 6d  |o 420 of the dem|
00001f90  6f 6e 73 74 72 61 74 69  6f 6e 20 70 72 6f 67 72  |onstration progr|
00001fa0  61 6d 2e 0d 0d 42 79 74  65 73 20 31 33 20 61 6e  |am...Bytes 13 an|
00001fb0  64 20 31 34 20 28 73 74  6f 72 65 64 20 69 6e 20  |d 14 (stored in |
00001fc0  62 75 66 66 3f 37 20 61  6e 64 20 62 75 66 66 3f  |buff?7 and buff?|
00001fd0  38 29 20 63 6f 6d 62 69  6e 65 20 74 6f 20 66 6f  |8) combine to fo|
00001fe0  72 6d 20 74 68 65 20 55  6e 69 74 65 64 0d 4b 69  |rm the United.Ki|
00001ff0  6e 67 64 6f 6d 20 4e 65  74 77 6f 72 6b 20 49 64  |ngdom Network Id|
00002000  65 6e 74 69 74 79 20 6e  75 6d 62 65 72 20 6f 66  |entity number of|
00002010  20 74 68 65 20 54 56 20  73 74 61 74 69 6f 6e 20  | the TV station |
00002020  62 72 6f 61 64 63 61 73  74 69 6e 67 20 74 68 65  |broadcasting the|
00002030  20 74 79 70 65 20 30 0d  54 53 44 50 20 70 61 63  | type 0.TSDP pac|
00002040  6b 65 74 2e 20 45 61 63  68 20 74 65 6c 65 76 69  |ket. Each televi|
00002050  73 69 6f 6e 20 63 6f 6d  70 61 6e 79 20 68 61 73  |sion company has|
00002060  20 62 65 65 6e 20 61 6c  6c 6f 63 61 74 65 64 20  | been allocated |
00002070  61 20 75 6e 69 71 75 65  20 6e 75 6d 62 65 72 20  |a unique number |
00002080  74 6f 0d 69 6e 73 65 72  74 20 69 6e 20 74 68 65  |to.insert in the|
00002090  73 65 20 62 79 74 65 73  20 6f 66 20 74 68 65 20  |se bytes of the |
000020a0  54 53 44 50 2e 20 54 68  65 73 65 20 6e 75 6d 62  |TSDP. These numb|
000020b0  65 72 73 20 77 65 72 65  20 67 65 6e 65 72 61 74  |ers were generat|
000020c0  65 64 20 62 79 20 61 0d  70 73 65 75 64 6f 2d 72  |ed by a.pseudo-r|
000020d0  61 6e 64 6f 6d 20 6e 75  6d 62 65 72 20 67 65 6e  |andom number gen|
000020e0  65 72 61 74 6f 72 20 77  68 69 63 68 20 77 61 73  |erator which was|
000020f0  20 27 73 65 65 64 65 64  27 20 77 69 74 68 20 74  | 'seeded' with t|
00002100  68 65 20 6e 75 6d 62 65  72 20 26 30 42 42 43 2e  |he number &0BBC.|
00002110  20 0d 41 20 66 75 6c 6c  20 6c 69 73 74 20 6f 66  | .A full list of|
00002120  20 74 68 65 20 42 72 69  74 69 73 68 20 54 56 20  | the British TV |
00002130  73 74 61 74 69 6f 6e 73  20 61 6e 64 20 74 68 65  |stations and the|
00002140  69 72 20 69 64 65 6e 74  69 74 79 20 63 6f 64 65  |ir identity code|
00002150  73 20 63 61 6e 20 62 65  0d 66 6f 75 6e 64 20 6f  |s can be.found o|
00002160  6e 20 70 61 67 65 20 35  32 20 6f 66 20 74 68 65  |n page 52 of the|
00002170  20 41 54 53 20 55 73 65  72 20 47 75 69 64 65 2c  | ATS User Guide,|
00002180  20 62 75 74 20 6e 6f 74  65 20 74 68 61 74 20 74  | but note that t|
00002190  68 65 20 65 6e 74 72 79  20 66 6f 72 0d 43 68 61  |he entry for.Cha|
000021a0  6e 6e 65 6c 20 34 20 73  68 6f 75 6c 64 20 62 65  |nnel 4 should be|
000021b0  20 26 33 46 38 42 2c 20  6e 6f 74 20 26 33 46 38  | &3F8B, not &3F8|
000021c0  38 20 61 73 20 70 75 62  6c 69 73 68 65 64 2e 20  |8 as published. |
000021d0  45 61 63 68 20 6c 6f 63  61 6c 20 49 54 56 20 63  |Each local ITV c|
000021e0  6f 6d 70 61 6e 79 0d 68  61 73 20 62 65 65 6e 20  |ompany.has been |
000021f0  61 6c 6c 6f 63 61 74 65  64 20 61 6e 20 69 64 65  |allocated an ide|
00002200  6e 74 69 74 79 20 63 6f  64 65 20 61 6c 74 68 6f  |ntity code altho|
00002210  75 67 68 20 74 68 65 79  20 61 6c 6c 20 73 65 65  |ugh they all see|
00002220  6d 20 74 6f 20 75 73 65  20 74 68 65 20 54 53 44  |m to use the TSD|
00002230  50 0d 62 72 6f 61 64 63  61 73 74 20 62 79 20 74  |P.broadcast by t|
00002240  68 65 20 70 61 72 65 6e  74 20 67 72 6f 75 70 20  |he parent group |
00002250  61 6e 64 20 61 72 65 20  74 68 75 73 20 69 64 65  |and are thus ide|
00002260  6e 74 69 66 69 65 64 20  61 73 20 49 54 56 20 4e  |ntified as ITV N|
00002270  65 74 77 6f 72 6b 2e 20  54 68 65 0d 63 6f 64 65  |etwork. The.code|
00002280  20 26 30 30 30 30 20 6d  65 61 6e 73 20 74 68 61  | &0000 means tha|
00002290  74 20 74 68 65 20 73 74  61 74 69 6f 6e 20 69 73  |t the station is|
000022a0  20 6e 6f 74 20 69 64 65  6e 74 69 66 69 65 64 2e  | not identified.|
000022b0  0d 0d 54 68 65 20 4d 6f  64 69 66 69 65 64 20 4a  |..The Modified J|
000022c0  75 6c 69 61 6e 20 44 61  74 65 20 28 4d 4a 44 29  |ulian Date (MJD)|
000022d0  20 69 73 20 62 72 6f 61  64 63 61 73 74 20 69 6e  | is broadcast in|
000022e0  20 62 79 74 65 73 20 31  36 2c 20 31 37 20 61 6e  | bytes 16, 17 an|
000022f0  64 20 31 38 20 6f 66 20  74 68 65 0d 74 79 70 65  |d 18 of the.type|
00002300  20 30 20 54 53 44 50 20  61 6e 64 20 74 68 65 73  | 0 TSDP and thes|
00002310  65 20 62 79 74 65 73 20  61 72 65 20 73 74 6f 72  |e bytes are stor|
00002320  65 64 20 69 6e 20 62 75  66 66 3f 31 30 2c 20 62  |ed in buff?10, b|
00002330  75 66 66 3f 31 31 20 61  6e 64 20 62 75 66 66 3f  |uff?11 and buff?|
00002340  31 32 20 62 79 0d 74 68  65 20 64 65 6d 6f 6e 73  |12 by.the demons|
00002350  74 72 61 74 69 6f 6e 20  70 72 6f 67 72 61 6d 2e  |tration program.|
00002360  0d 0d 54 68 65 20 4d 4a  44 20 75 73 65 73 20 61  |..The MJD uses a|
00002370  20 73 74 72 61 6e 67 65  2c 20 62 75 74 20 69 6e  | strange, but in|
00002380  74 65 72 6e 61 74 69 6f  6e 61 6c 6c 79 20 61 67  |ternationally ag|
00002390  72 65 65 64 2c 20 66 6f  72 6d 61 74 2e 20 49 6e  |reed, format. In|
000023a0  20 31 35 38 32 20 61 0d  46 72 65 6e 63 68 20 73  | 1582 a.French s|
000023b0  63 68 6f 6c 61 72 2c 20  4a 6f 73 65 70 68 20 53  |cholar, Joseph S|
000023c0  63 61 6c 69 67 65 72 2c  20 70 72 6f 70 6f 73 65  |caliger, propose|
000023d0  64 20 61 20 73 79 73 74  65 6d 20 6f 66 20 63 6f  |d a system of co|
000023e0  75 6e 74 69 6e 67 20 64  61 79 73 20 77 69 74 68  |unting days with|
000023f0  69 6e 0d 61 20 6c 61 72  67 65 20 70 65 72 69 6f  |in.a large perio|
00002400  64 2c 20 72 61 74 68 65  72 20 74 68 61 6e 20 75  |d, rather than u|
00002410  73 69 6e 67 20 74 68 65  20 75 73 75 61 6c 20 63  |sing the usual c|
00002420  61 6c 65 6e 64 61 72 2e  20 54 68 69 73 20 77 6f  |alendar. This wo|
00002430  75 6c 64 20 73 69 6d 70  6c 69 66 79 0d 74 68 65  |uld simplify.the|
00002440  20 6d 65 61 73 75 72 69  6e 67 20 6f 66 20 74 69  | measuring of ti|
00002450  6d 65 20 62 65 74 77 65  65 6e 20 61 73 74 72 6f  |me between astro|
00002460  6e 6f 6d 69 63 61 6c 20  6f 62 73 65 72 76 61 74  |nomical observat|
00002470  69 6f 6e 73 2c 20 61 73  20 64 69 66 66 65 72 65  |ions, as differe|
00002480  6e 63 65 73 0d 62 65 74  77 65 65 6e 20 74 68 65  |nces.between the|
00002490  20 76 61 72 69 6f 75 73  20 63 61 6c 65 6e 64 61  | various calenda|
000024a0  72 73 20 75 73 65 64 20  69 6e 20 74 68 65 20 70  |rs used in the p|
000024b0  61 73 74 20 63 6f 75 6c  64 20 62 65 20 69 67 6e  |ast could be ign|
000024c0  6f 72 65 64 2e 20 54 68  65 0d 70 65 72 69 6f 64  |ored. The.period|
000024d0  20 63 68 6f 73 65 6e 20  77 61 73 20 37 39 38 30  | chosen was 7980|
000024e0  20 28 4a 75 6c 69 61 6e  29 20 79 65 61 72 73 2e  | (Julian) years.|
000024f0  20 54 68 69 73 20 69 73  20 74 68 65 20 70 72 6f  | This is the pro|
00002500  64 75 63 74 20 6f 66 20  32 38 2c 20 31 39 2c 20  |duct of 28, 19, |
00002510  61 6e 64 0d 31 35 2c 20  62 65 69 6e 67 20 76 61  |and.15, being va|
00002520  72 69 6f 75 73 20 61 73  74 72 6f 6e 6f 6d 69 63  |rious astronomic|
00002530  61 6c 20 63 79 63 6c 65  73 2c 20 61 6e 64 20 69  |al cycles, and i|
00002540  73 20 63 61 6c 6c 65 64  20 74 68 65 20 27 4a 75  |s called the 'Ju|
00002550  6c 69 61 6e 20 50 65 72  69 6f 64 27 0d 28 61 66  |lian Period'.(af|
00002560  74 65 72 20 53 63 61 6c  69 67 65 72 27 73 20 66  |ter Scaliger's f|
00002570  61 74 68 65 72 2c 20 6e  6f 74 20 4a 75 6c 69 75  |ather, not Juliu|
00002580  73 20 43 61 65 73 61 72  29 2e 0d 0d 54 68 65 20  |s Caesar)...The |
00002590  62 65 67 69 6e 6e 69 6e  67 20 6f 66 20 74 68 65  |beginning of the|
000025a0  20 63 75 72 72 65 6e 74  20 4a 75 6c 69 61 6e 20  | current Julian |
000025b0  50 65 72 69 6f 64 2c 20  74 68 61 74 20 69 73 2c  |Period, that is,|
000025c0  20 74 68 65 20 6c 61 73  74 20 74 69 6d 65 20 74  | the last time t|
000025d0  68 61 74 0d 61 6c 6c 20  74 68 65 73 65 20 63 79  |hat.all these cy|
000025e0  63 6c 65 73 20 73 74 61  72 74 65 64 20 74 6f 67  |cles started tog|
000025f0  65 74 68 65 72 2c 20 77  61 73 20 34 37 31 33 20  |ether, was 4713 |
00002600  42 43 2e 20 41 73 20 61  73 74 72 6f 6e 6f 6d 65  |BC. As astronome|
00002610  72 73 20 63 61 6e 6e 6f  74 0d 6f 62 73 65 72 76  |rs cannot.observ|
00002620  65 20 74 68 65 20 73 6b  69 65 73 20 64 75 72 69  |e the skies duri|
00002630  6e 67 20 74 68 65 20 64  61 79 74 69 6d 65 2c 20  |ng the daytime, |
00002640  69 74 20 69 73 20 63 6f  6e 76 65 6e 69 65 6e 74  |it is convenient|
00002650  20 74 6f 20 63 68 61 6e  67 65 20 66 72 6f 6d 20  | to change from |
00002660  6f 6e 65 0d 64 61 79 20  6e 75 6d 62 65 72 20 74  |one.day number t|
00002670  6f 20 74 68 65 20 6e 65  78 74 20 61 74 20 6d 69  |o the next at mi|
00002680  64 64 61 79 2c 20 72 61  74 68 65 72 20 74 68 61  |dday, rather tha|
00002690  6e 20 6d 69 64 6e 69 67  68 74 2e 20 20 4e 6f 6f  |n midnight.  Noo|
000026a0  6e 20 6f 6e 20 74 68 65  20 31 73 74 0d 4a 61 6e  |n on the 1st.Jan|
000026b0  75 61 72 79 20 34 37 31  33 20 42 43 20 69 73 20  |uary 4713 BC is |
000026c0  74 68 65 72 65 66 6f 72  65 20 74 68 65 20 73 74  |therefore the st|
000026d0  61 72 74 69 6e 67 20 70  6f 69 6e 74 20 6f 66 20  |arting point of |
000026e0  74 68 69 73 20 63 6f 75  6e 74 69 6e 67 20 73 79  |this counting sy|
000026f0  73 74 65 6d 2e 0d 54 68  65 20 4a 75 6c 69 61 6e  |stem..The Julian|
00002700  20 44 61 79 20 6e 75 6d  62 65 72 20 69 73 20 61  | Day number is a|
00002710  20 63 6f 75 6e 74 20 6f  66 20 64 61 79 73 20 73  | count of days s|
00002720  69 6e 63 65 20 74 68 65  6e 2e 20 54 68 65 20 4d  |ince then. The M|
00002730  6f 64 69 66 69 65 64 20  4a 75 6c 69 61 6e 0d 44  |odified Julian.D|
00002740  61 79 20 6e 75 6d 62 65  72 20 69 73 20 66 6f 72  |ay number is for|
00002750  6d 65 64 20 62 79 20 73  75 62 74 72 61 63 74 69  |med by subtracti|
00002760  6e 67 20 32 2c 34 30 30  2c 30 30 30 2e 35 20 66  |ng 2,400,000.5 f|
00002770  72 6f 6d 20 74 68 65 20  4a 44 2c 20 74 68 75 73  |rom the JD, thus|
00002780  20 67 69 76 69 6e 67 20  61 0d 66 69 76 65 20 64  | giving a.five d|
00002790  69 67 69 74 20 6e 75 6d  62 65 72 20 74 68 61 74  |igit number that|
000027a0  20 63 68 61 6e 67 65 73  20 61 74 20 6d 69 64 6e  | changes at midn|
000027b0  69 67 68 74 20 47 4d 54  2c 20 61 6e 64 20 77 61  |ight GMT, and wa|
000027c0  73 20 69 6e 74 72 6f 64  75 63 65 64 20 74 6f 20  |s introduced to |
000027d0  65 61 73 65 0d 63 61 6c  63 75 6c 61 74 69 6f 6e  |ease.calculation|
000027e0  73 20 6f 6e 20 6d 61 63  68 69 6e 65 73 20 6f 66  |s on machines of|
000027f0  20 6c 69 6d 69 74 65 64  20 70 72 65 63 69 73 69  | limited precisi|
00002800  6f 6e 2e 0d 0d 54 68 65  20 74 68 72 65 65 20 68  |on...The three h|
00002810  65 78 61 64 65 63 69 6d  61 6c 20 4d 4a 44 20 62  |exadecimal MJD b|
00002820  79 74 65 73 20 74 61 6b  65 6e 20 66 72 6f 6d 20  |ytes taken from |
00002830  74 68 65 20 74 79 70 65  20 30 20 54 53 44 50 20  |the type 0 TSDP |
00002840  65 61 63 68 20 70 72 6f  64 75 63 65 20 61 0d 74  |each produce a.t|
00002850  77 6f 20 64 69 67 69 74  20 6e 75 6d 62 65 72 20  |wo digit number |
00002860  67 69 76 69 6e 67 20 61  20 74 6f 74 61 6c 20 6f  |giving a total o|
00002870  66 20 73 69 78 20 68 65  78 20 64 69 67 69 74 73  |f six hex digits|
00002880  2e 20 54 68 65 20 66 69  72 73 74 20 64 69 67 69  |. The first digi|
00002890  74 20 28 73 74 6f 72 65  64 0d 69 6e 20 62 75 66  |t (stored.in buf|
000028a0  66 3f 31 30 29 20 73 68  6f 75 6c 64 20 62 65 20  |f?10) should be |
000028b0  69 67 6e 6f 72 65 64 2c  20 61 73 20 69 74 20 64  |ignored, as it d|
000028c0  6f 65 73 20 6e 6f 74 20  66 6f 72 6d 20 70 61 72  |oes not form par|
000028d0  74 20 6f 66 20 74 68 65  20 35 20 64 69 67 69 74  |t of the 5 digit|
000028e0  0d 4d 4a 44 2e 20 45 61  63 68 20 6f 66 20 74 68  |.MJD. Each of th|
000028f0  65 20 66 69 76 65 20 72  65 6d 61 69 6e 69 6e 67  |e five remaining|
00002900  20 68 65 78 20 64 69 67  69 74 73 20 68 61 73 20  | hex digits has |
00002910  62 65 65 6e 20 69 6e 63  72 65 6d 65 6e 74 65 64  |been incremented|
00002920  20 62 79 20 6f 6e 65 0d  62 65 66 6f 72 65 20 74  | by one.before t|
00002930  72 61 6e 73 6d 69 73 73  69 6f 6e 2c 20 61 6e 64  |ransmission, and|
00002940  20 73 6f 20 6d 75 73 74  20 62 65 20 6c 6f 77 65  | so must be lowe|
00002950  72 65 64 20 62 79 20 6f  6e 65 20 62 65 66 6f 72  |red by one befor|
00002960  65 20 75 73 65 2e 20 54  68 65 20 72 65 73 75 6c  |e use. The resul|
00002970  74 0d 69 73 20 61 20 62  69 6e 61 72 79 20 63 6f  |t.is a binary co|
00002980  64 65 64 20 64 65 63 69  6d 61 6c 20 4d 4a 44 2e  |ded decimal MJD.|
00002990  20 54 68 69 73 20 69 73  20 70 72 69 6e 74 65 64  | This is printed|
000029a0  20 69 6e 20 6c 69 6e 65  73 20 34 39 30 20 74 6f  | in lines 490 to|
000029b0  20 35 34 30 20 6f 66 20  74 68 65 0d 70 72 6f 67  | 540 of the.prog|
000029c0  72 61 6d 20 54 53 44 50  30 2c 20 61 6e 64 20 69  |ram TSDP0, and i|
000029d0  6e 74 65 72 70 72 65 74  65 64 20 69 6e 20 6c 69  |nterpreted in li|
000029e0  6e 65 73 20 35 35 30 20  74 6f 20 36 33 30 2e 0d  |nes 550 to 630..|
000029f0  0d 54 68 65 20 63 6f 2d  6f 72 64 69 6e 61 74 65  |.The co-ordinate|
00002a00  64 20 75 6e 69 76 65 72  73 61 6c 20 74 69 6d 65  |d universal time|
00002a10  20 28 55 54 43 29 20 69  73 20 62 72 6f 61 64 63  | (UTC) is broadc|
00002a20  61 73 74 20 69 6e 20 62  79 74 65 73 20 31 39 2c  |ast in bytes 19,|
00002a30  20 32 30 20 61 6e 64 20  32 31 0d 6f 66 20 74 68  | 20 and 21.of th|
00002a40  65 20 74 79 70 65 20 30  20 54 53 44 50 20 61 6e  |e type 0 TSDP an|
00002a50  64 20 73 74 6f 72 65 64  20 69 6e 20 62 75 66 66  |d stored in buff|
00002a60  3f 31 33 2c 20 62 75 66  66 3f 31 34 20 61 6e 64  |?13, buff?14 and|
00002a70  20 62 75 66 66 3f 31 35  20 62 79 20 74 68 65 0d  | buff?15 by the.|
00002a80  64 65 6d 6f 6e 73 74 72  61 74 69 6f 6e 20 70 72  |demonstration pr|
00002a90  6f 67 72 61 6d 2e 20 45  61 63 68 20 6f 66 20 74  |ogram. Each of t|
00002aa0  68 65 73 65 20 74 68 72  65 65 20 62 79 74 65 73  |hese three bytes|
00002ab0  20 69 73 20 75 73 65 64  20 74 6f 20 70 72 6f 64  | is used to prod|
00002ac0  75 63 65 20 61 20 74 77  6f 0d 64 69 67 69 74 20  |uce a two.digit |
00002ad0  68 65 78 61 64 65 63 69  6d 61 6c 20 6e 75 6d 62  |hexadecimal numb|
00002ae0  65 72 20 61 6e 64 20 65  61 63 68 20 6f 66 20 74  |er and each of t|
00002af0  68 65 20 73 69 78 20 68  65 78 20 64 69 67 69 74  |he six hex digit|
00002b00  73 20 77 68 69 63 68 20  6d 61 6b 65 20 75 70 20  |s which make up |
00002b10  74 68 65 0d 74 68 72 65  65 20 62 79 74 65 73 20  |the.three bytes |
00002b20  68 61 73 20 62 65 65 6e  20 69 6e 63 72 65 6d 65  |has been increme|
00002b30  6e 74 65 64 20 62 79 20  6f 6e 65 20 62 65 66 6f  |nted by one befo|
00002b40  72 65 20 74 72 61 6e 73  6d 69 73 73 69 6f 6e 2e  |re transmission.|
00002b50  20 54 68 65 20 55 54 43  20 69 73 0d 65 78 74 72  | The UTC is.extr|
00002b60  61 63 74 65 64 20 66 72  6f 6d 20 74 68 65 73 65  |acted from these|
00002b70  20 62 79 74 65 73 20 62  79 20 73 75 62 74 72 61  | bytes by subtra|
00002b80  63 74 69 6e 67 20 26 31  31 20 66 72 6f 6d 20 65  |cting &11 from e|
00002b90  61 63 68 20 6f 6e 65 20  28 6c 69 6e 65 73 20 36  |ach one (lines 6|
00002ba0  35 30 20 74 6f 0d 36 39  30 29 20 61 6e 64 20 70  |50 to.690) and p|
00002bb0  72 69 6e 74 69 6e 67 20  74 68 65 20 72 65 73 75  |rinting the resu|
00002bc0  6c 74 61 6e 74 20 62 69  6e 61 72 79 20 63 6f 64  |ltant binary cod|
00002bd0  65 64 20 64 65 63 69 6d  61 6c 20 6e 75 6d 62 65  |ed decimal numbe|
00002be0  72 2e 20 54 68 65 20 74  69 6d 65 20 69 73 0d 65  |r. The time is.e|
00002bf0  71 75 69 76 61 6c 65 6e  74 20 74 6f 20 47 4d 54  |quivalent to GMT|
00002c00  20 61 6e 64 20 72 65 6c  61 74 65 73 20 74 6f 20  | and relates to |
00002c10  74 68 65 20 66 6f 6c 6c  6f 77 69 6e 67 20 73 65  |the following se|
00002c20  63 6f 6e 64 2e 0d 0d 42  79 74 65 20 31 35 20 28  |cond...Byte 15 (|
00002c30  73 74 6f 72 65 64 20 69  6e 20 62 75 66 66 3f 39  |stored in buff?9|
00002c40  29 20 67 69 76 65 73 20  61 6e 20 6f 66 66 73 65  |) gives an offse|
00002c50  74 20 74 6f 20 61 64 64  20 74 6f 2c 20 6f 72 20  |t to add to, or |
00002c60  73 75 62 74 72 61 63 74  20 66 72 6f 6d 2c 0d 74  |subtract from,.t|
00002c70  68 65 20 55 54 43 2e 20  4c 6f 63 61 6c 20 74 69  |he UTC. Local ti|
00002c80  6d 65 20 64 69 66 66 65  72 65 6e 63 65 73 2c 20  |me differences, |
00002c90  73 75 63 68 20 61 73 20  42 72 69 74 69 73 68 20  |such as British |
00002ca0  53 75 6d 6d 65 72 20 54  69 6d 65 2c 20 61 72 65  |Summer Time, are|
00002cb0  20 70 72 6f 76 69 64 65  64 0d 66 6f 72 20 75 73  | provided.for us|
00002cc0  69 6e 67 20 74 68 69 73  20 6f 66 66 73 65 74 2e  |ing this offset.|
00002cd0  20 45 61 63 68 20 62 69  74 20 6f 66 20 74 68 65  | Each bit of the|
00002ce0  20 6f 66 66 73 65 74 20  62 79 74 65 20 68 61 73  | offset byte has|
00002cf0  20 74 68 65 20 66 6f 6c  6c 6f 77 69 6e 67 0d 6d  | the following.m|
00002d00  65 61 6e 69 6e 67 3a 0d  0d 42 69 74 73 20 30 20  |eaning:..Bits 0 |
00002d10  61 6e 64 20 37 20 61 72  65 20 61 6c 77 61 79 73  |and 7 are always|
00002d20  20 73 65 74 2e 0d 0d 42  69 74 20 36 20 74 65 6c  | set...Bit 6 tel|
00002d30  6c 73 20 79 6f 75 20 77  68 65 74 68 65 72 20 74  |ls you whether t|
00002d40  6f 20 61 64 64 20 6f 72  20 73 75 62 74 72 61 63  |o add or subtrac|
00002d50  74 20 74 68 65 20 6f 66  66 73 65 74 2e 20 30 20  |t the offset. 0 |
00002d60  3d 20 61 64 64 2c 20 31  3d 73 75 62 74 72 61 63  |= add, 1=subtrac|
00002d70  74 0d 0d 42 69 74 73 20  31 20 74 6f 20 35 20 67  |t..Bits 1 to 5 g|
00002d80  69 76 65 20 74 68 65 20  61 6d 6f 75 6e 74 20 74  |ive the amount t|
00002d90  6f 20 61 64 64 20 6f 72  20 73 75 62 74 72 61 63  |o add or subtrac|
00002da0  74 3a 0d 0d 42 69 74 20  31 20 2d 20 68 61 6c 66  |t:..Bit 1 - half|
00002db0  20 68 6f 75 72 0d 42 69  74 20 32 20 2d 20 6f 6e  | hour.Bit 2 - on|
00002dc0  65 20 68 6f 75 72 0d 42  69 74 20 33 20 2d 20 74  |e hour.Bit 3 - t|
00002dd0  77 6f 20 68 6f 75 72 73  0d 42 69 74 20 34 20 2d  |wo hours.Bit 4 -|
00002de0  20 66 6f 75 72 20 68 6f  75 72 73 0d 42 69 74 20  | four hours.Bit |
00002df0  35 20 2d 20 65 69 67 68  74 20 68 6f 75 72 73 0d  |5 - eight hours.|
00002e00  0d 49 6e 20 42 72 69 74  61 69 6e 20 74 68 65 20  |.In Britain the |
00002e10  6f 66 66 73 65 74 20 69  73 20 6f 6e 6c 79 20 65  |offset is only e|
00002e20  76 65 72 20 7a 65 72 6f  20 6f 72 20 6f 6e 65 20  |ver zero or one |
00002e30  68 6f 75 72 2e 20 49 6e  20 77 69 6e 74 65 72 2c  |hour. In winter,|
00002e40  20 77 68 65 6e 20 47 4d  54 0d 69 73 20 75 73 65  | when GMT.is use|
00002e50  64 2c 20 74 68 69 73 20  62 79 74 65 20 68 61 73  |d, this byte has|
00002e60  20 61 20 76 61 6c 75 65  20 6f 66 20 26 38 31 20  | a value of &81 |
00002e70  28 69 65 2e 20 62 69 74  73 20 30 20 61 6e 64 20  |(ie. bits 0 and |
00002e80  37 20 73 65 74 29 20 6d  65 61 6e 69 6e 67 20 61  |7 set) meaning a|
00002e90  64 64 0d 6e 6f 74 68 69  6e 67 2e 20 49 6e 20 73  |dd.nothing. In s|
00002ea0  75 6d 6d 65 72 2c 20 77  68 65 6e 20 42 53 54 20  |ummer, when BST |
00002eb0  69 73 20 75 73 65 64 2c  20 74 68 69 73 20 76 61  |is used, this va|
00002ec0  6c 75 65 20 63 68 61 6e  67 65 73 20 74 6f 20 26  |lue changes to &|
00002ed0  38 35 20 28 62 69 74 73  20 30 2c 0d 32 2c 20 61  |85 (bits 0,.2, a|
00002ee0  6e 64 20 37 20 61 72 65  20 73 65 74 29 20 6d 65  |nd 7 are set) me|
00002ef0  61 6e 69 6e 67 20 61 64  64 20 6f 6e 65 20 68 6f  |aning add one ho|
00002f00  75 72 2e 20 4f 6e 65 20  77 6f 75 6c 64 20 65 78  |ur. One would ex|
00002f10  70 65 63 74 20 74 68 65  20 54 53 44 50 0d 62 72  |pect the TSDP.br|
00002f20  6f 61 64 63 61 73 74 20  69 6e 20 6f 74 68 65 72  |oadcast in other|
00002f30  20 63 6f 75 6e 74 72 69  65 73 20 74 6f 20 75 73  | countries to us|
00002f40  65 20 64 69 66 66 65 72  65 6e 74 20 6f 66 66 73  |e different offs|
00002f50  65 74 20 76 61 6c 75 65  73 20 61 63 63 6f 72 64  |et values accord|
00002f60  69 6e 67 20 74 6f 0d 74  68 65 20 74 69 6d 65 20  |ing to.the time |
00002f70  64 69 66 66 65 72 65 6e  63 65 20 61 70 70 6c 69  |difference appli|
00002f80  63 61 62 6c 65 20 69 6e  20 74 68 65 69 72 20 61  |cable in their a|
00002f90  72 65 61 2e 0d 0d 44 75  72 69 6e 67 20 74 68 65  |rea...During the|
00002fa0  20 73 75 6d 6d 65 72 20  6f 66 20 31 39 38 38 2c  | summer of 1988,|
00002fb0  20 74 68 65 20 49 42 41  20 6c 65 66 74 20 74 68  | the IBA left th|
00002fc0  65 20 74 69 6d 65 20 6f  66 66 73 65 74 20 62 79  |e time offset by|
00002fd0  74 65 20 61 74 20 26 38  31 20 28 69 65 2e 0d 6e  |te at &81 (ie..n|
00002fe0  6f 20 6f 66 66 73 65 74  29 20 61 6e 64 20 63 68  |o offset) and ch|
00002ff0  61 6e 67 65 64 20 74 68  65 20 63 6f 64 65 64 20  |anged the coded |
00003000  74 69 6d 65 20 74 6f 20  73 75 6d 6d 65 72 20 74  |time to summer t|
00003010  69 6d 65 2e 20 54 68 69  73 20 64 69 64 20 6e 6f  |ime. This did no|
00003020  74 20 63 6f 6e 66 6f 72  6d 0d 77 69 74 68 20 74  |t conform.with t|
00003030  68 65 20 72 65 71 75 69  72 65 6d 65 6e 74 20 74  |he requirement t|
00003040  6f 20 62 72 6f 61 64 63  61 73 74 20 55 54 43 20  |o broadcast UTC |
00003050  28 69 65 2e 20 47 4d 54  29 20 61 6e 64 20 69 74  |(ie. GMT) and it|
00003060  20 77 69 6c 6c 20 62 65  20 69 6e 74 65 72 65 73  | will be interes|
00003070  74 69 6e 67 0d 74 6f 20  73 65 65 20 77 68 61 74  |ting.to see what|
00003080  20 74 68 65 79 20 62 72  6f 61 64 63 61 73 74 20  | they broadcast |
00003090  69 6e 20 74 68 65 20 66  75 74 75 72 65 2e 0d 0d  |in the future...|
000030a0  54 68 65 20 74 65 6c 65  76 69 73 69 6f 6e 20 6c  |The television l|
000030b0  61 62 65 6c 20 69 6e 20  62 79 74 65 73 20 32 32  |abel in bytes 22|
000030c0  20 74 6f 20 32 35 20 28  62 75 66 66 3f 31 36 20  | to 25 (buff?16 |
000030d0  74 6f 20 62 75 66 66 3f  31 39 29 20 69 73 20 61  |to buff?19) is a|
000030e0  20 73 74 72 69 6e 67 20  6f 66 0d 37 20 62 69 74  | string of.7 bit|
000030f0  20 41 53 43 49 49 20 63  68 61 72 61 63 74 65 72  | ASCII character|
00003100  73 20 77 69 74 68 20 6f  64 64 20 70 61 72 69 74  |s with odd parit|
00003110  79 20 61 6e 64 20 63 6f  6e 74 61 69 6e 73 20 65  |y and contains e|
00003120  69 74 68 65 72 20 22 42  42 43 31 22 2c 20 22 42  |ither "BBC1", "B|
00003130  42 43 32 22 0d 6f 72 20  74 68 65 20 72 61 74 68  |BC2".or the rath|
00003140  65 72 20 75 6e 69 6d 61  67 69 6e 61 74 69 76 65  |er unimaginative|
00003150  20 22 50 52 4f 47 22 20  6f 6e 20 74 68 65 20 49  | "PROG" on the I|
00003160  54 56 20 6e 65 74 77 6f  72 6b 20 73 74 61 74 69  |TV network stati|
00003170  6f 6e 73 2e 20 54 68 65  73 65 20 34 0d 62 79 74  |ons. These 4.byt|
00003180  65 73 20 61 72 65 20 72  65 73 65 72 76 65 64 20  |es are reserved |
00003190  74 6f 20 69 64 65 6e 74  69 66 79 20 74 68 65 20  |to identify the |
000031a0  74 65 6c 65 76 69 73 69  6f 6e 20 70 72 6f 67 72  |television progr|
000031b0  61 6d 6d 65 20 63 75 72  72 65 6e 74 6c 79 20 6f  |amme currently o|
000031c0  6e 20 61 69 72 2c 0d 62  75 74 20 74 68 65 20 65  |n air,.but the e|
000031d0  78 61 63 74 20 66 6f 72  6d 61 74 20 68 61 73 20  |xact format has |
000031e0  79 65 74 20 74 6f 20 62  65 20 64 65 66 69 6e 65  |yet to be define|
000031f0  64 2e 0d 0d 54 68 65 20  73 74 61 74 75 73 20 64  |d...The status d|
00003200  69 73 70 6c 61 79 20 6d  65 73 73 61 67 65 20 69  |isplay message i|
00003210  6e 20 62 79 74 65 73 20  32 36 20 74 6f 20 34 35  |n bytes 26 to 45|
00003220  20 28 62 75 66 66 3f 32  30 20 74 6f 20 62 75 66  | (buff?20 to buf|
00003230  66 3f 33 39 29 20 69 73  0d 61 6e 6f 74 68 65 72  |f?39) is.another|
00003240  20 73 74 72 69 6e 67 20  6f 66 20 37 20 62 69 74  | string of 7 bit|
00003250  20 41 53 43 49 49 20 63  68 61 72 61 63 74 65 72  | ASCII character|
00003260  73 20 77 69 74 68 20 6f  64 64 20 70 61 72 69 74  |s with odd parit|
00003270  79 2c 20 61 6e 64 20 69  73 20 63 75 72 72 65 6e  |y, and is curren|
00003280  74 6c 79 0d 75 73 65 64  20 74 6f 20 69 64 65 6e  |tly.used to iden|
00003290  74 69 66 79 20 74 68 65  20 4e 65 74 77 6f 72 6b  |tify the Network|
000032a0  20 69 6e 20 61 20 68 75  6d 61 6e 20 72 65 61 64  | in a human read|
000032b0  61 62 6c 65 20 66 6f 72  6d 61 74 2e 20 49 74 20  |able format. It |
000032c0  69 73 20 64 69 73 70 6c  61 79 65 64 0d 62 79 20  |is displayed.by |
000032d0  74 68 65 20 54 46 53 20  61 66 74 65 72 20 69 73  |the TFS after is|
000032e0  73 75 69 6e 67 20 74 68  65 20 74 65 72 6d 69 6e  |suing the termin|
000032f0  61 6c 20 6d 6f 64 65 20  74 75 6e 65 20 63 6f 6d  |al mode tune com|
00003300  6d 61 6e 64 2c 20 53 68  69 66 74 2b 66 34 2c 20  |mand, Shift+f4, |
00003310  61 6e 64 20 62 79 0d 73  6f 6d 65 20 6e 65 77 20  |and by.some new |
00003320  74 65 6c 65 76 69 73 69  6f 6e 73 20 75 70 6f 6e  |televisions upon|
00003330  20 63 68 61 6e 67 69 6e  67 20 63 68 61 6e 6e 65  | changing channe|
00003340  6c 73 2e 20 54 68 69 73  20 6d 65 73 73 61 67 65  |ls. This message|
00003350  20 69 73 20 6e 6f 74 20  64 69 73 70 6c 61 79 65  | is not displaye|
00003360  64 0d 62 79 20 74 68 65  20 41 54 53 2c 20 62 75  |d.by the ATS, bu|
00003370  74 20 69 74 20 69 73 20  70 72 69 6e 74 65 64 20  |t it is printed |
00003380  62 79 20 74 68 65 20 70  72 6f 67 72 61 6d 20 54  |by the program T|
00003390  53 44 50 30 2e 0d 0d 43  68 61 69 6e 20 74 68 65  |SDP0...Chain the|
000033a0  20 70 72 6f 67 72 61 6d  20 54 53 44 50 30 20 61  | program TSDP0 a|
000033b0  6e 64 20 73 65 6c 65 63  74 20 6f 6e 65 20 6f 66  |nd select one of|
000033c0  20 74 68 65 20 66 6f 75  72 20 63 68 61 6e 6e 65  | the four channe|
000033d0  6c 73 20 77 68 65 6e 20  70 72 6f 6d 70 74 65 64  |ls when prompted|
000033e0  2e 0d 59 6f 75 20 63 61  6e 20 68 61 6c 74 20 74  |..You can halt t|
000033f0  68 65 20 70 72 6f 67 72  61 6d 20 61 74 20 61 6e  |he program at an|
00003400  79 20 74 69 6d 65 20 62  79 20 70 72 65 73 73 69  |y time by pressi|
00003410  6e 67 20 74 68 65 20 45  73 63 61 70 65 20 6b 65  |ng the Escape ke|
00003420  79 2e 0d 0d 0d 20 20 20  31 30 20 52 45 4d 3e 20  |y....   10 REM> |
00003430  54 53 44 50 30 0d 20 20  20 32 30 20 4d 4f 44 45  |TSDP0.   20 MODE|
00003440  37 0d 20 20 20 33 30 20  56 44 55 32 33 2c 31 2c  |7.   30 VDU23,1,|
00003450  30 3b 30 3b 30 3b 30 3b  0d 20 20 20 34 30 20 44  |0;0;0;0;.   40 D|
00003460  49 4d 20 6d 63 6f 64 65  20 26 35 30 30 20 3a 52  |IM mcode &500 :R|
00003470  45 4d 3a 20 73 70 61 63  65 20 66 6f 72 20 6d 61  |EM: space for ma|
00003480  63 68 69 6e 65 20 63 6f  64 65 0d 20 20 20 35 30  |chine code.   50|
00003490  20 44 49 4d 20 62 75 66  66 20 34 30 20 3a 52 45  | DIM buff 40 :RE|
000034a0  4d 3a 20 54 53 44 50 20  62 75 66 66 65 72 0d 20  |M: TSDP buffer. |
000034b0  20 20 36 30 20 50 52 4f  43 6d 63 6f 64 65 20 3a  |  60 PROCmcode :|
000034c0  52 45 4d 3a 20 61 73 73  65 6d 62 6c 65 20 6d 61  |REM: assemble ma|
000034d0  63 68 69 6e 65 20 63 6f  64 65 0d 20 20 20 37 30  |chine code.   70|
000034e0  20 74 74 78 24 3d 43 48  52 24 28 31 34 31 29 2b  | ttx$=CHR$(141)+|
000034f0  43 48 52 24 28 31 33 32  29 2b 43 48 52 24 28 31  |CHR$(132)+CHR$(1|
00003500  35 37 29 2b 43 48 52 24  28 31 33 31 29 0d 20 20  |57)+CHR$(131).  |
00003510  20 20 20 20 2b 22 54 65  6c 65 76 69 73 69 6f 6e  |    +"Television|
00003520  20 53 65 72 76 69 63 65  20 44 61 74 61 20 50 61  | Service Data Pa|
00003530  63 6b 65 74 20 30 20 20  22 2b 43 48 52 24 28 31  |cket 0  "+CHR$(1|
00003540  35 36 29 0d 20 20 20 38  30 20 50 52 49 4e 54 54  |56).   80 PRINTT|
00003550  41 42 28 30 2c 31 29 74  74 78 24 0d 20 20 20 39  |AB(0,1)ttx$.   9|
00003560  30 20 50 52 49 4e 54 54  41 42 28 30 2c 32 29 74  |0 PRINTTAB(0,2)t|
00003570  74 78 24 0d 20 20 31 30  30 20 49 4e 50 55 54 54  |tx$.  100 INPUTT|
00003580  41 42 28 31 30 2c 35 29  22 54 56 20 63 68 61 6e  |AB(10,5)"TV chan|
00003590  6e 65 6c 20 28 31 2d 34  29 20 3d 20 22 61 6e 73  |nel (1-4) = "ans|
000035a0  77 65 72 24 0d 20 20 31  31 30 20 63 68 61 6e 6e  |wer$.  110 chann|
000035b0  65 6c 3f 30 3d 45 56 41  4c 28 22 26 22 2b 4c 45  |el?0=EVAL("&"+LE|
000035c0  46 54 24 28 61 6e 73 77  65 72 24 2c 31 29 29 2b  |FT$(answer$,1))+|
000035d0  26 31 42 0d 20 20 31 32  30 20 49 46 20 63 68 61  |&1B.  120 IF cha|
000035e0  6e 6e 65 6c 3f 30 20 3c  20 26 31 43 20 54 48 45  |nnel?0 < &1C THE|
000035f0  4e 20 63 68 61 6e 6e 65  6c 3f 30 20 3d 20 26 31  |N channel?0 = &1|
00003600  43 0d 20 20 31 33 30 20  49 46 20 63 68 61 6e 6e  |C.  130 IF chann|
00003610  65 6c 3f 30 20 3e 20 26  31 46 20 54 48 45 4e 20  |el?0 > &1F THEN |
00003620  63 68 61 6e 6e 65 6c 3f  30 20 3d 20 26 31 46 0d  |channel?0 = &1F.|
00003630  20 20 31 34 30 20 50 52  49 4e 54 54 41 42 28 35  |  140 PRINTTAB(5|
00003640  2c 39 29 22 54 53 44 50  20 74 79 70 65 20 3d 22  |,9)"TSDP type ="|
00003650  0d 20 20 31 35 30 20 50  52 49 4e 54 54 41 42 28  |.  150 PRINTTAB(|
00003660  35 2c 31 30 29 22 49 6e  69 74 69 61 6c 20 70 61  |5,10)"Initial pa|
00003670  67 65 20 3d 22 0d 20 20  31 36 30 20 50 52 49 4e  |ge =".  160 PRIN|
00003680  54 54 41 42 28 35 2c 31  31 29 22 43 68 61 6e 6e  |TTAB(5,11)"Chann|
00003690  65 6c 20 63 6f 64 65 20  3d 20 26 22 0d 20 20 31  |el code = &".  1|
000036a0  37 30 20 50 52 49 4e 54  54 41 42 28 35 2c 31 32  |70 PRINTTAB(5,12|
000036b0  29 22 50 72 6f 67 72 61  6d 6d 65 20 3d 22 0d 20  |)"Programme =". |
000036c0  20 31 38 30 20 50 52 49  4e 54 54 41 42 28 35 2c  | 180 PRINTTAB(5,|
000036d0  31 33 29 22 4d 6f 64 2e  20 4a 75 6c 69 61 6e 20  |13)"Mod. Julian |
000036e0  64 61 74 65 20 3d 22 0d  20 20 31 39 30 20 50 52  |date =".  190 PR|
000036f0  49 4e 54 54 41 42 28 35  2c 31 34 29 22 44 61 79  |INTTAB(5,14)"Day|
00003700  2f 4d 6f 6e 74 68 2f 59  65 61 72 20 3d 22 0d 20  |/Month/Year =". |
00003710  20 32 30 30 20 50 52 49  4e 54 54 41 42 28 35 2c  | 200 PRINTTAB(5,|
00003720  31 35 29 22 54 69 6d 65  20 3d 22 0d 20 20 32 31  |15)"Time =".  21|
00003730  30 20 50 52 49 4e 54 54  41 42 28 35 2c 31 36 29  |0 PRINTTAB(5,16)|
00003740  22 47 4d 54 22 0d 20 20  32 32 30 20 50 52 49 4e  |"GMT".  220 PRIN|
00003750  54 54 41 42 28 35 2c 31  37 29 22 4d 65 73 73 61  |TTAB(5,17)"Messa|
00003760  67 65 20 3d 22 0d 20 20  32 33 30 20 43 41 4c 4c  |ge =".  230 CALL|
00003770  20 6d 63 6f 64 65 20 3a  52 45 4d 3a 20 65 6e 61  | mcode :REM: ena|
00003780  62 6c 65 20 54 54 58 20  69 6e 74 65 72 72 75 70  |ble TTX interrup|
00003790  74 73 0d 20 20 32 34 30  20 4f 4e 45 52 52 4f 52  |ts.  240 ONERROR|
000037a0  20 47 4f 54 4f 20 32 38  30 0d 20 20 32 35 30 20  | GOTO 280.  250 |
000037b0  52 45 50 45 41 54 0d 20  20 32 36 30 20 49 46 20  |REPEAT.  260 IF |
000037c0  67 72 61 62 66 6c 61 67  3f 30 3d 30 20 50 52 4f  |grabflag?0=0 PRO|
000037d0  43 64 69 73 70 6c 61 79  0d 20 20 32 37 30 20 55  |Cdisplay.  270 U|
000037e0  4e 54 49 4c 20 46 41 4c  53 45 0d 20 20 32 38 30  |NTIL FALSE.  280|
000037f0  20 43 41 4c 4c 20 6d 63  6f 64 65 20 3a 52 45 4d  | CALL mcode :REM|
00003800  3a 20 64 69 73 61 62 6c  65 20 54 54 58 20 69 6e  |: disable TTX in|
00003810  74 65 72 72 75 70 74 73  0d 20 20 32 39 30 20 56  |terrupts.  290 V|
00003820  44 55 33 31 2c 30 2c 32  31 2c 32 33 2c 31 2c 31  |DU31,0,21,23,1,1|
00003830  3b 30 3b 30 3b 30 3b 0d  20 20 33 30 30 20 45 4e  |;0;0;0;.  300 EN|
00003840  44 0d 20 20 33 31 30 20  44 45 46 50 52 4f 43 64  |D.  310 DEFPROCd|
00003850  69 73 70 6c 61 79 0d 20  20 33 32 30 20 50 52 49  |isplay.  320 PRI|
00003860  4e 54 54 41 42 28 31 37  2c 39 29 3b 62 75 66 66  |NTTAB(17,9);buff|
00003870  3f 30 0d 20 20 33 33 30  20 62 30 3d 28 28 62 75  |?0.  330 b0=((bu|
00003880  66 66 3f 34 29 41 4e 44  38 29 3c 3e 30 3a 52 45  |ff?4)AND8)<>0:RE|
00003890  4d 3a 20 62 69 74 20 30  20 6f 66 20 6d 61 67 61  |M: bit 0 of maga|
000038a0  7a 69 6e 65 20 6e 75 6d  62 65 72 0d 20 20 33 34  |zine number.  34|
000038b0  30 20 62 31 3d 28 28 62  75 66 66 3f 36 29 41 4e  |0 b1=((buff?6)AN|
000038c0  44 34 29 3c 3e 30 3a 52  45 4d 3a 20 62 69 74 20  |D4)<>0:REM: bit |
000038d0  31 20 6f 66 20 6d 61 67  61 7a 69 6e 65 20 6e 75  |1 of magazine nu|
000038e0  6d 62 65 72 0d 20 20 33  35 30 20 62 32 3d 28 28  |mber.  350 b2=((|
000038f0  62 75 66 66 3f 36 29 41  4e 44 38 29 3c 3e 30 3a  |buff?6)AND8)<>0:|
00003900  52 45 4d 3a 20 62 69 74  20 32 20 6f 66 20 6d 61  |REM: bit 2 of ma|
00003910  67 61 7a 69 6e 65 20 6e  75 6d 62 65 72 0d 20 20  |gazine number.  |
00003920  33 36 30 20 69 6e 69 74  3d 30 3a 52 45 4d 3a 20  |360 init=0:REM: |
00003930  69 6e 69 74 69 61 6c 20  6d 61 67 61 7a 69 6e 65  |initial magazine|
00003940  20 6e 75 6d 62 65 72 0d  20 20 33 37 30 20 49 46  | number.  370 IF|
00003950  20 62 30 20 69 6e 69 74  3d 31 0d 20 20 33 38 30  | b0 init=1.  380|
00003960  20 49 46 20 62 31 20 69  6e 69 74 3d 69 6e 69 74  | IF b1 init=init|
00003970  2b 32 0d 20 20 33 39 30  20 49 46 20 62 32 20 69  |+2.  390 IF b2 i|
00003980  6e 69 74 3d 69 6e 69 74  2b 34 0d 20 20 34 30 30  |nit=init+4.  400|
00003990  20 50 52 49 4e 54 54 41  42 28 32 30 2c 31 30 29  | PRINTTAB(20,10)|
000039a0  3b 7e 69 6e 69 74 3b 3a  52 45 4d 3a 20 69 6e 69  |;~init;:REM: ini|
000039b0  74 69 61 6c 20 6d 61 67  61 7a 69 6e 65 0d 20 20  |tial magazine.  |
000039c0  34 31 30 20 50 52 49 4e  54 3b 7e 62 75 66 66 3f  |410 PRINT;~buff?|
000039d0  32 3b 7e 62 75 66 66 3f  31 3b 3a 52 45 4d 3a 20  |2;~buff?1;:REM: |
000039e0  69 6e 69 74 69 61 6c 20  70 61 67 65 0d 20 20 34  |initial page.  4|
000039f0  32 30 20 50 52 49 4e 54  3b 22 20 22 3b 7e 28 28  |20 PRINT;" ";~((|
00003a00  62 75 66 66 3f 36 29 41  4e 44 33 29 3b 7e 62 75  |buff?6)AND3);~bu|
00003a10  66 66 3f 35 3b 7e 28 28  62 75 66 66 3f 34 29 41  |ff?5;~((buff?4)A|
00003a20  4e 44 37 29 3b 7e 62 75  66 66 3f 33 0d 20 20 20  |ND7);~buff?3.   |
00003a30  20 20 20 3a 52 45 4d 3a  20 69 6e 69 74 69 61 6c  |   :REM: initial|
00003a40  20 73 75 62 2d 70 61 67  65 0d 20 20 34 33 30 20  | sub-page.  430 |
00003a50  56 44 55 33 31 2c 32 31  2c 31 31 3a 50 52 4f 43  |VDU31,21,11:PROC|
00003a60  68 65 78 28 62 75 66 66  3f 37 29 3a 52 45 4d 3a  |hex(buff?7):REM:|
00003a70  20 63 68 61 6e 6e 65 6c  20 68 69 67 68 20 62 79  | channel high by|
00003a80  74 65 0d 20 20 34 34 30  20 50 52 4f 43 68 65 78  |te.  440 PROChex|
00003a90  28 62 75 66 66 3f 38 29  3a 52 45 4d 3a 20 63 68  |(buff?8):REM: ch|
00003aa0  61 6e 6e 65 6c 20 6c 6f  77 20 62 79 74 65 0d 20  |annel low byte. |
00003ab0  20 34 35 30 20 56 44 55  33 31 2c 31 37 2c 31 32  | 450 VDU31,17,12|
00003ac0  20 3a 52 45 4d 3a 20 70  72 69 6e 74 20 70 72 6f  | :REM: print pro|
00003ad0  67 72 61 6d 6d 65 0d 20  20 34 36 30 20 46 4f 52  |gramme.  460 FOR|
00003ae0  20 62 79 74 65 3d 31 36  20 54 4f 20 31 39 0d 20  | byte=16 TO 19. |
00003af0  20 34 37 30 20 56 44 55  20 28 62 75 66 66 3f 62  | 470 VDU (buff?b|
00003b00  79 74 65 20 4f 52 20 26  38 30 29 20 3a 52 45 4d  |yte OR &80) :REM|
00003b10  3a 20 73 65 74 20 62 69  74 20 37 20 66 6f 72 20  |: set bit 7 for |
00003b20  70 72 69 6e 74 69 6e 67  0d 20 20 34 38 30 20 4e  |printing.  480 N|
00003b30  45 58 54 0d 20 20 34 39  30 20 56 44 55 33 31 2c  |EXT.  490 VDU31,|
00003b40  32 34 2c 31 33 20 3a 52  45 4d 3a 20 6d 6f 64 69  |24,13 :REM: modi|
00003b50  66 69 65 64 20 4a 75 6c  69 61 6e 20 64 61 74 65  |fied Julian date|
00003b60  0d 20 20 35 30 30 20 50  52 4f 43 68 65 78 28 28  |.  500 PROChex((|
00003b70  28 62 75 66 66 3f 31 30  29 2d 26 30 31 29 41 4e  |(buff?10)-&01)AN|
00003b80  44 31 35 29 3a 52 45 4d  3a 20 31 30 30 30 30 27  |D15):REM: 10000'|
00003b90  73 0d 20 20 35 31 30 20  66 75 6c 6c 24 3d 70 61  |s.  510 full$=pa|
00003ba0  72 74 24 0d 20 20 35 32  30 20 50 52 4f 43 68 65  |rt$.  520 PROChe|
00003bb0  78 28 28 62 75 66 66 3f  31 31 29 2d 26 31 31 29  |x((buff?11)-&11)|
00003bc0  3a 52 45 4d 3a 20 31 30  30 30 27 73 20 61 6e 64  |:REM: 1000's and|
00003bd0  20 31 30 30 27 73 0d 20  20 35 33 30 20 66 75 6c  | 100's.  530 ful|
00003be0  6c 24 3d 66 75 6c 6c 24  2b 70 61 72 74 24 0d 20  |l$=full$+part$. |
00003bf0  20 35 34 30 20 50 52 4f  43 68 65 78 28 28 62 75  | 540 PROChex((bu|
00003c00  66 66 3f 31 32 29 2d 26  31 31 29 3a 52 45 4d 3a  |ff?12)-&11):REM:|
00003c10  20 31 30 27 73 20 61 6e  64 20 31 27 73 0d 20 20  | 10's and 1's.  |
00003c20  35 35 30 20 66 75 6c 6c  24 3d 66 75 6c 6c 24 2b  |550 full$=full$+|
00003c30  70 61 72 74 24 0d 20 20  35 36 30 20 4a 25 3d 56  |part$.  560 J%=V|
00003c40  41 4c 28 66 75 6c 6c 24  29 0d 20 20 35 37 30 20  |AL(full$).  570 |
00003c50  59 25 3d 28 31 30 30 2a  28 4a 25 2d 31 35 30 37  |Y%=(100*(J%-1507|
00003c60  38 2e 32 29 29 44 49 56  33 36 35 32 35 0d 20 20  |8.2))DIV36525.  |
00003c70  35 38 30 20 4d 25 3d 49  4e 54 28 28 4a 25 2d 31  |580 M%=INT((J%-1|
00003c80  34 39 35 36 2e 31 2d 49  4e 54 28 33 36 35 2e 32  |4956.1-INT(365.2|
00003c90  35 2a 59 25 29 29 2f 33  30 2e 36 30 30 31 29 0d  |5*Y%))/30.6001).|
00003ca0  20 20 35 39 30 20 44 25  3d 4a 25 2d 31 34 39 35  |  590 D%=J%-1495|
00003cb0  36 2d 49 4e 54 28 33 36  35 2e 32 35 2a 59 25 29  |6-INT(365.25*Y%)|
00003cc0  2d 49 4e 54 28 33 30 2e  36 2a 4d 25 29 20 3a 52  |-INT(30.6*M%) :R|
00003cd0  45 4d 3a 20 64 61 79 0d  20 20 36 30 30 20 49 46  |EM: day.  600 IF|
00003ce0  20 4d 25 3c 31 34 20 54  48 45 4e 20 4b 25 3d 30  | M%<14 THEN K%=0|
00003cf0  20 45 4c 53 45 20 4b 25  3d 31 0d 20 20 36 31 30  | ELSE K%=1.  610|
00003d00  20 4d 25 3d 4d 25 2d 31  2d 31 32 2a 4b 25 20 3a  | M%=M%-1-12*K% :|
00003d10  52 45 4d 3a 20 6d 6f 6e  74 68 0d 20 20 36 32 30  |REM: month.  620|
00003d20  20 59 25 3d 59 25 2b 4b  25 2b 31 39 30 30 20 3a  | Y%=Y%+K%+1900 :|
00003d30  52 45 4d 3a 20 79 65 61  72 0d 20 20 36 33 30 20  |REM: year.  630 |
00003d40  50 52 49 4e 54 54 41 42  28 32 32 2c 31 34 29 3b  |PRINTTAB(22,14);|
00003d50  44 25 3b 22 2f 22 3b 4d  25 3b 22 2f 22 3b 59 25  |D%;"/";M%;"/";Y%|
00003d60  20 3a 52 45 4d 3a 20 64  61 79 2f 6d 6f 6e 74 68  | :REM: day/month|
00003d70  2f 79 65 61 72 0d 20 20  36 34 30 20 56 44 55 33  |/year.  640 VDU3|
00003d80  31 2c 31 32 2c 31 35 20  3a 52 45 4d 3a 20 70 72  |1,12,15 :REM: pr|
00003d90  69 6e 74 20 74 69 6d 65  0d 20 20 36 35 30 20 50  |int time.  650 P|
00003da0  52 4f 43 68 65 78 28 28  62 75 66 66 3f 31 33 29  |ROChex((buff?13)|
00003db0  2d 26 31 31 29 3a 52 45  4d 3a 20 68 6f 75 72 73  |-&11):REM: hours|
00003dc0  0d 20 20 36 36 30 20 50  52 49 4e 54 3b 22 3a 22  |.  660 PRINT;":"|
00003dd0  3b 0d 20 20 36 37 30 20  50 52 4f 43 68 65 78 28  |;.  670 PROChex(|
00003de0  28 62 75 66 66 3f 31 34  29 2d 26 31 31 29 3a 52  |(buff?14)-&11):R|
00003df0  45 4d 3a 20 6d 69 6e 75  74 65 73 0d 20 20 36 38  |EM: minutes.  68|
00003e00  30 20 50 52 49 4e 54 3b  22 3a 22 3b 0d 20 20 36  |0 PRINT;":";.  6|
00003e10  39 30 20 50 52 4f 43 68  65 78 28 28 62 75 66 66  |90 PROChex((buff|
00003e20  3f 31 35 29 2d 26 31 31  29 3a 52 45 4d 3a 20 73  |?15)-&11):REM: s|
00003e30  65 63 6f 6e 64 73 0d 20  20 37 30 30 20 49 46 20  |econds.  700 IF |
00003e40  62 75 66 66 3f 39 20 3d  20 26 38 35 20 50 52 49  |buff?9 = &85 PRI|
00003e50  4e 54 54 41 42 28 35 2c  31 36 29 22 41 64 64 20  |NTTAB(5,16)"Add |
00003e60  31 20 68 72 20 66 6f 72  20 42 53 54 22 20 3a 52  |1 hr for BST" :R|
00003e70  45 4d 3a 20 26 38 31 3d  47 4d 54 0d 20 20 37 31  |EM: &81=GMT.  71|
00003e80  30 20 56 44 55 33 31 2c  31 35 2c 31 37 20 3a 52  |0 VDU31,15,17 :R|
00003e90  45 4d 3a 20 70 72 69 6e  74 20 6d 65 73 73 61 67  |EM: print messag|
00003ea0  65 0d 20 20 37 32 30 20  46 4f 52 20 62 79 74 65  |e.  720 FOR byte|
00003eb0  3d 32 30 20 54 4f 20 33  39 0d 20 20 37 33 30 20  |=20 TO 39.  730 |
00003ec0  56 44 55 20 28 62 75 66  66 3f 62 79 74 65 20 4f  |VDU (buff?byte O|
00003ed0  52 20 26 38 30 29 20 3a  52 45 4d 3a 20 73 65 74  |R &80) :REM: set|
00003ee0  20 62 69 74 20 37 20 66  6f 72 20 70 72 69 6e 74  | bit 7 for print|
00003ef0  69 6e 67 0d 20 20 37 34  30 20 4e 45 58 54 0d 20  |ing.  740 NEXT. |
00003f00  20 37 35 30 20 56 44 55  37 0d 20 20 37 36 30 20  | 750 VDU7.  760 |
00003f10  67 72 61 62 66 6c 61 67  3f 30 3d 32 20 3a 52 45  |grabflag?0=2 :RE|
00003f20  4d 3a 20 67 72 61 62 66  6c 61 67 20 3d 20 73 65  |M: grabflag = se|
00003f30  61 72 63 68 69 6e 67 0d  20 20 37 37 30 20 45 4e  |arching.  770 EN|
00003f40  44 50 52 4f 43 0d 20 20  37 38 30 20 44 45 46 50  |DPROC.  780 DEFP|
00003f50  52 4f 43 68 65 78 28 4e  25 29 3a 52 45 4d 3a 20  |ROChex(N%):REM: |
00003f60  70 72 69 6e 74 20 62 6f  74 68 20 6e 79 62 62 6c  |print both nybbl|
00003f70  65 73 20 6f 66 20 61 20  68 65 78 2e 20 6e 75 6d  |es of a hex. num|
00003f80  62 65 72 0d 20 20 37 39  30 20 4c 25 3d 4e 25 20  |ber.  790 L%=N% |
00003f90  4d 4f 44 20 31 36 0d 20  20 38 30 30 20 48 25 3d  |MOD 16.  800 H%=|
00003fa0  4e 25 20 44 49 56 20 31  36 0d 20 20 38 31 30 20  |N% DIV 16.  810 |
00003fb0  50 52 49 4e 54 3b 7e 48  25 3b 7e 4c 25 3b 0d 20  |PRINT;~H%;~L%;. |
00003fc0  20 38 32 30 20 70 61 72  74 24 3d 53 54 52 24 28  | 820 part$=STR$(|
00003fd0  48 25 29 2b 53 54 52 24  28 4c 25 29 0d 20 20 38  |H%)+STR$(L%).  8|
00003fe0  33 30 20 45 4e 44 50 52  4f 43 0d 20 20 38 34 30  |30 ENDPROC.  840|
00003ff0  20 44 45 46 50 52 4f 43  6d 63 6f 64 65 0d 20 20  | DEFPROCmcode.  |
00004000  38 35 30 20 70 61 63 6b  65 74 3d 26 37 30 20 3a  |850 packet=&70 :|
00004010  52 45 4d 3a 20 72 6f 77  20 6e 75 6d 62 65 72 20  |REM: row number |
00004020  6f 66 20 63 75 72 72 65  6e 74 20 70 61 63 6b 65  |of current packe|
00004030  74 0d 20 20 38 36 30 20  6d 61 67 61 7a 69 6e 65  |t.  860 magazine|
00004040  3d 26 37 31 20 3a 52 45  4d 3a 20 6d 61 67 61 7a  |=&71 :REM: magaz|
00004050  69 6e 65 20 6e 75 6d 62  65 72 20 6f 66 20 63 75  |ine number of cu|
00004060  72 72 65 6e 74 20 70 61  67 65 0d 20 20 38 37 30  |rrent page.  870|
00004070  20 67 72 61 62 66 6c 61  67 3d 26 37 32 20 3a 52  | grabflag=&72 :R|
00004080  45 4d 3a 20 70 61 67 65  20 67 72 61 62 62 65 72  |EM: page grabber|
00004090  20 66 6c 61 67 0d 20 20  38 38 30 20 63 68 61 6e  | flag.  880 chan|
000040a0  6e 65 6c 3d 26 37 33 20  3a 52 45 4d 3a 20 54 56  |nel=&73 :REM: TV|
000040b0  20 63 68 61 6e 6e 65 6c  0d 20 20 38 39 30 20 73  | channel.  890 s|
000040c0  61 76 65 72 65 67 3d 26  46 43 20 3a 52 45 4d 3a  |avereg=&FC :REM:|
000040d0  20 69 6e 74 65 72 72 75  70 74 20 61 63 63 75 6d  | interrupt accum|
000040e0  75 6c 61 74 6f 72 20 73  61 76 65 20 72 65 67 69  |ulator save regi|
000040f0  73 74 65 72 0d 20 20 39  30 30 20 69 72 71 32 76  |ster.  900 irq2v|
00004100  3d 26 32 30 36 20 3a 52  45 4d 3a 20 69 72 71 32  |=&206 :REM: irq2|
00004110  20 76 65 63 74 6f 72 0d  20 20 39 31 30 20 74 74  | vector.  910 tt|
00004120  78 63 6f 6e 74 72 6f 6c  3d 26 46 43 31 30 20 3a  |xcontrol=&FC10 :|
00004130  52 45 4d 3a 20 54 54 58  20 63 6f 6e 74 72 6f 6c  |REM: TTX control|
00004140  20 72 65 67 69 73 74 65  72 2c 20 77 72 69 74 65  | register, write|
00004150  20 6f 6e 6c 79 0d 20 20  39 32 30 20 74 74 78 73  | only.  920 ttxs|
00004160  74 61 74 75 73 3d 26 46  43 31 30 20 3a 52 45 4d  |tatus=&FC10 :REM|
00004170  3a 20 54 54 58 20 73 74  61 74 75 73 20 72 65 67  |: TTX status reg|
00004180  69 73 74 65 72 2c 20 72  65 61 64 20 6f 6e 6c 79  |ister, read only|
00004190  0d 20 20 39 33 30 20 72  6f 77 72 65 67 3d 26 46  |.  930 rowreg=&F|
000041a0  43 31 31 20 3a 52 45 4d  3a 20 54 54 58 20 72 6f  |C11 :REM: TTX ro|
000041b0  77 20 72 65 67 69 73 74  65 72 2c 20 77 72 69 74  |w register, writ|
000041c0  65 20 6f 6e 6c 79 0d 20  20 39 34 30 20 64 61 74  |e only.  940 dat|
000041d0  61 72 65 67 3d 26 46 43  31 32 20 3a 52 45 4d 3a  |areg=&FC12 :REM:|
000041e0  20 54 54 58 20 64 61 74  61 20 72 65 67 69 73 74  | TTX data regist|
000041f0  65 72 2c 20 72 65 61 64  20 26 20 77 72 69 74 65  |er, read & write|
00004200  0d 20 20 39 35 30 20 73  74 61 74 63 6c 72 3d 26  |.  950 statclr=&|
00004210  46 43 31 33 20 3a 52 45  4d 3a 20 54 54 58 20 63  |FC13 :REM: TTX c|
00004220  6c 65 61 72 20 73 74 61  74 75 73 20 72 65 67 69  |lear status regi|
00004230  73 74 65 72 2c 20 72 65  61 64 20 26 20 77 72 69  |ster, read & wri|
00004240  74 65 0d 20 20 39 36 30  20 46 4f 52 20 70 61 73  |te.  960 FOR pas|
00004250  73 3d 30 20 54 4f 20 32  20 53 54 45 50 20 32 0d  |s=0 TO 2 STEP 2.|
00004260  20 20 39 37 30 20 50 25  3d 6d 63 6f 64 65 0d 20  |  970 P%=mcode. |
00004270  20 39 38 30 20 5b 20 20  20 20 20 20 20 4f 50 54  | 980 [       OPT|
00004280  20 70 61 73 73 0d 20 20  39 39 30 20 20 20 20 20  | pass.  990     |
00004290  20 20 20 20 4c 44 41 20  23 26 30 32 0d 20 31 30  |    LDA #&02. 10|
000042a0  30 30 20 20 20 20 20 20  20 20 20 53 54 41 20 67  |00         STA g|
000042b0  72 61 62 66 6c 61 67 20  20 5c 20 67 72 61 62 66  |rabflag  \ grabf|
000042c0  6c 61 67 20 3d 20 73 65  61 72 63 68 69 6e 67 0d  |lag = searching.|
000042d0  20 31 30 31 30 20 20 20  20 20 20 20 20 20 4c 44  | 1010         LD|
000042e0  58 20 69 72 71 32 76 20  20 20 20 20 5c 20 6c 6f  |X irq2v     \ lo|
000042f0  61 64 20 73 65 63 6f 6e  64 61 72 79 20 69 6e 74  |ad secondary int|
00004300  65 72 72 75 70 74 20 76  65 63 74 6f 72 0d 20 31  |errupt vector. 1|
00004310  30 32 30 20 20 20 20 20  20 20 20 20 4c 44 59 20  |020         LDY |
00004320  69 72 71 32 76 2b 31 0d  20 31 30 33 30 20 20 20  |irq2v+1. 1030   |
00004330  20 20 20 20 20 20 43 50  59 20 23 69 6e 74 65 72  |      CPY #inter|
00004340  72 75 70 74 20 44 49 56  20 32 35 36 0d 20 31 30  |rupt DIV 256. 10|
00004350  34 30 20 20 20 20 20 20  20 20 20 42 45 51 20 64  |40         BEQ d|
00004360  69 73 61 62 6c 65 0d 20  31 30 35 30 20 20 20 20  |isable. 1050    |
00004370  20 20 20 20 20 53 54 58  20 6f 6c 64 69 72 71 32  |     STX oldirq2|
00004380  76 20 20 5c 20 73 61 76  65 20 73 65 63 6f 6e 64  |v  \ save second|
00004390  61 72 79 20 69 6e 74 65  72 72 75 70 74 20 76 65  |ary interrupt ve|
000043a0  63 74 6f 72 0d 20 31 30  36 30 20 20 20 20 20 20  |ctor. 1060      |
000043b0  20 20 20 53 54 59 20 6f  6c 64 69 72 71 32 76 2b  |   STY oldirq2v+|
000043c0  31 0d 20 31 30 37 30 20  20 20 20 20 20 20 20 20  |1. 1070         |
000043d0  4c 44 58 20 23 69 6e 74  65 72 72 75 70 74 20 4d  |LDX #interrupt M|
000043e0  4f 44 20 32 35 36 20 5c  20 69 6e 73 74 61 6c 6c  |OD 256 \ install|
000043f0  20 6e 65 77 20 69 6e 74  65 72 72 75 70 74 20 72  | new interrupt r|
00004400  6f 75 74 69 6e 65 0d 20  31 30 38 30 20 20 20 20  |outine. 1080    |
00004410  20 20 20 20 20 4c 44 59  20 23 69 6e 74 65 72 72  |     LDY #interr|
00004420  75 70 74 20 44 49 56 20  32 35 36 0d 20 31 30 39  |upt DIV 256. 109|
00004430  30 20 20 20 20 20 20 20  20 20 53 45 49 20 20 20  |0         SEI   |
00004440  20 20 20 20 20 20 20 20  5c 20 64 69 73 61 62 6c  |        \ disabl|
00004450  65 20 69 6e 74 65 72 72  75 70 74 73 20 77 68 65  |e interrupts whe|
00004460  6e 20 61 6c 74 65 72 69  6e 67 20 76 65 63 74 6f  |n altering vecto|
00004470  72 0d 20 31 31 30 30 20  20 20 20 20 20 20 20 20  |r. 1100         |
00004480  53 54 58 20 69 72 71 32  76 0d 20 31 31 31 30 20  |STX irq2v. 1110 |
00004490  20 20 20 20 20 20 20 20  53 54 59 20 69 72 71 32  |        STY irq2|
000044a0  76 2b 31 0d 20 31 31 32  30 20 20 20 20 20 20 20  |v+1. 1120       |
000044b0  20 20 43 4c 49 20 20 20  20 20 20 20 20 20 20 20  |  CLI           |
000044c0  5c 20 72 65 2d 65 6e 61  62 6c 65 20 69 6e 74 65  |\ re-enable inte|
000044d0  72 72 75 70 74 73 0d 20  31 31 33 30 20 20 20 20  |rrupts. 1130    |
000044e0  20 20 20 20 20 4c 44 41  20 63 68 61 6e 6e 65 6c  |     LDA channel|
000044f0  20 20 20 5c 20 6c 6f 61  64 20 28 63 68 61 6e 6e  |   \ load (chann|
00004500  65 6c 20 6e 75 6d 62 65  72 20 2b 20 23 26 31 43  |el number + #&1C|
00004510  29 0d 20 31 31 34 30 20  20 20 20 20 20 20 20 20  |). 1140         |
00004520  53 54 41 20 74 74 78 63  6f 6e 74 72 6f 6c 20 5c  |STA ttxcontrol \|
00004530  20 65 6e 61 62 6c 65 20  54 54 58 0d 20 31 31 35  | enable TTX. 115|
00004540  30 20 20 20 20 20 20 20  20 20 52 54 53 20 20 20  |0         RTS   |
00004550  20 20 20 20 20 20 20 20  5c 20 72 65 74 75 72 6e  |        \ return|
00004560  20 74 6f 20 42 41 53 49  43 0d 20 31 31 36 30 20  | to BASIC. 1160 |
00004570  2e 64 69 73 61 62 6c 65  0d 20 31 31 37 30 20 20  |.disable. 1170  |
00004580  20 20 20 20 20 20 20 4c  44 41 20 23 26 30 30 0d  |       LDA #&00.|
00004590  20 31 31 38 30 20 20 20  20 20 20 20 20 20 53 54  | 1180         ST|
000045a0  41 20 74 74 78 63 6f 6e  74 72 6f 6c 20 5c 20 64  |A ttxcontrol \ d|
000045b0  69 73 61 62 6c 65 20 54  54 58 0d 20 31 31 39 30  |isable TTX. 1190|
000045c0  20 20 20 20 20 20 20 20  20 4c 44 58 20 6f 6c 64  |         LDX old|
000045d0  69 72 71 32 76 20 20 5c  20 6c 6f 61 64 20 6f 72  |irq2v  \ load or|
000045e0  69 67 69 6e 61 6c 20 76  65 63 74 6f 72 0d 20 31  |iginal vector. 1|
000045f0  32 30 30 20 20 20 20 20  20 20 20 20 4c 44 59 20  |200         LDY |
00004600  6f 6c 64 69 72 71 32 76  2b 31 0d 20 31 32 31 30  |oldirq2v+1. 1210|
00004610  20 20 20 20 20 20 20 20  20 53 45 49 20 20 20 20  |         SEI    |
00004620  20 20 20 20 20 20 20 5c  20 64 69 73 61 62 6c 65  |       \ disable|
00004630  20 69 6e 74 65 72 72 75  70 74 73 20 77 68 65 6e  | interrupts when|
00004640  20 61 6c 74 65 72 69 6e  67 20 76 65 63 74 6f 72  | altering vector|
00004650  0d 20 31 32 32 30 20 20  20 20 20 20 20 20 20 53  |. 1220         S|
00004660  54 58 20 69 72 71 32 76  20 20 20 20 20 5c 20 72  |TX irq2v     \ r|
00004670  65 73 74 6f 72 65 20 6f  72 69 67 69 6e 61 6c 20  |estore original |
00004680  76 65 63 74 6f 72 0d 20  31 32 33 30 20 20 20 20  |vector. 1230    |
00004690  20 20 20 20 20 53 54 59  20 69 72 71 32 76 2b 31  |     STY irq2v+1|
000046a0  0d 20 31 32 34 30 20 20  20 20 20 20 20 20 20 43  |. 1240         C|
000046b0  4c 49 20 20 20 20 20 20  20 20 20 20 20 5c 20 72  |LI           \ r|
000046c0  65 2d 65 6e 61 62 6c 65  20 69 6e 74 65 72 72 75  |e-enable interru|
000046d0  70 74 73 0d 20 31 32 35  30 20 20 20 20 20 20 20  |pts. 1250       |
000046e0  20 20 52 54 53 20 20 20  20 20 20 20 20 20 20 20  |  RTS           |
000046f0  5c 20 72 65 74 75 72 6e  20 74 6f 20 42 41 53 49  |\ return to BASI|
00004700  43 0d 20 31 32 36 30 20  2e 69 6e 74 65 72 72 75  |C. 1260 .interru|
00004710  70 74 0d 20 31 32 37 30  20 20 20 20 20 20 20 20  |pt. 1270        |
00004720  20 42 49 54 20 74 74 78  73 74 61 74 75 73 20 5c  | BIT ttxstatus \|
00004730  20 70 6f 6c 6c 20 54 54  58 20 68 61 72 64 77 61  | poll TTX hardwa|
00004740  72 65 0d 20 31 32 38 30  20 20 20 20 20 20 20 20  |re. 1280        |
00004750  20 42 4d 49 20 74 74 78  69 6e 74 65 72 20 20 5c  | BMI ttxinter  \|
00004760  20 62 72 61 6e 63 68 20  69 66 20 54 54 58 20 69  | branch if TTX i|
00004770  6e 74 65 72 72 75 70 74  0d 20 31 32 39 30 20 20  |nterrupt. 1290  |
00004780  20 20 20 20 20 20 20 4a  4d 50 20 28 6f 6c 64 69  |       JMP (oldi|
00004790  72 71 32 76 29 20 5c 20  6e 6f 74 20 54 54 58 20  |rq2v) \ not TTX |
000047a0  69 6e 74 65 72 72 75 70  74 0d 20 31 33 30 30 20  |interrupt. 1300 |
000047b0  2e 74 74 78 69 6e 74 65  72 0d 20 31 33 31 30 20  |.ttxinter. 1310 |
000047c0  20 20 20 20 20 20 20 20  4c 44 41 20 73 61 76 65  |        LDA save|
000047d0  72 65 67 20 20 20 5c 20  69 6e 74 65 72 72 75 70  |reg   \ interrup|
000047e0  74 20 61 63 63 75 6d 75  6c 61 74 6f 72 20 73 61  |t accumulator sa|
000047f0  76 65 20 72 65 67 69 73  74 65 72 0d 20 31 33 32  |ve register. 132|
00004800  30 20 20 20 20 20 20 20  20 20 50 48 41 20 20 20  |0         PHA   |
00004810  20 20 20 20 20 20 20 20  5c 20 70 75 73 68 20 69  |        \ push i|
00004820  6e 74 65 72 72 75 70 74  20 61 63 63 75 6d 75 6c  |nterrupt accumul|
00004830  61 74 6f 72 20 73 61 76  65 20 72 65 67 69 73 74  |ator save regist|
00004840  65 72 0d 20 31 33 33 30  20 20 20 20 20 20 20 20  |er. 1330        |
00004850  20 54 58 41 0d 20 31 33  34 30 20 20 20 20 20 20  | TXA. 1340      |
00004860  20 20 20 50 48 41 20 20  20 20 20 20 20 20 20 20  |   PHA          |
00004870  20 5c 20 70 75 73 68 20  58 0d 20 31 33 35 30 20  | \ push X. 1350 |
00004880  20 20 20 20 20 20 20 20  54 59 41 0d 20 31 33 36  |        TYA. 136|
00004890  30 20 20 20 20 20 20 20  20 20 50 48 41 20 20 20  |0         PHA   |
000048a0  20 20 20 20 20 20 20 20  5c 20 70 75 73 68 20 59  |        \ push Y|
000048b0  0d 20 31 33 37 30 20 20  20 20 20 20 20 20 20 4c  |. 1370         L|
000048c0  44 41 20 67 72 61 62 66  6c 61 67 20 20 5c 20 68  |DA grabflag  \ h|
000048d0  61 73 20 54 53 44 50 20  62 65 65 6e 20 67 72 61  |as TSDP been gra|
000048e0  62 62 65 64 3f 0d 20 31  33 38 30 20 20 20 20 20  |bbed?. 1380     |
000048f0  20 20 20 20 42 45 51 20  63 6c 65 61 72 73 74 61  |    BEQ clearsta|
00004900  74 75 73 20 5c 20 63 6c  65 61 72 20 73 74 61 74  |tus \ clear stat|
00004910  75 73 20 61 6e 64 20 52  54 49 20 69 66 20 54 53  |us and RTI if TS|
00004920  44 50 20 67 72 61 62 62  65 64 0d 20 31 33 39 30  |DP grabbed. 1390|
00004930  20 20 20 20 20 20 20 20  20 43 4c 44 20 20 20 20  |         CLD    |
00004940  20 20 20 20 20 20 20 5c  20 63 6c 65 61 72 20 64  |       \ clear d|
00004950  65 63 69 6d 61 6c 20 66  6c 61 67 0d 20 31 34 30  |ecimal flag. 140|
00004960  30 20 20 20 20 20 20 20  20 20 4c 44 59 20 23 26  |0         LDY #&|
00004970  30 30 20 20 20 20 20 20  5c 20 73 74 61 72 74 20  |00      \ start |
00004980  77 69 74 68 20 72 6f 77  20 30 0d 20 31 34 31 30  |with row 0. 1410|
00004990  20 2e 72 65 61 64 74 74  78 74 0d 20 31 34 32 30  | .readttxt. 1420|
000049a0  20 20 20 20 20 20 20 20  20 53 54 59 20 72 6f 77  |         STY row|
000049b0  72 65 67 20 20 20 20 5c  20 74 72 79 20 72 6f 77  |reg    \ try row|
000049c0  73 20 30 20 74 6f 20 31  35 0d 20 31 34 33 30 20  |s 0 to 15. 1430 |
000049d0  20 20 20 20 20 20 20 20  4c 44 41 20 64 61 74 61  |        LDA data|
000049e0  72 65 67 20 20 20 5c 20  6c 6f 61 64 20 66 72 61  |reg   \ load fra|
000049f0  6d 69 6e 67 20 63 6f 64  65 20 28 23 26 32 37 29  |ming code (#&27)|
00004a00  0d 20 31 34 34 30 20 20  20 20 20 20 20 20 20 42  |. 1440         B|
00004a10  45 51 20 65 6d 70 74 79  72 6f 77 20 20 5c 20 69  |EQ emptyrow  \ i|
00004a20  66 20 7a 65 72 6f 20 74  72 79 20 6e 65 78 74 20  |f zero try next |
00004a30  72 6f 77 0d 20 31 34 35  30 20 20 20 20 20 20 20  |row. 1450       |
00004a40  20 20 54 59 41 0d 20 31  34 36 30 20 20 20 20 20  |  TYA. 1460     |
00004a50  20 20 20 20 50 48 41 20  20 20 20 20 20 20 20 20  |    PHA         |
00004a60  20 20 5c 20 73 61 76 65  20 72 6f 77 20 6e 75 6d  |  \ save row num|
00004a70  62 65 72 0d 20 31 34 37  30 20 20 20 20 20 20 20  |ber. 1470       |
00004a80  20 20 4a 53 52 20 72 65  61 64 70 61 63 6b 65 74  |  JSR readpacket|
00004a90  0d 20 31 34 38 30 20 20  20 20 20 20 20 20 20 50  |. 1480         P|
00004aa0  4c 41 0d 20 31 34 39 30  20 20 20 20 20 20 20 20  |LA. 1490        |
00004ab0  20 54 41 59 20 20 20 20  20 20 20 20 20 20 20 5c  | TAY           \|
00004ac0  20 72 65 73 74 6f 72 65  20 72 6f 77 20 6e 75 6d  | restore row num|
00004ad0  62 65 72 0d 20 31 35 30  30 20 2e 65 6d 70 74 79  |ber. 1500 .empty|
00004ae0  72 6f 77 0d 20 31 35 31  30 20 20 20 20 20 20 20  |row. 1510       |
00004af0  20 20 49 4e 59 20 20 20  20 20 20 20 20 20 20 20  |  INY           |
00004b00  5c 20 69 6e 63 72 65 6d  65 6e 74 20 72 6f 77 20  |\ increment row |
00004b10  6e 75 6d 62 65 72 0d 20  31 35 32 30 20 20 20 20  |number. 1520    |
00004b20  20 20 20 20 20 43 50 59  20 23 26 31 30 20 20 20  |     CPY #&10   |
00004b30  20 20 20 5c 20 74 72 79  20 72 6f 77 73 20 30 20  |   \ try rows 0 |
00004b40  2d 20 31 35 0d 20 31 35  33 30 20 20 20 20 20 20  |- 15. 1530      |
00004b50  20 20 20 42 4e 45 20 72  65 61 64 74 74 78 74 0d  |   BNE readttxt.|
00004b60  20 31 35 34 30 20 2e 63  6c 65 61 72 73 74 61 74  | 1540 .clearstat|
00004b70  75 73 0d 20 31 35 35 30  20 20 20 20 20 20 20 20  |us. 1550        |
00004b80  20 4c 44 41 20 23 26 30  30 0d 20 31 35 36 30 20  | LDA #&00. 1560 |
00004b90  20 20 20 20 20 20 20 20  4c 44 59 20 23 26 30 46  |        LDY #&0F|
00004ba0  20 20 20 20 20 20 5c 20  63 6c 65 61 72 20 31 36  |      \ clear 16|
00004bb0  20 72 6f 77 73 20 69 6e  20 61 64 61 70 74 6f 72  | rows in adaptor|
00004bc0  0d 20 31 35 37 30 20 2e  63 6c 65 61 72 6c 6f 6f  |. 1570 .clearloo|
00004bd0  70 0d 20 31 35 38 30 20  20 20 20 20 20 20 20 20  |p. 1580         |
00004be0  53 54 59 20 72 6f 77 72  65 67 0d 20 31 35 39 30  |STY rowreg. 1590|
00004bf0  20 20 20 20 20 20 20 20  20 53 54 41 20 64 61 74  |         STA dat|
00004c00  61 72 65 67 0d 20 31 36  30 30 20 20 20 20 20 20  |areg. 1600      |
00004c10  20 20 20 44 45 59 0d 20  31 36 31 30 20 20 20 20  |   DEY. 1610    |
00004c20  20 20 20 20 20 42 50 4c  20 63 6c 65 61 72 6c 6f  |     BPL clearlo|
00004c30  6f 70 0d 20 31 36 32 30  20 20 20 20 20 20 20 20  |op. 1620        |
00004c40  20 53 54 41 20 73 74 61  74 63 6c 72 20 20 20 5c  | STA statclr   \|
00004c50  20 63 6c 65 61 72 20 73  74 61 74 75 73 20 66 6c  | clear status fl|
00004c60  61 67 73 20 62 65 66 6f  72 65 20 72 65 74 75 72  |ags before retur|
00004c70  6e 69 6e 67 0d 20 31 36  33 30 20 20 20 20 20 20  |ning. 1630      |
00004c80  20 20 20 50 4c 41 0d 20  31 36 34 30 20 20 20 20  |   PLA. 1640    |
00004c90  20 20 20 20 20 54 41 59  20 20 20 20 20 20 20 20  |     TAY        |
00004ca0  20 20 20 5c 20 72 65 73  74 6f 72 65 20 59 0d 20  |   \ restore Y. |
00004cb0  31 36 35 30 20 20 20 20  20 20 20 20 20 50 4c 41  |1650         PLA|
00004cc0  0d 20 31 36 36 30 20 20  20 20 20 20 20 20 20 54  |. 1660         T|
00004cd0  41 58 20 20 20 20 20 20  20 20 20 20 20 5c 20 72  |AX           \ r|
00004ce0  65 73 74 6f 72 65 20 58  0d 20 31 36 37 30 20 20  |estore X. 1670  |
00004cf0  20 20 20 20 20 20 20 50  4c 41 0d 20 31 36 38 30  |       PLA. 1680|
00004d00  20 20 20 20 20 20 20 20  20 53 54 41 20 73 61 76  |         STA sav|
00004d10  65 72 65 67 20 20 20 5c  20 72 65 73 74 6f 72 65  |ereg   \ restore|
00004d20  20 69 6e 74 65 72 72 75  70 74 20 61 63 63 75 6d  | interrupt accum|
00004d30  75 6c 61 74 6f 72 20 73  61 76 65 20 72 65 67 69  |ulator save regi|
00004d40  73 74 65 72 0d 20 31 36  39 30 20 20 20 20 20 20  |ster. 1690      |
00004d50  20 20 20 52 54 49 20 20  20 20 20 20 20 20 20 20  |   RTI          |
00004d60  20 5c 20 72 65 74 75 72  6e 20 66 72 6f 6d 20 69  | \ return from i|
00004d70  6e 74 65 72 72 75 70 74  0d 20 31 37 30 30 20 2e  |nterrupt. 1700 .|
00004d80  72 65 61 64 70 61 63 6b  65 74 0d 20 31 37 31 30  |readpacket. 1710|
00004d90  20 20 20 20 20 20 20 20  20 4c 44 41 20 67 72 61  |         LDA gra|
00004da0  62 66 6c 61 67 20 20 5c  20 6a 75 73 74 20 63 68  |bflag  \ just ch|
00004db0  65 63 6b 69 6e 67 0d 20  31 37 32 30 20 20 20 20  |ecking. 1720    |
00004dc0  20 20 20 20 20 42 45 51  20 72 65 74 75 72 6e 0d  |     BEQ return.|
00004dd0  20 31 37 33 30 20 20 20  20 20 20 20 20 20 4c 44  | 1730         LD|
00004de0  59 20 64 61 74 61 72 65  67 20 20 20 5c 20 72 65  |Y datareg   \ re|
00004df0  61 64 20 6d 61 67 61 7a  69 6e 65 20 6e 75 6d 62  |ad magazine numb|
00004e00  65 72 0d 20 31 37 34 30  20 20 20 20 20 20 20 20  |er. 1740        |
00004e10  20 4c 44 41 20 68 61 6d  74 61 62 6c 65 2c 59 20  | LDA hamtable,Y |
00004e20  5c 20 64 65 2d 68 61 6d  20 69 74 0d 20 31 37 35  |\ de-ham it. 175|
00004e30  30 20 20 20 20 20 20 20  20 20 42 4d 49 20 72 65  |0         BMI re|
00004e40  74 75 72 6e 20 20 20 20  5c 20 73 74 6f 70 20 6c  |turn    \ stop l|
00004e50  6f 61 64 69 6e 67 20 69  66 20 65 72 72 6f 72 0d  |oading if error.|
00004e60  20 31 37 36 30 20 20 20  20 20 20 20 20 20 53 54  | 1760         ST|
00004e70  41 20 6d 61 67 61 7a 69  6e 65 20 20 5c 20 73 61  |A magazine  \ sa|
00004e80  76 65 20 6d 61 67 61 7a  69 6e 65 20 6e 75 6d 62  |ve magazine numb|
00004e90  65 72 0d 20 31 37 37 30  20 20 20 20 20 20 20 20  |er. 1770        |
00004ea0  20 4c 44 59 20 64 61 74  61 72 65 67 20 20 20 5c  | LDY datareg   \|
00004eb0  20 72 65 61 64 20 70 61  63 6b 65 74 20 6e 75 6d  | read packet num|
00004ec0  62 65 72 0d 20 31 37 38  30 20 20 20 20 20 20 20  |ber. 1780       |
00004ed0  20 20 4c 44 41 20 68 61  6d 74 61 62 6c 65 2c 59  |  LDA hamtable,Y|
00004ee0  20 5c 20 64 65 2d 68 61  6d 20 69 74 0d 20 31 37  | \ de-ham it. 17|
00004ef0  39 30 20 20 20 20 20 20  20 20 20 42 4d 49 20 72  |90         BMI r|
00004f00  65 74 75 72 6e 20 20 20  20 5c 20 73 74 6f 70 20  |eturn    \ stop |
00004f10  6c 6f 61 64 69 6e 67 20  69 66 20 65 72 72 6f 72  |loading if error|
00004f20  0d 20 31 38 30 30 20 20  20 20 20 20 20 20 20 53  |. 1800         S|
00004f30  54 41 20 70 61 63 6b 65  74 20 20 20 20 5c 20 73  |TA packet    \ s|
00004f40  61 76 65 20 70 61 63 6b  65 74 20 6e 75 6d 62 65  |ave packet numbe|
00004f50  72 0d 20 31 38 31 30 20  20 20 20 20 20 20 20 20  |r. 1810         |
00004f60  4c 44 41 20 6d 61 67 61  7a 69 6e 65 20 20 5c 20  |LDA magazine  \ |
00004f70  6c 6f 61 64 20 6d 61 67  61 7a 69 6e 65 20 6e 75  |load magazine nu|
00004f80  6d 62 65 72 0d 20 31 38  32 30 20 20 20 20 20 20  |mber. 1820      |
00004f90  20 20 20 43 4d 50 20 23  26 30 38 20 20 20 20 20  |   CMP #&08     |
00004fa0  20 5c 20 62 69 74 20 33  20 6f 66 20 6d 61 67 2e  | \ bit 3 of mag.|
00004fb0  20 6e 75 6d 62 65 72 20  69 73 20 62 69 74 20 30  | number is bit 0|
00004fc0  20 6f 66 20 70 61 63 6b  65 74 0d 20 20 20 20 20  | of packet.     |
00004fd0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00004fe0  20 20 20 20 20 20 20 5c  20 6e 75 6d 62 65 72 0d  |       \ number.|
00004ff0  20 31 38 33 30 20 20 20  20 20 20 20 20 20 52 4f  | 1830         RO|
00005000  4c 20 70 61 63 6b 65 74  20 20 20 20 5c 20 35 20  |L packet    \ 5 |
00005010  62 69 74 20 70 61 63 6b  65 74 20 6e 75 6d 62 65  |bit packet numbe|
00005020  72 0d 20 31 38 34 30 20  20 20 20 20 20 20 20 20  |r. 1840         |
00005030  41 4e 44 20 23 26 30 37  20 20 20 20 20 20 5c 20  |AND #&07      \ |
00005040  75 73 65 20 6f 6e 6c 79  20 62 69 74 73 20 30 2d  |use only bits 0-|
00005050  32 0d 20 31 38 35 30 20  20 20 20 20 20 20 20 20  |2. 1850         |
00005060  43 4d 50 20 23 26 30 30  20 20 20 20 20 20 5c 20  |CMP #&00      \ |
00005070  69 73 20 74 68 69 73 20  6d 61 67 61 7a 69 6e 65  |is this magazine|
00005080  20 30 3f 0d 20 31 38 36  30 20 20 20 20 20 20 20  | 0?. 1860       |
00005090  20 20 42 4e 45 20 72 65  74 75 72 6e 20 20 20 20  |  BNE return    |
000050a0  5c 20 72 65 74 75 72 6e  20 69 66 20 6e 6f 74 0d  |\ return if not.|
000050b0  20 31 38 37 30 20 20 20  20 20 20 20 20 20 4c 44  | 1870         LD|
000050c0  41 20 70 61 63 6b 65 74  0d 20 31 38 38 30 20 20  |A packet. 1880  |
000050d0  20 20 20 20 20 20 20 43  4d 50 20 23 26 31 45 20  |       CMP #&1E |
000050e0  20 20 20 20 20 5c 20 6c  6f 6f 6b 20 66 6f 72 20  |     \ look for |
000050f0  54 53 44 50 0d 20 31 38  39 30 20 20 20 20 20 20  |TSDP. 1890      |
00005100  20 20 20 42 4e 45 20 72  65 74 75 72 6e 20 20 20  |   BNE return   |
00005110  20 5c 20 69 67 6e 6f 72  65 20 61 6c 6c 20 6f 74  | \ ignore all ot|
00005120  68 65 72 20 70 61 63 6b  65 74 73 0d 20 31 39 30  |her packets. 190|
00005130  30 20 20 20 20 20 20 20  20 20 4c 44 59 20 23 26  |0         LDY #&|
00005140  30 30 20 20 20 20 20 20  5c 20 72 65 61 64 20 62  |00      \ read b|
00005150  79 74 65 73 20 30 20 2d  20 33 39 0d 20 31 39 31  |ytes 0 - 39. 191|
00005160  30 20 2e 72 65 61 64 6d  6f 72 65 0d 20 31 39 32  |0 .readmore. 192|
00005170  30 20 20 20 20 20 20 20  20 20 4c 44 58 20 64 61  |0         LDX da|
00005180  74 61 72 65 67 20 20 20  5c 20 72 65 61 64 20 64  |tareg   \ read d|
00005190  61 74 61 20 72 65 67 69  73 74 65 72 0d 20 31 39  |ata register. 19|
000051a0  33 30 20 20 20 20 20 20  20 20 20 4c 44 41 20 68  |30         LDA h|
000051b0  61 6d 74 61 62 6c 65 2c  58 20 5c 20 64 65 2d 68  |amtable,X \ de-h|
000051c0  61 6d 20 74 68 65 20 62  79 74 65 0d 20 31 39 34  |am the byte. 194|
000051d0  30 20 20 20 20 20 20 20  20 20 42 4d 49 20 72 65  |0         BMI re|
000051e0  74 75 72 6e 20 20 20 20  5c 20 72 65 74 75 72 6e  |turn    \ return|
000051f0  20 69 66 20 65 72 72 6f  72 0d 20 31 39 35 30 20  | if error. 1950 |
00005200  20 20 20 20 20 20 20 20  53 54 41 20 62 75 66 66  |        STA buff|
00005210  2c 59 20 20 20 20 5c 20  73 74 6f 72 65 20 69 6e  |,Y    \ store in|
00005220  20 62 75 66 66 65 72 0d  20 31 39 36 30 20 20 20  | buffer. 1960   |
00005230  20 20 20 20 20 20 49 4e  59 20 20 20 20 20 20 20  |      INY       |
00005240  20 20 20 20 5c 20 69 6e  63 72 65 6d 65 6e 74 20  |    \ increment |
00005250  69 6e 64 65 78 0d 20 31  39 37 30 20 20 20 20 20  |index. 1970     |
00005260  20 20 20 20 43 50 59 20  23 26 30 37 0d 20 31 39  |    CPY #&07. 19|
00005270  38 30 20 20 20 20 20 20  20 20 20 42 4e 45 20 72  |80         BNE r|
00005280  65 61 64 6d 6f 72 65 20  20 5c 20 67 6f 20 62 61  |eadmore  \ go ba|
00005290  63 6b 20 66 6f 72 20 6d  6f 72 65 0d 20 31 39 39  |ck for more. 199|
000052a0  30 20 2e 72 65 61 64 61  67 61 69 6e 0d 20 32 30  |0 .readagain. 20|
000052b0  30 30 20 20 20 20 20 20  20 20 20 4c 44 41 20 64  |00         LDA d|
000052c0  61 74 61 72 65 67 20 20  20 5c 20 72 65 61 64 20  |atareg   \ read |
000052d0  64 61 74 61 20 72 65 67  69 73 74 65 72 0d 20 32  |data register. 2|
000052e0  30 31 30 20 20 20 20 20  20 20 20 20 53 54 41 20  |010         STA |
000052f0  62 75 66 66 2c 59 20 20  20 20 5c 20 73 74 6f 72  |buff,Y    \ stor|
00005300  65 20 69 6e 20 62 75 66  66 65 72 0d 20 32 30 32  |e in buffer. 202|
00005310  30 20 20 20 20 20 20 20  20 20 49 4e 59 20 20 20  |0         INY   |
00005320  20 20 20 20 20 20 20 20  5c 20 69 6e 63 72 65 6d  |        \ increm|
00005330  65 6e 74 20 69 6e 64 65  78 0d 20 32 30 33 30 20  |ent index. 2030 |
00005340  20 20 20 20 20 20 20 20  43 50 59 20 23 26 32 38  |        CPY #&28|
00005350  20 20 20 20 20 20 5c 20  64 65 63 69 6d 61 6c 20  |      \ decimal |
00005360  34 30 0d 20 32 30 34 30  20 20 20 20 20 20 20 20  |40. 2040        |
00005370  20 42 4e 45 20 72 65 61  64 61 67 61 69 6e 20 5c  | BNE readagain \|
00005380  20 67 6f 20 62 61 63 6b  20 66 6f 72 20 6d 6f 72  | go back for mor|
00005390  65 0d 20 32 30 35 30 20  20 20 20 20 20 20 20 20  |e. 2050         |
000053a0  4c 44 41 20 62 75 66 66  20 20 20 20 20 20 5c 20  |LDA buff      \ |
000053b0  54 53 44 50 20 74 79 70  65 20 62 79 74 65 0d 20  |TSDP type byte. |
000053c0  32 30 36 30 20 20 20 20  20 20 20 20 20 41 4e 44  |2060         AND|
000053d0  20 23 26 30 45 20 20 20  20 20 20 5c 20 25 30 30  | #&0E      \ %00|
000053e0  30 30 31 31 31 30 0d 20  32 30 37 30 20 20 20 20  |001110. 2070    |
000053f0  20 20 20 20 20 53 54 41  20 67 72 61 62 66 6c 61  |     STA grabfla|
00005400  67 20 20 5c 20 67 72 61  62 66 6c 61 67 20 3d 20  |g  \ grabflag = |
00005410  30 20 6f 72 20 32 0d 20  32 30 38 30 20 2e 72 65  |0 or 2. 2080 .re|
00005420  74 75 72 6e 0d 20 32 30  39 30 20 20 20 20 20 20  |turn. 2090      |
00005430  20 20 20 52 54 53 0d 20  32 31 30 30 20 2e 6f 6c  |   RTS. 2100 .ol|
00005440  64 69 72 71 32 76 0d 20  32 31 31 30 20 20 20 20  |dirq2v. 2110    |
00005450  20 20 20 20 20 45 51 55  57 20 26 30 30 0d 20 32  |     EQUW &00. 2|
00005460  31 32 30 20 2e 68 61 6d  74 61 62 6c 65 0d 20 32  |120 .hamtable. 2|
00005470  31 33 30 20 20 20 20 20  20 20 20 20 45 51 55 44  |130         EQUD|
00005480  20 26 30 31 30 31 46 46  30 31 20 0d 20 32 31 34  | &0101FF01 . 214|
00005490  30 20 20 20 20 20 20 20  20 20 45 51 55 44 20 26  |0         EQUD &|
000054a0  46 46 30 31 30 30 46 46  20 0d 20 32 31 35 30 20  |FF0100FF . 2150 |
000054b0  20 20 20 20 20 20 20 20  45 51 55 44 20 26 46 46  |        EQUD &FF|
000054c0  30 31 30 32 46 46 20 0d  20 32 31 36 30 20 20 20  |0102FF . 2160   |
000054d0  20 20 20 20 20 20 45 51  55 44 20 26 30 37 46 46  |      EQUD &07FF|
000054e0  46 46 30 41 0d 20 32 31  37 30 20 20 20 20 20 20  |FF0A. 2170      |
000054f0  20 20 20 45 51 55 44 20  26 46 46 30 31 30 30 46  |   EQUD &FF0100F|
00005500  46 20 0d 20 32 31 38 30  20 20 20 20 20 20 20 20  |F . 2180        |
00005510  20 45 51 55 44 20 26 30  30 46 46 30 30 30 30 20  | EQUD &00FF0000 |
00005520  0d 20 32 31 39 30 20 20  20 20 20 20 20 20 20 45  |. 2190         E|
00005530  51 55 44 20 26 30 42 46  46 46 46 30 36 20 0d 20  |QUD &0BFFFF06 . |
00005540  32 32 30 30 20 20 20 20  20 20 20 20 20 45 51 55  |2200         EQU|
00005550  44 20 26 46 46 30 33 30  30 46 46 0d 20 32 32 31  |D &FF0300FF. 221|
00005560  30 20 20 20 20 20 20 20  20 20 45 51 55 44 20 26  |0         EQUD &|
00005570  46 46 30 31 30 43 46 46  20 0d 20 32 32 32 30 20  |FF010CFF . 2220 |
00005580  20 20 20 20 20 20 20 20  45 51 55 44 20 26 30 37  |        EQUD &07|
00005590  46 46 46 46 30 34 20 0d  20 32 32 33 30 20 20 20  |FFFF04 . 2230   |
000055a0  20 20 20 20 20 20 45 51  55 44 20 26 30 37 46 46  |      EQUD &07FF|
000055b0  46 46 30 36 20 0d 20 32  32 34 30 20 20 20 20 20  |FF06 . 2240     |
000055c0  20 20 20 20 45 51 55 44  20 26 30 37 30 37 30 37  |    EQUD &070707|
000055d0  46 46 0d 20 32 32 35 30  20 20 20 20 20 20 20 20  |FF. 2250        |
000055e0  20 45 51 55 44 20 26 30  35 46 46 46 46 30 36 20  | EQUD &05FFFF06 |
000055f0  0d 20 32 32 36 30 20 20  20 20 20 20 20 20 20 45  |. 2260         E|
00005600  51 55 44 20 26 46 46 30  44 30 30 46 46 20 0d 20  |QUD &FF0D00FF . |
00005610  32 32 37 30 20 20 20 20  20 20 20 20 20 45 51 55  |2270         EQU|
00005620  44 20 26 46 46 30 36 30  36 30 36 20 0d 20 32 32  |D &FF060606 . 22|
00005630  38 30 20 20 20 20 20 20  20 20 20 45 51 55 44 20  |80         EQUD |
00005640  26 30 37 46 46 46 46 30  36 0d 20 32 32 39 30 20  |&07FFFF06. 2290 |
00005650  20 20 20 20 20 20 20 20  45 51 55 44 20 26 46 46  |        EQUD &FF|
00005660  30 31 30 32 46 46 20 0d  20 32 33 30 30 20 20 20  |0102FF . 2300   |
00005670  20 20 20 20 20 20 45 51  55 44 20 26 30 39 46 46  |      EQUD &09FF|
00005680  46 46 30 34 20 0d 20 32  33 31 30 20 20 20 20 20  |FF04 . 2310     |
00005690  20 20 20 20 45 51 55 44  20 26 30 32 46 46 30 32  |    EQUD &02FF02|
000056a0  30 32 20 0d 20 32 33 32  30 20 20 20 20 20 20 20  |02 . 2320       |
000056b0  20 20 45 51 55 44 20 26  46 46 30 33 30 32 46 46  |  EQUD &FF0302FF|
000056c0  0d 20 32 33 33 30 20 20  20 20 20 20 20 20 20 45  |. 2330         E|
000056d0  51 55 44 20 26 30 35 46  46 46 46 30 38 20 0d 20  |QUD &05FFFF08 . |
000056e0  32 33 34 30 20 20 20 20  20 20 20 20 20 45 51 55  |2340         EQU|
000056f0  44 20 26 46 46 30 33 30  30 46 46 20 0d 20 32 33  |D &FF0300FF . 23|
00005700  35 30 20 20 20 20 20 20  20 20 20 45 51 55 44 20  |50         EQUD |
00005710  26 46 46 30 33 30 32 46  46 20 0d 20 32 33 36 30  |&FF0302FF . 2360|
00005720  20 20 20 20 20 20 20 20  20 45 51 55 44 20 26 30  |         EQUD &0|
00005730  33 30 33 46 46 30 33 0d  20 32 33 37 30 20 20 20  |303FF03. 2370   |
00005740  20 20 20 20 20 20 45 51  55 44 20 26 30 35 46 46  |      EQUD &05FF|
00005750  46 46 30 34 20 0d 20 32  33 38 30 20 20 20 20 20  |FF04 . 2380     |
00005760  20 20 20 20 45 51 55 44  20 26 46 46 30 34 30 34  |    EQUD &FF0404|
00005770  30 34 20 0d 20 32 33 39  30 20 20 20 20 20 20 20  |04 . 2390       |
00005780  20 20 45 51 55 44 20 26  46 46 30 46 30 32 46 46  |  EQUD &FF0F02FF|
00005790  20 0d 20 32 34 30 30 20  20 20 20 20 20 20 20 20  | . 2400         |
000057a0  45 51 55 44 20 26 30 37  46 46 46 46 30 34 0d 20  |EQUD &07FFFF04. |
000057b0  32 34 31 30 20 20 20 20  20 20 20 20 20 45 51 55  |2410         EQU|
000057c0  44 20 26 30 35 30 35 30  35 46 46 20 0d 20 32 34  |D &050505FF . 24|
000057d0  32 30 20 20 20 20 20 20  20 20 20 45 51 55 44 20  |20         EQUD |
000057e0  26 30 35 46 46 46 46 30  34 20 0d 20 32 34 33 30  |&05FFFF04 . 2430|
000057f0  20 20 20 20 20 20 20 20  20 45 51 55 44 20 26 30  |         EQUD &0|
00005800  35 46 46 46 46 30 36 20  0d 20 32 34 34 30 20 20  |5FFFF06 . 2440  |
00005810  20 20 20 20 20 20 20 45  51 55 44 20 26 46 46 30  |       EQUD &FF0|
00005820  33 30 45 46 46 0d 20 32  34 35 30 20 20 20 20 20  |30EFF. 2450     |
00005830  20 20 20 20 45 51 55 44  20 26 46 46 30 31 30 43  |    EQUD &FF010C|
00005840  46 46 20 0d 20 32 34 36  30 20 20 20 20 20 20 20  |FF . 2460       |
00005850  20 20 45 51 55 44 20 26  30 39 46 46 46 46 30 41  |  EQUD &09FFFF0A|
00005860  20 0d 20 32 34 37 30 20  20 20 20 20 20 20 20 20  | . 2470         |
00005870  45 51 55 44 20 26 30 42  46 46 46 46 30 41 20 0d  |EQUD &0BFFFF0A .|
00005880  20 32 34 38 30 20 20 20  20 20 20 20 20 20 45 51  | 2480         EQ|
00005890  55 44 20 26 46 46 30 41  30 41 30 41 0d 20 32 34  |UD &FF0A0A0A. 24|
000058a0  39 30 20 20 20 20 20 20  20 20 20 45 51 55 44 20  |90         EQUD |
000058b0  26 30 42 46 46 46 46 30  38 20 0d 20 32 35 30 30  |&0BFFFF08 . 2500|
000058c0  20 20 20 20 20 20 20 20  20 45 51 55 44 20 26 46  |         EQUD &F|
000058d0  46 30 44 30 30 46 46 20  0d 20 32 35 31 30 20 20  |F0D00FF . 2510  |
000058e0  20 20 20 20 20 20 20 45  51 55 44 20 26 30 42 30  |       EQUD &0B0|
000058f0  42 30 42 46 46 20 0d 20  32 35 32 30 20 20 20 20  |B0BFF . 2520    |
00005900  20 20 20 20 20 45 51 55  44 20 26 30 42 46 46 46  |     EQUD &0BFFF|
00005910  46 30 41 0d 20 32 35 33  30 20 20 20 20 20 20 20  |F0A. 2530       |
00005920  20 20 45 51 55 44 20 26  30 43 46 46 30 43 30 43  |  EQUD &0CFF0C0C|
00005930  20 0d 20 32 35 34 30 20  20 20 20 20 20 20 20 20  | . 2540         |
00005940  45 51 55 44 20 26 46 46  30 44 30 43 46 46 20 0d  |EQUD &FF0D0CFF .|
00005950  20 32 35 35 30 20 20 20  20 20 20 20 20 20 45 51  | 2550         EQ|
00005960  55 44 20 26 46 46 30 46  30 43 46 46 20 0d 20 32  |UD &FF0F0CFF . 2|
00005970  35 36 30 20 20 20 20 20  20 20 20 20 45 51 55 44  |560         EQUD|
00005980  20 26 30 37 46 46 46 46  30 41 0d 20 32 35 37 30  | &07FFFF0A. 2570|
00005990  20 20 20 20 20 20 20 20  20 45 51 55 44 20 26 46  |         EQUD &F|
000059a0  46 30 44 30 43 46 46 20  0d 20 32 35 38 30 20 20  |F0D0CFF . 2580  |
000059b0  20 20 20 20 20 20 20 45  51 55 44 20 26 30 44 30  |       EQUD &0D0|
000059c0  44 46 46 30 44 20 0d 20  32 35 39 30 20 20 20 20  |DFF0D . 2590    |
000059d0  20 20 20 20 20 45 51 55  44 20 26 30 42 46 46 46  |     EQUD &0BFFF|
000059e0  46 30 36 20 0d 20 32 36  30 30 20 20 20 20 20 20  |F06 . 2600      |
000059f0  20 20 20 45 51 55 44 20  26 46 46 30 44 30 45 46  |   EQUD &FF0D0EF|
00005a00  46 0d 20 32 36 31 30 20  20 20 20 20 20 20 20 20  |F. 2610         |
00005a10  45 51 55 44 20 26 30 39  46 46 46 46 30 38 20 0d  |EQUD &09FFFF08 .|
00005a20  20 32 36 32 30 20 20 20  20 20 20 20 20 20 45 51  | 2620         EQ|
00005a30  55 44 20 26 30 39 30 39  30 39 46 46 20 0d 20 32  |UD &090909FF . 2|
00005a40  36 33 30 20 20 20 20 20  20 20 20 20 45 51 55 44  |630         EQUD|
00005a50  20 26 46 46 30 46 30 32  46 46 20 0d 20 32 36 34  | &FF0F02FF . 264|
00005a60  30 20 20 20 20 20 20 20  20 20 45 51 55 44 20 26  |0         EQUD &|
00005a70  30 39 46 46 46 46 30 41  0d 20 32 36 35 30 20 20  |09FFFF0A. 2650  |
00005a80  20 20 20 20 20 20 20 45  51 55 44 20 26 46 46 30  |       EQUD &FF0|
00005a90  38 30 38 30 38 20 0d 20  32 36 36 30 20 20 20 20  |80808 . 2660    |
00005aa0  20 20 20 20 20 45 51 55  44 20 26 30 39 46 46 46  |     EQUD &09FFF|
00005ab0  46 30 38 20 0d 20 32 36  37 30 20 20 20 20 20 20  |F08 . 2670      |
00005ac0  20 20 20 45 51 55 44 20  26 30 42 46 46 46 46 30  |   EQUD &0BFFFF0|
00005ad0  38 20 0d 20 32 36 38 30  20 20 20 20 20 20 20 20  |8 . 2680        |
00005ae0  20 45 51 55 44 20 26 46  46 30 33 30 45 46 46 0d  | EQUD &FF030EFF.|
00005af0  20 32 36 39 30 20 20 20  20 20 20 20 20 20 45 51  | 2690         EQ|
00005b00  55 44 20 26 46 46 30 46  30 43 46 46 20 0d 20 32  |UD &FF0F0CFF . 2|
00005b10  37 30 30 20 20 20 20 20  20 20 20 20 45 51 55 44  |700         EQUD|
00005b20  20 26 30 39 46 46 46 46  30 34 20 0d 20 32 37 31  | &09FFFF04 . 271|
00005b30  30 20 20 20 20 20 20 20  20 20 45 51 55 44 20 26  |0         EQUD &|
00005b40  30 46 30 46 46 46 30 46  20 0d 20 32 37 32 30 20  |0F0FFF0F . 2720 |
00005b50  20 20 20 20 20 20 20 20  45 51 55 44 20 26 46 46  |        EQUD &FF|
00005b60  30 46 30 45 46 46 0d 20  32 37 33 30 20 20 20 20  |0F0EFF. 2730    |
00005b70  20 20 20 20 20 45 51 55  44 20 26 30 35 46 46 46  |     EQUD &05FFF|
00005b80  46 30 38 20 0d 20 32 37  34 30 20 20 20 20 20 20  |F08 . 2740      |
00005b90  20 20 20 45 51 55 44 20  26 46 46 30 44 30 45 46  |   EQUD &FF0D0EF|
00005ba0  46 20 0d 20 32 37 35 30  20 20 20 20 20 20 20 20  |F . 2750        |
00005bb0  20 45 51 55 44 20 26 46  46 30 46 30 45 46 46 20  | EQUD &FF0F0EFF |
00005bc0  0d 20 32 37 36 30 20 20  20 20 20 20 20 20 20 45  |. 2760         E|
00005bd0  51 55 44 20 26 30 45 46  46 30 45 30 45 0d 20 32  |QUD &0EFF0E0E. 2|
00005be0  37 37 30 20 5d 0d 20 32  37 38 30 20 4e 45 58 54  |770 ]. 2780 NEXT|
00005bf0  0d 20 32 37 39 30 20 45  4e 44 50 52 4f 43 0d     |. 2790 ENDPROC.|
00005bff
08-04-89/T\TTX05.m0
08-04-89/T\TTX05.m1
08-04-89/T\TTX05.m2
08-04-89/T\TTX05.m4
08-04-89/T\TTX05.m5