Skip to main content

MVBasic

There are several differences associated with MultiValue Basic on Caché. The status of individual items in MVBasic can be found in the Caché MultiValue Basic Reference manual.

Source Files And Studio

MultiValue files containing MVBasic programs will be automatically recognized by Studio, the Caché IDE, if they have a “B” character in attribute 6. This use reduces the amount of information needed in Studio dialog boxes for opening files and also affects the files that are searched when using the Studio Find-in-files feature.

This attribute can be set when the file is created, for example,

CREATE-FILE <filename> (B

or

CREATE-FILE <filename> DIR <dirpath> (B

For individual files, the attribute can also be set using ED.

Studio Debugging and MVBasic

The current version of Studio provides a fully-functioning debugger for use with ObjectScript, Caché Basic and MVBasic.

Duplicate Naming Conflicts

The name of a subroutine or the names of formal parameters in a SUBROUTINE declaration may not be the same as the names of variables declared in named common. for example, an application containing the lines

SUBROUTINE MYSUB (VARA, VARB)
COMMON /NCOM/ VARA, CNT, DATE

will produce an error message at compile time because the compiler cannot uniquely identify any later reference to VARA.

Also, the subroutine name itself (MYSUB) cannot be redefined in the named common. However, the subroutine name is not used internally and can be replaced with something else to remove the error.

Variables

Caché MultiValue and most other emulations support case-sensitive variable names. D3 emulation, by default, provides variable names that are not case-sensitive. Use of such variables is not advised when interacting with Caché CSP variables, ZEN, and other InterSystems software, all of which uses case-sensitive variables. To make D3 emulation use case-sensitive variables, specify the flag option $OPTIONS -NO.CASE.

@DATE And @TIME

The values of @DATE and @TIME are the date and time that the process started respectively, NOT the current date and time of the system.

Intrinsic Objects

$SYSTEM

MVBasic has an intrinsic object that may be used to obtain system information. The name is $SYSTEM. Basic information is available in the Caché ObjectScript Reference; further details are found in the %SYSTEM package in the InterSystems Class Reference.

Statements

FOR – NEXT Iteration Variable Restriction

Caché does not permit the iteration variable for a loop to be of the form “%var”, “@var”, or “^var”, nor can it be a property of a Caché class.

RELEASE with no argument

A RELEASE statement with no argument releases all record locks held by the current process that were applied at the current @LEVEL execution level. This is true for all emulations. This differs from native UniData behavior, which releases all locks held by the current process on all levels.

Expressions

Interpretation Of Apparent Undimensioned Arrays

The compiler will not accept references of the form

name (expr)

Depending on the format mask, these must be manually converted to one of the two forms:

OCONV(name, expr)
FMT(name, expr)

Ambiguous References

The compiler will report ambiguous references as an error. For example, a statement of the form:

PRINT ON PTR ('ABC':'DEF')'R#20'

is ambiguous because it could be interpreted as

  • a variable reference, name(expr) mask

  • an array reference followed by mask

  • a name (expr)mask local variable followed by masked expression

To be accepted it must be rewritten as, for example,

X=('ABC':'DEF')'R#20'
PRINT ON PTR X

Multiple Subscript Evaluation For Compound Assignment Operators

Caché does not guarantee that the left side of a compound assignment statement will be evaluated only once. For example, consider the sequence of statements

deffun otherfunc(a)
dim v(10)
v(otherfunc(1)) += 1 

Because of the use of the compound assignment, “+=” in the last statement, it can be rewritten during compilation as

v(otherfunc(1)) = v(otherfunc(1)) + 1 

In this rewritten form, the function otherfunc will be called twice.

If the expressions used for a subscript has no side effects, that is, its resulting value depends only on its argument values, then this will not be an issue. However, if the expression used for the subscript depends on other values in the environment beyond those passed in as arguments, then the statement may not accomplish its intended effect. For example, the statement sequence

dim temp(10)
temp(rnd(10)) += 2

will not add 2 to a random value in the array. Instead, in its rewritten form as

dim temp(10)
temp(rnd(10)) = temp(rnd(10)) + 2

will result in adding the value, 2, to a random element of the array and storing the sum n a second (perhaps different value of the array.

The compound assignment operators that provoke this behavior are: “+=”, “–=”, “*=”, “/=”, and “:=”.

Line Continuation in MVBasic

Caché MVBasic does not support a specific line continuation character. You can, however, break a line of code that contains a comma right after the comma. The compiler will attempt to join a line that ends with a comma to the following line. For example, in the sequence

COMMON /BASICINFO/ MACHINE, IPADDR, USERNAME,
PASSWORD

the comma which ends the first line is sufficient indication that the line is continued. However,

LET x = 1 + 2 + 3 +
4 + 5 + 6

will result in a parse error.

Interaction with Caché Classes

Property Manipulation Restriction

In this release, a program cannot assign a value to a property of a Caché class reference using “<>” syntax. Instead of

obj -> Name<2,3> = 'abc'

use the statement

obj -> Name = REPLACE(obj->Name, 2, 3, 'abc')

Properties may also not be deleted with the REMOVE or REVREMOVE statements, or with the REMOVE() function.

$OPTIONS

Normally, the characteristics of the program, such as the emulation to be used, are taken from the account that contains the source file. The $OPTIONS statement is used to alter some of these settings and thereby change the interpretation of the source program.

Caution:

The $OPTIONS statement should be used with caution. The preferred approach is to work as much as possible within a defined emulation and reserve the use of this statement for very specific needs. Internal documentation within the program justifying the use of the $OPTIONS is also recommended.

Note:

The choice of actions selected by $OPTIONS is in effect at the time the program is compiled. For MVBasic statements such as EXECUTE, when the statement is processed at runtime the settings used are those of the account, not the $OPTIONS of the containing program.

The BNF for the statement is:

$OPTIONS EMU? (FLAG  |  -FLAG  | FLAG=VALUE )*

where:

  • EMU is the name of a supported emulation.

  • FLAG is the name of an emulation flag to alter. The three forms are:

    • “FLAG” turns the flag ON.

    • “–FLAG” turns the flag OFF.

    • “FLAG=VALUE” sets the value associated with the specified flag.

Available $OPTIONS A — M
Option Meaning
ACOR.INTSUMS

Indicates whether A correlative arithmetic is integer-only or not.

ACOR.NUMLIT

Indicates if unquoted numbers in A correlatives are treated as numeric values or as references to attributes. ON means they are numeric literals.

ADD.DELIMS

Indicates whether additional delimiters are added to delimited arrays if the last element is already a trailing delimiter. This affects the behavior of functions and statements that extend arrays such as

X<-1> = "Attval"

and so on. Set to ON to add delimiters anyway.

ARITH.DELIM

Indicates whether arithmetic is delimiter aware or not. When set to ON,

Addition = "41":@AM:"3"

will return

"42":@AM:"3"

If not delimiter aware, then a Non-Numeric Zero Used would ensue.

ARITH.NO.WS

Causes spaces and TABS to be ignored when converting string to numerics. Set to ON if leading whitespace should cause a string to remain a string and not be convertible to numeric.

ARRAY.IS.FMT

Indicates that name(expr) is treated as FMT(name,expr) if name is not a DIM'ed array.

ARRAY.RESELECT

Causes override of NO.RESELECT for dynamic arrays.

ASSUNASS.OK

Indicates that the assignment of a variable to another does NOT cause an error if the source variable is Unassigned (ON setting). If set to off, then the assignment of an unassigned variable to anything else causes a runtime error.

ATPTR

Support printer @)-) codes: @(-27 through -33, -47 through -55, -59 through -126, -220 through -239).

ATTR.0IS1

UniData treats attribute numbers < 1 in EXTRACT and <> differently than the other MultiValue implementations. Setting this option correctly handles that difference.

BTYPE.PRM

Indicates whether subroutines called from DICT entries pass a parameter which contains the current item being processed, or not.

BYDR.ISDN

Indicates whether the BY 'DR' clause of the LOCATE command should act the same as BY 'DN' (ON setting) or not (OFF setting).

CASE

Indicates that the MVBasic compiler should treat identifiers (variable names) in a case-sensitive fashion when set to ON. This means that a variable Abc is NOT considered to be the same variable as ABC and abc. This is the default mode for everything except D3.

CMD.IN.HDR

Indicates whether a default heading, being the command typed in should be used by the output processor in this emulation mode. That is,

LIST MD

will be displayed in the heading of the output for that command.

COM.EMPTYSTR

Indicates that unnamed commons should be initialized at program startup to the empty string.

COM.UNASSIGNED

Indicates that unnamed commons should be initialized at program startup to Undefined.

Default: UNASSIGNED

COM.ZERO

Indicates that unnamed commons should be initialized at program startup to numeric zero.

CONV.DIV0IS0

Indicates the behavior of division by zero in conversions. If set to ON, division by zero returns zero. If OFF, then return the numerator unchanged.

CONV.ESZERO

Indicates whether conversions involving an empty string "" will treat the string as numeric 0 or an invalid input. For instance, Sequoia-based systems will take "" string as being 0.

COUNT.OVLP

Indicates that COUNT and INDEX should use overlapped counting when multiple characters are allowed for delimiters. So a string “CCCC” when counted for “CC”returns 3 and not 2.

D

Indicates that dates and times in headers or footers are in D2 (fixed length) format rather than variable (D) format.

DELIM.MATCH

Indicates whether a trailing delimiter on a MATCH will match the source or not. For example,

"T]R]Y]"

will match with

"Y]"

if this option is turned ON.

E

Indicates (ON) that STOP and ABORT statements use the ERRMSG file rather than just print the string they are given.

ELSE.ON.WRITE

Indicates that an ELSE clause is allowed on WRITE statements.

This is set ON by default if you are in UniVerse mode, and OFF otherwise.

ENHANCED.MATCH

Indicates whether to use Prime/UniVerse enhanced pattern matching or not. Note that the MATCHFIELD function comes from UniVerse/Prime and always uses this type of pattern matching.

EXEC.AM

Indicates that dynamic arrays passed to EXECUTE/PERFORM will execute each attribute in the array in turn, rather than just the first attribute.

EXTRA.DELIM

Synonym for ADD.DELIMS

F

Indicates that the FOR loop should increment/decrement the index BEFORE instead of AFTER the bounds checking.

FCOR.REVERSE

Indicates whether F correlatives are true reverse Polish or not. ON means to operate the same way as Reality.

FM.DEC.OUTPUT

ON indicates that a format mask that does not specify decimal places will output decimal places anyway as needed.

FMT.HASLEN

Indicates whether the format codes are preceded with a length field or not.

FOLD.DELIM.VM

Changes the behavior of the FOLD function by setting the delimiter character to @VM rather than @FM.

FOLD.LEN

Changes the behavior of the FOLD function by setting a length of less than 1 equal to a length of 1.

FOR.INCR.BEF

Indicates that the FOR loop should increment/decrement the index BEFORE instead of AFTER the bounds checking.

FORMAT.OCONV

Indicates that FMT is allowed to process out conversion codes as format masks. This is here for compiler compatibility; CACHE mode always allows this.

FSELECT

Indicates that the BASIC SELECT statement should set the @SELECTED variable to whatever it selects from.

This may be a performance issue on some emulations if the selected lists are large.

FULL.DELIM

Indicates whether functions like INDEX and FIELD will use the whole string supplied as the delimiter (ON), or just the first character (OFF).

FULL.LOGICAL.EVALUATION

Specifies that AND and OR operators evaluate both sides of the operation, even if the left hand side evaluates to False.

G

Indicates (ON) that ON GOTO and ON GOSUB statements that receive values that are out of range for the control variable just ignore the GOSUB or GOTO and move on to the next line. If this is set to OFF, then if the value is too small the first branch is taken, and if too big then the last branch is taken.

H

Indicates that a newly installed HEADER from BASIC is printed immediately, rather than just installed ready for the next page break.

HEAD.PRNNN

Indicates whether HEADINGs in queries suppress "nnn Records Listed." message. ON to causes them to be printed.

HEADER.BRK

Indicates that the PIOpen flavor of 'I' and 'P' options for HEADING statements is in use, if set to ON.

HEADER.DATE

Indicates that dates and times in headers or footers are in D2 (fixed length) format rather than variable (D) format.

HEADER.EJECT

Indicates that a newly installed HEADER from BASIC is printed immediately, rather than just installed ready for the next page break.

HUSH.IO

Indicates whether the HUSH command operates on both Input and Output (ON), or just INPUT echoing (OFF).

I

Indicates (ON) that the INPUT statement does not echo data that comes from a DATA statement.

ICONV.BDATE

Indicates whether the conversion processor should try to make some sense of questionable dates such as 31 FEB nnnn (ON), or should treat them as invalid input.

ICONV.RET.ES

Indicates that ICONV should return the empty string and not the original value if the input string was invalid.

IGNORE.EXTRA.LINES

When set, directs the compiler to ignore any lines that occurs after the logical end of the program. Normally, in this situation the compiler will report an error.

IM1.TA

Indicates that

INPUT X,-1

checks for type ahead (ON) or NOT (OFF).

IMTS.HOURS

Indicates whether ICONV MTS returns hours or minutes when ambiguous. If ON then

ICONV(1, "MTS")

returns 3600 assuming 1 hour, and OFF returns 60 assuming 1 minute.

IN.FMT.MASK

Indicates that a string that is specified as a format mask in an input:

INPUT A,len {,} Fmt

is really a format mask with which to format input for display and validate input as it goes rather than a 3 character sequence as per Reality/jBASE.

IN2.SUBSTR

Indicate that a single parameter substring extract [nn] assumes a length of 1 character rather than that position to the end of the string.

INFO.LOCATE

Indicates (ON) that LOCATE uses the PRIME / INFORMATION style syntax instead of the Reality syntax. This is turned on by defaults for INFO, PIOpen and UniData emulation modes.

INFO.MARKS

Indicate that RAISE and LOWER use a limited range of delimiters in the same way as PI/Open does. When set to ON, this flag restricts raise and lower characters to CHAR(252) to CHAR(255). When OFF, the character range translated is CHAR(248) to CHAR(255).

INSERT.0IS1

Indicates (ON) that values supplied to the INSERT function (not the INS BEFORE...) should treat a parameter that is 0 as if it were 1. This is quite a subtle difference as it is only the INSERT function and only on Prime and UniVerse emulations.

ITYPE

Indicates (ON) that we are compiling I-types.

K

Indicates (ON) that the emulations supports negative subscripts in string extractions, as per Reality/ROS.

KEEP.ECOMMON

Indicates whether

ENTER "PROG (I"

keeps the global common intact or not.

L

Indicates (ON) that LOCATE uses the PRIME / INFORMATION style syntax instead of the Reality syntax.

LENCNV.ONEMAX

Indicates (ON) that the length conversion with a single parameter should treat that as a max length rather that a length to equal.

LINE.CONT.BSLASH

Indicate that the backslash character (\) can be used as the line continuation character. Refer to Line Continuation in Caché MVBasic Reference for details.

LINE.CONT.VBAR

Indicate that the vertical bar character (|) can be used as the line continuation character. Refer to Line Continuation in Caché MVBasic Reference for details.

LIST.KEYS

Indicate whether the COPY command should list the keys it is copying or not.

LOCATE.R83

Synonym for BYDR.ISDN

MASK.DESCALE

Indicates whether output formatting masks should descale or not. When this flag is ON, for say Reality, then a format such as:

FMT("987654", "R26")

yields 0.98 but when this flag is OFF, it will yield 9876.54.

MATBUILD.UNASSIGNED.ERROR

When this flag is ON, MATBUILD generates an error when it encounters an unassigned array node. When this flag is OFF, MATBUILD treats an unassigned array node as a null string, and returns a dynamic array with the same number of elements as the array dimension. Refer to MATBUILD statement in Caché MVBasic Reference for details.

MATREAD.EMPTY

Synonym for PIOPEN.MATREAD

MX.IS.MCDX

Indicates (ON) that MX conversions should be treated as MCDX rather than an ASCII HEX conversion.

Available $OPTIONS N — Z
Option Meaning
NCOM.EMPTYSTR

Indicates that named common should be initialized to an empty string when first loaded by a program.

NCOM.UNASSIGNED

Indicates that named common should be initialized to Undefined when first loaded by a program.

NCOM.ZERO

Indicates that named common should be initialized to numeric zero when first loaded by a program.

NO.CASE

Indicates that the MVBasic compiler should treat identifiers (variable names) in a not case-sensitive fashion when set to ON. This means that a variable Abc is considered to be the same variable as ABC and abc. This is the default mode for D3.

NO.IMPLICIT.FMT

Indicates (ON) that implicit FMT operator is not allowed, that is

expr1 expr2

will give an error, not act like

FMT(expr1,expr2)

NO.RESELECT

Indicates (ON) that if select list 0 (the default select list) is already active (has values), then a subsequent SELECT is not performed and select list 0 remains active.

NULL.SORT.ZERO

Indicate whether Empty String "" sorts equally to Zero. This is primarily for UniVerse/Prime.

NUM.SYMS

Indicate whether the numeric symbols . + and - are treated as non-numeric values if they are the only thing in a string. Set ON to reject this interpretation.

O

Indicates that COUNT and INDEX should use overlapped counting when multiple characters are allowed for delimiters. So a string “CCCC” when counted for “CC” returns 3 and not 2.

OCONV.ES

Indicate if the OCONV code should run against empty strings (ON) or not.

OCONV.SCALE

Indicate whether OCONV formatting uses the scale factor or not by default. ON means it does.

ONGO.RANGE

Indicates (ON) that ON GOTO and ON GOSUB statements that receive values that are out of range for the control variable just ignore the GOSUB or GOTO and move on to the next line. If this is set to OFF, then if the value is too small the first branch is taken, and if too big then the last branch is taken.

OP.LSUP

Indicate whether the 'L' option in a BREAK ON clause means that a blank line before the data line is skipped (ON setting) or it means to skip the break line.

OP.PICK.STYLE

Indicate the general style of query output. If set to ON then the Olde Worlde Pick/ROS style output is sent out, otherwise (OFF) the output is like the U2 style.

OP.PAUSE.NULL

Indicates whether the output processor should pause at the end of a page of output if the HEADING statement in BASIC was set to "". ON to pause the output regardless.

OSEQ.CREATE

ON indicates that OPENSEQ should create the target file if it does not already exist.

PAGE0.CHDR

ON indicate that "PAGE 0" clears any existing HEADINGS or FOOTINGS or not.

PARA.DATA

ON indicates that DATA stacked for a paragraph is only used by the paragraph and not passed on to any program that the paragraph subsequently executes.

PCLOSE.ALL

Indicates (ON) that the PRINTER close statement closes ALL print channels and not just channel 1.

PHANTOM.TO.SPOOLER

Indicates (ON) that the terminal output from the PHANTOM command, or similar commands (ZH, PH-START) goes to the spooler. If set OFF, then the terminal output goes to the &PH& file.

PICK.CONVERT

Indicates (ON) that conversions from string to numeric, integer, or boolean use the MV/Pick rules like UniVerse and UniData, namely:

A) An empty string will convert to 0 in all cases.

B) A simple numeric string will convert to number in all cases (that is, with a single + or minus initial character, any number of leading zeros, optionally followed by digits, optionally a decimal point, and optionally more digits)

If PICK.CONVERT is OFF, Caché conversion rules are in effect. Strings that have a leading number return that number, and the boolean value is simply whether the resulting number is 0 or non-zero. Multiple leading +/- characters are allowed, and the final sign is based on the # of - characters before the number.

If PICK.CONVERT mode is ON, strings that are not a simple numeric string return TRUE if converted to boolean, and give an error message and return 0 if converted to integer or numeric.

PICK.SELECT

Indicates that the default (internal) list is list # 10, not # 0.

PIOPEN.ENTER

Indicates (ON) that ENTER is a synonym for CALL.

PIOPEN.MATREAD

Indicates (ON) that the MATREAD statement will sets all values of the target array to empty strings "" if the record ID is not found.

PROMPT.4IDS

Indicates whether commands assume that not specifying a list of IDs or a '*' for all, assume '*' rather than prompt for a list of IDs.

Q

Indicates whether a READ that fails should set the target variable to the empty string or leave it untouched.

QRY.AND.WITH

Indicates whether queries of the form:

SELECT FILE WITH <clause> WITH <clause>

are assumed to be AND WITH (ON) or OR WITH (OFF).

QRY.MSUBCALL

Indicate whether a BASIC subroutine called from a DICT should be called for each value and subvalue, or just once.

RADIANS

Indicates (ON) that trigonometric function arguments are in radians instead of degrees.

RAW.OUTPUT

Indicates (ON) that terminal output is not automatically translated into printable characters which happens in some emulations.

READ.RETAIN

Indicates whether a READ that fails should set the target variable to the empty string (ON) or leave it untouched.

REAL.SUBSTR

Indicates (ON) that the emulations supports negative subscripts in string extractions, as per Reality/ROS.

REFORMAT.OVR

ON indicates that REFORMAT overwrites existing attributes or not.

RETURNING.AM

Indicates whether a RETURNING clause wants the return codes in attribute delimited form (ON) or not.

RETURNING.CODE

Indicates (ON) that the returning clause on execute returns the value of SYSTEM.RETURN.CODE (UniVerse) rather than the error string.

RJUST.WRAP

Indicate whether right-justified data should wrap in query output. Set to ON it will operate like Prime/UniVerse, OFF like everything else.

RNEXT.EXPL

Indicates (ON) that READNEXT returns exploded values in the ID.

ROS.VIDEO

Indicates whether the @(-) function should support Reality video mode or not (where the codes -128 through -191 are indicative of effects such as BOLD or REVERSE and so on).

ROUND.UP.NEG

Indicates whether negative rounding is up or down. If turned ON, then a number such as -0.5 will round to 0 rather than -1.

RV0.DCOUNT

Indicates that READV on attribute 0 should return the DCOUNT() of the record.

RV0.EXISTS

Indicates that READV on attribute 0 should return 1 if the record exists, and 0 otherwise.

RV0.KEY

Indicates that READV on attribute 0 should return the record key.

S

Indicates (ON) that the SELECT statement behaves as SELECTV.

SELECT.ANY

Indicates (ON) that the SELECT statement behaves as SELECTV.

SMALL.RAISE

Synonym for INFO.MARKS.

SPASS.ALL

Indicate whether SP-ASSIGN assigns to all channels when no specific channel number is indicated.

SS.0IS1

Indicates whether zero is treated as 1 within substring specifications. When this option is ON,

X[0,6] = "string"

means the same things as

X[1,6] = "string"

When OFF, it means that the "string" is inserted before the first character of X.

SSEL.2ALIST

Indicates if the BASIC SSELECT statement should install the results as the active select list or not (for return from a BASIC program). You have the BASIC default select list and the system active select list. They can be the same on some systems and this flag indicates whether BASIC SSELECT affects the active select list (ON) or not.

STACK.GLOBAL

Indicates that stacked data acts as in UniVerse and Prime and is global to everything (ON). If set to OFF, then the DATA stack acts like Pick/Reality.

The default is on for Cache, UniVerse (all flavors), and UniData; and off for all others such as jBASE, D3, MVBase, Ultimate, Reality.

STATIC.DIM

Indicate whether REDIM of arrays at runtime is supported or not.

STOP.MSG

Indicates (ON) that STOP and ABORT statements use the ERRMSG file rather than just printing the string they are given.

STR.ONEISONE

Synonym for IN2.SUBSTR

SUPP.DATA.ECHO

Indicates (ON) that the INPUT statement does not echo data that comes from a DATA statement.

SYS11.BOOL

ON indicates that SYSTEM(11) returns a binary 1 or 0 (ON setting) if a select list active or not. OFF indicates that SYSTEM(11) returns the number of elements selected to the active list or 0 if no list is active.

T

Indicates that a single parameter substring extract [nn] assumes a length of 1 character rather than that position to the end of the string.

TCONV.REPSYS

Indicates whether Tfile Conversions replace system delimiters. When ON, system delimiters are replaced by the blank character. The default is ON for Caché and all emulations except UniData, which defaults to OFF.

TD.2SPC

OFF indicates this system only returns a result separated by a single space character, or uses the more common 2 spaces (ON).

TRANS.REPSYS

On indicates that TRANS() function in ITYPES replaces delimiters with spaces or not.

U

Indicates (ON) that if select list 0 (default select list) is already active (has values), then a subsequent SELECT is not performed and select list 0 remains active.

UCASE.DATE

Indicates whether date conversions force the output text to uppercase or not: For example, if this flag is ON. July 14 1964 will be JULY 14 1964.

V

Indicates (ON) that the operators “*”, “/”, “+”, “-” should be compiled as vector arithmetic.

VAR.SELECT

Indicates (ON) that the SELECT statement behaves as SELECTV.

VEC.MATH

Indicates (ON) that the operators “+”, “-”, “*”, “/”, and “**” should be compiled as vector arithmetic. Refer to Arithmetic Operators in Caché MVBasic Reference for details.

W

Synonym for ADD.DELIMS

WHO1

Indicates the style of output for WHO and related user exits should be:

PID/PORT ACCOUNT.

WHO2

Indicates the style of output for WHO and related user exits should be:

PID/PORT ACCOUNT From systemloginname.

WHO3

Indicates the style of output for WHO and related user exits should be:

PID/PORT ACCOUNT (systemloginname).

WRITE.LOCK.WAIT

Indicates that this emulation requires WRITE to wait on a lock held by someone else. ON means to wait for the lock.

X

Indicates (ON) that READNEXT returns exploded values in the ID.

Z

Indicates (ON) that the PRINTER close statement closes ALL print channels and not just channel 1.

PI/Open Compatibility Subroutines

Caché MVBasic does not include the subroutines for PI/Open compatibility (for example, CALL !ADDS and following) that are listed in the UniVerse Basic manual.

Soundex Differences

Given the same input, the SOUNDEX() function occasionally yields different results among legacy MultiValue platforms. This is also true of Caché. Any data fields whose values are based on a SOUNDEX() computed value should be regenerated on Caché as part of the migration of the application.

Conversion Of UniData SUBR Usage

When any of the subroutines of the form

SUBR('-XXX',  args)

is used in I-types instead of the built-in names for the corresponding MultiValue function, that is,

XXX(args)

then it is converted to the built-in form at I-type compilation time. The functions for which this is done are:

  • ADDS, ANDS

  • CATS, CHARS, COUNTS

  • DIVS

  • EQS

  • FIELDS, FMTS

  • GES, GTS

  • ICONVS, IFS, INDEXS

  • LENS, LES, LTS

  • MODS, MULS

  • NES, NOTS, NUMS

  • OCONVS, ORS

  • SEQS, SPACES, SPLICE, STRS, SUBS, SUBSTRINGS

SYSTEM(100)

The SYSTEM() function provides numerous configuration and status values, many of which are standard to MultiValue implementations, a few of which are specific to Caché MultiValue. The SYSTEM() function, with its various code values, is described in the Caché MultiValue Basic Reference.

The SYSTEM(100) code returns the system ID. The format of the returned information varies according to the platform and the emulation, as shown in the following table:

Field Windows Platform Non-Windows Platform
1 System name System name
2 Name of configuration file: the contents of the “name” statement in the configuration file Operating system name, for example, “AIX®”
3 Current release level Name of configuration file: the contents of the “name” statement in the configuration file
4 Current version level UNIX® system release
5 Type of hardware UNIX® system version
6 The date of the release Machine hardware name, or serial number
7 Not used Once, the release level of the monitor code; now not used; value: “”
8 Not used Once, the date of the boot monitor release; now not used; value: “”
9 † Caché configuration name Caché configuration name
10 † Operating system name Operating system name
11 † Hardware serial number Hardware serial number

† This field is provided by Caché for cross-platform consistency.

FeedbackOpens in a new tab