home *** CD-ROM | disk | FTP | other *** search
- .hm 1
- .he
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- PART 5:
-
-
- Programming Reference Information
-
- .paè.he UCPM Manual, Reference, Page #
-
- A. CP/M BDOS AND BIOS REFERENCE
-
- 1. BDOS Calls
-
- Function and Number Input Parameters Output Parameters
-
- System Reset 0 None None
- Read Console 1 None ASCII Char in A
- Write Console 2 ASCII Char in E None
- Read Reader 3 None ASCII Char in A
- Write Punch 4 ASCII Char in E None
- Write List 5 ASCII Char in E None
- Direct Con I/O 6 ASCII Char in E I/O Status in A if E=0FFH
- Get I/O Status 7 None I/O Status in A
- Put I/O Status 8 I/O Status in E None
- Print Buffer 9 Address of string None
- terminated by $
- in DE
- Read Buffer 10 Address of Read Read Buffer is filled
- Buffer in DE
- Console Ready 11 None LSB of A is 1 if char
- ready
- *All function numbers are passed in Reg C.
-
-
- 2« BIOS Calls
-
- Function and Number Input Parameters Output Parameters
-
- Return Version # 12 None Version Info in HL
- H=0 CP/M, H=1 MP/M
- L=00 CP/M 1.x, 2x 2.x
- Init BDOS 13 None None
- Log-In Disk 14 Value in Reg E None
- A=0, B=1, C=2,
- D=3
- Open File 15 Address of FCB Byte address of FCB
- in DE if found or 0FFH if not
- Close File 16 Address of FCB Byte address of FCB
- in DE if found or 0FFH if not
- Search for File 17 Address of FCB Byte address of FCB (0-3)
- in DE if found or 0FFH if not
- Search for Next 18 Address of FCB Byte address of next FCB
- in DE if found or 0FFH if not
- Delete File 19 Address of FCB Byte address of FCB (0-3)
- in DE if found or 0FFH if not
- Read Next Record 20 Address of FCB 0=successful read
- in DE 1=read past EOF
- 2=reading random data
- Write Next Rec 21 Address of FCB 0=successful write
- in DE 1=error in extending
- 2=end of disk data
- 255=no more dir space
- Make File 22 Address of FCB Byte address of FCB orè in DE 255 if no more dir space
- Rename FCB 23 Address of FCB Byte Address of Dir entry
- in DE or 255 if no match
- Return Log Code 24 None Login vector in HL
- Read Drive No 25 None Number of logged-in drive
- (A=0, B=1, C=2, D=3)
- Set DMA Address 26 Address of 128 None
- byte buffer in DE
- Get Alloc Vect 27 None Allocation Vect Addr in
- HL
- Write Prot Disk 28 None None
- Get R/O Vect 29 None HL=R/O Vect Val
- Set File Attrib 30 Ptr to FCB in DE Dir code in A
- Get Disk Parms 31 None HL=DPB Address
- Set/Get Usr Code 32 E=0FFH (get)/Code A=Current code (get)/no
- (set) value (set)
- Read Random 33 DE=FCB addr A=return code
- 1=reading unwritten data
- 2=(not used)
- 3=can't close curr ext
- 4=seek to unwritten ext
- 5=(not used)
- 6=seek past end of disk
- Write Random 34 DE=FCB addr A=return code
- 1=reading unwritten data
- 2=(not used)
- 3=can't close curr ext
- 4=seek to unwritten ext
- 5=dir overflow
- 6=seek past end of disk
- Compute File Siz 35 DE=FCB addr Random Rec Field set
- to file size
- Set Random Rec 36 DE=FCB addr Random Rec Field set
-
-
- *All function numbers are passed in Reg C
-
- .paèB. Reference for Standard CP/M Assembly-Language Tools
-
-
- 1. ASM
-
- The ASM Command loads and executes the CP/M 8080 assembler. It is of
- the form --
-
- ASM filename.xyz
-
- where
-
- filename ... is the name of the file 'filename.ASM' to assemble
- x ... designates the disk name which contains the source
- y ... designates the disk name to contain the hex file
- (y=Z suppresses generation of the hex file)
- z ... designates the disk name to contain the print file
- (y=X lists on CON:, y=Z suppresses listing)
-
-
- 2. LOAD
-
- áááááThσá LOA─á CommanΣ read≤ thσ filσ specified¼á whicΦ i≤á assumeΣá t∩ ì
- ááááácontaiεá Inte∞ he° forma⌠ machinσ codσ anΣ produce≤ ß memor∙á imagσ ì
- áááááfilσá whicΦá caε bσ subsequentl∙ executeΣ (convert≤á .HE╪á t∩á .CO═ ì
- áááááfiles)« I⌠ i≤ oµ thσ forφ --
-
- LOAD filename
-
- áááááwherσ filenamσ i≤ thσ namσ oµ thσ filσ 'filename.HEX'.
-
-
- 3. DDT
-
-
- áááááThσá DD╘ Prograφ allow≤ dynamiπ interactivσ testinτ anΣ debugginτ ì
- áááááoµ program≤ generateΣ iε thσ CP/═ environment« I⌠ i≤ invokeΣ b∙ --
-
- DDT
- DDT filename.HEX
- DDT filename.COM
-
- where 'filename' is the name of the program to be loaded or tested.
-
- DDT responds to the normal CP/M input line editing characters.
-
- DDT responds to the following commands --
-
- As Perform inline assembly starting at the specified address s.
- D Display memory from the current address for 16 display lines.
- Ds Display memory from address s for 16 display lines.
- Ds,f Display memory from address s to address f.
-
- Fs,f,c
- Fill memory from start address s to final address f with byte c.è
- G Start execution at the current value of the PC.
- Gs Start execution at the specified address s.
- Gs,b Start execution at the specified address s and set a breakpoint
- at the address b.
- Gs,b,c
- Same as above with breakpoints at b and c.
- G,b Start execution at the current value of the PC with breakpoint b.
- G,b,c
- Same as above with breakpoints at b and c.
-
- If Insert a file name f into the default FCB.
-
- L List 12 lines of disassembled code from the current address.
- Ls List 12 lines from the specified address s.
- Ls,f List lines of disassembled code from s to f.
-
- Ms,f,d
- Move the block from address s to f to destination at address d.
-
- R Read file in FCB into memory at 100H.
- Rb Read file in FCB into memory with offset b from 100H.
-
- Ss Set (examine and alter) memory starting at address s.
-
- T Trace the next instruction.
- Tn Trace the next n instructions.
-
- U Untrace -- like Trace, but intermediate steps are not displayed.
-
- X Examine all registers and flags.
- Xr Examine specified registers or flag, where r may be --
- C Carry flag
- Z Zero flag
- M Minus (sign) flag
- I Interdigit Carry flag
- A Accumulator
- B BC Reg pair
- D DE Reg pair
- H HL Reg pair
- S Stack pointer
- P PC
-
-
- 4. MAC
-
- áááááMA├á i≤ thσ CP/═ StandarΣ Macr∩ Assembler╗á i⌠ i≤ upward-compatablσ ì
- áááááwitΦá ASM¼á thσ CP/═ StandarΣ Assembler«á Thσ facilitie≤ oµá MA├ ì
- áááááincludσá assembl∙á oµá Inte∞á 808░á microcompute≥á mnemonics¼ ì
- áááááalonτá witΦ assembly-timσ expressions¼á conditiona∞á assembly¼ ì
- ááááápagσ formattinτ features¼ anΣ ß macr∩ processo≥ whicΦ i≤ compaì
- ááááátablσá witΦá thσ standarΣ Inte∞ definitioε (MA├á implement≤á thσ ì
- ááááámid-197╖ revisioε oµ Intel'≤ definition).
-
- .cp 6è MAC is invoked by the following command --
- MAC d:filename $parms
- áááááOnl∙ 'filenameº i≤ required¼á anΣ i⌠ represent≤ ß filσ nameΣ 'fileì
- áááááname.ASM'«á MA├á ma∙ theε generatσ u≡ t∩ │ othe≥ file≤á -- fileì
- áááááname.HE╪ (thσ Inte∞ He° Forma⌠ File)¼á filename.PR╬ (thσ Prin⌠ o≥ ì
- áááááListinτ file)¼á anΣ filename.SY═ (ß filσ containinτ ß sorteΣ lis⌠ ì
- áááááoµ thσ symbol≤ useΣ iε thσ program).
-
- áááááMACR╧ Librar∙ file≤ ma∙ bσ referenceΣ b∙ thσ program╗á thesσ file≤ ì
- áááááarσ nameΣ 'filename.LIB'.
-
- ááááá$parm≤á represent≤ thσ optiona∞ assembl∙ contro∞ parameter≤á whicΦ ì
- áááááarσ discusseΣ iε thσ nex⌠ section.
-
- áááááMA├á ma∙á bσá executeΣ b∙ employinτá thσá SUBMI╘á filσá MAC.SUB« ì
- áááááMAC.SU┬ assemble≤ thσ specifieΣ MA├ .AS═ file¼á convert≤ i⌠ int∩ ì
- áááááßá .CO═á filσá viß LOAD¼á anΣ erase≤ thσ .HE╪á file«á MAC.SU┬á i≤ ì
- áááááinvokeΣ b∙ --
-
- SUBMIT MAC filename
-
- áááááwherσ 'filenameº i≤ thσ namσ oµ thσ MA├ filσ 'filename.ASM'.
-
- áááááThσ contro∞ paramete≥ lis⌠ i≤ precedeΣ b∙ ß $¼ anΣ ma∙ contaiε an∙ ì
- áááááoµ thσ followinτ iε an∙ orde≥ --
- A - controls the source disk for the .ASM file
- H - controls the destination of the .HEX machine code file
- L - controls the source disk for the .LIB files
- M - controls MACRO listing in the .PRN file
- P - controls the destination of the .PRN listing file
- Q - controls the listing of LOCAL symbols
- S - controls the generation and destination of the .SYM file
- 1 - controls pass 1 listing
-
- áááááIε thσ casσ oµ thσ A¼á H¼á L¼á P¼á anΣ ╙ parameters¼á the∙ ma∙á bσ ì
- áááááfolloweΣ b∙ thσ drivσ namσ froφ whicΦ t∩ obtaiε o≥ t∩ whicΦ t∩ senΣ ì
- ááááádata¼ wherσ --
-
- A,B,C,D -- designates that particular drive
- P -- designates the LST: device
- X -- designates the user console (CON:)
- Z -- designates a null file (no output)
-
- For example,
- $PB AA HB SX
- ááááásend≤á thσ .PR╬ filσ t∩ drivσ B:¼á get≤ thσ .AS═ filσ froφá drivσ ì
- áááááA:¼á send≤á thσ .HE╪ filσ t∩ drivσ B:¼á anΣ send≤ thσ .SY═ filσ t∩ ì
- áááááCON:.
-
- áááááThσ parameter≤ L¼ S¼ M¼ Q¼ anΣ ▒ ma∙ bσ precedeΣ b∙ eithe≥ ½ o≥ - ì
- ááááát∩ enablσ o≥ disablσ thei≥ respectivσ function≤ --
-
- +L - list the input lines read from the MACRO library
- -L - suppress listing of the MACRO library (default)
- è +S - append the .SYM output to the end of the .PRN file (default)
- -S - suppress the generation of the sorted symbol table
-
- +M - list all MACRO lines as they are processed (default)
- -M - suppress all MACRO lines as they are processed
- *M - list only HEX code generated by macro expansions in listing
-
- +Q - list all LOCAL symbols in the symbol list
- -Q - suppress all LOCAL symbols in the symbol list (default)
-
- +1 - produce a listing file on the first pass (for MACRO debugging)
- -1 - suppress listing on pass 1 (default)
-
- áááááThσá programme≥á caεá interspersσá control≤á throughou⌠áá thσ ì
- áááááassembl∙ languagσ sourcσ o≥ librar∙ files«á IntersperseΣ control≤ ì
- áááááarσá denoteΣá b∙ ß "$ó iε thσ firs⌠ columε oµ thσá inpu⌠á linσ ì
- áááááfolloweΣ immediatel∙ b∙ ß parameter.
-
- The following Pseudo-Ops are supported --
- DB defines data bytes or strings of data
- DS reserves storage areas
- DW defines words of storage
- ELSE alternate to IF
- END terminates the physical program
- ENDIF marks the end of conditional assembly
- ENDM marks the end of a MACRO
- EQU performs a numeric "equate"
- EXITM abort expansion of the current MACRO level
- IF begins conditional assembly
- IRP INLINE MACRO with string substitution
- IRPC INLINE MACRO with character substitution
- LOCAL define LOCAL variables unique to each MACRO repetition
- MACLIB specify MACRO Library to load
- MACRO defines beginning of a MACRO
- ORG sets the program or data origin
- PAGE defines the listing page size for output
- REPT defines the beginning of a INLINE MACRO
- SET performs a numeric "set" or assignment
- TITLE enables page titles and options
-
-
- ááááá┬á - Balancσ error║á MACR╧ doesn'⌠ terminatσ properl∙ o≥ condiì
- ááááátiona∞ assembly is ill-formed
- ááááá├á - Commßá error║áá expressioεá wa≤á encountereΣá bu⌠á no⌠ ì
- ááááádelimiteΣ properly from the next item by a comma
- ááááá─á - Datσá error║á elemen⌠ iε ß datß statemen⌠ (DB,DW⌐á canno⌠á bσ ì
- áááááplaceΣ iε thσ specifieΣ datß area
- E - Expression error: expression is ill-formed and cannot be computed
- I - Invalid character: a non-graphic character has been found
- L - Label error: label cannot appear in this context
- M - MACRO overflow error: internal MACRO expansion table overflow
- N - Not implemented error: unimplemented feature used
- ááááá╧ - Overflo≈ error║á expressioε i≤ to∩ complicateΣ o≥ thσ numbe≥ ì
- áááááoµ LOCA╠ label≤ ha≤ exceedeΣ 9999
- ááááá╨á - Phasσá error║á label≤ doe≤ no⌠ havσ samσ valuσá oεá botΦ ìèááááápasse≤ (multiplσ label)
- ááááá╥á - Registe≥ error║á valuσ specifieΣ fo≥ ß registe≥ i≤ no⌠á comì
- ááááápatablσ witΦ o≡ code
- S - Statement/Syntax error: statement is ill-formed
- V - Value error: operand is improperly formed or out of range
-
- Console Error Messages:
-
- NO SOURCE FILE PRESENT - .ASM file not found
- NO DIRECTORY SPACE - Directory is full
- áááááSOURC┼á FIL┼á NAM┼á ERRO╥ - Thσ forφ oµ thσ sourcσá filσá namσá i≤ ì
- áááááinvalid╗á notσ tha⌠ MA├ i≤ invokeΣ b∙ 'MA├ filename'¼ anΣ thσ .AS═ ì
- áááááfilσ typσ i≤ NO╘ specified.
- SOURCE FILE READ ERROR - Error in reading source file
- OUTPUT FILE WRITE ERROR - Error in writing output file
- CANNOT CLOSE FILE - An output file cannot be closed.
- UNBALANCED MACRO LIBRARY - No ENDM encountered for a MACRO definition
- áááááINVALI─á PARAMETE╥ - InvaliΣ assembl∙ paramete≥ wa≤ founΣá iεá thσ ì
- áááááinpu⌠ line.
-
-
- 5. LINK
-
- The format for the invocation of Linker is
-
-
- LINK <filename1.ext/s,filename2.ext/s,....>
-
- where filename stands for Disk drive letter followed by a colon
- followed by the absolute file name
-
- ext is used if the module extension is different than .rel
-
- /s stands for switch options.
-
- EXAMPLE of a link
-
- LINK MAIN,FORLIB/S,MAIN/N/G/E
-
- The first MAIN is the name of the module from the fortran compiler
- The FORLIB/S is the library of standard fortran routines that will
- be selected
- The MAIN/N/G/E means to name the .COM file MAIN and to save it on
- current disk then execute MAIN automatically.
-
- SWITCH OPTIONS
-
- Each switch option is preceded by a /
-
- E .... Exit to operating system
-
- G .... Go start execution
- Start execution of the program as soon as the current command
- line has been interpreted.
- è M .... Map all symbols
- List both all the defined globals and their values and all
- undefined globals followed by an asterisk.
-
- R .... Reset the linker
- Puts the linker back to its initial state. the /R is used
- to restart LINK if the wrong file was loaded by mistake.
-
- S .... Search file
- Search the disk file having the filename immediately preceding
- the /S in the command string, to satisfy any undefined globals.
- This is convenient for having the linker search a library file
- of musch-used routines.
-
- U .... List all undefined globals
- List all undefined globals as soon as the current command line
- has been interpreted and executed. Link defaults to this
- switch; therefore it is generally not needed.
-
- ERROR MESSAGES:
-
- No start address a /G is issued but no main program module
- has been loaded.
-
- Loading error The file given is not a properly formatted
- link object file.
-
- Fatal Table Collision There is not enough memory
-
- Command error Unrecognizable link command
-
- File not found Specified file not on specified disk
-
- mult def global More than one definition of the global name
- (possibly wrong modules combined)
-
-
- 6. SID
-
- Syntax:
-
- SID {pgm-filespec} {,sym-filespec}
-
- Explanation:
-
- áááááThσá SI─ symboliπ debugge≥ allow≤ yo⌡ t∩ monito≥ anΣá tes⌠ ì
- áááááprogram≤á developeΣ fo≥ thσ 808░ microprocessor«á SI─ support≤ ì
- áááááreal-timσ breakpoints¼á full∙ monitoreΣ execution¼á symboliπ ì
- ááááádisassembly¼á assembly¼á anΣ memor∙ displa∙ anΣ fil∞ functions« ì
- áááááSI─á caε dynamicall∙ loaΣ SI─ utilit∙ program≤ t∩á providσ ì
- ááááátracebacδ anΣ histograφ facilities.
-
- .cp 6è Commands:
-
- Command Meaning
-
- As (Assemble) Enter assembly language
- statements
- s is the start address
-
- Cs{b{,d}} (Call) Call to memory location from SID
- s is the called address
- b is the value of the BC register
- pair d is the value of the DE
- register pair
-
- D{W}{s}{,f} (Display) Display memory in hex and ASCII
- W is a 16-bit word format
- s is the start address
- f is the finish address
-
- Epgm-filespec (Load) Load program and symbol table
- {,sym-filespec} for execution
-
-
-
- E*sym-filespec (Load) Load a symbol table file
-
- Fs,f,d (Fill) Fill memory with constant value
- s is the start address
- f is the finish address
- d is an eight-bit data item
-
- G{p}{,a{,b}} (Go) Begin Execution
- p is a start address
- a is a temporary breakpoint
-
- H (Hex) Displays all symbols with
- addresses in Hex
- H.a Displays hex, decimal, and ASCII
- values of a where
- a is a symbolic expression
-
- Ha,b Computes hex sum and difference
- of a and b where
- a and b are symbolic expressions
-
- Icommand tail (Input) Input CCP command line
-
- L{s}{,f} (List) List 8080 mnemonic instructions
- s is the start address
- f is the finish address
- Ms,h,d (Move) Move Memory Block
- s is the start address
- h is the high address of the block
- d is the destination start address
- è P{p{,c}} (Pass) Pass point set, reset, and display
- p is a permanent breakpoint address
- c is initial value of pass counter
-
- Rfilespec{,d} (Read) Read Code/Symbols
- d is an offset to each address
-
- S{W}s (Set) Set Memory Values
- s is address where value is sent
- W is 16 bit word
-
- T{n{,c}} (Trace) Trace Program Execution
- n is the number of program steps
- c is the utility entry address.
-
- T{W}{n{,c}} (Trace) Trace Without Call
- W instructs SID not to trace
- subroutines
- n is the number of program steps
- c is the utility entry address
-
- U{W}{n{,c}} (Untrace) Monitor Execution without Trace
- n is the number of program steps
- c is the utility entry address
- W instructs SID not to trace
- subroutines
-
- V (Value) Display the value of the next
- available location in memory
- (NEXT), the next location after
- the largest file read in (MSZE),
- the current value of the Program
- counter (PC), and the address of
- the end of available memory (END)
-
- Wfilespec,s,f (Write) Write the contents of a contiguous
- block of memory to filespec.
- f is finish address
-
- X{f}{r} (Examine) Examine/alter CPU state.
- f is flag bit C,Z,M,E or I.
- r is register A,B,D,H,S or P.
-
- .paèC. Microsoft BASIC Reference
-
- 1. General Statements
-
- Command Syntax Function
- AUTO AUTO [line][,inc] Generate line numbers
- CLEAR CLEAR [,[exp1][,exp2]] Clear program variables; Exp1 sets
- end of memory and Exp2 sets amount
- of stack space
- CONT CONT Continue program execution
- DELETE DELETE [[start][-[end]]] Delete program lines
- EDIT EDIT line Edit a program line
-
- FILES FILES [filename] Directory
- LIST LIST [line[-[line]]] List program line(s)
- LLIST LLIST [line[-[line]]] List program line(s) on printer
- LOAD LOAD filename[,R] Load program; ,R means RUN
- MERGE MERGE filename Merge prog on disk with that in mem
-
- NAME NAME old AS new Change the name of a disk file
- NEW NEW Delete current prog and vars
- NULL NULL exp Set num of <NULL>s after each line
- RENUM RENUM [[new][,[old][,inc]]] Renumber program lines
- RESET RESET Init CP/M; use after disk change
- RUN RUN [line number] Run a prog (from a particular line)
- RUN filename[,R] Run a prog on disk
- SAVE SAVE filename[,A or ,P] Save prog onto disk; ,A saves prog
- in ASCII and ,P protects file
- SYSTEM SYSTEM Return to CP/M
- TROFF TROFF Turn trace off
- TRON TRON Turn trace on
- WIDTH WIDTH [LPRINT] exp Set term or printer carriage width;
-
- 2. Program Control Statements
-
- CALL CALL variable [(arg list)] Call assembly or FORTRAN routine
- CHAIN CHAIN [MERGE] filename [,[line exp][,ALL][,DELETE range]]
- Call a program and pass variables to it; MERGE with ASCII
- files allows overlays; start at line exp if given; ALL means
- all variables will be passed (otherwise COMMON only); DELETE
- allows deletion of an overlay before CHAIN is executed
- COMMON COMMON list of vars Pass vars to a CHAINed prog
- DEF DEF FNx[(arg list)]=exp Arith or String Function
- DEF USRn=address Define adr for nth assembly routine
- DEFINT range(s) of letters Define default var type INTeger
- DEFSNG " " " " " " " Single
- DEFDBL " " " " " " " Double
- DEFSTR " " " " " " " String
- DIM DIM list of subscripted vars Allocate arrays
-
- END END Stop prog and close files
- ERASE ERASE var [,var ... ] Release space and var names
- ERROR ERROR code Generate error code/message
- FOR FOR var=exp TO exp [STEP exp] FOR loop
- GOSUB GOSUB line number Call BASIC subroutineèGOTO GOTO line number Branch to specified line
- IF/GOTO IF exp GOTO line [ELSE stmt ... ]
- IF exp <> 0 then GOTO
- IF/THEN IF exp THEN stmt[:stmt] [ELSE stmt ... ]
- IF exp <> 0 then ... else ...
- LET [LET] var=exp Assignment
-
- MID$ MID$(string,n[,m])=string2 Replace a portion of string with
- string2; start at pos n for m chars
- NEXT NEXT var[,var ... ] End FOR
- ON ERROR ON ERROR GOTO line Error trap subroutine
- GOTO
- ON/GOSUB ON exp GOSUB line[,line] Computed GOSUB
- ON/GOTO ON exp GOTO line[,line] Computed GOTO
- OPTION OPTION BASE n Min val for subscripts (n=0,1)
- BASE
- OUT OUT port,byte Output byte to port
- POKE POKE address,byte Memory put
- RANDOMIZE RANDOMIZE [exp] Reseed random number generator
- REM REM any text Remark -- comment
- RESTORE RESTORE [line] Reset DATA pointer
- RESUME RESUME or RESUME 0 Return from ON ERROR GOTO
- RESUME NEXT Return to stmt after error line
- RESUME line Return to specified line
- RETURN RETURN Return from subroutine
- STOP STOP Stop prog and print BREAK msg
- WAIT WAIT prot,mask[,select] Pause until input port [XOR select]
- AND mask <> 0
- WHILE/ WHILE exp stmts ... WEND Execute stmts as long as exp is T
- WEND
-
- 3. Input - Output Statements
-
- Statement Syntax/Function
- CLOSE CLOSE [[#]f[,[#]f ... ]]
- Close disk files; if no arg, close all
- DATA DATA constant list
- List data for READ statement
- FIELD FIELD [#]f,n AS string var [,n AS string var ...]
- Define fields in random file buffer
- GET GET [#]f[,record number]
- Read a record from a random disk file
- INPUT INPUT [;] [prompt string;] var [,var ...]
- INPUT [;] [prompt string,] var [,var ...]
- Read data from the terminal; leading semicolon suppresses echo
- of <CR>/<LF> and semicolon after prompt string causes question
- mark after prompt while comma after prompt suppresses question
- mark
- KILL KILL filename
- Delete a disk file
- LINE LINE INPUT [;] [prompt string;] string var
- INPUT Read an entire line from terminal; leading semicolon suppresses
- echo of <CR>/<LF>
- LINE INPUT #f,string var
- Read an entire line from a disk fileèLSET LSET field var=string exp
- Store data in random file buffer left-justified or left-justify
- a non-disk string in a given field
- OPEN OPEN mode,[#] f,filename
- Open a disk file; mode must be one of --
- I = sequential input file
- O = sequential output file
- R = random input/output file
- PRINT PRINT [USING format string;] exp [,exp ...]
- Print data at the terminal using the format specified
- PRINT #f, [USING format string;] exp [,exp ...]
- Write data to a disk file
- LPRINT [USING format string;] var [,var ...]
- Write data to a line printer
- PUT PUT [#] f [,record number]
- Write data from a random buffer to a data file
- READ READ var [,var ...]
- Read data from a DATA statement into the specified vars
- RSET RSET field var = string exp
- Store data in a random file buffer right justified or right
- justify a non-disk string in a given field
- WRITE WRITE [list of exps]
- Output data to the terminal
- WRITE #f, list of exps
- Output data to a sequential file or a random field buffer
-
- 4. Mathematica∞ Functions
-
- Function Action
-
- ABS(exp) Absolute value of expression
- ATN(exp) Arctangent of expression (in radians)
- CDBL(exp) Convert the expression to a double precision number
- CINT(exp) Convert the expression to an integer
- COS(exp) Cosine of the expression (in radians)
- CSNG(exp) Convert the expression to a single precision number
- EXP(exp) Raises the constant E to the power of the expression
- FIX(exp) Returns truncated integer of expression
- FRE(exp) Gives memory free space not used by MBASIC
- INT(exp) Evaluates the expression for the largest integer
- LOG(exp) Gives the natural log of the expression
- RND[(exp)] Generates a random number
- exp <0 seeds new sequence
- exp =0 returns previous number
- exp >0 or omitted returns new random number
- SGN(exp) 1 if exp >0
- 0 if exp =0
- -1 if exp <0
- SIN(exp) Sine of the expression (in radians)
- SQR(exp) Square root of expression
- TAN(exp) Tangent of the expression (in radians)
-
- .cp 6è5« Strinτ Functions
-
- ASC(str) Returns ASCII value of first char in string
- CHR$(exp) Returns a 1-char string whose char has ASCII code of exp
- FRE(str) Returns remaining memory free space
- HEX$(exp) Converts a number to a hexadecimal string
- INPUT$(length [,[#]f])
- Returns a string of length chars read from console or from a
- disk file; characters are not echoed
-
- INSTR([exp,]str1,str2)
- Returns the first position of the first occurrence of str2
- in str1 starting at position exp
- LEFT$(str,len) Returns leftmost length chars of the string expression
- LEN(str) Returns the length of a string
- MID$(string,start[,length])
- Returns chars from the middle of the string starting at the
- position specified to the end of the string or for length
- characters
- OCT$(exp) Converts an expression to an Octal string
- RIGHT$(str,len)
- Returns rightmost length chars of the string expression
- SPACE$(exp) Returns a string of exp spaces
- STR$(exp) Converts a numeric expression to a string
- STRING$(length,str)
- Returns a string length long containing the first char of
- the str
- STRING$(length,exp)
- Returns a string length long containing chars with numeric
- value exp
- VAL(str) Converts the string representation of a number to its
- numeric value
-
- 6« Othe≥ Functions
-
- Function Action
- CVI(str) Converts a 2-char string to an integer
- CVS(str) Converts a 4-char string to a single precision number
- CVD(str) Converts an 8-char string to a double precision number
- EOF(f) Returns TRUE (-1) if file is positioned at its end
- ERL Error Line Number
- ERR Error Code Number
- INP(port) Inputs a byte from an input port
- LOC(f) Returns next record number to read or write (random file) or
- number of sectors read or written (sequential file)
- LPOS(n) Returns carriage position of line printer (n is dummy)
- MKI$(value) Converts an integer to a 2-char string
- MKS$(value) Converts a single precision values to a 4-char string
- MKD$(value) Converts a double precision value to an 8-char string
- PEEK(exp) Reads a byte from memory location specified by exp
- POS(n) Returns carriage position of terminal (n is dummy)
- SPC(exp) Used in PRINT statements to print spaces
- TAB(exp) Used in PRINT statements to tab to specified positionèUSR[n](arg) Calls the user's machine language subroutine with the arg
- VARPTR(var) Returns address of var in memory or zero if var has not been
- assigned a value
- VARPTR(#f) Returns the address of the disk I/O buffer assigned to file
- number
-
- .paè