Web article two- published March 1999 
Includes:                                 
Tips on programming menu choices; Using the various TI99/4A 
graphics programming  packages with examples;  how to use Basic 
PRINT USING;  Jim Peterson's   Tips No 65    
                                          
MENU CHOICES
         
TIPS was a commercial clip art program for the TI99/4A.
The TIPS program allows you to input the name of a graphic - but it goes a
little farther than that. You do not have to key in the full name of the
graphic, just enough to identify it. If there is more than one possible match,
the program selects the first possible.
  For example, if the graphics on file are ANT, APE, APPLE, when you select A
you will have an ANT, if you type AP you will have an APE and for APP you get
an APPLE.
We can copy this into our Basic programs when a typed selection is required,
like this:
1 ! AS TIPS CHOICE 
2 !
3 ! INPUT AS LITTLE AS IS
4 ! REQUIRED TO IDENTIFY
5 ! CHOICE
6 !
7 ! FIRST MATCH IS
8 ! SELECTED IF MORE THAN
9 ! ONE CHOICE
10 !
92 !
93 ! DATA IS SORTED
94 !
100 DIM A$(25)
110 DATA BACK,BAG,BOA,BODY,B
OND,BONE,CAB,CABIN,CABINET,C
AKE,CAR,CARD,CARE,CAROL,CARP
,CART,CASE,CASK,CAT,,,
120 FOR T=1 TO 19 :: READ A$
(T):: NEXT T
130 REM
140 PRINT "SELECT FROM":
150 FOR T=1 TO 19 :: PRINT A$(T);"  ";:: NEXT T
160 PRINT "":"":"":""
170 REM
180 INPUT B$
190 LA=LEN(B$)
200 FOR T=1 TO 19
210 IF B$=SEG$(A$(T),1,LA)THEN 240
220 NEXT T
230 PRINT "UNABLE TO MATCH":"":"" :: GOTO 140
240 PRINT "MATCHED ON ";A$(T):"":"":"":""
250 GOTO 130
260 END
Users of other computers will be used to more sophisticated selection routines,
and we can go a little way towards these in Basic - not quite as fast as
machine code perhaps, but usable... in the following listing, the four arrow
keys are usable... see if you can follow the different inputs for different
choices. And don't type too fast when inputting a choice...
100 ! AS PC CHOICE
110 !
120 ! INPUT AS LITTLE AS IS
130 ! REQUIRED TO IDENTIFY
140 ! CHOICE
150 !
160 ! FIRST MATCH IS
170 ! DISPLAYED. TYPE MORE
180 ! IF REQUIRED OR USE
190 ! ARROW KEYS E&S (WITH
200 ! FCTN KEY! )
210 !
220 !
230 ! DATA IS SORTED
240 !
250 DIM A$(25)
260 !
270 DATA BACK,BAG,BOA,BODY,B
OND,BONE,CAB,CABIN,CABINET,C
AKE,CAR,CARD,CARE,CAROL,CARP
,CART,CASE,CASK,CAT,FORD,FOR
K,FORT,,,
280 FOR T=1 TO 22 :: READ A$(T):: NEXT T
290 REM
300 PRINT "SELECT FROM":
310 FOR T=1 TO 22 :: PRINT A$(T);"  ";:: NEXT T
320 PRINT "":"":"":""
330 PRINT "after first letter typed,   use fctn e and fctn x to   
 move up and down list or    carry on typing":"":"":
340 ROW=24 :: COL=3
350 CALL HCHAR(ROW,COL,30)::
 CALL KEY(5,X,Y):: IF Y>0 TH
EN 370 ELSE  CALL HCHAR(ROW,
COL,32):: GOTO 350
360 !
370 CALL HCHAR(ROW,COL,X):: COL=COL+1 :: B$=B$&CHR$(X):: LB=LEN(B$)
380 !
390 FOR T=1 TO 22
400 IF B$=SEG$(A$(T),1,LB)THEN DISPLAY AT(24,1):A$(T):: GOTO 460
410 !
420 IF B$<A$(T)THEN T=T-
1 :: CALL SOUND(100,140,4)::
 DISPLAY AT(24,1):A$(T):: B$
=SEG$(B$,1,1):: LB=LEN(B$)::
 GOTO 460
430 !
440 NEXT T :: CALL SOUND(100,200,4):: T=22 :: DISPLAY AT(24,1):A$(T)
450 !
460 ! FIRST LETTER CHOSEN
470 ! NOW IS IT WHAT WE WANT?
480 CALL HCHAR(23,3,32,28)
490 CALL HCHAR(23,3,95,28)
500 !
510 CALL KEY(5,X,Y):: IF Y<1 THEN 510
520 IF X=13 THEN 640 ! GOT IT
530 IF X=11 AND T>1 THEN T=T-1 :: DISPLAY AT(24,1):A$(T):: B$=SE
G$(A$(T),1,LB):: GOTO 460
540 IF X=11 AND T<2 THEN CALL SOUND(200,200,4):: GOTO 460
550 IF X=10 AND T<22 THE
N T=T+1 :: DISPLAY AT(24,1):
A$(T):: B$=SEG$(A$(T),1,LB):
: GOTO 460
560 IF X=10 AND T=22 THEN CA
LL SOUND(200,200,4):: GOTO 460
570 IF X=8 AND LB>1 THEN B$=
SEG$(B$,1,LB-1):: LB=LEN(B$)
:: GOTO 390
580 IF X=9 AND LB<LEN(A$(T)
)THEN B$=SEG$(A$(T),1,LB+1):
: :: LB=LEN(B$):: GOTO 390
590 !
600 IF X<32 THEN 390
610 !
620 CALL SOUND(100,800,13)
630 B$=B$&CHR$(X):: DISPLAY AT(24,1):B$ :: LB=LEN(B$):: GOTO 390
640 CALL CLEAR :: PRINT "CHOICE WAS":"":A$(T)
650 RUN
Return to top of page
====================================
 
TI Logo was designed for the TI99/4, and in the absence of pixel graphics, utilised a routine which continually redefined characters (or tiles) as you drew on the screen. Sooner or later you ran out of characters, and in the colourful terms of TI Logo, you ran out of ink!
Back in 1982, we were blessed with a routine in TI Basic which allowed high resolution graphics plotting, continually redefining characters, thanks to Peter Brooks, a felow founder member of the first UK user group. This was painfully slow, and as TI Basic does not have CALL CHARPAT had to make use of a large string array, and also boolean algebra had to be done the hard way.
Then along came Extended Basic, which I think most people now have? And Gary
Harding rewrote Peter's routine making use of CHARPAT and OR. The program below
is an example of its use. The maths is placed in a subroutine, so the only
variable you need to avoid in your inserted routines is S, which keeps track of
which character we are redefining.
100 ! hi res plotting - ti ex bas only
110 ! after brooks, harding etc.
120 ! initialise:
130 S=31 :: FOR C=0 TO 14 :: CALL COLOR(C,16,2) :: NEXT C
140 CALL HCHAR(1,1,S,768) :: CALL SCREEN(2)
150 !
160 !
170 !
180 ! YOUR PROGRAM HERE
190 !
200 !
210 FOR COL=40 TO 140 STEP 100 :: FOR ROW=20 TO 160
220 CALL PLOT(ROW,COL,S) :: NEXT ROW :: NEXT COL
230 !
240 FOR RAD=0 TO 6.5 STEP 0.0125
250 CALL PLOT(36*SIN(RAD)+99,36*COS(RAD)+76,S) :: NEXT RAD
260 !
270 !
280 !
10000 GOTO 10000
10010 STOP
10020 !
30000 SUB PLOT(R,C,S)
30010 IF R>190 OR C>254 THEN SUBEXIT
30020 IF R<1 OR C<1 THEN SUBEXIT
30030 R=INT(R+.4) :: C=INT(C+.4)
30040 Y=INT(R/8+0.875) :: X=INT(C/8+0.875)
30050 H$="0123456789ABCDEF"
30060 B=C-X*X+8 :: P=2*R-16*Y+16+(B<5)
30070 IF B>4 THEN B=B-4
30080 CALL GCHAR(Y,X,H)
30090 IF H>31 THEN 30120 ELSE IF S=143 THEN SUBEXIT
30100 S=S+1 :: D$=RPT$("0000",4) :: CALL CHAR(S,D$)
30110 CALL HCHAR(Y,X,S) :: H=S :: GOTO 30130
30120 CALL CHARPAT(H,D$)
30130 N=(POS(H$,SEG$(D$,P,1),1)-1)OR(S^(4-B))
30140 D$=SEG$(D$,1,P-1)&SEG$(H$,N+1,1)&SEG$(D$,P+1,16-P)
30150 CALL CHAR(H,D$) :: SUBEND
31000 ! ORIGINAL ROUTINE TIDINGS OCT 1982
Yes it is just a little slow, but remember it is all Extended Basic with no
extras required, no disk drive, no 32k ram!
Chuck also wrote directly to me, asking about using the Drawnplot routines to
be found in the Triton module Super Extended Basic.
When driven from a program, Drawnplot has only a limited set of commands, but
sufficient for our purposes. The biggest drawback -to me! - is that the image
does not appear on the screen until it is finished. For a lengthy chaotic or
fractal image this can mean a long time with nothing obvious happening, so in
the program below I have added a screen counter. During processing some odd
characters appear on the screen - ignore them! - Drawnplot does not really like
you to use the screen while it is plotting!
The program below is a routine for a chaotic graphics plot, and really does
take a very long time to finish! The end result is interesting as total order,
represented by a single line, becomes total chaos after repeated bifurcation.Super Extended Basic requires that you have the 32k ram attached, and you enter
the graphics mode by typing the command sequence:
CALL FILES(2) NEW CALL INIT CALL DRAWNPLOT
10 ! high resolution graphics using
20 ! triton super extended basic and 32k ram
30 ! after brooks, harding etc
40 !
100 CALL LINK("GCLEAR")
110 ! ORBITDGM PROGRAM
120 ! OR insert your program here:
130 FOR C=-2 TO 0.25 STEP .00625
140 X=0 :: M=160*(C+2) :: FOR I=0 TO 200
150 X=X*X+C :: IF I<50 THEN 170
160 N=(180/4)*(2-X) :: CALL PSET(M,N)
170 NEXT I
172 NEXT C
180 CALL LINK("MOVE",80,160)
190 CALL LINK("LABEL","Press E to Exit")
200 CALL LINK("SHOW")
210 STOP
10000 SUB PSET(X,Y)
10010 CALL LINK("MOVE",X,Y) :: CALL LINK("DRAW",X,Y)
10020 SUBEND
-  -  -  -  -         
It would be amiss of me not to make this a complete article by covering some
other possibilities...      
For Myarc Extended Basic, you require the Myarc module, Myarc expansion memory,
and the disk and rom chip supplied with the module. The listing immediately
above needs the following changes:
100 CALL GRAPHICS(3) 180 REM 190 CALL WRITE(0,160,80,"* done *") 200 REM 10010 CALL POINT(1,X,Y)
100 CALL LINK("CLEAR")
180 REM
190 CALL LINK("PRINT",160,80,"* DONE *")
200 REM
10010 CALL LINK("PIXEL",X,Y)
100 CALL LOAD(-31890,56,0) :: CALL LOAD(-31964,56,0)
105 CALL LINK("CLEAR") :: CALL LINK("SCR2")
180 REM
190 REM
200 REM
10010 CALL LINK("POINT",16,X,Y)
100 REM CIRCLES
110 REM JE CONNETT/PWH MOON/ 
 
S SHAW 1990 
 
120 SIDE=20 
 
130 REM 
 
140 CALL LINK("CLEAR") 
 
150 FOR I=1 TO 150 :: FOR J= 
 
1 TO 150 
 
160 X=I*SIDE/150 :: Y=J*SIDE 
 
/150 :: C=INT(X*X+Y*Y):: D=C 
 
/2 :: IF D-INT(D)>.1 THEN 180 
 
170 CALL LINK("PIXEL",I+20,J+20) 
 
180 NEXT J :: NEXT I 
 
190 PIC=PIC+1 :: A$="DSK2."&STR$(PIC) 
 
200 CALL LINK("SAVEP",A$) 
 
210 SIDE=SIDE*1.2 :: GOTO 140 
 
220 END 
 
=========================== 
 
100 CALL LINK("CLEAR") 
 
110 H=240 :: V=180 
 
120 REM 
 
130 REM 
 
140 X=6.10 
 
150 Y=6.00 
 
160 REM 
 
170 REM 
 
180 FOR L=1 TO 3299 
 
190 NX=1-Y+ABS(X):: NY=X :: X=NX :: Y=NY 
 
200 A=100+X*7-Y*7 
 
210 B=70+X*7+Y*7 
 
220 CALL LINK("PIXEL",A,B) 
 
230 NEXT L 
 
240 CALL LINK("PRINT",180,180,"END") 
 
250 X=8.30 :: Y=8.02 
 
260 FLAG=FLAG+1 :: IF FLAG>2 
 
 THEN 260 ELSE IF FLAG>1 THE 
 
N X=8.56 :: Y=3.76 :: GOTO 1 
 
60 ELSE GOTO 160 
 
--------------------------------- 
100 CALL LINK("CLEAR")
110 H=240 :: V=180
120 REM
130 REM
140 X=-.100000000001
150 Y=0
160 REM
170 REM
180 FOR L=1 TO 5299
190 NX=1-Y+ABS(X):: NY=X :: 
X=NX :: Y=NY
200 A=100+X*14-Y*14
210 B=60+X*14+Y*14
220 CALL LINK("PIXEL",A,B)
230 NEXT L
240 CALL LINK("PRINT",180,18
0,"END")
260 GOTO 260
==============================
               
Return to top of page
============================
                                                        
Tips from the Tigercub Issue 65.                        
Note: Jim died a few years back. He contributed some 72 monthly
articles to TI user groups.  He always formatted them for 28 column
printing- here presented as he produced it. Depending on your screen size you may see one two or three 
columns!  Each pseudo-page is separated by two short rows of equals signs:
=========== 
 ===========
If your screen is wide enough for three columns each pseudo-page will about fit onto one screen. With one or two columns you will need to scroll, sorry.
---------------------------------------
 
 
      
                                   
           
      No. 65                  
 
                                        
      
       Tigercub Software           
 
          1N6 Nnuyngwood Ave.           
      
      ZxCdmbus, OH 43XY3           
 
                                        
      
          *********                 
                                         
        My   three  Nuts  &  Bolts   
      disks,  each  containing 100       
      or  more  subprograms,  have       
      been reduced to $5.00. I  am       
      out of printed documentation       
      so  it  will be  supplied on       
      on disk.                           
        My  TI-PD library now  has       
      well over 500 disks of fair-       
      ware (by author's permission       
      only) and public domain, all       
      arranged  by"category and as       
      full  as  possible, provided       
      with loaders by full program       
      name  rather  than filename,       
      Basic  programs converted to       
      XBasic,  etc.  The  price is       
      just $1.50 per disk(!), post       
      paid  if  at least eight are       
      ordered.  TI-PD  catalog  #5       
      and the latest supplement is       
      available  for  $1  which is       
      deductible  from  the  first       
      order.                             
                                         
        It  is a bit of a nuisance       
      to  have  to hit Enter after       
      inputting a single character       
      such  as Y or N for "yes" or       
      "no".  CALL  KEY  accepts  a       
      single   character   without       
      Enter, but  has  no blinking       
      cursor  to  tell you that it       
      is  waiting.  I  should have       
      had  this  one  in my Nuts &   
      Bolts  years  ago - the CALL       
      KEY  WITH CURSOR subprogram!       
      R  is  the row, C is the TAB       
      position,  V$ is the valida-       
      tion string, such as "YyNn",       
      and  the  character selected       
      is returned in K$.                 
                                         
      30000 SUB CALLKEY(R,C,V$,K$)       
      30001 CALL HCHAR(R,C+2,30)::       
       FOR T=1 TO 3 :: CALL KEY(0,       
      K,S):: IF S<>0 THEN 30004       
      30002 NEXT T :: CALL HCHAR(R       
      ,C+2,20):: FOR T=1 TO 3 :: C       
  ALL KEY(0,K,S):: IF S<>0 THE 
  N 30004 
  30003 NEXT T :: GOTO 30001 
  30004 IF POS(V$,CHR$(K),1)=0 
  THEN 30001 ELSE K$=CHR$(K) 
  30005 SUBEND 
    
    And for a demonstration of 
  the  use of that subprogram, 
      here  is  a little game that 
  no one will ever play to the 
  end - 
    
  100 DISPLAY AT(3,6)ERASE ALL 
  :"THE ULTIMATE TEST":"":" An 
  swer the question with a num 
  ber according to whether the  
   number or color shown," 
  110 DISPLAY AT(8,1):"or the 
  note sounded, was 1stor 2nd 
  or 3rd, etc." 
  120 DISPLAY AT(23,6):"PRESS 
  ANY KEY" :: DISPLAY AT(23,6) 
  :"press any key" :: CALL KEY 
  (0,K,SS):: IF SS=0 THEN 120 
  ELSE CALL CLEAR 
  130 DATA 2,BLACK,3,GREEN,5,B 
  LUE,9,RED,12,YELLOW,14,PURPL 
  E 
  140 FOR J=1 TO 6 :: READ C(J 
  ),C$(J):: CT$=CT$&CHR$(J):: 
  W$=W$&CHR$(J+48):: NEXT J :: 
   T=2 :: DL=500 :: V$="12" 
  150 RANDOMIZE :: T$,NN$=CT$ 
  :: FOR J=1 TO T :: X=INT(RND 
  *LEN(T$)+1):: X$=SEG$(T$,X,1 
  ):: T$=SEG$(T$,1,X-1)&SEG$(T 
  $,X+1,255):: Y(J)=ASC(X$) 
  160 X=INT(RND*LEN(NN$)+1):: 
  X$=SEG$(NN$,X,1):: NN$=SEG$( 
  NN$,1,X-1)&SEG$(NN$,X+1,255) 
  :: S(J)=ASC(X$):: NEXT J :: 
  FOR J=1 TO T 
      170 Z(J)=INT(89*RND+10):: FO 
  R K=1 TO J-1 :: IF Z(J)=Z(K) 
  THEN 170 
  180 NEXT K :: NEXT J :: CALL 
   CLEAR :: CALL COLOR(3,16,1, 
  4,16,1)         
  190 FOR J=1 TO T :: CALL SCR 
  EEN(C(Y(J))):: CALL SOUND(-9 
  99,110*S(J),0):: DISPLAY AT( 
  12,12):Z(J):: FOR D=1 TO DL 
  :: NEXT D :: NEXT J 
  200 CALL CLEAR :: CALL SCREE 
     N(16):: CALL COLOR(3,2,1,4,2 
  ,1):: X=INT(3*RND+1):: W=INT 
  (T*RND+1):: ON X GOTO 210,23 
      0,210                         
      
      210 IF X=1 THEN Q$=C$(Y(W))E       
 
      LSE IF X=3 THEN Q$=STR$(Z(W)        
      )                                   
      220 DISPLAY AT(12,1):"WHICH         
      WAS ";Q$ :: GOTO 240                
      230 CALL SOUND(1,30000,30)::        
       DISPLAY AT(12,1):"WHICH WAS        
      ?" :: FOR D=1 TO 200 :: NEXT        
       D :: CALL SOUND(500,110*S(W        
      ),0)                                
      240 CALL CALLKEY(12,20,V$,K$        
      ):: Q=ASC(K$)-48                    
      250 IF Q=W THEN DISPLAY AT(1        
      5,12):"RIGHT!" ELSE DISPLAY         
      AT(15,12):"WRONG!"                  
      260 IF Q=W THEN DL=DL-50 ELS        
      E DL=DL+50                          
      270 IF DL<100 THEN DL=500 ::     
       T=T+1 :: V$=SEG$(W$,1,T)           
      280 GOUO 150                        
      290 SUB CALLKEY(R,C,V$,K$)          
      300 CALL HCHAR(R,C+2,30):: F        
      OR T=1 TO 3 :: CALL KEY(0,K,        
      S):: IF S<>0 THEN 330            
      310 NEXT T :: CALL HCHAR(R,C        
      +2,20):: FOR T=1 TO 3 :: CAL        
      L KEY(0,K,S):: IF S<>0 THEN      
      330                                 
      320 NEXT T :: GOTO 300              
      330 IF POS(V$,CHR$(K),1)=0 T        
      HEN 300 ELSE K$=CHR$(K)             
      340 SUBEND                          
                                          
        I  have  warned repeatedly        
      over  the  years,  in  these        
      Tips and in Micropendium and        
      elsewhere,   that   printing        
      program listings through the        
      Funlweb   Formatter  usually        
      results  in garbled listings        
      that cannot be keyed in cor-        
      rectly - but I still see the        
      garbled  listings published.        
      Here is a fix to the Funlweb        
      FO  file that will partially        
      solve the problem -                 
      Boot  DSKU.  Select  1. File        
      Utilities.  Select  5.  Find        
      String.  Enter  filename  FO        
      and the drive number.  Enter        
      H for hex.  Enter the string        
      2A23214026 .  Enter  replace        
      string 7C2321605C . When the        
      string is found, enter R for        
      replace,  then  CTRL W,  hit        
      Enter  twice  to  accept the        
      defaults.  Thereafter,   use        
 FCTN Z instead of & to under 
 line, FCTN C instead of @ to 
 double-strike,  and  FCTN  A 
 instead of * to call a value 
 added file. I don't know why 
 Texas  Instruments didn't do 
 that in the first place, and 
 I  wonder  why the McGoverns      
  
 didn't make that fix. 
   Now,  can  anyone  tell me 
 how  to replace the ^, which 
 tends  to disappear, and the 
 period,  which will make the 
 whole  line  disappear if it 
 happens  to be at the begin- 
 ning of the line? 
   
   If  you are one of the few 
    who  are still interested in 
 recreational computing - the 
 use of the computer to solve 
 puzzles  and  math  problems 
 just for the fun of it - you 
 might  be interested in Rec- 
    reational   and  Educational 
 Computing, published 8 times 
 a year at xyz tyulet Terrace 
    (REC is no more alas) . The 
 annual  subscription is $36. 
 Program listings are in dia- 
 lects of Basic other than TI 
 but usually not hard to con- 
 vert. 
   That is where I found this 
 ridiculously  short,  simple 
 and fast card shuffling rou- 
 tine. 
   
 100 DIM C(52) 
 110 FOR X=1 TO 52 :: C(X)=X 
 :: NEXT X 
 120 FOR X=52 TO 1 STEP -1 :: 
  I=INT(RND*X+1) 
 130 T=C(I):: C(I)=C(X):: C(X 
 )=T :: NEXT X 
   
   In  the same place, I read 
 a  routine to extract a root 
 to 16-digit accuracy instead 
 of  the  8  digits available 
 on  a PC from the basic for- 
 mula  ROOT=NUMBER^(1/POWER). 
 We don't need it - our obso- 
 lete 16k 16-bit computer can 
 give  us  14-digit  accuracy 
 from the basic formula! 
   
   The  same publication gave 
       me  the idea for this little     
      game -                            
                                        
      100 DISPLAY AT(3,6)ERASE ALL      
      :"THE GAME OF N":"":"You and      
       the computer will   take tu      
      rns adding to a num- ber to       
      reach a goal."                    
      110 DISPLAY AT(8,1):"If you       
      reach the goal, you  win. Yo      
      u get to go first andyou sho      
      uld be able to win   almost       
      every time."                      
      120 RANDOMIZE :: N=INT(RND*1      
      5)+15 :: R=INT(4*RND+3):: S=      
      R+1 :: D=N-INT(N/S)*S :: T=0      
      130 DISPLAY AT(13,1):"The go      
      al is";N:"":"Maximum input i      
      s";R :: DISPLAY AT(19,1):RPT      
      $(" ",96)                         
      140 DISPLAY AT(17,1):"Your n      
      umber?" :: ACCEPT AT(17,14)S      
      IZE(1)VALIDATE(DIGIT):A :: I      
      F A<1 OR A>R THEN DISPLAY AT   
      (15,1):"" :: GOTO 130             
      150 T=T+A :: DISPLAY AT(21,1      
      ):"Total is";T :: IF T=N THE      
      N DISPLAY AT(23,1):"YOU WIN!      
 
      " :: GOSUB 190 :: GOTO 120        
      160 IF N-T<S THEN P=N-T :: T   
      =T+P :: DISPLAY AT(19,1):"Co      
      mputer adds";P :: DISPLAY AT      
      (21,1):"Total is";T :: DISPL      
      AY AT(23,1):"COMPUTER WINS!"      
       :: GOSUB 190 :: GOTO 120         
      170 IF T=0 THEN P=D ELSE IF       
      (N-T)/S=INT((N-T)/S)THEN P=I      
      NT(R*RND+1)ELSE Y=N-T :: P=Y      
      -INT(Y/S)*S                       
      180 T=T+P :: DISPLAY AT(19,1      
      ):"Computer adds";P :: DISPL      
      AY AT(21,1):"Total is";T ::       
      GOTO 140                          
      190 DISPLAY AT(24,8):"PRESS       
      ANY KEY" :: DISPLAY AT(24,8)      
      :"press any key" :: CALL KEY      
      (0,K,S):: IF S=0 THEN 190 EL      
      SE T=0 :: RETURN                  
                                        
        REC  also printed a puzzle      
      which  seemed so simple that      
      I could not see why. It goes      
      like this -                       
        A game show host shows you      
      three  curtains.  Behind one      
      is  a  new  car,  behind the      
      other  two  are  goats.  You      
      choose  one.  The  host, who      
    can peek behind the curtain, 
   opens  one  of those you did 
   not  pick, and shows a goat. 
   Then  he  offers  to let you 
   change  your  choice. Should 
   you  switch,  stand  pat, or 
   does it make no difference? 
     You  now have a 50-50 bet, 
   so  it  makes no difference, 
   right? But some very distin- 
   guished  mathematicians were 
   saying you should switch, so 
   I wrote  this computer simu- 
   lation  to prove them wrong. 
   Key  it  in,  run it, and be 
   surprised.  Do  figures lie? 
   Do  computers  lie? Is there 
   something wrong with my sim- 
   ulation? 
        
   100 CALL CLEAR 
   110 DATA CAR BEHIND,A PICKS, 
   HOST SHOWS,A WINS,B WINS,C W 
      INS 
   120 FOR J=1 TO 3 :: READ M$ 
   :: DISPLAY AT(J,1):M$ :: NEX 
   T J :: FOR J=12 TO 14 :: REA 
   D M$ :: DISPLAY AT(J,1):M$ : 
   : NEXT J 
      130 FOR J=1 TO 1000 :: RANDO 
   MIZE :: X=INT(3*RND+1):: DIS 
   PLAY AT(1,13):X !RANDOMLY PL 
   ACE CAR 
   140 A=INT(3*RND+1):: DISPLAY 
    AT(2,13):A !PLAYER CHOOSES 
   150 E=INT(3*RND+1):: IF D=X 
   OR D=A THEN 150 :: DISPLAY A 
   T(3,13):D :: ! HOST PICKS CU 
   RTAIN WITH GOAT 
   160 IF A=X THEN AA=AA+1 :: D 
   ISPLAY AT(12,7):AA ! A DOES 
   NOT SWITCH 
   170 B=INT(3*RND+1):: IF B=A 
   OR B=D THEN 170 
   180 IF B=X THEN BB=BB+1 :: D 
   ISPLAY AT(13,7):BB ! B SWITC 
   HES 
   190 C=INT(3*RND+1):: IF C=D 
   THEN 190 
   200 IF C=X THEN CC=CC+1 :: D 
   ISPLAY AT(14,6):CC ! C CHOOS 
   ES RANDOMLY 
   210 NEXT J 
           
     Here  is  an improved ver- 
   sion  of  a program that was 
   in a Tips long ago, to strip 
   out  the extra blanks from a 
      Filled  and Adjusted Funlweb      
      Formatter file -                  
                                        
      100 DISPLAY AT(3,6)ERASE ALL      
      :"TIGERCUB UNFILLER":"":" To      
       remove extra spaces from":"      
      a TI-Writer text which has":      
      "been Filled and Adjusted by      
      "                                 
      110 DISPLAY AT(8,1):"the For      
      matter, prior to":"reformatt      
      ing."                             
      120 DISPLAY AT(15,1):"Input       
      file? DSK" :: ACCEPT AT(15,1      
      6):IF$ :: OPEN #1:"DSK"&IF$,  
      INPUT                             
      130 DISPLAY AT(17,1):"Output      
       file? DSK" :: ACCEPT AT(17,      
      17):OF$ :: OPEN #2:"DSK"&OF$  
      140 LINPUT #1:M$ :: P=1           
      150 X=POS(M$,"a",P):: IF X=P      
       THEN P=P+1 :: GOTO 150           
      160 X=POS(M$,"  ",P):: IF X=      
      0 THEN PRINT #2:M$ :: GOTO 1      
      80                                
      170 M$=SEG$(M$,1,X)&SEG$(M$, CE 
      X+2,255):: GOTO 160               
      180 IF EOF(1)<>1 THEN 140 ::  
       CLOSE #1 :: CLOSE #2             
                                        
        While  a  program  is run-      
      ning,  the computer periodi-      
      cally  pauses for a fraction      
      of a second to do a "garbage      
      collection",  getting rid of      
      information  it  no   longer      
      needs, to make room in memo-      
      ry.  If this pause occurs at      
      a critical moment in program      
      execution, it can cause pro-      
      blems.  Thanks to the Sydney      
      User   Group  in  Australia,      
      here  is  a  CALL LOAD which      
      will force a garbage collec-      
      tion just before that criti-      
      cal point -                       
      CALL LOAD(-31885,144,"",-318      
      58,81,169,152,0)                  
                                
        
        Here  is  a  neat one from      
      Bruce  Harrison.  Key it in,      
      (you can skip the lines that      
      start with an asterisk)  and      
      assemble it, then use ALSAVE      
      to  imbed  it in any program      
      that  opens a disk file. Put      
      CALL LINK("DEVICE",DEV$)  at      
      the beginning of the program      
   and  change any line reading 
   OPEN #1:"DSK1.FILENAME" - or 
 
   whatever - to read - 
   OPEN #1:DEV$&".FILENAME" 
   (don't forget the period be- 
   fore the filename!). Now you 
   can  load  the  program from 
   any  drive  and it will open 
   the file on that same drive! 
          
   * STRING ASSIGN DEVICE NAME 
   * PLACES DEVICE NAME IN AN 
   *  XBASIC STRING 
   * HARRISON SOFTWARE 
       * 8 OCTOBER 1990 
   * FOR USE WITH ALSAVE AND XB 
   * TAKES ONLY 42 BYTES MEMORY 
   STRASG EQU   >2010 
       WS         EQU   >20BA 
                 DEF   DEVICE 
   DEVICE 
   * USE OUR WORKSPACE 
                 LWPI WS 
   * GET THE CRU BASE IN R12 
                 MOV   @>83D0,R12 
       * GET ROM ADDRESS FOR DEVI 
   *  IN R2 
                     MOV   @>83D2,R2 
   * ENABLE THE ROM 
                 LDCR @ONES,0 
   * ADDING 4 PUTS US AT THE 
   *  LENGTH BYTE 
                 AI     R2,4 
   * FIRST PARAMETER 
                 LI     R1,1 
   * NOT AN ARRAY VARIABLE 
                 CLR   R0 
   * ASSIGN DEVICE NAME TO A 
   *  STRING 
                 BLWP @STRASG 
   * CLEAR CRU, DISABLE ROM 
                 LDCR R0,0 
   * LOAD GPL WORKSPACE 
                LWPI >83E0 
   * RETURN TO GPL INTERPRETER 
                B       @>006A 
   * WORD TO TURN ON ROM IN CRU 
   ONES   DATA >0101 
                END 
     
     
     Getting  short  on memory, 
   so more next time. 
     
     
               Jim Peterson