home *** CD-ROM | disk | FTP | other *** search
-
- Archimedes MUMPS v1.0 documentation
-
-
- MUMPS COMMANDS
-
-
-
- BREAK
- - no arguments.
- - may be post-conditionalised
-
- Halts execution. There is no way (yet) to continue after BREAK.
-
- EXAMPLE:
- S X=Y B:DEBUG ; Examine value of X if DEBUG'=0
-
-
- CLOSE_<expression specifying a device>[:<device parameters>]
- <device parameters> ::= <expression> |
- (<expression>[:<expression>]*)
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - argument cannot be post-conditionalised
-
- Closes one or more devices (if they're open).
-
- EXAMPLES:
- C:DEV'=0 DEV ; Close device if it isn't the default device
- CLOSE FILE1,FILE2 ; FILE1 & 2 are device specifiers (ints in MUMPS)
-
-
- DO_<entry reference>
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments can be post-conditionalised
-
- Call the subroutine specified by the <entry reference>.
-
- EXAMPLES:
- D TOTAL ; Call subroutine total in current routine
- D:DSPL DISPLAY^UTILS ; Call label DISPLAY in routine UTILS if DSPL'=0
- DO:'ERR TOTAL:TOT,AVG:AVG,MIN:MIN,MAX:MAX ; Skip DO on error
- ; DO any of the arguments if their postconditions are <> 0
- D @SUB ; Choose subroutine indirectly.
-
-
- ELSE_
- - may not be post-conditionalised
-
- ELSE does not have arguments. It tests $T. If $T is 1, the rest of
- the line is skipped.
-
- EXAMPLE:
- I X=Y W "X equals Y"
- E W "X does not equal Y"
-
-
- FOR_<local variable>=<for parameter>[,<for parameter>]*
- <for parameter> ::= <expression>
- | <numex> 1:<numex> 2
- | <numex> 1:<numex> 2:<numex> 3
- (<numex> is short for <numeric expression>
- - may not be post-conditionalised
- - argument listing is not possible
- - argument indirection is not allowed (FOR parameters also)
- - arguments cannot be post-conditionalised
-
- Execute a FOR loop.
- If the FOR parameter is just one expression, then the FOR loop is
- executed with the <local variable> having the value of the
- expression.
- If the FOR parameter is of the second form, an endless loop is
- specified. Termination of the loop can be achieved by executing a
- QUIT command or a GOTO command
- The third form specifies the 'usual' FOR loop that has a begin and
- an end. If <numex> 1 'exceeds' <numex> 3 at the start of the FOR
- loop, the loop is never executed.
-
- EXAMPLES:
- F I=0:1:99 W I ; Write the first 100 numbers in |N
- F I="Hi there,","I am","your",1:1:10,"computer !" W I," "
- ; Result: "Hi there, I am your 1 2 3 4 5 6 7 8 9 10 computer ! "
- F I=1:1 ; Endless loop
- F I=1:1 Q:I>100 ; Let I have the values 1..101
- F I=1:1:100 ; At the end of the FOR loop, I=100
- F I=-1,1 F J=1,-1 W $J(I*J,4) ; Output: " -1 1 1 -1"
- F I=1:1:2 S I="HI" W I ; Produce an endless loop of "HI"'s !
- FOR__ The argumentless FOR loops forever, but it does not use a
- loop-variable.
-
-
- GOTO_<entry reference>
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments can be post-conditionalised
-
- If no label is specified, control transfers to the first line of the
- specified routine. If both a line and routine are specified, control
- transfers of course to the specified line in the specified routine.
- If only a line reference is given, then control transfers to that
- line in the current routine.
- All FOR loops on the same line as the GOTO are terminated
-
- EXAMPLE:
- G:TRANSFER A:x=1,B:x=2,C:x>2,ERR
- If TRANSFER is non-zero, control is transferred to label A of the
- current routine if x=1, label B if x=2, label C if x>2, and finally,
- if none of the postconditions of the arguments was true, to label
- ERR. So only ONE of the jumps is made !
-
-
- HALT_
- - may be post-conditionalised
-
- Halts execution of the current JOB. It's LOCK list is emptied, the
- devices that were opened by the partition are closed and released.
-
-
- HANG_<numeric expression>
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- Waits a specified time (in seconds) before execution is continued.
-
- EXAMPLES:
-
- H:SLOW DELAY
- OPENDEV O 2:("FILE":"R"):0 I '$T H 1 G OPENDEV
-
-
- IF_<boolean expression>
- - may not be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- Evaluates the expression, if it is non-zero (i.e. 1) the rest of the
- line is executed, otherwise it is skipped.
- IF__ (No arguments) The boolean expression in the above explanation is
- taken to be $T.
-
-
- JOB_<entry reference>[:<job parameters>[<timeout>] | <timeout>]
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- A new JOB is created in it's own partition. The routine specified by
- the <entry reference> is loaded and control is transferred to the
- specified line (or the first if no line was specified).
-
- The job parameters in Archimedes MUMPS are:
- 1) A UCI name (default: UCI name of parent partition)
- 2) Partition size (default: partition size of parent partition)
- 3) Principle device ((default: principle device of parent partition)
- The parameters are specified as follows:
- (<par1>:<par2>:<par3>)
- Note that parameters are not portable !
-
- EXAMPLES:
- J ^QSORT ; run QSORT in current UCI
- J ^QSORT:("TST":4:20) ; run QSORT in UCI "TST", partition size=4
- ; principle device is NULL-device.
-
-
- KILL__
- KILL_<glvn>
- KILL_(<glvn>[,<glvn>]*)
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- The form without arguments kills all local variables. The second form
- kills thespecified variable (and it's descendants !). The third form
- kills all local variables, except the once that are specified in the
- argument and their descendants
-
- EXAMPLES:
- K D READVARS ; kill old values and read fresh ones
- K:NEW ^TEMP ; Kill the global ^TEMP (the entire global is killed !)
- K (POSPOSC,U,INE,INO) ; kill all local variables except the ones
- ; specified in the only argument
- K (A,B,C,D,EF(10)),^ZZZ
- K @A ; using argument indirection is possible
-
-
- LOCK__
- LOCK_<glvn>[timeout]
- LOCK_(<glvn>[,<glvn>]*)[timeout]
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- All LOCK forms release all previously locked variables. A LOCK with
- arguments stores all it's arguments in the partitions LOCK-list,
- unless a timeout is specified and it was impossible to satisfy the
- LOCK; the $T switch is then set to 0, afterwards. If a timeout was
- specified and it WAS possible to satisfy the LOCK, then $T is set to
- 1 afterwards. A LOCK can be satisfied if all the arguments do NOT
- violate the "descendant-exclusivity-rule" for any other variables in
- the LOCK lists of ALL the other partitions. One variable violates
- the "descendant-exclusivity-rule" if it is a 'prefix' of the other
- variable, or the other variable is a prefix of the one variable. In
- other words, they may not 'interfere' with each other. The LOCK
- command ensures that no two processes modify the same data (or
- datatree-branch) at the 'same' time.
- *Note: LOCK does not provide protection against modification of
- the same information by two processes. It merely provides a
- mechanism by which clashes can be avoided.
-
-
- OPEN_<device>[:[<device parameters><timeout>|<timeout>]]
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- For the syntax and meaning of the device parameters, look at the
- "DEVICE"-entrypoint in the "MUMPS TERMINOLOGY" chapter.
- The parameters are specified as follows: (<par>[:<par>]*)
- OPEN tries to open the specified device(s) in the argument list. To
- open a device, no other partition may have that device in it's
- "open-list" (when a device is succesfully opened, it is put in the
- partition's "open-list"). If a device cannot be opened, execution is
- stopped until that device can be opened. Unless there's a timeout
- (say t), in which case execution is only stopped for a maximum of
- t seconds. If the device could not be opened after t seconds, the $T
- switch is given the value 0 (zero), otherwise it is given the value
- 1 (one).
-
- EXAMPLES:
- O 1:("FILE"_I:"W")
- PRT O 11::1 I '$T W *7,"Printer in use, try again N//" R R Q:R="N" G PRT
- O DEV U DEV W !,"Hi there, device DEV !" U 0 C DEV
-
-
- PRINT
- Print prints out the current routine
-
-
- QUIT
- - may be post-conditionalised
-
- QUIT is used to terminate a DO a XECUTE or a FOR command. If a QUIT
- command is executed in a FOR loop, it terminates the FOR loop.
- Execution proceeds with the 'next FOR' of the FOR loop to the left
- of the terminated FOR, or with the nextline if there's no FOR to the
- left of the terminated FOR.
-
- EXAMPLES:
- F I=1:1 D TEST Q:I>TEST W I ; Write I until I>TEST
- R A G:A="AGAIN" START Q:A="QUIT" W !,"'AGAIN' OR'QUIT',PLEASE !"
- F I=1:1:3 F I=1:1:3 Q:J>I W $J(J,2) ; Write "1 1 2 1 2 3"
-
-
- READ_<string>
- |<format>
- |<locvar>[<readcount>][<timeout>]
- |*<locvar>[<timeout>]
- <readcount>::= #<integer expression>
- <format>: see MUMPS TERMINOLOGY
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- READ is used for I/O using the current device. The first form
- outputs the string to the current device (if that's possible,
- otherwise an error will occur). The second form is explained under
- the "FORMAT" entry in "MUMPS TERMINOLOGY".
- The third form reads characters from the current device and puts the
- resulting string in the local variable. If a <readcount> is present
- (say r), a maximum of r characters is read. If a timeout is present
- (say t), reading is terminated after t seconds (or when a READ
- terminator is received before that time).
- The fourth form reads exactly one character and puts the ASCII value
- of that character as an integer result in the local variable. Again,
- a timeout (say t) may be specified, and -1 is the value if no
- character was read in t seconds.
-
- EXAMPLES:
- R R
- R @A
- ASK R !,"A,B,C or D",*ANS G A:ANS=65,B:ANS=66,C:AND=67,D:ANS=68,ASK
- R !,NAME#32,!,STREET#32,!,CITY#32
- READ D:0 IF D'=-1 D @$S(R=65:UP,R=90:DOWN,1:DEFAULT)
-
-
- SET_$P(...)=<expression>
- | <glvn>=<expression>
- | (<glvn>[,<glvn>]*)=<expression>
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- SET sets (values of) local or global variables. The first form of the
- set argument is used for setting a $P of a local or global (see
- $PIECE). The second form sets just one variable. The third form
- conceptually sets all named variables at the same time, i.e. it's an
- atomic action. SET evaluates any indirections or subscripts first,
- then evaluates the <expression>, and finally sets the variable(s).
- This is significant if you're using a Naded Indicator, because any
- arguments may change the naked indicator before the full
- variablename is evaluated.
-
- EXAMPLES:
- S A=1
- S @A=9 ; Gives B the value 9 if A="B"
- S @A ; Gives B the value 10 if A="B=9"
- S:NEWHS (X(1),^SCORE($I),Y($I,"score"))=SCORE
- S ^C("A","B")="Hi",^D("HUIB")="VERWEIJ",^(^("HUIB))=^C("A","B")
- ; An example of indirection:
- ; ^(^("HUIB")) expands/evaluates to: ^C("A","VERWEIJ")
- ; First the argument ^("HUIB") is evaluated: "VERWEIJ".
- ; Then the expression ^C("A","B") which sets the naked indicator to
- ; ^C("A").
- ; Then the 'name' of ^(^(3)) is evaluated and the use of the naked
- ; indicator expands ^("VERWEIJ") into ^C("A","VERWEIJ").
-
-
- USE_<expression specifying a device>[:<device parameters>]
- <device parameters> ::= <expression> |
- (<expression>[:<expression>]*)
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - argument cannot be post-conditionalised
-
- After opening a device using OPEN i/o may be directed to the device
- using the USE command.
-
- EXAMPLES:
- O 1:("VARS":"R") F U 1 R VAR,VAL C:VAR="" 1 Q:VAR="" S @VAR=VAL
- ; read variables from file "VARS"
- O 0:(2:0) ; Input not echoed in Archimedes MUMPS
- U:WRITE DEV ; Post conditions can be used
-
-
- VIEW_<expression>[:(<expression>[:<expression>]*)]
- - may be post-conditionalised
- - argument listing is not possible
- - argument indirection is not allowed
- - argument cannot be post-conditionalised
-
- In Archimedes MUMPS, the VIEW command has no meaning whatsoever.The
- VIEW command just eats all its arguments and so may set the naked
- indicator, but no other actions take place.
- WARNING: The VIEW command is not portable and should only be used in
- system specific routines.
-
-
- WRITE__
- WRITE_<format>
- |<expression>
- |*<integer expression>
- <format>: see MUMPS TERMINOLOGY
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments cannot be post-conditionalised
-
- WRITE is the PRINT/printf command of MUMPS. It outputs the values
- evaluated to the current device. The third form of the argument
- outputs the ASCII character corresponding to the integer
- interpretation of the <expression>.
- The argumentless form of WRITE is not standard MUMPS, but 'all'
- implementations use it to list the local variables, Archimedes MUMPS
- is no exception.
-
- EXAMPLES:
- W #!?35,"Main Menu" S X=10,Y=5 W@POSC
- ; POSC="*31,*X-1,*Y-1", it positions the cursor in RISC OS
- I ERR W *7," error "
- W @A
- W:OUTPUT A1,A2,A3,@B ; Postconditionalise the command
-
-
- XECUTE_<expression>
- - may be post-conditionalised
- - argument listing is possible
- - argument indirection is allowed
- - arguments can be post-conditionalised
-
- XECUTE interprets the <expression> as if it were MUMPS code.
-
- EXAMPLES:
- X ^% ; invoke the editor
- X "W 12*12" ; Output "144"
- S X="X X" X X ; Run out of stack space
- X "ZL @%ROU W $T(+1)" ; Write first line of routine @%ROU
-
- /* end of Commands */
-