This page contains articles on the TI99/4a. There is a brief linked index to help you find something useful.
Web article Three- published April 1999
Includes:
Hints and Tips from Bill Sponchia; graphics programming listings; Jim Swedlow: TI Bits; and Number systems- hex, dec, bin, nibbles.
Bill Sponchia presents...
HINTS, TIPS & ANSWERS (HTA)
BASIC & EXTENDED BASIC
1. The following program will load, run and then remove itself from
memory and will put you in XB without going to to disk drive #1
looking for the program "LOAD". (You could place it on disk as a
dummy LOAD file).
100 CALL INIT::CALL LOAD(-31
952,255,0,255,0)
110 END
2. The following program should be saved in the MERGE format as a
handy utility:
1 CALL CLEAR
2 OPEN #1:"DSKn.",INPUT,REL
ATIVE,INTERNAL !!n = disk d
rive #
3 INPUT #1:A$,J,J,K
4 DISPLAY "SIZE=";K;" USED= ";J-K
5 FOR LOOP= 1 TO 127
6 INPUT #1:A$,A,J,K
7 IF LEN(A$)=0 THEN 10
8 DISPLAY A$;TAB(12);J
9 NEXT LOOP
10 CLOSE #1
11 INPUT "NAME OF PGM TO DEL
ETE ELSE TYPE GO ":DEL$
12 IF DEL$="GO" THEN 15
13 DELETE "DSKn."&DEL$ !!n = disk drive #
14 GOTO 11
15 STOP
When programming this program can be used to catalog a diskette without getting out and loading in a disk manager. It is also written to allow for the deleting of files from the diskette.
To use just merge in with the program you are presently working on (of course it is assumed you started it a line 100 and did not use lines 1 to 15).
3. To turn off the QUIT key (FCTN =): CALL LOAD(-31806,16)
Note: Now you must use "BYE" to quit BASIC and get back to the
title screen.
4. In an IF-THEN-ELSE statement if you refer to a variable without any other type of relationship then this means "does not equal zero"
eg - IF X THEN 140 ELSE 100 - means
If X does not equal 0 then go to 140 but if it equals 0 then go to 100.
5. When using XB prescan it will enable you to run programs that
the computer will normally reject. Two things that I have been
able to do are - (a) mixing FOR-TO statements and IF-THEN-ELSE
statements under one line number; and (b) input two NEXT's but
have only one FOR. Here is the program showing these:
100 J=0
110 !@P-
120 FOR J=1 TO 20 :: IF J/2=
INT(J/2) THEN PRINT J ELSE N
EXT J
130 IF J>19 THEN 150
140 NEXT J :: !@P+
150 END
6. To automatically return to the Master Title Screen (or Menu for
Vermenu users) instead of "END" insert the following:
CALL INIT::CALL PEEK(2,A,B):
:CALL LOAD(-31804,A,B)
or
CALL INIT::CALL LOAD(31804,0,36)
7. To restrict a CALL KEY statement to taking only one input at a
time, no matter how long a particular key is held down -
100 CALL KEY(0,K,S)::IF S<1 THEN 100
By restricting the status to +1 this will overcome the problem
of the sometimes repeating key.
8. To get TRUE random numbers install this line into your program: CALL PEEK(-31880,A,B)::CALL INIT::CALL LOAD(-31808,A,B)
9. To erase the program from memory but not erase the screen (and
not disturb any assembly routines in lower memory:
CALL INIT::CALL LOAD(-31952,255,231,255,231)
10. The manual tells you that there are 16 different character sets that you can redefine and change colors on. Actually there are 17 - Set #0 is never mentioned.
11. When LISTing a program and you see a line reference to "32767" this means (unless you actually used that line #) that you resequenced the program while you had a GOTO (or GOSUB, etc) to a non-existing line.
12. To LIST a portion of a program to the printer then enter the
following command:
LIST "filename":line number range
eg: LIST "PIO":130-240 -
will LIST to PIO lines 130 to 240 inclusive)
13. deleted. sjs.
14. deleted. repeat of no 3 above! sjs
15. Did you know that you could identify your GOSUB routines within
the program without using the "!" or REM statement. You are
allowed to put one word (string) after the GOSUB line number.
Here's an example program:
10 CALL CLEAR::PRINT "HERE I
GO.."
20 GOSUB 50 DELAY_ROUTINE ::
PRINT "I'M BACK!"
30 END
50 FOR T=1 TO 400::NEXT T::R
ETURN
16. Here are some interesting redefinitions for characters. To use
them the proper format is "CALL CHAR(##,string) where "##"
stands for the number of Character to be redefined and "string"
is one of the following (or any other that you may have).
000804027F020408 = right arrow
00102040FE402010 = left arrow
081C2A4908080800 = up arrow
0008080B492AC108 = down arrow
00FF = solid line
0000FE2828282828 = pi symbol
00083C4848483C08 = cent sign
0002020404482810 = check mark
17. The IMAGE statement (eg - 100 IMAGE ###.##) can be used with the
DISPLAY AT statement using the following format -
DISPLAY AT(5,12):USING 100:A
18. Instead of using the IMAGE statement you can define a variable
in the image you would like the output to look and then say
"USING variable name".
eg - 100 F$="###.##"
110 DISPLAY AT(12,1):USING F$:A
Of course, unlike the IMAGE statement which can be anywhere in
the program, the variable would have to be defined BEFORE using
it in a DISPLAY AT or PRINT statement.
19. When using the DISPLAY AT statement you can use TAB to properly
locate where further information is to be displayed.
eg: To set up the following display
MAIN MENU:
1 - Edit
2 - Add
3 - Exit
you can set up each line with an individual DISPLAY AT
statement or you can do the following:
DISPLAY AT(5,5):"MAIN MENU";
This will put the information on 4 separate lines because
when the computer tries to perform the TAB(7) it finds that
that location has been already bypassed on the present row
and therefore it automatically goes to the next row.
TAB(7);"1 - Edit";TAB(7);"2 -
Add";TAB(7);"3 - Exit"
20. Did you know that you could delete a file when you close it.
The statement is: CLOSE #1:DELETE
21. When programming in XB it pays in two ways to squeeze as many
statements as you can into each program line. The first reason
is that it saves memory by eliminating line numbers; the second
is that it speeds up execution by eliminating the need for the
program to process extra lines of code.
22. Another method to save memory by reducing the size of a program is to replace a constants used with a variable. This is assuming that that constant is used a number of different times in the program.
23. When you are editing a program and accidently erase a line by
pressing FCTN 3 to get the line back simply type in a single
quote mark and then press ENTER. This gives a syntax error and
the erased line is back because the change was not syntactically
correct and thus not acceptable. The putting in of the quote
mark must be done before moving from the line that was erased.
24. If you need to know if CALL INIT has already been executed in
your program put in the following lines:
10 CALL PEEK(8198,A,B)::IF A
=170 AND B=85 THEN xxx ELSE
CALL INIT
!!xxx = line number to go to if CALL INIT already executed.
25. Here's a use of the MIN and MAX statements:
MIN - If a variable is restricted to being no higher than 6 you
would normally say IF A>6 THEN A=6 however you can say
A=MIN(A,6)
MAX - If a variable is restricted to being no lower than 6 you
would normally say IF A<6 THEN A=6 however you can say
A=MAX(A,6)
26. You can LIST a program to disk by stating LIST "DSKn.program".
This gives a D/V 80 file which is then readable by TI-Writer.
This can be helpful for putting program listings in documents
and allows you to use RS to amend or FS to locate something in a
long program.
27. Here's a short program to write DATA lines which can then be
merged into another program.
100 ON WARNING NEXT
110 DISPLAY AT(10,1)ERASE AL
L:"ENTER FIRST LINE NUMBER:"
:: ACCEPT AT(10,25)BEEP VALI
DATE(DIGIT)SIZE(4):LN
120 DISPLAY AT(12,1):"ENTER
INCREMENT":: ACCEPT AT(12,17
)BEEP SIZE(3)VALIDATE(DIGIT)
:I
130 DISPLAY AT(14,1):"ENTER
FILENAME:":: ACCEPT AT(14,16
)BEEP VALIDATE(UALPHA,DIGIT)
SIZE(10):FN$
140 OPEN #1:"DSK1."&FN$,VAR
IABLE 163
150 DISPLAY AT(2,6)ERASE ALL
:"PRESS ENTER TO END":: DIS
PLAY AT(22,1):"ENTER A LINE
OF DATA:":: LINPUT D$
160 IF D$="" THEN 190
170 PRINT #1:CHR$(INT(LN/256
)&CHR$(LN-256*INT(LN/256))&
CHR$(147)&D$&CHR$(0)
180 LN=LN+I:: GOTO 150
190 PRINT #1:CHR$(255)&CHR$(255)
200 CLOSE #1:: END
This will save your DATA lines in a Merge format almost ready to
be merged into you program. Before this can be done you must do
the following:
i) type NEW and press ENTER to clear memory
ii) MERGE in the saved DATA lines. (ie - MERGE DSK1.filename
iii) EDIT each DATA line by retyping (typing over) the word DATA
iv) SAVE the edited DATA lines in the MERGE format (ie - SAVE DSK1.filename, MERGE)
It is now ready to be put into you program.
THIS ARTICLE HAS BEEN PUT TOGETHER FROM MANY SOURCES BY BILL SPONCHIA.
==============================
Return to top of page
FRACTAL...
Here is a truly fractal program, which, using The Missing Link and Extended Basic ONLY takes about 12 hours or so to plot a graphic of 120 x 200 pixels!The total graphic is vertically reflected about 0, so if 0 is at screen centre
you can plot top and bottom parts at the same time to half plotting time...
This program requires The missing Link disk for emulators.
This program is all about "attraction basins" which I do not understand, and while the program can probably be modified for other functions, I do not know how! What I know is that it plots a truly fractal shape which we can zoom in on.
100 ! TO DRAW AN ATTRACTION
BASIN USING NEWTON
FORMULA ON
110 ! F(z)=z^(-3)-1
120 !
130 !
140 ! J C TOPHAM
! Fractal Report 13
! Feb 1991
150 ! for ti+tml by s shaw
march 1991
160 !
170 !
180 !
190 !
200 WIDE=242 :: HEIGHT=190
210 !
220 !
230 CALL LINK("CLEAR")
239 ! actual pixels plotted:
240 ACROSS=200 :: DOWN=120
246 ! area to be plotted
247 ! whole image is within X=-2 to +2
248 ! Y= -1.75 to +1.75
249 ! Y is vertical and is reflected about 0.
250 XMIN=-1.1 :: XMAX=0.9
260 YMIN=-1.70 :: YMAX=0.30
270 !
280 !
290 RY(1)=-SQR(3)/2
300 RY(2)=SQR(3)/2
310 RY(3)=0
320 !
330 DX=(XMAX-XMIN)/ACROSS
340 DY=(YMAX-YMIN)/DOWN
350 XPOS=INT((WIDE-ACROSS)/2)
360 YPOS=INT((HEIGHT-DOWN)/2)
370 !
380 FOR YP=0 TO DOWN
390 FOR XP=0 TO ACROSS
400 CALL LINK("PRINT",181,12
,STR$(YP)&":"&STR$(XP))
410 YN=YMIN+YP*DY
420 XN=XMIN+XP*DX
430 FOR ITER=1 TO 30
440 GOSUB 650
450 XM=(A*C+B*D)/9
460 YM=(B*C-A*D)/9
470 IF XM*XM+YM*YM>1000 THEN 620
480 !
490 !
500 IF ABS(YN-YM)>1E-2 THEN 590
510 IF ABS(XN-XM)>1E-2 THEN 580
520 FOR I=1 TO 3
530 IF ABS(RY(I)-YM)>1E-2 THEN 560
540 CALL LINK("PRINT",1,200,
STR$(ITER)&" "):: IF ITER/2
<>INT(ITER/2)THEN ITER=30 ::
GOTO 570
550 CALL LINK("PIXEL",YPOS+D
OWN-YP,XPOS+XP):: ITER=300
560 !
570 NEXT I
580 !
590 !
600 XN=XM :: YN=YM
610 NEXT ITER
620 NEXT XP
630 NEXT YP
640 END
650 ! INVERT Z3
655 X2=XN*XN :: X3=X2*XN ::
X4=X2*X2 :: Y2=YN*YN :: Y3=
Y2*YN :: Y4=Y2*Y2
660 A=4*XN-X4+6*X2*Y2-Y4
670 B=4*YN-4*X3*YN+4*XN*Y3
680 C=3 :: D=0
690 RETURN
700 END
==========================
MANDELBROT PLOT
This is EXCEEDINGLY SLOW if you want a detailed plot! However, a minimum
detailed plot over a limited screen area is not TOO slow! Maximum detail and
you could be looking at SEVERAL DAYS to complete a screenful.
THIS PROGRAM DOES WORK! and cries out for some machine code! Some means of
saving the picture, to disk or printer, would be required- that's perhaps the
hardest bit!
User should input area to be plotted, and possibly be given a choice of what
method is to be used for deciding if a pixel is to be plotted or not- see
comments in listing! - and the degree of inner detail required!
======================================================
100 ! MANDELBROT PLOTTER
110 ! VERY SLOW!
120 ! FOR EX BAS + THE MISSING LINK
130 !
140 CALL LINK("CLEAR")
150 !
160 ! DESIGN LIES IN AREA
170 ! PMIN -2.25 PMAX 0.75
180 ! QMIN -1.50 QMAX +1.50
190 !
200 ! use smaller area for
more detail- ensure
there IS detail there though!
210 !
220 ! Concentrate on areas
very close to central
creature!
230 !
240 A=240 :: B=180 ! maximum values
250 !
260 ! A=width plotted
B=height plotted
in pixels
270 !
280 ! M= number of iterations per point. Needs to be enough to reach CMAX at centre of beast.
290 ! 100 is often used but lower values can usually be safely used.
300 !
310 !
320 A=160 ! A=width
330 B=150 ! B=height in pixels
340 M=71 ! MAX ITERATIONS
350 ! P=REAL Q=IMAG
360 PMIN=-.250 ! DEFINE AREA
370 PMAX=-.20 ! TO BE
380 QMIN=-0.83 ! DRAWN
390 QMAX=-0.79 !
400 !
410 ! CMAX must be a power of 2, eg 2,4,8,16,32,64,128...
420 ! The higher the value the more detail close to the beast.
430 ! 16 gives minimum aceptable detail, 32 is reasonable for an odd/even test, while 64 and higher give maybe too much detail.
440 ! If using 64 or higher you must use a logarithmic scale with greater gaps as K gets larger... eg
450 ! 64...pixel on.
53 to 63...pixel off
K= 44 to 52...pixel on
K= 36 to 43...pixel off
K= 29 to 35...pixel on...
460 !
470 ! or use
IF INT(K^.8)/2=INT(INT(K^.8)
/2) THEN pixel on...
or some other fractional power
480 ! note that processing time really does get longer as CMAX increases!!!!!!
490 !
500 !
510 CMAX=64 ! DETAIL, 8,16,32,64,128,256 ETC
520 !
530 DP=(PMAX-PMIN)/(A-1)
540 DQ=(QMAX-QMIN)/(B-1)
550 FOR NP=1 TO A
560 FOR NQ=1 TO B
570 P=PMIN+NP*DP :: Q=QMIN+NQ*DQ :: K,X,Y=0
580 ! LOOP
590 !
600 !
610 XN=X*X-Y*Y+P
620 Y=2*X*Y+Q
630 X=XN :: K=K+1
640 !
650 IF X*X+Y*Y>M THEN 690
660 IF K=CMAX THEN 690
670 GOTO 580
680 !
690 IF K/2=INT(K/2)THEN CALL
LINK("PIXEL",NQ,NP)! SEE CO
MMENTS ON CMAX ABOVE!
700 !
710 CALL LINK("PRINT",170,20
0,STR$(NQ)&STR$(K)&" ")
720 NEXT NQ
730 NEXT NP
740 CALL LINK("SAVEP","DSK2.
PIC2")
750 GOTO 750
THE GOLDEN RATIO
Disks for emulators: jbm103.dsk ||
tml.dsk
1 ! THE GOLDEN RATIO 1: 1.618...
============================
2 ! removing a square from a rectangle with sides in this ratio leaves a sma
ller rectangle which also has sides in the Golden Ratio
3 ! -points dividing sides lie on a logarithmic spiral which can be found in
shells, and in art works by da Vinci, Dali- even in
4 ! the Parthenon.
5 ! Fractal in nature- it keeps getting smaller or larger depending on whi
ch way you go...
6 ! program written by Ashley Tilling for JBM103 converted b
y S Shaw for TML.
7 !
8 ! Due to our not having square pixels the rectangle on screen is
NOT in the golden ratio as viewed. Ah well...
9 !
99 ! remove ! from line 100 for use with JBM103.
100 ! call load(-31890,56,0)
:: CALL LOAD(-31964,56,0)
110 AX=12 :: AY=8
120 CL=200 ! side length
130 CALL LINK("CLEAR")!for j
bm103 CALL LINK("SCR2") also.
140 RL=INT(CL/1.618)
150 FOR I=0 TO 1 :: FOR J=0 TO 1
160 CALL LINK("LINE",AX+RL*I
,AY+CL*I,AX+RL*J,AY-CL*(J=0))
162 ! CALL LINK("LIGNE",16,A
X+RL*I,AY+CL*I,AX+RL*J,AY-CL
*(J=0))
170 NEXT J :: NEXT I
180 FOR K=1 TO 3
190 M=CL-RL :: N=INT(CL*.236):: P=INT(CL*.146)
195 CALL LINE(AX,AY,AX,AY)
200 CALL LINE(RL,M,1,M)
210 CALL LINE(N,1,N,M)
220 CALL LINE(1,N,N,N)
230 CALL LINE(P,M,P,N)
240 AX=AX+P :: AY=AY+N :: CL=P :: RL=INT(CL/1.618)
250 NEXT K
260 GOTO 260
270 SUB LINE(A,B,C,D)
280 REM ! LINES for JBM103 INSTEAD of CALL LINK("LINE".. and CALL LINK("PIXEL"..
290 IF (A=C)*(B=D)THEN AX=A :: AY=B :: SUBEXIT
300 CALL LINK("LINE",AX+A,AY
+B,AX+C,AY+D)
310 ! CALL LINK("LIGNE",16,A
X+A,AY+B,AX+X,AY+D)
320 IF B=D THEN 350
330 L=ABS(B-D)-1
340 ST=-PI*(B>D):: FI=PI/2+P
I*(D>B):: GOTO 370
350 L=ABS(A-C)
360 ST=-PI/2-PI*(A>C):: FI=PI*(C>A)
370 IF L<3 THEN SUBEXIT
380 FOR J=ST TO FI STEP -1/L
390 Y=AY+D+INT(.5+L*SIN(J))
400 X=AX+C+INT(.5+L*COS(J))
410 CALL LINK("PIXEL",X,Y)
420 ! CALL LINK("POINT",16,X,Y)
430 NEXT J
440 SUBEND
450 END
POLYNOMIAL EQUATIONS...
1 ! Newtons method for solving polynomial equations.
I gather this method is best for orders up to ^6 but better methods are
available for higher orders... so I am told...
2 ! eg find z when 4Z^6-2Z^3+z-1=0
3 ! sorry about the input format, you just need to enter the multiplicand for each power of z and its sign if negative (6z or -6z)
4 ! enter the default zero if that power is not in the equation.
5 ! one numeric answer will usually be given but some formulae may have more than one answer- try varying the seed
6 ! in line 290, value of X
7 ! to produce different answers.
8 ! a few equations MAY not be sovable with this program.
9 ! amend input method if using multipliers over +99 or under -9 or if you wish
to use higher powers (remember to DIM the array).
10 !
11 !
100 CALL CLEAR :: V$="012345
6789-+"
110 DISPLAY AT(1,1):"NEWTONS
METHOD TO SOLVE Polynom
ial Equations"
120 DISPLAY AT(3,4):" Dr M E
cker 1987. S Shaw for TI 1991"
130 DISPLAY AT(6,1):"Your eq
uation is in the form 5Z^5 +
0Z^4 -2Z^3 +0Z^2-2Z +9 =0"
140 DISPLAY AT(12,1):" 0 Z^9
0 Z^8 0 Z^7 0 Z^6"
150 DISPLAY AT(13,1):" 0 Z^5
0 Z^4 0 Z^3 0 Z^2"
160 DISPLAY AT(14,1):" 0 Z 0
= 0"
170 ACCEPT AT(12,2)SIZE(-2)V
ALIDATE(V$):A(9)
180 ACCEPT AT(12,8)SIZE(-2)V
ALIDATE(V$):A(8)
190 ACCEPT AT(12,14)SIZE(-2)
VALIDATE(V$):A(7)
200 ACCEPT AT(12,20)SIZE(-2)
VALIDATE(V$):A(6)
210 ACCEPT AT(13,2)SIZE(-2)
VALIDATE(V$):A(5)
220 ACCEPT AT(13,8)SIZE(-2)
VALIDATE(V$):A(4)
230 ACCEPT AT(13,14)SIZE(-2)
VALIDATE(V$):A(3)
240 ACCEPT AT(13,20)SIZE(-2)
VALIDATE(V$):A(2)
250 ACCEPT AT(14,2)SIZE(-2)
VALIDATE(V$):A(1)
260 ACCEPT AT(14,6)SIZE(-2)
VALIDATE(V$):A(0)
270 FOR T=0 TO 9 :: IF A(T)
<>0 THEN N=T
280 NEXT T
290 TLD,TL=.00000000001 :: X
=.800 ! INITIAL GUESS
300 FOR K=0 TO N
310 Y=Y+A(K)*X^K
320 NEXT K
330 IF ABS(Y-0)<TL THEN 410
340 FOR K=1 TO N
350 YD=YD+K*A(K)*X^(K-1)
360 NEXT K
370 IF YD=0 THEN X=X+.01 :: GOTO 400
380 X=X-Y/YD
390 DISPLAY AT(22,1):"Next i
terate:":X;" "
400 Y,YD=0 :: GOTO 300
410 DISPLAY AT(20,1):"***DON
E***":"<any key for another>"
420 DISPLAY AT(16,3):"Z=";X
430 CALL HCHAR(18,6,42,6)
440 CALL KEY(5,P,B)
450 IF B=1 THEN RUN
460 CALL HCHAR(18,6,32,6)
470 CALL HCHAR(18,6,45,6)
480 GOTO 430
491 ! Recreational & Educational Computing
500 END
==============================
Return to top of page
TI BITS Number 23
By Jim Swedlow
[This article originally appeared in the User Group of Orange County,
California ROM]
A DIRTY DOZEN
Being a compendium of things small and not so small that are worth a
word or two.
DOCS, Part 1
On disk documentation is a good way to tell you how to use a program.
There are a number of ways to print them. The program may print the
docs. You may have to print them through the Formatter. Other times
there is a special program just to print the docs.It would be nice if there was a README file that told you how to print
the docs.
TI WRITER, Part 1
Sometimes, when you display a disk text (DV80) file on your screen, the
last line looks like hieroglyphics. When you save a TI Writer file
using SaveFile, the very last record contains the tab and margin
settings. The characters are outside the ASCII 32 to 127 range, so they
show on your screen as strange graphics.
When you save a file with PrintFile, the tabs and margins are not saved
as TI Writer thinks that you are going to send your file to a printer.
PrintFile, however, will accept any legal devise name (PIO,
DSKn.FILENAME, RS232, etc).
FAIRWARE, Part 1
People who use Fairware but don't send the author a contribution earn a
place in the dirty dozen.
NEWSLETTERS, Part 1
If you ever read through all the various TI news letters that TI User
Groups publish you will be awed by the vast array of information that
they purvey. From original software to hardware fixes to reviews to
commentary, the range is immense.
Why is this in the dirty dozen?^ Because you probably have never looked
at all of these wonderful resources.
THIS AND THAT, Part 1
Another category in the dirty dozen is presentations at User Group
meetings that are so complex, so techy that no one understands what is
being said. Drives members away.
FAIRWARE, Part 2
Right next to users who do not contribute are Fairware authors who
receive our contributions but fail to acknowledge them. It is good
manners to say thanks. Just taking the money discourages future
support.
THIS AND THAT, Part 2
An IF^THEN problem that many of us have is figuring out how to match
IF's and ELSE's.
Reading from the start of the line, each ELSE matches the last unmatched
IF. Consider the following:
IF A THEN IF B THEN C ELSE D ELSE E
This can be displayed as a flow chart- ->
_________ ( ) ( Start ) (_________) | v /\ /\ _____ / \ T / \ T | | / A? \-->/ B? \-->| C | \ / \ / |_____| \ / \ / | \/ \/ | | F | F | __v__ __v__ v | | | | | | E | | D | | |_____| |_____| | | | | `------->|<-------' ____v____ (GOTO Next) ( Line ) (_________)
NEWSLETTERS, Part 2
If you do get around to reading through old newsletters you will see
articles that run something like this:
"Your officers are getting sick and tired of doing everything ourselves.
If some of you don't start helping, things just aren't going to get
done".
Folks, this does not solve the problem. Broad band appeals in
newsletter articles almost always result in nothing. The only way to
get folks to help is to ask them, one to one.
THIS AND THAT, Part 3
The PE Box fuses get special attention in the dirty dozen. TI put a
1.25 amp slow blow fuse outside the PE Box (the one you can get to).
Inside the box (actually inside the main transformer) they put a one amp
regular fuse. Guess which fuse goes when you get a short?
TI WRITER, Part 2
When FIll and ADjust are on, TI Writer always adds two spaces after a
period. This is good for a sentence but bad for names and
abbreviations. Mr. Jones looks wrong.
There is an easy fix. Use the circumflex (^) as a required space. If
you type this in the Editor:
Mr.^JonesYou will get this from the Formatter:
Mr. Jones
Makes a better final document.
CLOSING SHOT
One last item to fill this dirty dozen. The thing in the TI World that
bothers me the most is when folks loose sight of our prime objective.
The 4A will have strong support as long as we hang together and keep our
eye on the ball. For us, the center issue is survival.
Enjoy.
XB X X BBBB # 18 X X B B X BBBB By X X B B Jim X X BBBB Swedlow
Computers really think in binary. In this numbering system there are two numbers, 0 and 1 (or, if you are a computer, off and on). While this works for your 4A, binary is cumbersome for humans. For example, in binary 41,576 is 1010001100011100.
Hex, or hexadecimal, has sixteen numbers from zero to F. Here are the first sixteen numbers in binary, decimal and hex:
DECIMAL HEX BINARY 0 0 0000 1 1 0001 2 2 0010 3 3 0011 4 4 0100 5 5 0101 6 6 0110 7 7 0111 8 8 1000 9 9 1001 10 A 1010 11 B 1011 12 C 1100 13 D 1101 14 E 1110 15 F 1111The next number would be 16 or >10 or b1000 (> means hex and b means binary).
A byte is eight bits or two nibbles. With a bit you can count from
zero to one. A nibble gets you from zero to fifteen. The range of
byte is:
Base Low High Binary 0 11111111 Hex 0 FF Decimal 0 255
>14 is >10 plus >4
>10 is 16 and >4 is 4
16 plus 4 is 20
Hence, >14 is 20
b10100 is b10000 plus b100
b10000 is 16 and b100 is 4
16 plus 4 is 20
b10100 is 20
Further than that I cannot go in this space. Base Low High Binary 0 1111111111111111 Hex 0 FFFF Decimal 0 65,535
Hex range Decimal Range 0-7FFF 0 to 32,767 8000-FFFF -32,768 to -1Remember that >8000 is the next number after >7FFF.
Some examples: 7FFF is 32,767 8000 is -32,768 FFFF is -1 0 is 0
>>Subtract 65536 from any number over 32,767.
>>Add 65536 to any number less than zero.
This conversion process can be expressed in basic:
AD=AD+65536*(AD>32767)
If AD is the address, this returns the same number if AD is less than or equal to 32767. If AD is greater than 32767, the test returns true (-1) and a negative 65536 is added to AD. Try it on your computer.
Bottom line time. Suppose you see CALL PEEK(-31952,A,B). Where is -31952? Well, since it is less than zero, we add 65536 and get 33584 or >8330. Now you know!
Enjoy!