Links to other parts of this web site are at the bottom of the page.
.Other TI99/4A sections:
Book- Getting Started   |    TI Articles | TI Resources Page |   PC99 Review |   Programs for the TI99/4A and emulations

Jump to:
V2 No2 | |   V2 No 3 | |   Graphics from P Brooks | |   Sound under 100Hz | |   Graphics from S Shaw | |   Program location
Designs for Fun ||   Program storage

TIHOME Tidings Volume 2

Volume 2 Numbers 1 to 3. .

TIdings Volume 2 Number 1, February 1982-
This was the first PAID FOR issue as the prior six were freely issued.
I reported that the first program listing for the TI99/4 was published in the January 1982 issue of Computer and Video Games Magazine, issue three of a magazine which continued in print for many years and still exists as a web publication. The program was written by me and required Extended Basic, which at that time was probably unknown.
I at last received my first TI Disk Drive and Disk Manager module in time for Christmas 1981.
Kays and GUS Mail Order Catalogues were selling the TI99/4, with a cassete cable and Video Games 1 module for GBP 450.

Peter Brooks Graphics Peter Brooks wrote a very long article on using Basic to plot simple graphics (on a screen just 32 x 24 characters remember)- I have extracted the listings which appear below, the first is the actual plotting bit and can be saved to disk in merge format then merged into the other routines.

See Also: TIdings12 for an ExBas improvement by Gary Harding and also Times 27 for a shorter and faster main routine for Extended Basic


In lines 1030 and 1070, remove the REMs to allow for protected axes.

10 REM FASTER PLOTTING SUBRO
UTINE 7/1/82 PETE BROOKS
20 REM RESERVED VARIABLES:B,
C,H,I,P,R,S,X,Y,B$,C$(),H$,I
$,P$,Z$
30 REM R,C MUST BE INTEGERS
ON INTERVALS (1,192),(1,256)
RESP. NO VALIDITY CHECKS IN
SUBROUTINES
40 REM NO END OF CHARACTERS
WARNING. NB:CHR$(159) MUST N
OT BE 'PROTECTED'
50 REM SUBROUTINE ACCESSED B
Y SETTING R,C AND 'GOSUB 100
0'
60 REM INITIALIZATION MUST B
E INCLUDED IN ALL PROGRAMS
100 CALL SCREEN(2)
110 S=31
120 CALL HCHAR(1,1,S,768)
130 DIM C$(128)
140 B$="0000.0001.0010.0011.
0100.0101.0110.0111.1000.100
1.1010.1011.1100.1101.1110.1
111"
150 H$="0123456789ABCDEF"
160 Z$="0000000000000000"
170 FOR I=1 TO 16
180 CALL COLOR(I,16,2)
190 NEXT I
200 REM INSERT ROUTINE HERE
AND GOSUB 1000
1000 Y=INT(R/8+.875)
1010 X=INT(C/8+.875)
1020 CALL GCHAR(Y,X,H)
1030 REM IF POS(P$,CHR$(H),1
) THEN 1220
1040 IF H>31 THEN 1120
1050 IF S=159 THEN 1220
1060 S=S+1
1070 REM IF POS(P$,CHR$(S),1
) THEN 1050
1080 C$(S-31)=Z$
1090 CALL CHAR(S,Z$)
1100 CALL HCHAR(Y,X,S)
1110 H=S
1120 H=H-31
1130 B=C-X*8+8
1140 P=2*R-16*Y+16+(B<5)
1150 IF B<5 THEN 1170
1160 B=B-4
1170 I$=SEG$(B$,POS(H$,SEG$(
C$(H),P,1),1)*5-4,4)
1180 I$=SEG$(I$,1,B-1)&"1"&S
EG$(I$,B+1,4-B)
1190 I=POS(B$,I$,1)/5+.8
1200 C$(H)=SEG$(C$(H),1,P-1)
&SEG$(H$,I,1)&SEG$(C$(H),P+1
,16-P)
1210 CALL CHAR(H+31,C$(H))
1220 RETURN

Sine Wave
10 REM SIMPLE PLOT OF SINE W
AVE
200 FOR C=1 TO 255
210 R=96+INT(.5+SIN(C/16)*40
)
220 GOSUB 1000
230 NEXT C
240 GOTO 240



==========
SINE WAVES
10 REM SIMPLE SIMULTANEOUS P
LOTS OF SINE WAVE
200 FOR C=54 TO 192
210 R=96+INT(.5+SIN(C/16)*40
)
220 GOSUB 1000
230 R=96+INT(.5+SIN(C/8)*40)
240 GOSUB 1000
250 NEXT C
260 GOTO 260

CIRCLES
10 REM PLOTTING CIRCLES FROM
TRIG FUNCTIONS
200 R=96
210 C=128
220 GOSUB 1000
230 V=4*ATN(1)
240 FOR K=10 TO 40 STEP 10
250 FOR J=-V TO V STEP 1/K
260 C=128+INT(.5+K*SIN(J))
270 R=96+INT(.5+K*COS(J))
280 GOSUB 1000
290 NEXT J
300 NEXT K
310 GOTO 310



ELLIPSES
10 REM PLOTTING ELLIPSES FRO
M TRIG FUNCTIONS
200 R=96
210 C=128
220 GOSUB 1000
230 V=4*ATN(1)
240 FOR K=5 TO 25 STEP 5
250 FOR J=-V TO V STEP 1/K
260 C=128+INT(.5+2*K*SIN(J))
270 R=96+INT(.5+K*COS(J))
280 GOSUB 1000
290 NEXT J
300 NEXT K
310 GOTO 310

NESTED ELLIPSES
10 REM NESTED ELLIPSES
200 FOR K=1 TO 5
210 FOR N=1 TO 30
220 C=INT(128-(15+K^2.8)*COS
(N/15*4*ATN(1)))
230 R=INT(96+60*SIN(N/15*4*A
TN(1)))
240 GOSUB 1000
250 NEXT N
260 NEXT K
270 GOTO 270


3d PLOT
10 REM SLIGHTLY DIFFERENT 3D
PLOT FUNCTION IN LINE 250,
TILT CONTROL IN LINE 260
200 FOR X1=0 TO 48
210 SS=X1^2
220 P1=SQR(2304-SS)
230 I1=-P1
240 R1=SQR(SS+I1^2)/48
250 Q=(R1-1)*SIN(24*R1)
260 YY=I1/3+Q*36
270 IF I1<>-P1 THEN 300
280 M=YY
290 GOTO 340
300 IF YY<=M THEN 330
310 M=YY
320 GOTO 350
330 IF YY>=N THEN 400
340 N=YY
350 R=98-INT(YY)
360 C=128-X1
370 GOSUB 1000
380 C=128+X1
390 GOSUB 1000
400 I1=I1+4
410 IF I1<P1 THEN 240
420 NEXT X1
430 GOTO 430



==========Return to top of page
BANTHORPE 3D PLOT
10 REM NEW 3D PLOT AFTER BAN
THORPE(PCW):ALLOW 35 MINUTES
FOR COMPLETION. NO DATA DUM
P
20 REM FUNCTION PLOTTED IS I
N LINE 320
200 M1=192
210 V=104
220 X1=M1/2
230 X2=X1^2
240 Y1=V/2
250 Y2=V/4
260 FOR X5=0 TO X1
270 X4=X5^2
280 M=-Y1
290 A=SQR(X2-X4)
300 FOR I1=-A TO A STEP V/10
310 R1=SQR(X4+I1^2)/X1
320 F=(R1-1)*SIN(R1*12)
330 R=INT(I1/5+F*Y2)
340 IF R<=M THEN 410
350 M=R
360 R=Y1-R
370 C=X1-X5+32
380 GOSUB 1000
390 C=X1+X5+32
400 GOSUB 1000
410 NEXT I1
420 NEXT X5
430 GOTO 430
See TIdings 10 for a reworked faster routine!

Protected Axes
Use this with the plotting routine with the rems in lines 1030 and 1070 removed.
10 REM PLOTTING WITH PROTECT
ED AXES,SAMPLE FUNCTION PLOT
TED IS IN LINE 310. ONLY 3 C
HARACTERS USED FOR AXES
200 P$=" !""
210 C$(1)="10101010F0101010"
220 C$(2)="00000000FF101010"
230 C$(3)="10101010FF101010"
240 FOR I=32 TO 34
250 CALL CHAR(I,C$(I-31))
260 NEXT I
270 CALL VCHAR(1,16,32,24)
280 CALL HCHAR(12,1,33,32)
290 CALL HCHAR(12,16,34)
300 FOR C=1 TO 256
310 R=96+INT(SIN(C/9)*40)
320 GOSUB 1000
330 NEXT C
340 GOTO 340

Unprotected Axes
Use the plotting routine with the rems left in lines 1030 and 1070
10 REM PLOTTING WITH UNPROTE
CTED AXES.SAMPLE FUNCTION PL
OTTED IS IN LINE 470. 55(!)C
HARACTERS USED FOR AXES
200 A$="10101010F0101010"
210 FOR S=32 TO 42
220 C$(S-31)=A$
230 CALL CHAR(S,A$)
240 CALL VCHAR(S-31,16,S)
250 NEXT S
260 C$(S-31)="10101010FF1010
10"
270 CALL CHAR(S,C$(S-31))
280 CALL HCHAR(S-31,16,S)
290 FOR S=44 TO 55
300 C$(S-31)=A$
310 CALL CHAR(S,A$)
320 CALL VCHAR(S-31,16,S)
330 NEXT S
340 A$="00000000FF101010"
350 FOR S=56 TO 70
360 C$(S-31)=A$
370 CALL CHAR(S,A$)
380 CALL HCHAR(12,S-55,S)
390 NEXT S
400 FOR S=71 TO 86
410 C$(S-31)=A$
420 CALL CHAR(S,A$)
430 CALL HCHAR(12,S-54,S)
440 NEXT S
450 S=S-1
460 FOR C=32 TO 225
470 R=96+INT(SIN(C/9)*40)
480 GOSUB 1000
490 NEXT C
500 GOTO 500



==========Return to top of page
Random Symmetry
10 REM SYMMETRICAL RANDOM PL
OTTER
200 R=INT(RND*96)+49
210 C=INT(RND*80)+113
220 GOSUB 1000
230 R=193-R
240 GOSUB 1000
250 C=257-C
260 GOSUB 1000
270 R=193-R
280 GOSUB 1000
290 GOTO 200

Random Symmetry 2
10 REM SYMMETRICAL RANDOM PL
OTTER II
200 R=INT(RND*96)+49
210 C=INT(RND*80)+113
220 GOSUB 500
230 R1=INT(C/256*192)
240 C1=INT(R/192*256)
250 R=R1
260 C=C1
270 GOSUB 500
280 GOTO 200
500 GOSUB 1000
510 R=193-R
520 GOSUB 1000
530 C=257-C
540 GOSUB 1000
550 R=193-R
560 GOSUB 1000
570 C=257-C
580 RETURN



Drawing
Note that the test for K=0 does not work if the alpha lock is down so we have used K<1 instead.

10 REM SIMPLE USER-DIRECTED
PLOT
200 R=96
210 C=128
220 GOSUB 1000
230 CALL KEY(1,K,T)
240 IF T=0 THEN 230
250 R=R+(K=4)+(K=5)+(K=6
)-(K<1)-(K=14)-(K=15)
260 C=C+(K=2)+(K=4)+(K=15)-(
K=3)-(K=6)-(K=14)
270 GOTO 220



Figures of 8
10 REM ODD PLOTS I : NESTED
FIGURES OF 8
200 V=4*ATN(1)
210 FOR K=5 TO 25 STEP 5
220 FOR J=-V TO V STEP 1/K
230 C=128+INT(.5+K*SIN(2*J))
240 R=96+INT(.5+2*K*COS(J))
250 GOSUB 1000
260 NEXT J
270 NEXT K
280 GOTO 280





==========Return to top of page
More Eights
10 REM ODD PLOTS II : NESTED
FIGURES OF 8
200 V=4*ATN(1)
210 FOR K=4 TO 20 STEP 4
220 FOR J=-V TO V STEP 1/K
230 C=128+INT(.5+2*K*COS(J))
240 R=96+2*INT(.5+K*SIN(3*J)
)
250 GOSUB 1000
260 NEXT J
270 NEXT K
280 GOTO 280

Turtle
10 REM 'TURTLE'-TYPE GRAPHIC
S
200 R=96
210 C=128
220 GOSUB 1000
230 DATA -1,0,-1,1,0,1,1,1,1
,0,1,-1,0,-1,-1,-1
240 FOR J=1 TO 8
250 READ V(J,1),V(J,2)
260 NEXT J

Triangles
10 REM RANDOM EQUILATERAL TR
IANGLES
200 R=INT(RND*24)+84
210 C=INT(RND*32)+96
220 T=INT(RND*8)+4
230 FOR J=1 TO T
240 R=R+1
250 C=C-1
260 GOSUB 1000
270 NEXT J
280 FOR J=1 TO 2*T
290 C=C+1
300 GOSUB 1000
310 NEXT J
320 FOR J=1 TO T
330 R=R-1
340 C=C-1
350 GOSUB 1000
360 NEXT J
370 GOTO 200


I see that in 1981 I disclosed some personal financial information to the world at large- monthly net salary GBP 483, monthly commuting costing 14.56 and local authority taxes of GBP 33 per month.
Return to top of page
TIdings Volume 2 Number 2, 28th April 1982-
Group membership reported as 180.
Editor/Assembler was due to be released imminently.
A review of the TI99/4a in Personal Computer World suggested that TI Basic was faster if you didn't put a module in - rubbish!

Report of how to obtain sound tones below 110Hz:
10 INPUT FREQ
20 CALL SOUND(400,22000,30,2
2000,30,FREQ,30,-4,0)
30 GOTO 10

With FREQ set to under 500, the sound output is not too useful. The sound output is around three octaves below the value of FREQ - still waiting for someone to put a frequency meter on it to tell us the principal tone output.
You can replace the -4 value with a -8 but the sound can only be described as weird.


Report that Computer and Video Games magazine paid an overwhelming ten pounds for each program listed in the magazine.

An odd bit of programming in Extended Basic to consider:
10 CALL CLEAR
20 DEF YES=A$="Y"
30 DISPLAY AT(3,5):"Would you care to input a Y or an N?"
40 ACCEPT BEEP AT(5,5) SIZE(1) VALIDATE("YN"):A$
50 IF YES THEN 50 ELSE 70
60 PRINT "YOU INPUT Y FOR YES"
70 GOTO 30
80 PRINT "YOU INPUT N FOR NO"
90 GOTO 30
The binary value of YES is set to true when the string variable A$ is set to "Y".

My first Extended Basic program printed in Computer and Video Games Magazine was written for the TI99/4, and was causing problems with TI99/4A consoles, which everyone but me had, due to the extended character definitions. When using a sprite made up of four characters it became necessary to make sure that the 2nd 3rd and 4th characters were defined- you could no longer assume some characters started as blanks.

The change required:
CALL CHAR(100,"96FEBA3838BAFEBA")
to become:
CALL CHAR(100,"96FEBA3838BAFEBA"&RPT$("0",48)

===================================

Return to top of page

Report on importing software from the USA. At this time the Post Office handling charge was a mere two pounds 50p for parcels; and you paid the post man the vat and duty in cash! (No longer the case- the handling charge is now Eight Pounds and you have to go to the collection office to pay it). Also at this stage there was no duty or vat on parcels worth up to fifty pounds- that has now been reduced to 15 pounds, and VAT is now 20%. It costs a lot more to import low value items now than it did in 1982.
Comparitive prices of UK purchases and imports, after paying the handling fee, postage from the US, and VAT at 15%:
U K Price | Final cost
. . . . . | of import . . Item
in pounds |in pounds
. . 19.95.|...13.50....Zero Zap module
. . 29.95.|...13.50....Teach Yourself Extended Basic
. . 24.95.|...16.50....Programming Aids Two on Disk
=============

Freeform Art
30 REM FREEFORM ART BY STEPH
EN SHAW 1982 SUBPROGRAMS BY:
40 REM PETER BROOKS AND
50 REM JEREMY RUSTON
60 CALL CLEAR::PRINT "FREE F
ORM ART":"1982":"STEPHEN SHA
W":"PETER BROOKS":"JEREMY RU
STON":::
70 PRINT "RANDOM DESIGN":"CU
RSOR WILL APPEAR":"AT TOP WH
EN NO MORE CHARS & AT BOTTOM
WHEN DESIGN ENDED"::"PRESS
ENTER FOR ANOTHER "
72 PRINT "DESIGN"::
80 ACCEPT AT(24,20):Q$::CALL
CLEAR
100 REM RESERVED: B1 C HI1 P
1 RS1 X1 Y1 B$ C$()H$ I$P$ Z
$ R<192 C<256 USE GOSUB 2970
0 ***PLOT*
110 CALL SCREEN(16)::S1=31::
CALL HCHAR(1,1,S1,768)::DIM
C$(120)::B$="0000.0001.0010.
0011.0100.0101.0110.0111.100
0.1001.1010.1011"
120 B$=B$&"1100.1101.1110.11
11"::H$="0123456789ABCDEF"::
Z$=RPT$("0",16)
130 RANDOMIZE::CALL HCHAR(1,
1,31,768)::S=31 ! RESTART HE
RE
140 XX=INT(RND*110+40)::YY=I
NT(RND*110+40)::LL=INT(RND*1
10+40)::MM=INT(RND*100+40)::
UU=(10-RND*20)
150 VV=(10-RND*20)::PP=(10-R
ND*20)::QQ=(10-RND*20)::FOR
K=1 TO 30
160 X2=XX::Y2=YY::X3=LL::Y3=
MM::GOSUB 240
170 IF XX+UU>150 OR XX+UU<40
THEN UU=-UU
180 IF YY+VV>150 OR YY+VV<41
THEN VV=-VV
190 IF LL+PP>150 OR LL+PP<39
THEN PP=-PP
200 IF MM+QQ>148 OR MM+QQ<38
THEN QQ=-QQ
210 XX=XX+UU::YY=YY+VV::LL=L
L+PP::MM=MM+QQ::NEXT K
220 ACCEPT AT(23,4):KEY$
230 RANDOMIZE::GOTO 120
240 DX=X3-X2::DY=Y3-Y2::IF (
DX=0)+(DY=0) THEN 290
250 IF ABS(DX)>ABS(DY) THEN
270
260 FOR LCV=Y2 TO Y3 STEP SG
N(DY)::R=INT(.5+LCV)::C=INT(
.5+X2+DX/DY*(LCV-Y2))::GOSUB
340::NEXT LCV::RETURN
270 FOR LCV=X2 TO X3 STEP SG
N(DX)::C=INT(.5+LCV)::R=INT(
.5+Y2+DY/DX*(LCV-X2))::GOSUB
340::NEXT LCV::RETURN
280 IF (DX=0)-(DY=0) THEN 30
0
290 RETURN
300 IF DY=0 THEN 320
310 C=INT(.5+X2)::FOR LCV=Y2
TO Y3 STEP SGN(DY)::R=INT(.
5+LCV)::GOSUB 340::NEXT LCV:
:RETURN
320 !R=INT(.5+Y2):: FOR LCV=
X2 TO X3 STEP SGN(DX):: C=IN
T(.5+LCV):: GOSUB 340 :: NEX
T LCV :: RETURN
330 STOP
340 REM PLOT SUBROUTINE
350 Y1=MIN(INT(R/8+.875),24)
::X1=MIN(INT(C/8+.875),32)::
CALL GCHAR(Y1,X1,H1)::IF H1>
31 THEN 380
360 IF S1>=143 THEN CALL SOU
ND(900,440,0)::ACCEPT AT(1,1
) SIZE(-2) BEEP:ZED$::GOTO 1
30
370 S1=S1+1::C$(S1-31)=Z$::C
ALL CHAR(S1,Z$)::CALL HCHAR(
Y1,X1,S1)::H1=S1
380 H1=H1-31::B1=C-X1*8+8::P
1=2*R-16*Y1+16+(B1<5)::IF B1
<5 THEN 400
390 B1=B1-4
400 I$=SEG$(B$,POS(H$,SEG$(C
$(H1),P1,1),1)*5-4,4)::I$=SE
G$(I$,1,B1-1)&"1"&SEG$(I$,B1
+1,4-B1)::I1=POS(B$,I$,1)/5+
.8
410 C$(H1)=SEG$(C$(H1),1,P1-
1)&SEG$(H$,I1,1)&SEG$(C$(H1)
,P1+1,16-P1)::CALL CHAR(H1+3
1,C$(H1))
420 RETURN

==================

ETCH A SKETCH

40 CALL CLEAR::PRINT "ETCH A
SKETCH TYPE HIGH":"RESOLUTIO
N DRAWING PROG"
50 PRINT "":"STEPHEN SHAW 19
82":"PETER BROOKS"::"USE THE
8 ARROW KEYS TO MOVE THE PEN
(LIGHT RED DOT)":"PRESS KEY
1 TO LEAVE A TRACE"
60 PRINT "& KEY 2 TO SWITCH
TRACE OFF":::"PRESS ENTER TO
CONTINUE"::INPUT A$::CALL C
LEAR
100 REM KEYBOARD PLOTTER
110 CALL COLOR(0,11,11)
120 CALL INIT::CALL LOAD(-31
878,2)
130 REM RESERVED:B1 C H1 I1
P1 R S X1 Y1 B$ C$() H$ I$ P
$ Z$ R<192 C<256 USE GOSUB 2
9700 ***PLOT*
140 CALL SCREEN(2)::S1=32::C
ALL HCHAR(1,1,170,768)::DIM
C$(120)::B$="0000.0001.0010.
0011.0100.0101.0110.0111.100
0.1001.1010.1011"
150 CALL CHAR(32,"404")
160 CALL HCHAR(1,1,31,128)::
CALL HCHAR(21,1,31,128)::CAL
L VCHAR(1,1,31,140)::CALL VC
HAR(1,28,31,140)
170 RR=0
180 B$=B$&".1100.1101.1110.1
111"::H$="0123456789ABCDEF":
:Z$=RPT$("0",16)::FOR IQ=1 T
O 14::CALL COLOR(IQ,16,2)::N
EXT IQ
190 R=96::C=128
200 CALL SPRITE(#1,32,10,96,
128)
210 CALL KEY(1,K,T)::IF T=0
THEN 210 ELSE R=R+(K=4)+(K=5
)+(K=6)-(K+1=1)-(K=14)-(K=15
)::C=C+(K=2)+(K=4)+(K=15)-(K
=3)-(K=6)-(K=14)
220 IF K=19 THEN PR=1 ELSE I
F K=7 THEN PR=0
230 CALL LOCATE(#1,R,C)
240 IF PR=0 THEN 210
250 GOSUB 260::GOTO 210
260 REM PLOT SUBROUTINE
270 Y1=MIN(INT(R/8+.875),24)
::X1=MIN(INT(C/8+.875),32)::
CALL GCHAR(Y1,X1,H1)::IF H1<
144 THEN 300 ELSE IF H1>150
THEN H1=32
280 IF S1>=143 THEN CALL SOU
ND(900,440,0)::ACCEPT AT(1,1
) BEEP:ZED$::GOTO 190
290 S1=S1+1::C$(S1-31)=Z$::C
ALL CHAR(S1,Z$)::CALL HCHAR(
Y1,X1,S1)::H1=S1
300 IF H1=31 THEN 340 ELSE H
1=H1-31::B1=C-X1*8+8::P1=2*R
-16*Y1+16+(B1<5)::IF B1<5 TH
EN 320
310 B1=B1-4
320 I$=SEG$(B$,POS(H$,SEG$(C
$(H1),P1,1),1)*5-4,4)::I$=SE
G$(I$,1,B1-1)&"1"&SEG$(I$,B1
+1,4-B1)::I1=POS(B$,I$,1)/5+
.8
330 C$(H1)=SEG$(C$(H1),1,P1-
1)&SEG$(H$,I1,1)&SEG$(C$(H1)
,P1+1,16-P1)::CALL CHAR(H1+3
1,C$(H1))
340 RETURN

=================

TRIANGLES

10 CALL CLEAR::PRINT "TRIANG
LES"::"1982"::"STEPHEN SHAW"
:"PETER BROOKS":"JEREMY RUST
ON"::"RANDOMIZED DESIGNS"::"
CURSOR WILL APPEAR AT"
20 PRINT "TOP WHEN NO MORE C
HARS &":"AT BOTTOM WHEN PICT
URE":"IS FINISHED"::"PRESS E
NTER FOR ANOTHER":"DESIGN"::
:
50 RANDOMIZE::ACCEPT AT(24,2
4) BEEP:Q$
100 REM RESERVED:B1 C H1 I P
1R S1 X1 Y1 B$ C$() H$ I$ P$
Z$ R<192 C<256 USE GOSUB 29
700 ***PLOT*
110 CALL SCREEN(2)::S1=31::C
ALL HCHAR(1,1,S1,768)::DIM C
$(120)::B$="0000.0001.0010.0
011.0100.0101.0110.0111.1000
.1001.1010.1011"
120 B$=B$&".1100.1101.1110.1
111"::H$="0123456789ABCDEF":
:Z$=RPT$("0",16)::FOR IQ=1 T
O 14::CALL COLOR(IQ,16,2)::N
EXT IQ
130 S1=31::RANDOMIZE::AA=RND
*110+40::BB=RND*110+40::CC=R
ND*110+40::DD=RND*110+40::EE
=RND*110+40::FF=RND*100+40
140 UU=28*RND-14::VV=28*RND-
14::WW=28*RND-14::XX=28*RND-
14::YY=28*RND-14::ZZ=28*RND-
14
150 FOR KK=1 TO 10
160 X2=AA::Y2=BB::X3=CC::Y3=
DD::GOSUB 270
170 X2=X3::Y2=Y3::X3=EE::Y3=
FF::GOSUB 270
180 X2=X3::Y2=Y3::X3=AA::Y3=
BB::GOSUB 270
190 IF AA+UU>150 OR AA+UU<38
THEN UU=-UU
200 IF BB+VV>151 OR BB+VV<38
THEN VV=-VV
210 IF CC+WW>151 OR CC+WW<38
THEN WW=-WW
220 IF DD+XX>151 OR DD+XX<38
THEN XX=-XX
230 IF EE+YY>151 OR EE+XX<38
THEN YY=-YY
240 IF FF+ZZ>151 OR FF+ZZ<39
THEN ZZ=-ZZ
250 AA=AA+UU::BB=BB+VV::CC=C
C+WW::DD=DD+XX::EE=EE+YY::FF
=FF+ZZ
260 NEXT KK::ACCEPT AT(24,20
):AAA$::CALL HCHAR(1,1,31,76
8)::GOTO 130
270 DX=X3-X2::DY=Y3-Y2::IF (
DX=0)+(DY=0) THEN 310
280 IF ABS(DX)>ABS(DY) THEN
300
290 FOR LCV=Y2 TO Y3 STEP SG
N(DY)::R=INT(.5+LCV)::C=INT(
.5+X2+DX/DY*(LCV-Y2))::GOSUB
370::NEXT LCV::RETURN
300 FOR LCV=X2 TO X3 STEP SG
N(DX)::C=INT(.5+LCV)::R=INT(
.5+Y2+DY/DX*(LCV-X2))::GOSUB
370::NEXT LCV::RETURN
310 IF (DX=0)-(DY=0) THEN 33
0
320 RETURN
330 IF DY=0 THEN 350
340 C=INT(.5+X2)::FOR LCV=Y2
TO Y3 STEP SGN(DY)::R=INT(.
5+LCV)::GOSUB 370::NEXT LCV:
:RETURN
350 R=INT(.5+Y2)::FOR LCV=X2
TO X3 STEP SGN(DX)::C=INT(.
5+LCV)::GOSUB 370::NEXT LCV:
:RETURN
360 STOP
370 REM PLOT SUBROUTINE
380 Y1=MIN(INT(R/8+.875),24)
::X1=MIN(INT(C/8+.875),32)::
CALL GCHAR(Y1,X1,H1)::IF H1>
31 THEN 410
390 IF S1=143 THEN CALL SOUN
D(900,440,0)::ACCEPT AT(1,1)
BEEP SIZE(-2):ZED$::CALL HC
HAR(1,1,31,768)::GOTO 130
400 S1=S1+1::C$(S1-31)=Z$::C
ALL CHAR(S1,Z$)::CALL HCHAR(
Y1,X1,S1)::H1=S1
410 H1=H1-31::B1=C-X1*8+8::P
1=2*R-16*Y1+16+(B1<5)::IF B1
<5 THEN 430
420 B1=B1-4
430 I$=SEG$(B$,POS(H$,SEG$(C
$(H1),P1,1),1)*5-4,4)::I$=SE
G$(I$,1,B1-1)&"1"&SEG$(I$,B1
+1,4-B1)::I1=POS(B$,I$,1)/5+
.8
440 C$(H1)=SEG$(C$(H1),1,P1-
1)&SEG$(H$,I1,1)&SEG$(C$(H1)
,P1+1,16-P1)::CALL CHAR(H1+3
1,C$(H1))
450 RETURN

===================================

Program Storage:
Location -31952 and -31951 store the largest line number, e.g. actual usage:
CALL PEEK(-31952,A,B)

Gives A=247, B=248. Now using LOC=A*256+B-65536 we get LOC=-2056 so we:
CALL PEEK(-2056,A,B)

and A=21, B=144. Now using LINNUM= A*256+B we find that this program has the maximum line number of 400. Locations LOC+2 and +3 give the memory address for that line.

====================


TIdings Volume 2 Number 3, 30th June 1982-

Group membership now reported as 260.
This was the last issue of TIdings in A4 format, future issues to be photoreduced to A5.
New computer on the market - Sinclair Spectrum, 48k for gbp 175 - it was expected that the 16k TI99/4a price would fall to GBP 200 .

Peter Brooks raised a query regarding TE2 and speech, which he answered in the next issue- and his query was also answered by TI directly also in that issue. To have the computer LIST a program verbally, with TE2 and speech synthesiser, type LIST "SPEECH". There are some restrictions.
Robin Frowd, Product Manager at Texas Instruments Ltd contributed a three page article:
Big price reductions announced (eg TI Invaders from GBP 40 to GBP 20)
Peripheral Expansion Box to be available in the UK from August 1982.
Editor Assmbler coming soon for GBP 90.
The TI99/4a to be shown on stand 220/224 at the Personal Computer World show in London in September 1982.

I was authorised to distribute the programs of PRP Computergraphics in the UK (they never sold) and had 58 programs on sale.

Return to top of page

The big article in this issue was Designs for Fun by Peter Brooks. This list has been modified in line 130 per Pete Brooks October 1982. Here first is the simple TI Basic listing:

100 CALL CLEAR
110 CALL SCREEN(5)
120 OPTION BASE 1
130 DIM C$(24),D$(121)
140 H$="0123456789ABCDEF"
150 I$="084C2A6E195D3B7F"
160 L$="54433322222"
170 S$="01234789CEF"
180 S=LEN(S$)
190 DEF R=INT(RND*S+1)
200 INPUT "ENTER ROOT PATTER
N AREA:":Z
210 CALL CLEAR
220 Z=INT(Z)
230 IF (Z<1)+(Z>11) THEN 200
240 FOR L=33 TO 153 STEP 4
250 CALL CHAR(L,"0103070F1F3
F7FFF")
260 CALL CHAR(L+1,"80C0E0F0F
8FCFEFF")
270 CALL CHAR(L+2,"FF7F3F1FF
0F070301")
280 CALL CHAR(L+3,"FFFEFCF8F
0E0C08")
290 NEXT L
300 FOR L=1 TO Z
310 FOR M=1 TO Z
320 C$(L)=C$(L)&CHR$(32-Z+L*
Z+M)
330 NEXT M
340 NEXT L
350 FOR L=1 TO Z
360 FOR M=1 TO VAL(SEG$(L$,Z
,1))
370 C$(L)=C$(L)&C$(L)
380 NEXT M
390 C$(L)=SEG$(C$(L),1,28)
400 NEXT L
410 FOR L=Z+1 TO 24
420 C$(L)=C$(L-Z)
430 NEXT L
440 FOR L=1 TO 24
450 PRINT C$(L);
460 NEXT L
470 FOR L=1 TO Z*8
480 D$(L)=""
490 NEXT L
500 FOR L=1 TO Z*4
510 FOR M=1 TO Z
520 A$=SEG$(S$,R,1)
530 D$(L)=A$&D$(L)&SEG$(I$,P
OS(H$,A$,1),1)
540 NEXT M
550 D$(Z*8-L+1)=D$(L)
560 NEXT L
570 Q=33
580 FOR L=1 TO Z*8 STEP 8
590 FOR M=1 TO 2*Z-1 STEP 2
600 A$=""
610 FOR N=L TO L+7
620 A$=A$&SEG$(D$(N),M,2)
630 NEXT N
640 CALL CHAR(Q,A$)
650 Q=Q+1
660 NEXT M
670 NEXT L
680 GOTO 470

In 1990 I (Stephen Shaw) adopted this listing to be used with The Missing Link and Extended Basic.

Here is some of what Peter wrote in 1982:

Designs for Fun

To produce some (I think) startling patterns. An apparently random collection of dots and lines can become highly patterned when vertically- and horizontally-symmetrical images are added.

This particular version makes use of 121 of the 128 ASCII characters available for redefinition, and simply sets up a pattern area in response to your selection, and continuously generates random patterns. The larger the pattern area used, the longer the generation time.

How it's all done

Take an image composed of dots and lines. Place a mirror on the right edge of the image, so that it is reflected. This gives you the Left-Right symmetry (LR). Place another mirror along the bottom edge, so that both images above are reflected, giving you Up-Down symmetry (UD). Now transfer the whole pattern to the screen and duplicate it over the entire display area.

In essence, that is the algorithm (or set of algorithms) which defines the principle of operation of the "Designs For Fun" program.

You define your own shapes using CALL CHAR. To begin with, let's look at how the algorithm could be applied to the 8 × 8 dot matrix of a single character. In order for the finished image to fit within that matrix, the original shape will have to be confined to a quarter of that area: 4 × 4 dots in say the upper left hand corner.

The "source string", which is assigned to S$ in the listing.
In order to exert some small control over the types of design which are produced by the program, I decided to make the program select the hex digits at "random" not from H$ but from another string (S$) so that instead of being able to compose or create designs using the full range of "shapes" possible using the hex digits 0 to F inclusive, the choice could be restricted to a chosen set of particular hex digits. In this way, different types of pattern could be produced, still with some semblance of being random, but falling into what might be termed "categories".
For example, by assigning the digits F, E, C, and 8 to S$, the program can only select the shapes which are equivalent in binary to "1111", "1110", "1100", and "1000". This will tend to produce patterns which are heavy and dark, and on the whole rather angular. However, using 0, 1, 2, 4, and possibly 8, the images will tend to be light and ornate, perhaps too detailed. In addition, there is the factor of pattern area: the larger the pattern area, the more dispersed the shapes tend to be, depending on the source string.

Using a root area of 1 does not do full justice to strings like "12480". The frequency and position of the chosen digits within the source string does also have a large part to play, but there the effects are complicated by the "pseudo-random" number generator used by the 99; in fact, under certain circumstances, the PRNG (pseudo-random number generator) will generate the same series of numbers over and over again, which means that the patterns will also become cyclic; the use of RANDOMIZE without a "seed" should obviate this.

Additional experiments that you can perform involve removing the CALL CHAR in line 640 and placing it in 625, so that shapes change during the process of compilation, rather than after it. Also the sequence of compilation can be slightly changed: by concatenating the contents of A$ in line 620 to SEG$(D$(N),M,2) thus
620 A$=SEG$(D$(N),M,2)&A$
the shapes can be made to appear as though they are "dropping" into place, albeit very slowly. It doesn't make any difference to the pattern being produced. Why?


I wrote a piece about how the TI99/4a stores programs in token format:
Tokenization or how the 99/4(A) stores programs

When you enter or load a program into your Home Computer you do not need to know where in memory it is stored, or how it is stored. It is sufficient if your program RUNs OK! However, if you do know, you can use your knowledge to write programs which use less memory - e.g. get more out of your "16K".

If you have Extended Basic and the Expansion Memory, it is fairly easy to obtain these details (use CALL PEEK from 0 to -24K in -1 steps) - but what if you have only the console? With only the console, only one area of memory is used for everything - string and numeric variables, character definitions, and your program, etc.

Your program in stored in memory in two parts - the line numbers, and in a separate section the line contents.

Thus the Computer needs an index - and has one - to see where the line contents are! This is why a program line takes up 6 bytes before you put anything into it. The index uses four bytes - two bytes for the line number and two bytes for the memory location of its contents.

The length of the program line (in bytes) takes up one byte and an end of line separator takes up another byte. That's 6 bytes and nothing there yet!

If you have a line i.e. 100 REM, how many bytes is that going to take up? The 99/4(A) uses a single byte for Basic commands - such as REM. So this simple line will take up 7 bytes of memory.

If the sample is 100 GOTO 120, how many bytes? GOTO as we have seen uses ONE byte (but if you use GO TO which is two command words, that uses two bytes).

The LINE NUMBER 120 takes up 3 bytes - the first a marker to say "this is a line number" and the next two the actual number (if the first byte is A, the 2nd is B, the line number will be A*256+B). So this line uses up 10 bytes.

If the sample is 100 B=C then B, =, and C each take up one byte, making a line total of 9 bytes.

However 100 B=3456 will take up 14 bytes. B and = use 1 byte. The number 3456 takes up 6 bytes - four for 3456, and one to indicate "number". The other byte says how many characters are in the number. HINT: If memory in tight, replace all numbers used a few times by numeric variables.

String variables are dealt with in a similar manner. One byte says "this is a string", another "this is string length" if you use a quoted string. If you use a string variable, only the characters in your listing take up space, e.g. "TEST" is 6 bytes, "TST$" is 4 bytes.

The CALL routines use what are called UNQUOTED STRINGS - that is the word following CALL is a string, but without quotes. You cannot therefore use CALL A$ - 'cos A$ has quotes.

CALL COLOR uses one byte for CALL and 7 bytes for COLOR, two bytes say "unquoted string" and "length of string".

Using a lot of CALLs can eat into your memory - well worth using GOSUBS if you can.
(100 GOSUB 140 = 10 bytes, remember! )
(150 RETURN = 7 bytes )
The "tokens" which take up one byte of memory to indicate these commands and so on, are numeric values 129 to 254 - but not all are used. The ones used are listed below, Note the same codes are used for Extended Basic as for TI Basic, but some codes cannot be translated by TI Basic and will appear on your screen as funny characters.

PRINT : takes up two bytes in both languages, but PRINT :: also takes up two bytes in Extended Basic, as :: is covered by a one byte token.

The codes for !@P- and !@P+ are not known at present (used in Extended Basic v110). When you use a NUMERIC variable the value resides in its own memory location and uses 8 bytes. If you keep a careful watch on your numeric variables, and don't use more than you really need, you can save worthwhile memory space.

Similarly, if you use DIM, 8 bytes are set aside for each numeric value, e..g DIM B(7,8) sets aside 7*8*8 bytes if you use OPTION BASE 1, or 8*9*8 bytes if you don't.

If you use a two-dimensioned subscript without using DIM, because neither of the values exceeds ten, in OPTION BASE 0 the computer will set aside 11*11*8 bytes. That is a lot of memory gone west if you are not using it.

Hint: Always DIM numeric arrays. Use OPTION BASE 1 if you are not going to use 0 as the subscript.

String arrays are not so heavy on memory, a mere two bytes being set aside for each possible subscript. (Replace 8 with 2 in above examples.)

Incidentally, using the same block of memory for everything CAN cause a lockout if you RUN, EDIT, RUN, EDIT - the lockout occurring much earlier if your program is a long one.

Have you noticed your computer pausing for a second every now and then? When you redefine a variable, the old value remains in memory, taking up space. When you have defined enough times, there is no more memory, and the "rubbish" is kicked out. The 99/4A is remarkably efficient at this process, but it still takes a little time. The old definitions are not kicked out immediately, to give a faster running program.


TML Version of DFF

My notes with my TML version of the Designs for Fun program in 1990 (I can't see it listed in the UK User Group magazine!) were as follows:

During pattern generation:
Press and hold key S to return to main menu.
User prompted pattern change: Any key except S and A for next pattern.
To print: Hold CTRL and FCTN together.
To save in TI-Artist format: Once the pattern is on screen and before the definitions at screen bottom start to change, press and hold key A. Indicate drive number, then file name (up to 8 characters, omit _P). Easier to use if user prompt mode is specified.
Patterns saved in TI-Artist format can then be cut out into Instances and used for texture or repeated over the full screen as required before printing. Can be used for book jackets or fly leaves or even wallpaper (enlarge and use as a crosswork design, etc.).
As listed the equivalent character definitions are given at screen bottom.

The TML version of the program is quite lengthy but I have it as a simple text file DFFTML.TXT which you may be able to copy and paste into a TI99/4a emulator, but note that some program lines extend over two text lines and may require some clean up on pasting. As the lines have maximum compaction you may need to split some long lines to get them in, and as memory is also tight set CALL FILES(1) and possibly remove some lines.... it ran OK in 1990 but TML has since been modified.


Access Key Details
Stephen's Entry Page   |    TI99/4a   |  Linux |  Search   |   History St Thomas Church Heaton Chapel |   Entertainment   | Music Links

Light Reference   |   Educational Reference   |   Science Fiction   |   Travel    |   News Links   |   Anime