home *** CD-ROM | disk | FTP | other *** search
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 1
-
-
-
- Compiled by Alice Barney, (703) 978-9376, NOVATARI
-
- 1. VARIABLE TYPES:
- A% Integer
- (holds numbers between -32768 and 32767)
- B! Real (Single Precision--Default Type)
- C# Double Precision Numbers. Ex. C#=3.33333333D+3
- D$ String Variable (Combine with +, as D$=E$+".")
- Note: A string variable <= 255 bytes
- String arrays are supported
- Arrays may have three dimensions.
-
- PURPOSE CMD SYNTAX
-
- MATH X = ABS(<numeric expression>) is pos. or 0
-
- STRING I% = ASC(<string expression>)
- This gives ASCII value of first character in a string.
-
- MATH X! = ATN(<numeric expression>)
- This gives the angle in radians, between -PI/2 and PI/2.
- See TAN function (opposite).
-
- BASIC AUTO [<starting line number>] [,<increment>]
- This generates a line number after [Return] until turned
- off by a [Control] [G]. EX. AUTO 50, 25 generates 50, 75,...
- **75 means line 75 exists--keep it with empty [Return].
-
- FILE BLOAD <filespec>[,<address>]
- This can load arrays, screen images or subroutines.
- If address left out, uses same address as in BSAVE.
- Ex: 110 BLOAD "ARRAY",23
-
- TEST BREAK [<list of line numbers>]
- This prints out program line, and results, and pauses.
- This is turned off by UNBREAK or STOP or END.
-
- FILE BSAVE <filespec>,<address>,<length>
- This saves part of memory to a file.
-
- CONTROL CALL <numeric variable>[(<parameter list>)]
- This invokes a machine language routine in memory.
- Example: 600 CALL PGPNT(I%,A$,X)
-
- CONTROL CHAIN <filespec>[,<line descriptor>][,ALL]
- CHAIN MERGE <filespec>[,<line descr.>]
- [,DELETE<line descriptor list>]
- This loads and passes control to another program, which
- can be merged with the current program.
- COMMON variables are passed to the new/modified program.
-
- STRING A$ = CHR$(<numeric expression>)
- This gives ASCII character with the decimal value MOD 256.
-
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 2
-
-
- MATH I% = CINT(<numeric expression>)
- This rounds to the nearest integer, in range -32768 to 32767.
-
- GRAPHIC CIRCLE <horizontal center,vertical center,radius>
- [<,start angle,end angle>]
- This draws circles and arcs for angles given as degrees
- times 10. 60 degrees is 600; 360 degrees is 3600.
- Circles are drawn in current plot color (COLOR parm 3).
-
- BASIC CLEAR This erases all data but keeps program.
-
- GEM CLEARW <numeric expression> Clears a window:
- 0 = EDIT Window; 1 = LIST; 2 = OUTPUT; 3 = Command Window
-
- FILE CLOSE [#]<file number>[,<file number>]...
- CLOSE without any file number closes all open disk files.
-
- GEM CLOSEW <window number> Closes one BASIC window.
-
- GRAPHIC COLOR [<text color,fill color,line color,style,index>]
- Text color is 0-15 (LOW), 0-3 (MED) and 0-1 (High Res.)
- Colors for fill (background) and line have same limits.
- Style is Hollow, Pattern or Hatch.
- Index is the pattern type for the style.
-
- CONTROL COMMON <variable>,<variable>... (see CHAIN)
-
- CONTROL CONT Continue after BREAK. (Or use GOTO)
-
- MATH X = COS(<numeric expression>)
- The angle must be given in radians = degrees*(PI/180),
- where PI = 3.14159 (etc.)
-
- FILE CVD(<8-byte string>) (See MKD,MKI,MKS)
- This converts byte string to a double precision number,
- normally input from FIELD in buffer of a random file.
-
- FILE CVI(<2-byte string>) converts to an integer.
-
- FILE CVS(<4-byte string>)
- This converts to Single Precision real number.
-
- BASIC DATA <constant>,<constant>...
- This holds values so READ statement assigns to variables.
-
- BASIC DEF FN<function name>[(parameter,parameter>)] = <definition>
- Ex: DEF FNA(A) = A*2+5
- The definition must be one program line.
- Arrays are not supported.
-
- GEM DEF SEG [<numeric expression>] EX: DEF SEG X
- If X > 0, 1 byte is PEEK or POKE size, with offset X
- If X = 0 and is not double precision, 2 bytes PEEK size.
- If X = 0 and is double precision, 4 bytes PEEK size.
-
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 3
-
-
- BASIC DEFDBL <letter>[-<letter>]
- This declares a range of letters for double precision numbers.
-
- BASIC DEFINT <letter>[-<letter>] defines integers
-
- BASIC DEFSNG <letter>[-<letter>] defines real numbers
- These are single precision (default type) numbers.
-
- STRING DEFSTR <letter>[-<letter>] defines strings.
-
- BASIC DELETE <line number list> erases BASIC line numbers
-
- ARRAYS DIM <array name>(<subscript>,<subscript>)
- [,<array name>(<subscript>)]
- This defines dimensions of arrays. Max dimensions = 15.
- Lower bound of each dimension is 0 or 1--see OPTION BASE.
- Arrays can be 1/3 of memory but below 32K.
-
- FILE DIR [<disk drive:>][<filename,filetype>]
- This lists file names on screen or printer--with wild cards.
-
- BASIC EDIT <line number> or ED
- This invokes ST BASIC editor beginning at line given, or 0.
-
- GRAPH ELLIPSE <horiz. center,vert. center,horiz. radius,
- vert. radius>[<start angle,end angle>]
- This draws ellipses and elliptical arcs.
-
- CONTROL END (Stops program, closes files)
-
- FILE X = EOF(<file number>) Note: EOF = -1 (true)
-
- FILE ERA [<disk drive:>]<filename> erases matching files.
-
- BASIC ERASE <array name>,<array name>
- This erases array contents so you can use it again.
-
- CONTROL X = ERL (error line); Y = ERR (error code)
- These apply after an ERROR condition.
-
- CONTROL ERROR <numeric expression> (Sets error number.)
-
- MATH X = EXP(<numeric expression>) (expr. < 43.6682)
- Returns the exponent of e, which is 2.7182
-
- FILE FIELD #<file number>,<field width> AS <string var.>,
- <,field width> AS <string variable>
- This allocates space in random file buffers.
- Buffer fields must be filled by LSET or RSET, or by input.
- Do not use INPUT or LET for FIELD buffer variables.
-
- GRAPHIC FILL <numeric X expr.>,<numeric Y expr.>
- This fills drawn shape, starting at X,Y with color
- or pattern set by most recent COLOR statement.
-
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 4
-
-
- MATH X = FIX(<numeric expression>)
- This truncates a real number decimal part to get the integer.
- The real number must be between -32768 and 32767.
-
- MATH X = FLOAT(<integer expression>)
- This converts an integer to the format of a real number.
-
- DEBUG FOLLOW <variable>[,<variable>] (See UNFOLLOW)
- This detects changes in the variables. When one changes,
- the variable name, value and line number are printed.
-
- CONTROL FOR <counter variable> = <numeric expression>
- TO <numeric expression> [STEP <num. expr.>]
- This loops until NEXT is reached.
-
- CONTROL X = FRE(<dummy argument>) Ex: ? FRE(0)
-
- GEM FULLW <numeric expression>
- Sets BASIC window to full size: 0=Edit;1=List;2=Output;3=CMD
-
- GEM GEMSYS(AES Op Codes) allows access to mouse
- Ex: 10 REM PRINT MOUSE X,Y POS. & BUTTON STATES
- 20 A#=GB
- 30 CONTROL=PEEK(A#):GLOBAL=PEEK(A#+4)
- 50 GINTIN=PEEK(A#+8):GINTOUT=PEEK(A#+12)
- 70 ADDRIN=PEEK(A#+16):ADDROUT=PEEK(A#+20):GEMSYS(79)
- 100 PRINT PEEK(GINTOUT+2):? PEEK(GINTOUT+4)
- 120 PRINT PEEK(GINTOUT+6):? PEEK(GINTOUT+8)
-
- FILE GET [#]<file number>[,<record number>]
- This reads a record from a random disk file.
-
- CONTROL GOSUB <line number> or GOSUB <label name>
-
- CONTROL GOTO <line number> or GOTO <label name>
-
- GRAPHIC GOTOXY <Column Position>,<Row Position>
- This controls the output Cursor position in the
- Output Window.
-
- BASIC X = HEX$(numeric expression)
- This returns the result, in HEX.
- EX: X=HEX$(15):? X GIVES 'F'
-
- CONTROL IF <logical expression> THEN <statement> <:statement>
- [ELSE <statement> <:statement>
- This may include imbedded FOR...NEXT or WHILE...WEND loop.
-
- I/O X = INP(<port number>) Gets byte from input port
- To get port status use neg like INP(-3)--0=n/avail;-1=avail
- Port 0 = PRINTER (Parallel Port)
- 1 = AUX (RS-232)
- 2 = CONSOLE (Screen)
- 3 = MIDI (Musical Instr. Dig. Interface)
- 4 = KEYBOARD
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 5
-
-
-
- I/O INPUT [;] [<prompt string><; or ,>] <variable>,<variable>
- If ';' used, get '? ' before reply. ',' omits both.
- If no quoted prompt or null string used, '? ' is printed.
-
- I/O INPUT#<file number>,<variable>, <variable>
- This inputs data from a disk file, bypassing leading spaces,
- tabs, carr.returns, and line feeds. After data found, it is
- ended by space, carr.return, line feed, comma, or char.#255.
- --Quoted strings are ended by quote or EOF or char #255.
- --Unquoted strings are ended by carr.rtn, line-feed, comma,EOF
- or 255 char, and drop trailing spaces.
-
- I/O X = INPUT$(<number of char.>[,[#]<file number>])
- This returns requested number of characters from disk or
- keyboard.
-
- I/O X = INSTR([<starting point>,]
- <target string expression>, <pattern string>)
- This searches for imbedded string and gives pos. or 0.
-
- MATH X = INT(numeric expression)
- This converts from floating to integer number form.
-
- FILE KILL<string expression>
- Deletes disk file -- works inside BASIC program.
-
- STRING X$ = LEFT$(<target string>,<number of char.>)
- This extracts leftmost characters from a string.
-
- STRING Z = LEN(<string expression>) Gives string length
-
- BASIC [LET] <variable>=<expression> [LET is optional]
- This assigns a value to a variable, converting as needed.
-
- I/O LINE INPUT[;] [<prompt>[, or ;]]<string variable>
- This requests keyboard string variable input ended by <RETURN>
- or <Line Feed>.
-
- I/O LINE INPUT#<file number>,<string variable>
- This inputs up to 254 byte disk file string ended by CARR.RTN.
- A line feed preceding CARR.RTN. is input--does not end line.
-
- GRAPHIC LINEF <X1,Y1,X2,Y2> draws line from X1,Y1 to X2,Y2
-
- BASIC LIST [<line descriptor, list>] Ex. LIST 10-30,70-90
- LIST - 30 lists lines up to 30. [CONTROL] [G] stops LIST.
-
- BASIC LLIST [<line descriptor list>] lists program to printer.
- WIDTH LPRINT <integer expression> sets printer line width.
-
- FILE LOAD <file name> Loads new program, clearing any previous.
-
- FILE X = LOC(<file number>) Gives current record # in Random file.
- In a sequential file, gives #bytes read or written.
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 6
-
-
-
- FILE X = LOF(<file number>) Gives file length in bytes.
-
- MATH X = LOG(<positive numeric expression>)
- Gives natural log (to base e) of number > 0
-
- MATH X = LOG10(<pos. numeric expression>) Gives base 10 logarith.
-
- I/O LPOS(X) Gives approx. current print column for printer.
-
- BASIC LPRINT (<list of expressions>] or
- LPRINT USING <format string expr.>;<list of expressions>)
-
- I/O LSET<string variable>=<string expression>
- Moves string into existing string variable, left jusified.
- For random file buffer, use MKD$,MKI$ or MKS$ for numbers.
-
- I/O MERGE <filename> (into existing BASIC program in memory)
-
- STRING X$ = MID$(<string expression>,<starting point>,[length>])
- This returns a segment of a string.
-
- FILE X$ = MKD$(<numeric double precision expression>)
- This converts number to an 8-byte string for file buffer.
-
- FILE X$ = MKI$(<integer expression>) returns two-byte string.
-
- FILE X$ = MKS$(<numeric single precision expression>) -- 4 bytes
-
- FILE NAME <old file name> AS <new file name> -- renames disk file
-
- BASIC NEW [<new program name>] clears memory, may name new program
-
- LOOP NEXT [<counter>][,<counter>]
-
- STRING X$ = OCT$(<numeric integer expression>)
-
- BASIC OLD <filename> clears memory & loads program into memory
-
- CONTROL ON <numerical expr.> GOTO <line number list>
-
- CONTROL ON <numerical expr.> GOSUB <label list>
-
- CONTROL ON ERROR GOTO <line descriptor> line = 0 to show error num.
-
- FILE OPEN <mode I,O or R>,[#]<file numb>,<filename>[<rcd length>]
- Random file record length is optional--default is 128 bytes.
-
- GEM OPENW <window number> opens one ST BASIC window.
- Windows: 0=EDIT, 1=LIST, 2=OUTPUT, 3=COMMAND
-
- ARRAY OPTION BASE <1 or 0> Sets base subscript values of array.
- (Default base is 0. If 0, array has N+1 elements.)
-
- I/O OUT <integer port number>,<integer expression>
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 7
-
-
- Sends data byte to port: 0=Pr,1=RS232,2=Scr,3=MIDI,4=Keybd
-
- GRAPHIC PCIRCLE <XC,YC,R>[<,start angle,end angle>]
- This draws solid circles and arcs at center XC,YC,Radius R
- Angles are in degrees times 10, from right, counter-
- clockwise. The FILL color is parm 2 of COLOR statement.
-
- GEM X = PEEK(<memory location>) Returns memory contents
- (Controlled by DEF SEG--see explanation)
-
- GRAPHIC PELLIPSE <XC,YC,XR,YR<[<,start angle,end angle>]
- This draws filled ellipses and elliptical pie shapes.
-
- GEM POKE <location to poke>,<data to poke>
- Stores data in memory, as governed by DEF SEG.
- This could crash the system.
-
- I/O X = POS(<dummy argument>) Returns current cursor position.
- This is on screen (or printer?)
-
- I/O PRINT [<expression><, or ;><expression>[<, or ;>]]
- This prints data to the ST BASIC GEM Output Window.
- PRINT can be abbreviated with a question mark '?'.
-
- I/O PRINT# <file number>,<expression>,<expression>
- This prints data to a disk file in same format as screen.
- It can be abbreviated as '?#' instead of 'PRINT#'.
-
- I/0 PRINT USING <string expr>;<list of expr.>
- PRINT# <file number>,USING<"string expr.">;<list of expr>
- These can be abbreviated with '?' in place of 'PRINT'.
- The print "mask" characters include: !, \chars\, &, #, '.',
- +, -, **, $$, **$, ',', _, and ^^^^.
-
- I/O PUT [#]<file number>,<record number>
- This outputs a random file record from a buffer.
-
- CONTROL QUIT Leaves ST BASIC and returns to GEM command level
-
- MATH RANDOMIZE [<numeric expression>] makes new border print.
-
- I/0 READ <variable>,<variable>
- Assigns DATA statement values to variables.
-
- BASIC REM THIS IS A REMARK or ' THIS IS A REMARK
-
- BASIC RENUM [<new first line>][,<starting line>][<increment>]
- This renumbers BASIC program lines, via BASIC.WRK
-
- I/O REPLACE [<filename>][,<line number list>]
- Replaces old file name.
-
- GEM RESET puts outout window into graphics buffer.
- (Opposite of OPENW <number>)
-
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 8
-
-
- I/O RESTORE <line descriptor> Allows rereading of DATA.
-
- CONTROL RESUME (0) or RESUME NEXT or RESUME <line descriptor>
- Returns from error routine.
-
- CONTROL RETURN Returns from subroutine after GOSUB entry.
-
- STRING X$ = RIGHT$(<target string> , <number of char>)
- This returns right end of string.
-
- MATH X = RND[(<numeric expression>)] Gives random number.
- RND(0) repeats random number. RND(Y) gives next number.
- RND(-Y) reseeds random number and gives first value.
-
- FILE RSET <string variable>=<string expression>
- This right justifies string for fielded random file buffer.
-
- BASIC RUN <,line descriptor> or RUN <filename>
-
- BASIC SAVE [<filename>], [<line descriptor list>] Saves program
-
- MATH X = SGN(<numeric expression>) Returns sign of a number:
- POS = 1; NEG = -1; and ZERO = 0.
-
- MATH X = SIN(<numeric expression>) where argument is radians.
- rad = degrees * pi/180, where pi = 3.141593. Result is
- a real number even when angle given as an integer.
-
- SOUND SOUND VOICE, VOLUME, NOTE, OCTAVE, DURATION
- Voice=channel 1-3. VOL=0-15. NOTE number=1-12. OCTAVE=1-8.
- Duration=time in 1/50 sec.
-
- STRING X$ = SPACE$(<numeric expression>) returns up to 255 spaces
-
- PRINT PRINT SPC(<numeric expression>)
- This prints spaces, MOD the printer width if<256.
- IF Num.Xpr. > 255, MOD 255.
-
- MATH X = SQR(numeric expression) Gives square root of pos. num.
-
- CONTROL STEP or STEP <,line descr.) or STEP <filename>
- This runs program one line at a time.
-
- CONTROL STOP Stops PGM, returns to BASIC Command GEM window.
- Stops, leaving open files--use CONT or [Return] to continue.
-
- STRING X$ = STR$(<numeric expression>) (Oppos. of VAL)
- This puts a number in a string as though printed.
- Pos. numbers begin with SPACE--Neg. begin with '-'.
-
- STRING X$ = STRING$(<num. expr>,<num or string expr>)
- This gives a string of length arg-1, from arg-2.
- Ex. ? STRING$(5,"*") prints '*****'. 'AAA' = STRING$(3,65)
-
- BASIC SWAP <first variable>,<second variable> trade values
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 9
-
-
-
- GEM X = PEEK(SYSTAB+OFFSET) (See page C-141)
- SYSTAB + 0: Resolution: 1 = HI, 2 = MED, 4 = LO
- +20: Graphics Buffer if BUFFERED GRAPHICS enabled.
- --4 byte pointer to 32768 byte buffer
- +24: GEMFLAG (0 = normal, 1 = off)
- --on required for MOUSE, SCREEN & KEYBOARD)
-
- CONTROL SYSTEM (Same as QUIT--closes files, returns to GEM)
-
- PRINT PRINT TAB(<tab position>) moves cursor to column given.
- If WIDTH < <tab> < 256, MOD Width.
- If <tab> > 256, MOD 256.
-
- MATH X = TAN(<angle in radians>)
- Radians = Degrees * 3.141593 / 180
-
- DEBUG TRACE [<line descriptor list>] -- Opp. is UNTRACE
- This prints selected line number commands as they execute.
- Ex. TRACE 20,40 does two lines; TRACE 20-40 does the range.
-
- DEBUG TROFF [<line descriptor list>]
- This cancels TRON all or partially.
-
- DEBUG TRON [<line descriptor list>] prints line numbers only
-
- DEBUG UNBREAK [<line descriptor list>]
- This [selectively] cancels BREAK (STOP on line#) command.
-
- CONTROL UNFOLLOW [<variable>],[<variable>]
- This (partially) cancels FOLLOW
-
- CONTROL UNTRACE [<line descriptor list>] cancels TRACE all or part.
-
- STRING X = VAL(<digit string expression>) -- Converts to real num.
- This scans strings like the INPUT# statement. (Opp: STR$)
-
- CONTROL X = VARPTR(<variable>) or = VARPTR(#<file number>)
- This gives variable address, or gives addr. of file buffer
- This could be used with BSAVE or BLOAD.
-
- GEM VDISYS(<Dummy Argument>)
- This gives access to VDI interface--see page C-156.
-
- I/O WAIT <port number>,<integer expression>[,<integer expression>]
- Waits (forever?) until bit pattern found--see page C-157
-
- SOUND WAVE ENABLE, ENVELOPE, SHAPE, PERIOD, DELAY (5 num.expr)
- ENABLE: 0 in bits 0-2 enable voice 1-3.
- 0 in bits 3-5 places noise on voice 1-3.
- ENVELOPE: 1 in bits 0-2 enables envelope for voices 1-3.
- SHAPE: Env. shape & cycle register--bits 0-3?
- PERIOD: Sets period of the envelope.
- DELAY: Sets time in 1/50 second incr.
-
-
-
-
-
-
-
-
-
- ATARI 520ST--BASIC QUICK REFERENCE (Nov. 1985)--Page 10
-
-
- CONTROL WEND Signals the end of a WHILE/WEND loop.
-
- CONTROL WHILE <logical expression> begins loop ended by WEND
-
- CONTROL WIDTH [LPRINT] <integer expression> -- default is 72 char
- If printer width = 255, omits carriage return at line end.
-
- I/O WRITE [<expression>],<expression> outputs to screen line
-
- I/O WRITE #[<expression>],<expression> outputs to sequen. file
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa