Atari BASIC Instructions

Atari BASIC Instructions – Update 1998 by TMT

Hello World - Screenshot 01

Hello World – Screenshot 01


Short description of all Atari Basic instructions

Index

ABS
ADR
AND
ASC
ATN
BYE
CHR$
CLOAD
CLOG
CLOSE
CLR
COLOR
COM
CONT
COS
CSAVE
DATA
DEG
DIM
DOS
DRAWTO
END
ENTER
EXP
FOR
FRE
GET
GOSUB
GOTO
GO TO
GRAPHICS
IF
INPUT
INT
LEN
LET
LIST
LOAD
LOCATE
LOG
LPRINT
NEW
NEXT
NOT
NOTE
ON
OPEN
OR
PADDLE
PEEK
PLOT
POINT
POKE
POP
POSITION
PRINT
PTRIG
PUT
RAD
READ
REM
RESTORE
RETURN
RND
RUN
SAVE
SETCOLOR
SGN
SIN
SOUND
SQR
STATUS
STICK
STRIG
STEP
STOP
STR$
THEN
TO
TRAP
USR
VAL
XIO
?


ABS

Usage:
ABS(number_value)
Description:
Returns absolute value of given argument (ABS(-12.4) will be 12.4).

Examples:

  • 10 X=ABS(Y)
  • 10 IF X &lt 0 THEN X=ABS(X)

ADR

Usage:
ADR(text_value)
Description:
Returns memory address of first char of string given as argument.

Examples:

  • 10 X=ADR("Atari")
  • 10 POKE ADR(A$),34
  • 10 Z=USR(ADR(ROUTINE$),128)

See also:


AND

Usage:
logical_value AND logical_value
Description:
Executes logical AND with given arguments. Returns TRUE (1) if both
arguments are different from zero, or 0 otherwise.

Examples:

  • 10 X=(A AND B+3)
  • 10 IF A &gt 0 AND B &gt 0 THEN C=A/B

See also:


ASC

Usage:
ASC(text_value)
Description:
Returns ASCII code of first char of string given as argument.

Examples:

  • 10 X=ASC(TEXT$(5))
  • 10 IF ASC(STRING$)=65 THEN ? "First letter of the alphabet"

See also:


ATN

Usage:
ATN(number_value)
Description:
Returns arcus tangens of value given as argument. Returned value depends
on kind of trigonometric unit (see RAD and DEG).

Examples:

  • 10 PRINT ATN(1)
  • 10 Y=ATN(X)

See also:


BYE

Usage:
BYE
Description:
Ends work in Atari Basic and executes SELF TEST.

Examples:

  • 10 GET #1,A:IF A=27 THEN BYE

See also:


CHR$

Usage:
CHR$(number_value)
Description:
Returns char represented by ASCII code given as argument.

Examples:

  • 10 A$=CHR$(X)
  • 10 X$(4,4)=CHR$(155)

See also:


CLOAD

Usage:
CLOAD
Description:
Removes program in memory and loads a new one from tape recorder. Program
loaded by CLOAD must be saved by command CSAVE.

See also:


CLOG

Usage:
CLOG(number_value)
Description:
Returns decimal logarithm of value given as argument.

Examples:

  • 10 Y=CLOG(X)
  • 10 ? CLOG(10^5)

See also:


CLOSE

Usage:
CLOSE #number_value
Description:
Closes given IOCB. Contents of buffers is saved before closing channel.

Examples:

  • 10 CLOSE #1
  • 10 CLOSE #CHN

See also:


CLR

Usage:
CLR
Description:
Clears all variables and Basic’s stack. Removes all arrays and strings.

See also:


COLOR

Usage:
COLOR number_value
Description:
In char modes sets char using for PLOT and DRAWTO instructions. In pixel
modes sets color register using for drawing. In mode 9 sets luminance and
in mode 11 sets color for drawing.

Examples:

  • 10 GRAPHICS 0:POKE 752,1:COLOR 124:PLOT 1,1:DRAWTO 30,20
  • 10 GRAPHICS 7:COLOR 1:DRAWTO 100,50:COLOR 2:DRAWTO 10,60
  • 10 GRAPHICS 9:FOR I=0 TO 15:COLOR I:PLOT 0,0:DRAWTO 4*I,100:NEXT I

See also:


COM

Usage:
COM number_variable(number_value[,number_value]), or
COM string_variable(number_value)
Description:
Works the same that DIM. Look for DIM.

Examples:

  • 10 COM X(30,5)
  • 10 COM A$(120),X(400),XYZ(100,3)

See also:


CONT

Usage:
CONT
Description:
Resumes executing of program which has been stopped by: instruction STOP or
END, pressing BREAK key, or error detection. Program would be executed
from next line that line which program has been stopped at.

Examples:

  • 10 PRINT "CONT":POSITION 0,0:STOP

See also:


COS

Usage:
COS(number_value)
Description:
Returns cosinus of value given as argument. Returned value depends on
kind of trigonometric unit (see RAD and DEG).

Examples:

  • 10 Y=COS(X)
  • 10 ? SIN(X)*SIN(X)+COS(X)*COS(X)

See also:


CSAVE

Usage:
CSAVE
Description:
Saves program on tape recorder. Program would be saved in tokenized form,
with short breaks between records. Program saved by CSAVE can be loaded
only by CLOAD.

See also:


DATA

Usage:
DATA constant[,constant,…]
Description:
DATA keeps strings and values that can be copied to variables by
instruction READ.

Examples:

  • 10 DATA 10,12.8,-0.13,6.2E-4
  • 10 DATA 600 XL,16,800 XL,64,65 XE,64,800 XE,64,130 XE,128

See also:


DEG

Usage:
DEG
Description:
Sets degree as unit used by trigonometric functions. Devault unit is
radian.

Examples:

  • 10 DEG
  • 10 DEG :X1=ATN(100):RAD :X2=ATN(100)

See also:


DIM

Usage:
DIM number_variable(number_value[,number_value]), or
DIM string_variable(number_value)
Description:
Defines arrays and strings and reserves memory space for them. Arguments
defines maximal lenght of array or string. First element of number array
has got index=0, and first char of string has got index=1. Number arrays
may has up to two dimensions, strings (char arrays) – only one dimension.

Examples:

  • 10 DIM X(30,5)
  • 10 DIM A$(120),X(400),XYZ(100,3)

See also:


DOS

Usage:
DOS
Description:
Ends work in Atari Basic and goes to Disk Operating System. If DOS hasn’t
been loaded, DOS goes to Self Test (just like BYE).

Examples:

  • 10 GET #1,A:IF A=27 THEN DOS

See also:


DRAWTO

Usage:
DRAWTO number_value,number_value
Description:
Draws line from actual position of cursor to point with coordinates given
as arguments. Point 0,0 is at left top corner. First coordinate describes
column (X), second – row (Y). Unlegal coordinate causes error 141.

Examples:

  • 10 DRAWTO I*2,J+10
  • 10 DRAWTO X,191-Y

See also:


END

Usage:
END
Description:
Closes all IOCB channels (except channel 0), turns off all sound
generators and finishes executing of program. Program could be re-runned
by CONT instruction. END instruction isn’t required, because these actions
take place also after executing last line of program.

Examples:

  • 10 GET #1,A:IF A=27 THEN END

See also:


ENTER

Usage:
ENTER file_spec
Description:
Reads lines from file given as argument. Lines are interpreted just like
entered from keybord: if line is preceded by number, it is attached to the
program, if it isn’t, it is executed. Useful for linking programs.

Examples:

  • 10 ENTER "D:ROUTINES.LST"
  • 10 INPUT FILE$:ENTER FILE$:GOSUB 1000

See also:


EXP

Usage:
EXP(number_value)
Description:
Returns exponent of argument.

Examples:

  • 10 EULER=EXP(1)
  • 10 Y=EXP(X)

See also:


FOR

Usage:
FOR number_variable=number_value TO number_value
[STEP number_value]
Description:
Executes all lines between FOR and NEXT as loop with counter. Lines are
executed as long as counter is less than final value (given after word
TO), but at least one time. After every executing counter is increased by
value given after word STEP (if isn’t present, it is assumed 1). Step
value can be also less then zero. Loops can also be imbedded.

Examples:

  • 10 S=0:FOR I=1 TO 100:S=S+I:NEXT I
  • 10 FOR I=1.96 TO 5.48 STEP 0.0037

See also:


FRE

Usage:
FRE(number_value)
Description:
Returns size of free memory, in bytes. Argument han’t got any meaning,
it could be any number value.

Examples:

  • 10 ? FRE(0)
  • 10 D=FRE(0)-1024:DIM A$(D)

GET

Usage:
GET #number_value,number_variable
Description:
Gets one byte from channel given as first argument and assign its value
to variable given as second argument. If it is necessary (for example
keyboard buffer is empty), waits for this byte. Channel had to be opened
before.

Examples:

  • 10 GET #CHN,KEY
  • 10 IF PEEK(764) &lt &gt 255 THEN GET #1,A:A$=CHR$(A)

See also:


GOSUB

Usage:
GOSUB number_value
Description:
Jumps to subroutine, which starts from line given as argument. GOSUB
stores number of actual line on stack. Instruction RETURN will resume
executing of program from this line.

Examples:

  • 10 GOSUB KEY
  • 10 GOSUB 1000+X*100

See also:


GOTO

Usage:
GOTO number_variable
Description:
Jumps to line given as argument immediately. Doesn’t remember number of
line which jumps from. Could also be used in form GO TO.

Examples:

  • 10 GOTO 10
  • 10 GO TO 1000+X*100

See also:


GO TO

Usage:
GO TO number_variable
Description:
Works like a GOTO.

See also:


GRAPHICS

Usage:
GRAPHICS number_value
Description:
Sets graphics mode given as argument. There is 16 different graphics modes
on Atari (from 0 to 15). Number could be increased by 16 to turn off text
window, or by 32 to omit cleaning screen memory. GRAPHICS opens channel 6
for device S:.

Examples:

  • 10 GRAPHICS 0
  • 10 GRAPHICS 8+16

See also:


IF

Usage:
IF number_value THEN number_constant|instruction
Description:
Tests the value for truth. It is truth if it isn’t equal to zero. Logical
expressions could also be used. If the expression is true, instruction
placed after THEN or line with number given after THEN will be executed.
If expression is false, next line will be executed.

Examples:

  • 10 IF A=B THEN ? "A = B"
  • 10 IF X THEN Y=1/X
  • 10 IF (X>3)*(X=4) THEN 100

See also:


INPUT

Usage:
INPUT [#number_value,]variable[,variable...]
Description:
Reads data from channel and assigns it to variable given as argument. If
no channel is given, reads from channel 0. It displays then question mark
(?). If it confuses you, use form INPUT #16,A.

Examples:

  • 10 INPUT TEXT$
  • 10 INPUT #CHN,A,B,TXT$
  • 10 PRINT "Enter file name:";:INPUT #16,FILE$

See also:


INT

Usage:
INT(number_variable)
Description:
Returns integer part of given value. Result is always less or equal to
argument, for example INT(-2.5)=-3.

Examples:

  • 10 MSB=INT(WORD/256)
  • 10 IF A=INT(A) THEN 100

LEN

Usage:
LEN(text_value)
Description:
Returns actual lenght in chars of text string given as argument.

Examples:

  • 10 LENGHT=LEN(TEXT$)
  • 10 A$(LEN(A$)+1)=B$

See also:


LET

Usage:
[LET] number_variable=number_value
[LET] text_variable=text_value
Description:
Assigns value to given variable. Word LET isn’t necessary unless name of
variable is Atari Basic keyword.

Examples:

  • 10 Y=LEN(A$)+LOG(2*Z)
  • 10 LET PRINT=6

LIST

Usage:
LIST [file_spec,][number_value[,number_value]]
Description:
Displays lines of program. If file_spec is given, listing is directed to
this file. Program saved by LIST can be loaded by ENTER. If first number
is given then only line with this number is displayed. If both numbers are
given then all lines from first number to second number inclusive.

Examples:

  • 10 LIST
  • 10 LIST "D:PRG1.LST",1000,1999

See also:


LOAD

Usage:
LOAD file_spec
Description:
Removes actual program and load a new one from file given as argument.
Program should be stored with SAVE instruction.

See also:


LOCATE

Usage:
LOCATE number_value,number_value,number_variable
Description:
Gets value (char of color) of point with given coordinates and assigns
this value to given variable. It is value of COLOR used to setting
this point.

Examples:

  • 10 LOCATE X,Y,CHAR
  • 10 LOCATE 0,0,A

See also:


LOG

Usage:
LOG(number_value)
Description:
Returns natural logarithm (ln) of argument.

Examples:

  • 10 A=LOG(3.1415927)
  • 10 IF X &gt 0 THEN Y=LOG(X)

See also:


LPRINT

Usage:
LPRINT [value][[,]|[;][value]...]
Description:
Prints given values on printer. It is using channel 7. Separators like
a comma or semicolon can be used to formatting data. Semicolon determines
printing without any space between data. Comma determines printing next
data at first column n*10.

Examples:

  • 10 LPRINT A;"^3 = ";A^3
  • 10 LPRINT 1;".",TEXT$

See also:


NEW

Usage:
NEW
Description:
Closes all IOCB channels (except channel 0), turns off all sound
generators, finishes executing of program and removes program from memory.

Examples:

  • 10 IF CRC &lt &gt CODE THEN NEW

See also:


NEXT

Usage:
NEXT number_variable
Description:
Last instruction of FOR loop. It checks if counter is less then final
value. If it is, increases it by step value and jumps to begin of loop.
If it isn’t, ends FOR loop.

Examples:

  • 10 NEXT INDEX
  • 10 FOR I=0 TO 1000:NEXT I

See also:


NOT

Usage:
NOT number_value
Description:
Reverses logical value of given expression. If argument is equal to 0
then it returns 1, if it isn’t equal to 0, it returns 0.

Examples:

  • 10 IF NOT X=2 THEN 100
  • 10 X= NOT Y

See also:


NOTE

Usage:
NOTE #number_value,number_variable,number_variable
Description:
Reads actual position of disk drive head and assign it to two given
variables. First contains sector number, second contains byte number.
These values can be used with POINT instruction.

Examples:

  • 10 NOTE #CHN,X,Y
  • 10 OPEN #1,4,0,"D:FILE.EXT":NOTE #1,SECT,BYTE:CLOSE #1

See also:


ON

Usage:
ON number_value GOTO|GOSUB number_value[,...]
Description:
Tests given value and jumps to line indexed by this value or do nothing
(if value is equal to 0). Value can’t be less then 0, or greater then 255.

Examples:

  • 10 ON 2 GOTO 10,20,30
  • 10 GET #1,K:ON K-48 GOSUB 100,500,900

See also:


OPEN

Usage:
OPEN #number_value,number_value,number_value,file_spec
Description:
Opens given channel (from 1 to 7) for transmition with given device or
file. Second and third argument describes transmition mode (read/write
mode and AUX1 byte). Open channel can be used for other I/O instructions:
GET, INPUT, NOTE, POINT, PRINT, PUT, XIO. After transmition channel should
be closed with CLOSE instruction.

Examples:

  • 10 CLOSE #1:OPEN #1,4,0,"K:"
  • 10 OPEN #CHN,MODE,AUX,FILE$
  • 10 OPEN #1,6,0,"D:*.BAS"

See also:


OR

Usage:
number_value OR number_value
Description:
Executes logical OR with given arguments. Returns FALSE (0) if both
arguments are are equal to 0, or 0 otherwise.

Examples:

  • 10 IF A OR B THEN Y=X/(A*A+B*B)
  • 10 MOVE=(X=1) OR (X=-1) OR (Y=1) OR (Y=-1)

See also:


PADDLE

Usage:
PADDLE(number_value)
Description:
Returns position of paddle manipulator connected to port with number given
as argument. Result could be from 1 to 228 inclusive.

Examples:

  • 10 V=PADDLE(A)
  • 10 IF PADDLE(0) &lt 100 THEN 10

See also:


PEEK

Usage:
PEEK(number_value)
Description:
Returns byte from memory address given as argument.

Examples:

  • 10 IF PEEK(53279)=7 THEN 10
  • 10 SCREEN=PEEK(88)+256*PEEK(89)

See also:


PLOT

Usage:
PLOT number_value,number_value
Description:
Sets point with coordinates given as arguments. Point 0,0 is at left top
corner. First coordinate describes column (X), second – row (Y). Unlegal
coordinate causes error 141.

Examples:

  • 10 PLOT X,Y
  • 10 PLOT 0,0

See also:


POINT

Usage:
POINT #number_value,number_value,number_value
Description:
Sets disk drive head to sector and byte given as arguments. These values
can be taken by NOTE instruction.

Examples:

  • 10 POINT #CHN,X,Y
  • 10 OPEN #1,4,0,"D:FILE.EXT":POINT #1,SECT,BYTE

See also:


POKE

Usage:
POKE number_value,number_value
Description:
Stores second value in byte with address given as first argument.

Examples:

  • 10 POKE 82,0
  • 10 POKE 10,LSB:POKE 11,MSB

See also:


POP

Usage:
POP
Description:
Takes from Basic stack bytes placed there by last instruction GOSUB
(6 bytes) or FOR (16 bytes). It makes accessible leaving FOR loop or
subroutine by GOTO instruction.

Examples:

  • 10 IF I &gt 6 THEN POP :GOTO 60

See also:


POSITION

Usage:
POSITION number_value,number_value
Description:
Moves cursor to point with coordinates given as arguments. Cursor is
visible only in graphics mode 0.

Examples:

  • 10 POSITION 0,0
  • 10 POSITION X,Y

See also:


PRINT

Usage:
PRINT|? [#number_value[,|;]][value][,|;[value]...]
Description:
Writes to given channel values. If no channel is given writes to
channel 0. Values must be separated by commas (,) or semicolons (;).
Semicolon determines printing without any space between data. Comma
determines printing next data at first column n*10. If it isn’t separator
at the end of values list, then EOL char is also sent. Values written to
file can be read by INPUT instruction.

Examples:

  • 10 PRINT
  • 10 ? :? "Atari"
  • 10 ? CHR$(125);CHR$(253),1000
  • 10 PRINT #2;"DATA: ";X1,X2,X3
  • 10 PRINT #6;"ATARI":? #6,"computer"

See also:


PTRIG

Usage:
PTRIG(number_value)
Description:
Returns state of button on paddle manipulator connected to the port given
as argument. If button is pressed, it returns 0, or 1 otherwise.

Examples:

  • 10 IF NOT PTRIG(0) THEN GOSUB FIRE

See also:


PUT

Usage:
PUT #number_value,number_value
Description:
Writes byte given as second argument to channel given as first argument.
Channel had to be opened before.

Examples:

  • 10 PUT #1,BYTE
  • 10 PUT #6,155
  • 10 PUT #CHN,PEEK(I)

See also:


RAD

Usage:
RAD
Description:
Sets radian as unit used by trigonometric functions. Devault unit is
radian.

Examples:

  • 10 RAD

See also:


READ

Usage:
READ variable[,variable]
Description:
Reads value from DATA line and assign it to given variable. Values are
taken sequencely from one DATA instruction or from next DATA.

Examples:

  • 10 READ A,B,C,TXT$:GOSUB 1000
  • 10 READ X:A(I)=X

See also:


REM

Usage:
REM [any char string]
Description:
Do nothing. All words after REM (in this line) are ignored by interpreter.
Can be used for comments.

Examples:

  • 10 REM
  • 10 REM ------------------------------
  • 10 REM Anything you want: ,$#"@ RUN
  • 10 DIM A$(15):REM name

RESTORE

Usage:
RESTORE [number_value]
Description:
Causes reading datas from line given as argument, or from first DATA line,
if no argument is given.

Examples:

  • 10 RESTORE 1000+X:READ A$
  • 10 RESTORE :GOSUB 1000

See also:


RETURN

Usage:
RETURN
Description:
Ends current subprogram and returns to line which this subprogram has been
called from. Gets number of this line from Basic stack.

Examples:

  • 10 RETURN
  • 10 IF IS_END THEN RETURN

See also:


RND

Usage:
RND(number_value)
Description:
Returns random value from 0 to 1. Argument hasn’t got any meaning, it
could be any value.

Examples:

  • 10 X=1000*RND(0)
  • 10 NUMBER=INT(RND(0)*6)+1
  • 10 IF RND(Z)<0.5 THEN GOSUB WIN

RUN

Usage:
RUN [file_spec]
Description:
If no argument is given, it does the same operations that END and CLR and
then starts executing program in memory from its first line. If argument
is given, it loads program from given file (just like LOAD) and starts its
executing. Program must be stored by SAVE instruction.

Examples:

  • 10 IF DATA_CORRUPTED THEN RUN
  • 10 IF KEY=START THEN RUN

See also:


SAVE

Usage:
SAVE file_spec
Description:
Stores program to file given as argument. Program is saved in tokenized
form (similar to representation of program in memory). File can be read by
LOAD or RUN.

Examples:

  • 10 SAVE A$

See also:


SETCOLOR

Usage:
SETCOLOR number_value,number_value,number_value
Description:
Sets hue and luminance of colour register given as first argument. Second
argument describe hue and third one – luminance.

Examples:

  • 10 SETCOLOR 2,0,0
  • 10 SETCOLOR I,H(I),I*2

See also:


SGN

Usage:
SGN(number_value)
Description:
Returns signum of argument. If argument is less then 0, it returns -1. If
argument is greater then 0, it returns 1. If argument is equal to 0, it
returns 0.

Examples:

  • 10 X=SGN(Z)*COUNTER
  • 10 IF NOT SGN(A) THEN GOSUB 1000

SIN

Usage:
SIN(number_value)
Description:
Returns sinus of value given as argument. Result depends on unit of
trigonometric functions.

Examples:

  • 10 Y=SIN(X)
  • 10 X=A*SIN(OMEGA*T+F)

See also:


SOUND

Usage:
SOUND number_value,number_value,number_value,number_value
Description:
Sets sound generator given as first argument (from 0 to 3) to plaing sound
given as rest of arguments. Second argument (from 0 to 255) describes
frequency, third one (from 0 to 15) – choose kind of roars (10 or 14 means
no roars), fourth argument (from 0 to 15) describes volume of sound. If
all three sound arguments are equal to 0, it turns off this generator.

Examples:

  • 10 SOUND 0,0,0,0
  • 10 FOR I=0 TO 255:SOUND 1,I,10,10:NEXT I

See also:


SQR

Usage:
SQR(number_value)
Description:
Returns square root of argument. Argument must be greater or equal to 0.

Examples:

  • 10 Y=SQR(ABS(X))

STATUS

Usage:
STATUS #number_value,number_variable
Description:
Reads operation status for IOCB channel given as first argument and
assigns this value to given variable. Value 1 means SUCCESS.

Examples:

  • 10 STATUS #X,ST
  • 10 PUT #1,A:STATUS #1,STAT

See also:


STICK

Usage:
STICK(number_value)
Description:
Returns value which describes position of joystick connected to port given
as first argument. Position values:

 10 14 6 \ | / \ |/ 11--15--7 / |\ / | \ 9 13 5

Examples:

  • 10 IF STICK(A)=UP THEN X=X-1
  • 10 GOSUB PROCS(STICK(0))

See also:


STRIG

Usage:
STRIG(number_value)
Description:
Returns state of button on joystick connected to the port given as
argument. If button is pressed, it returns 0, or 1 otherwise.

Examples:

  • 10 IF NOT STRIG(A) THEN GOSUB FIRE
  • 10 IF STRIG(0) THEN GOTO 10

See also:


STEP

Description:
Optional part of the FOR instruction. Defines value which is added to
loop counter after each executing of the loop. If no given, 1 is assumed.

See also:


STOP

Usage:
STOP
Description:
Breaks executing of program and displays message: STOPPED AT LINE
n
. Doesn’t close IOCB channels and doesn’t turn off
sound generators. Executing of the program can be recovered by CONT
instruction.

Examples:

  • 10 ? A,B,X,Y,FILE$,TEST:STOP
  • 10 ? "CONT":POSITION 0,0:STOP

See also:


STR$

Usage:
STR$(number_value)
Description:
Returns string which is ASCII equivalent of number given as argument.
Result is char string and it can contain chars like: numbers from 0 to 9,
‘-‘, ‘+’ (only in exponent) and letter ‘E’.

Examples:

  • 10 ? STR$(SQR(3.714))
  • 10 Y$=STR$(X)

See also:


THEN

Description:
Part of the IF instruction. Precedes list of instructions which are
executed, if logical expression is not equal to 0.

See also:


TO

Description:
Part of the FOR instruction. Describes final value of the loop counter.

See also:


TRAP

Usage:
TRAP number_value
Description:
Sets trap for error in line given as argument. When error occurs, it will
not be error message, program will be continued from given line. Error
code could be read by PEEK(195) and number of line which
caused error could be read by PEEK(186)+256*PEEK(187). Error
trapping is turned off by error detection or instruction TRAP with
argument greater then 32767.

Examples:

  • 10 TRAP 10:INPUT A
  • 10 TRAP ERR
  • 10 TRAP 40000

USR

Usage:
USR(number_value[,number_value...])
Description:
Executes binary program in machine language placed from address given as
first argument. Rest of arguments is stored on 6502 stack (LSB first, MSB
second) and it can be used as arguments for binary program. Last byte
placed on 6502 stack describes number of bytes to pull from it. After
return from binary program (RTS code) Basic gets value from bytes 212 and
213. This value is returned as result of USR function.

Examples:

  • 10 ? USR(1536)
  • 10 X=USR(PMG,2,HPOS,VPOS)
  • 10 X=USR(ADR(ML$),ADR(TEXT$),LEN(TEXT$))

See also:


VAL

Usage:
VAL(text_value)
Description:
Returns number value represented by string given as argument. Scans string
to first unexpected char.

Examples:

  • 10 X=VAL(A$(I,I+10))
  • 10 ? VAL("8254E3")
  • 10 TEXT$="-1.2+34":? TEXT$:? VAL(TEXT$)

See also:


XIO

Usage:
XIO number_val,#number_val,number_val,number_val,file_spec
Description:
Universal IO instruction. It can handle all commands akcepted by CIO and
the device. Some operation can be done by other Basic instruction (OPEN,
GET, PRINT, STATUS…).

Examples:

  • 10 XIO 18,#6,0,0,"S:"
  • 10 XIO 35,#1,0,0,FILE$
  • 10 XIO CMD,#CHN,A1,A2,FILE$

See also:


?

Description:
Abbreviation for PRINT instruction. Represented by another token, but
works just like PRINT.

See also:


Last updated on 16-December-98
TMT

Leave a Reply

Your email address will not be published. Required fields are marked *