Annotation of rpl/man/rpl.1.in, revision 1.2

1.1       bertrand    1: .\" Manual page for the RPL/2 language 
                      2: .\" 04.19.2006
                      3: .TH RPL/2 1 "@DATE@" JKB-Labs "RPL/2 user manual"
                      4: .SH NAME
                      5: Reverse Polish Lisp/2 release @VERSION@,
                      6: .br
                      7: half-compiled high-level language using shared libaries
                      8: and mainly aiming at scientific calculations and complex algorithms
                      9: .SH SYNOPSIS
                     10: .B rpl
                     11: [\-acdDhilnpPsv] [\-A data] [\-S script] [\-t level] [program]
                     12: .SH DESCRIPTION
                     13: The
                     14: .B rpl
                     15: sequencer allows either the execution of a RPL/2 program or the opening
                     16: of an interactive session to enter commands directly
                     17: .SH OPTIONS
                     18: .TP
                     19: .B -a
                     20: displays informations about the author, the RPL/2 mailing-list and the
                     21: official WWW page of the language
                     22: .br
                     23: .TP
                     24: .B -A
                     25: sends parameters to main program
                     26: .br
                     27: .TP
                     28: .B -c
                     29: allows creation of a
                     30: .I rpl-core
                     31: file, providing a way to debug a program
                     32: .br
                     33: .TP
                     34: .B -d
                     35: debugs memory allocations inside RPL/2. Do not use if you do not
                     36: know what you do!
                     37: .br
                     38: .TP
                     39: .B -D
                     40: launches RPL/2 in daemon mode
                     41: .br
                     42: .TP
                     43: .B -h
                     44: shows a summary of available options
                     45: .br
                     46: .TP
                     47: .B -i
                     48: runs the RPL/2 sequencer in interactive mode. This option can't be used
                     49: with a program name as argument
                     50: .br
                     51: .TP
                     52: .B -l
                     53: prints the user licence of the software
                     54: .br
                     55: .TP
                     56: .B -n
                     57: ignores HUP signal
                     58: .br
                     59: .TP
                     60: .B -p
                     61: precompiles scripts before execution
                     62: .br
                     63: .TP
                     64: .B -P
                     65: computes profile data
                     66: .br
                     67: .TP
                     68: .B -s
                     69: disables splash screen
                     70: .br
                     71: .TP
                     72: .B -S
                     73: executes script on command line
                     74: .br
                     75: .TP
                     76: .B -t
                     77: enables tracing mode. Each internal operation is echoed on standard
                     78: output
                     79: .br
                     80: .TP
                     81: .B -v
                     82: prints the version number
                     83: .br
                     84: .RE
                     85: .SH "EXIT STATUS"
                     86: The sequencer returns a value of 0 if no error occurs when running a
                     87: program, else it returns a nonzero value.
                     88: .SH "PREREQUISITES AND VARIOUS ADVICES"
                     89: RPL_TMP_PATH env variable is used to specify the location of tempfiles.
                     90: If this variable is not set, RPL/2 tries to use /tmp, /var/tmp or ./.
                     91: It is also recommended to
                     92: use
                     93: \fIgnuplot\fR,
                     94: \fITeX/LaTeX\fR,
                     95: \fIdvips\fR and
                     96: \fIgv\fR in association with RPL/2, to get advanced graphical
                     97: capabilities
                     98: .SH "RELATED STANDARDS"
                     99: The RPL/2 sequencer is compliant with the HP-28S calculator user manual,
                    100: and with the HP-28S itself, in its 2BB version (C) HP 1986-1987.
                    101: Some operations dealing with complex numbers are not following the
                    102: definitions from HP, because they are bogus. The main such operations
                    103: are transposition and scalar product.
                    104: .SH "DELIMITERS"
                    105: .br
                    106: .TP
                    107: .B "none"
                    108: scalar, integer or real number, coded with at least 64 bits;
                    109: .br
                    110: .TP
                    111: .B "( )"
                    112: complex number, coded with at least 128 bits;
                    113: .br
                    114: .TP
                    115: .B "#"
                    116: binary integer, 64 bits of length;
                    117: .TP
                    118: .B "<< >>"
                    119: user-defined function, or equation (expressed in RPN);
                    120: .br
                    121: .TP
                    122: .B "' '"
                    123: algebraic equation or variable name;
                    124: .br
                    125: .TP
                    126: .B "[ ]"
                    127: scalar vector;
                    128: .br
                    129: .TP
                    130: .B "[[ ]]"
                    131: scalar matrix;
                    132: .br
                    133: .TP
                    134: .B "<[ ]>"
                    135: table;
                    136: .br
                    137: .TP
                    138: .B """ """
                    139: character string;
                    140: .br
                    141: .TP
                    142: .B "{ }"
                    143: list containing various objects. A list might contain other lists;
                    144: .TP
                    145: .br
                    146: .B "/* */"
                    147: comment;
                    148: .br
                    149: .TP
                    150: .B "//"
                    151: comment running to the end of a line;
                    152: .br
                    153: .SH "INSTRUCTIONS"
                    154: We list in this section the build-in instructions of the language. Some
                    155: might be written in several ways; the alternatives ways are listed
                    156: between parenthesis. Definitions between parenthesis in a structure are
                    157: optional. Instructions written in upper case are not case-sensitive.
                    158: .br
                    159: .TP
                    160: .B "CONTROL STRUCTURES"
                    161: IF/THEN/(ELSEIF/THEN)/(ELSE)/END, IFT, IFTE,
                    162: SELECT/CASE/THEN/END/(DEFAULT)/END
                    163: .br
                    164: .TP
                    165: .B "ERROR HANDLING"
                    166: CLRERR, ERRM, ERRN, IFERR/THEN/(ELSE)/END
                    167: .br
                    168: .TP
                    169: .B "LOOPS PROVIDING A COUNT"
                    170: FOR/(CYCLE)/(EXIT)/NEXT, FOR/(CYCLE)/(EXIT)/STEP
                    171: .br
                    172: .TP
                    173: .B "LOOPS WITHOUT COUNT"
                    174: START/(CYCLE)/(EXIT)/NEXT, START/(CYCLE)/(EXIT)/STEP
                    175: .br
                    176: .TP
                    177: .B "UNDEFINED LOOPS"
                    178: DO/(EXIT)/UNTIL/(EXIT)/END, WHILE/(EXIT)/REPEAT/(EXIT)/END
                    179: .br
                    180: .TP
                    181: .B "INPUT/OUTPUT"
                    182: BEEP, CLMF, DISP, INPUT, KEY, PROMPT
                    183: .br
                    184: .TP
                    185: .B "DEBUGGING"
                    186: CONT, HALT, SST
                    187: .br
                    188: .TP
                    189: .B "STACK HANDLING"
                    190: CLEAR, COPY, DEPTH, DROP, DROP2, DROPN, DUP, DUP2, DUPN, EDIT, OVER, PICK,
                    191: ROLL, ROLLD, ROT, SWAP
                    192: .br
                    193: .TP
                    194: .B "WORKING WITH VARIABLES"
1.2     ! bertrand  195: ->, CLUSR, PARAMETER, PRIVATE, PROTECT,
1.1       bertrand  196: PURGE, RCEQ, RCL, RECALL, SAVE, SCONJ, SHARED,
                    197: SINV, SNEG, STATIC, STEQ, STO, STO+,
                    198: STO-, STO*, STO/, STORE, UNPROTECT, VARIABLE, VARS, VISIT, VOLATILE
                    199: .br
                    200: .TP
                    201: .B "ARITHMETICAL OPERATIONS AND ELEMENTARY CALCULUS"
                    202: +, -, *, /, ^ (**), =, %, %CH, %T,
                    203: ABS, ARG, C->R, CEIL, CONJ, DECR, DER,
                    204: DFT, EVAL, EXP, EXPM, FACT, FFT, FLOOR,
                    205: FP, IDFT,
                    206: IFFT, IM, INCR, INT, INV, IP, MANT, MAX, MCLRIN, MIN, MOD, NEG,
                    207: P->R, ->Q, R->C, R->P, RE, RELAX, SIGN, SQ, SQRT, TAYLR, XPON, XROOT
                    208: .br
                    209: .TP
                    210: .B "CONSTANTS"
                    211: e, FALSE, i, PI, TRUE
                    212: .br
                    213: .TP
                    214: .B "FORMATTING"
                    215: ENG, FIX, RND, SCI, STD, TRNC
                    216: .br
                    217: .TP
                    218: .B "LOGICAL AND BINARY OPERATIONS"
                    219: <, <= (=<), <>, >, >= (=>), ==,
                    220: AND, ASL, ASR, B->R, BIN, CF, DEC, FC?, FC?C, FC?S, FS?, FS?C, FS?S,
                    221: HEX, IN, NOT, OCT, OR, R->B,
                    222: RCLF, RCWS, RL, RLB, RR, RRB, SAME, SF, SL, SLB, SR, SRB, STOF,
                    223: STWS, XOR
                    224: .br
                    225: .TP
                    226: .B "TRIGONOMETRY"
                    227: ACOS, ASIN, ATAN, COS, D->R, DEG, ->HMS, HMS->,
                    228: HMS-, HMS+, R->D, RAD, SIN, TAN
                    229: .br
                    230: .TP
                    231: .B "LOGARITHMS"
                    232: ACOSH, ALOG, ASINH, ATANH, COSH, LN, LNP1, LOG,
                    233: SINH, TANH
                    234: .br
                    235: .TP
                    236: .B "SPECIAL FUNCTIONS"
                    237: BESSEL, GAMMA
                    238: .br
                    239: .TP
                    240: .B "STATISTICS"
                    241: CLS, COLS, COMB, CORR, COV, DRWS, MAXS, MEAN, MINS, NRAND, NS, PCOV, PERM,
                    242: PSDEV, PVAR, RAND, RCLS, RDGN,
                    243: RDZ, S-, S+, SCLS, SDEV, SPAR, STOS, SX, SX2, SXY, SY,
                    244: SY2, TOT,
                    245: UTPC, UTPF, UTPN, UTPT, VAR, XCOL, YCOL
                    246: .br
                    247: .TP
                    248: .B "DEALING WITH MATRIX AND VECTOR"
                    249: ->ARRAY (->ARRY), ARRAY-> (ARRY->), CNRM, COL+, COL-, COL->, ->COL, CON, COND,
                    250: CROSS, CSWP, DET, DOT, DIAG->, ->DIAG, EGV, EGVL,
                    251: GEGV, GEGVL, GET, GETC, GETI, GETR,
                    252: GLEGV, GREGV, IDN, LCHOL, LEGV, LQ, LSQ, LU, MAX, MIN,
                    253: PUT, PUTC, PUTI, PUTR, QR, RANK,
                    254: RCI, RCIJ, RDM, REGV, RNRM, ROW+, ROW-, ROW->, ->ROW,
                    255: RSD, RSWP, SCHUR, SIZE, SQ, SVD, SVL, TRN, UCHOL
                    256: .br
                    257: .TP
                    258: .B "DEALING WITH TABLES"
                    259: CRTAB, GET, PUT, ->TABLE, TABLE->
                    260: .br
                    261: .TP
                    262: .B "LISTS"
                    263: GET, GETI, HEAD, ->LIST, LIST->, POS, PUT, PUTI, REPL,
                    264: REVLIST, SIZE, SORT, SUB, TAIL
                    265: .br
                    266: .TP
                    267: .B "STRINGS"
                    268: CHR, CURRENC, LCASE, NUM, POS, RECODE, REPL, SIZE, ->STR, STR->, SUB,
                    269: TOKENIZE, TRIM, UCASE
                    270: .br
                    271: .TP
                    272: .B "EXPRESSIONS HANDLING"
                    273: OBGET, OBSUB, EXGET, EXSUB
                    274: .br
                    275: .TP
                    276: .B "FILE AND SOCKET HANDLING"
                    277: APPEND, BACKSPACE, CLOSE, CREATE, DELETE, FORMAT, INQUIRE, LOCK, OPEN,
                    278: READ, REWIND, SEEK, SYNC, TARGET, UNLOCK, WFLOCK, WFSOCK, WRITE
                    279: .br
                    280: .TP
                    281: .B "GRAPHICAL OUTPUT AND PRINTING"
                    282: *D, *H, *S, *W,
                    283: AUTOSCALE, AXES, CENTR, CLLCD, CR, DEPND, DGTIZ, DRAW, DRAX, ERASE, EYEPT,
                    284: FUNCTION, HISTOGRAM, INDEP,
                    285: LABEL, LCD->, ->LCD, LINE,
                    286: LOGSCALE, MARK, NEWPLANE, PAPER,
                    287: PARAMETRIC, PERSIST, PLOT, PLOTTER, PMAX, PMIN, POLAR, PPAR, PR1, PRINT,
                    288: PRLCD,
                    289: PRMD, PRST, PRSTC, PRUSR, PRVAR, REDRAW, RES, SCATTER, SCALE, SLICE,
                    290: SLICESCALE, TITLE,
                    291: WIREFRAME
                    292: .br
                    293: .TP
                    294: .B "LIBRARIES"
                    295: EXTERNALS, REMOVE, USE
                    296: .br
                    297: .TP
                    298: .B "PROCESS"
                    299: CLRFUSE, CLRMTX, CLRSMPHR, CLRSWI, CONTINUE, CRMTX, CRSMPHR, CSTOP, DAEMONIZE,
                    300: DETACH, FUSE, ISWI, MTXLOCK, MTXSTATUS, MTXTRYLOCK, MTXUNLOCK,
                    301: NRPROC, PEEK, POKE, RCLSWI, RECV, RFUSE, RSTOP, SCHED,
                    302: SEND, SMPHRDECR, SMPHRGETV, SMPHRINCR, SMPHRTRYDECR,
                    303: SPAWN, STOP, STOSWI, SUSPEND,
                    304: SWI, SWILOCK, SWIQUEUE, SWISTATUS,
                    305: SWIUNLOCK, WFACK, WFDATA, WFPOKE, WFPROC, WFSWI, YIELD
                    306: .br
                    307: .TP
                    308: .B "MISC"
                    309: <<, >>, ABORT, ALARM, CLRCNTXT, CONVERT, COPYRIGHT, DATE, DROPCNTXT,
                    310: DUPCNTXT, HELP, ITRACE, JDATE, KILL, LAST, LOCALIZATION, LOGGER, MEM,
                    311: PSHCNTXT, PSHPRFL, PULCNTXT, PULPRFL, RDATE, RETURN,
                    312: SPLASH, SWAPCNTXT, SYSEVAL, TIME, TYPE, VERIFY, VERSION, WAIT, WARRANTY, WORKDIR
                    313: .br
                    314: .TP
                    315: .B "DATABASES"
                    316: SQLCONNECT, SQLDISCONNECT, SQLQUERY
                    317: .br
                    318: .TP
                    319: .B "PREPROSSESSING"
                    320: #date, #define, #defeval, #else, #endif, #error, #eval, #file, #if,
                    321: #ifdef, #ifeq, #ifndef, #ifneq, #include, #line, #mode, #undef, #warning
                    322: .br
                    323: .RE
                    324: .SH "USEFUL LINKS"
                    325: .TP
                    326: .B http://www.rpl2.net
                    327: official WWW page of RPL/2;
                    328: .br
                    329: .TP
                    330: .B jkb@systella.fr
                    331: the author's email address;
                    332: .br
                    333: .TP
                    334: .B rpl2@rayleigh.systella.fr
                    335: RPL/2 mailing-list, useful to ask some advice, report bugs and talk
                    336: about new features

CVSweb interface <joel.bertrand@systella.fr>