Predefined identifiers (formerly called pervasives) are language defined identifiers that are visible in any lexical scope without import. They fall into five categories:
- constants
- types
- procedures
- functions
- compile-time macros
Predefined Constants
Invalid pointer value: NIL
Empty collection value: EMPTY
Boolean truth values: TRUE
, FALSE
Predefined Types
Boolean type: BOOLEAN
Character types: CHAR
, UNICHAR
Unsigned whole number types: OCTET
, CARDINAL
, LONGCARD
Signed whole number types: INTEGER
, LONGINT
Real number types: REAL
, LONGREAL
Predefined Procedures
INSERT
(c, ...)
inserts values or accessor/value pairs into collection c
APPEND
(c, v1, v2, v3)
appends values to the end of list or array collection c
REMOVE
(c, ...)
removes values or key/value pairs from collection c
SORT
(t, s, order)
sorts values of source collection s
into target collection t
SORTNEW
(t, s, order)
sorts values of source collection s
into newly allocated target collection t
READ
(f, x)
invokes TypeOf(x).Read(f, x)
READNEW
(f, x)
invokes TypeOf(x).Read(f, x)
WRITE
(f, x)
invokes TypeOf(x).Write(f, x)
WRITEF
(f, fmtStr, x, ...)
invokes TypeOf(x).WriteF(f, fmtStr, x, ...)
TODO
(str)
prints str
to console, causes warning in DEBUG mode, or error otherwise
where TypeOf(x)
means the identifier of type x.
Predefined Functions
ABS
(x)
returns the absolute value of x
ODD
(x)
returns TRUE
if x
is an odd number
PRED
(x, n)
returns n
-th predecessor of x
SUCC
(x, n)
returns n
-th successor of x
ORD
(x)
returns the ordinal value of x
CHR
(x)
returns the character for codepoint x
EXISTS
(c, a, v)
returns TRUE
if value v
exists for accessor a
in collection c
COUNT
(c)
returns the number of values stored in collection c
LENGTH
(s)
returns length of character string s
PTR
(v, T)
returns typed pointer to variable v
if its type is compatible with T
FIRST
(c)
returns first value of ordered collection c
LAST
(c)
returns last value of ordered collection c
MIN
(v1, v2, v3 ...)
returns smallest value of a list of ordinal or scalar values
MAX
(v1, v2, v3 ...)
returns largest value of a list of ordinal or scalar values
Built-in Compile-Time Macros
TMIN
(T)
replaced by smallest legal value of type T
TMAX
(T)
replaced by largest legal value of type T
TLIMIT
(T)
replaced by the capacity of collection type T
TSIZE
(T)
replaced by allocation size required for type T
Changes
moved to pseudo-module RUNTIME
:
SIZE
(v)
returns the allocated size of variable v
to be moved to pseudo-module for primitives:
STORE
(c, ...)
stores values in set or list, or value at index, or key for value in collection c
VALUE
(c, a)
returns value for accessor from collection c
SUBSET
(s1, s2)
returns TRUE
if s2
is a subset of s1
to do: add SEEK
to pseudo-module for primitives
Detailed Descriptions
Constant NIL
The constant NIL
represents an invalid pointer. It is compatible with any pointer type. Its value is defined as:
CONST NIL = 0 :: POINTER TO CONST OCTET;
Dereferencing the constant NIL
results in a compile time error. Dereferencing a pointer whose value is NIL
results in a runtime error.
Constants TRUE
and FALSE
The constants TRUE
and FALSE
represent the values of type BOOLEAN
. Their values are defined as:
CONST TRUE = BOOLEAN.TRUE;
CONST FALSE = BOOLEAN.FALSE;
ORD(TRUE) = 0
ORD(FALSE) = 1
see also BOOLEAN
Type BOOLEAN
Type BOOLEAN
is an ordinal type for boolean algebra. All boolean expressions evaluate to type BOOLEAN
. It is defined as:
TYPE BOOLEAN = ( TRUE, FALSE );
TMIN(BOOLEAN) = BOOLEAN.TRUE
TMAX(BOOLEAN) = BOOLEAN.FALSE
TSIZE(BOOLEAN) = 1 (* one octet *)
Type CHAR
Type CHAR
is an ordinal type for 7-bit character values. It is defined as:
TYPE CHAR = ( CHR(0) .. CHR(127) );
TMIN(CHAR) = CHR(0)
TMAX(CHAR) = CHR(127)
TSIZE(CHAR) = 1 (* 1 octet *)
Type UNICHAR
TO DO
Type OCTET
Type OCTET
is an unsigned integer type that represents a storage unit of eight bits. The type is defined as:
TMIN(OCTET) = 0
TMAX(OCTET) = 255
TSIZE(OCTET) = 1 (* one octet, eight bits by definition *)
Type CARDINAL
Type CARDINAL
is an unsigned integer type large enough to hold any value in the range 0 to 65535 and any value of type SYSTEM.WORD
whichever is larger. The type is defined as:
TMIN(CARDINAL) = 0
TMAX(CARDINAL) = pow(2, TSIZE(CARDINAL) * 8) - 1
TSIZE(CARDINAL) >= MAX(TSIZE(OCTET) * 2, TSIZE(WORD))
Type LONGCARD
Type LONGCARD
is an unsigned integer type large enough to hold the size of the largest allocatable storage area measured in octets. The type is defined as:
TMIN(LONGCARD) = 0
TMAX(LONGCARD) = pow(2, TSIZE(LONGCARD) * 8) - 1
TSIZE(LONGCARD) >= (TSIZE(ADDRESS) DIV 8)
Type INTEGER
Type INTEGER
is a signed integer type large enough to hold any value in the range -32768 to 32767 and any value of type SYSTEM.WORD
whichever is larger. The type is defined as:
TMIN(INTEGER) = (pow(2, TSIZE(INTEGER) * 8) DIV 2) * (-1)
TMAX(INTEGER) = (pow(2, TSIZE(INTEGER) * 8) DIV 2) - 1
TSIZE(INTEGER) = TSIZE(CARDINAL)
Type LONGINT
Type LONGINT
is a signed integer type large enough to hold the size of the largest allocatable storage area measured in octets. The type is defined as:
TMIN(LONGINT) = (pow(2, TSIZE(LONGINT) * 8) DIV 2) * (-1)
TMAX(LONGINT) = (pow(2, TSIZE(LONGINT) * 8) DIV 2) - 1
TSIZE(LONGINT) = TSIZE(LONGCARD)
Type REAL
TO DO
Type LONGREAL
TO DO
Predefined Procedures
Predefined procedures are built-in macro procedures that are bound to predefined identifiers visible in every scope without import.
A predefined procedure differs from a library defined procedure:
- it does not have an address
- it cannot be passed as a procedure parameter
- it cannot be assigned to any procedure variable
Procedure READ
Procedure READ
invokes library procedure Read
in the module whose name is the type identifier of the second argument passed to READ
. If the type is an array type, then the module name is prepended with ARRAYOF
. Arguments are passed to procedure Read
in the same order they are passed to READ
. The procedure is defined as:
<*INLINE*> PROCEDURE READ ( f : inFile; VAR v : <AnyType> );
(* invokes TypeOf(v).Read( f, v ) *)
The semantics are defined as:
macro READ ( f : File; v : anyType )
typeName := typeOf(v)
insert typeName.Read(f, v)
endm
Procedure WRITE
Procedure WRITE
invokes library procedure Write
in the module whose name is the type identifier of the second argument passed to READ
. If the type is an array type, then the module name is prepended with ARRAYOF
. Arguments are passed to procedure Write
in the same order they are passed to WRITE
. The procedure is defined as:
(* MACRO *) PROCEDURE WRITE ( f : outFile; v : <AnyType> );
(* invokes TypeOf(v).Write( f, v ) *)
The semantics are defined as:
macro WRITE ( f : File; v : anyType )
typeName := typeOf(v)
insert typeName.Write(f, v)
endm
Procedure WRITEF
Procedure WRITEF
invokes library procedure WriteF
in the module whose name is the type identifier of the third argument passed to READ
. If the type is an array type, then the module name is prepended with ARRAYOF
. Arguments are passed to procedure WriteF
in the same order they are passed to WRITEF
. The procedure is defined as:
<*INLINE*> PROCEDURE WRITEF ( outFile : File; fmtStr : ARRAY OF CHAR;
items : UNSIGNED; VARIADIC v[items] OF n : <AnyType> );
(* invokes TypeOf(v).WriteF( f, fmtStr, ... ) *)
The semantics are defined as:
macro WRITEF ( f : File; s : charArrayType ; list of v : anyType )
typeName := baseTypeOf(v)
insert typeName.WriteF(f, s, list of v)
endm
Function ABS
Function ABS
returns the absolute value of its operand. It accepts any numeric type as operand type. The returned type is always the same type as the operand type. The function is defined as:
PROCEDURE ABS ( x : <AnyNumericType> ) : <OperandType>;
(* returns the absolute value of operand x *)
This function may be bound to by library defined numeric type implementations:
PROCEDURE [ABS] abs ( b : BCD ) : BCD;
(* returns the absolute value of BCD number b, bound to pervasive function ABS *)
Static Semantics:
A call of ABS
must have one actual parameter. The parameter may be an expression of any numeric type. The function returns a value of the same type as its parameter.
ABS
is a function macro. It does not have an address and it can only be used inline.
- it cannot be passed as a procedure parameter
- it cannot be assigned to any procedure variable
- it can be used in compile time expressions as long as the actual parameter is a pervasive type
Dynamic Semantics:
Function ABS
calculates the absolute value and returns it. For arguments that are not of a pervasive type the function calls the argument type's library function that is bound to ABS
. Passing an argument of a non-pervasive type for which no function is bound to ABS
results in a compile time error. The semantics are defined as:
function macro ABS ( x : anyType ) : typeOf(x)
argType := typeOf(x)
if isPervasive(argType) then
absFunc := builtinAbsForType(argType)
else
absFunc := boundAbsForType(argType)
if absFunc = NIL then
negFunc := boundNegForType(argType)
lessFunc := boundLessForType(argType)
endif
endif
if absFunc # NIL then
if isCompileTimeExpr(x) then
codeFragment := evaluate absFunc(x)
else (* runtime expression *)
codeFragment := 'absFunc(x)'
endif
elsif negFunc # NIL and lessFunc # NIL then
if isCompileTimeExpr(x) then
if lessFunc(x, 0) then
codeFragment := evaluate negFunc(x)
else
codeFragment := 'x'
endif
else (* runtime expression *)
codeFragment := 'IF lessFunc(x, 0) THEN negFunc(x) ELSE x END'
endif
else (* unsupported type *)
raiseCompileTimeError
endif
insert codeFragment
endm
Function NEG
Function NEG
returns the sign reversed value of its operand. It accepts any signed numeric type as operand type. The returned type is always the same as the operand type. This function is used to determine the value of an expression with a unary minus. The function is defined as:
PROCEDURE NEG ( x : <AnySignedNumericType> ) : <OperandType>;
(* returns the sign reversed value of operand x *)
This function may be bound to by library defined signed numeric type implementations:
PROCEDURE [NEG] unaryMinus ( b : BCD ) : BCD;
(* returns the sign reversed value of b, bound to pervasive function NEG *)
The semantics are defined as:
function macro NEG ( x : anyType ) : typeOf(x)
argType := typeOf(x)
if isPervasive(argType) then
negFunc := builtinNegForType(argType)
else
negFunc := boundNegForType(argType)
endif
if negFunc # NIL then
if isCompileTimeExpr(x) then
codeFragment := evaluate negFunc(x)
else (* runtime expression *)
codeFragment := 'negFunc(x)'
endif
else (* unsupported type *)
raiseCompileTimeError
endif
insert codeFragment
endm
Function ODD
Function ODD
returns TRUE
if its operand is an odd number, otherwise it returns FALSE
. It accepts any ordinal type as operand type. The returned type is always BOOLEAN
. The function is defined as:
PROCEDURE ODD ( x : <AnyOrdinalType> ) : BOOLEAN;
(* returns TRUE if operand x is odd, otherwise FALSE *)
This function may be bound to by library defined whole number type implementations:
PROCEDURE [ODD] isOdd ( b : LONGLONGCARD ) : BOOLEAN;
(* returns TRUE if b is odd, otherwise FALSE, bound to pervasive function ODD *)
The semantics are defined as:
function macro ODD ( x : anyType ) : boolean
argType := typeOf(x)
if isPervasive(argType) then
oddFunc := builtinOddForType(argType)
else
oddFunc := boundOddForType(argType)
endif
if oddFunc # NIL then
if isCompileTimeExpr(x) then
codeFragment := evaluate oddFunc(x)
else (* runtime expression *)
codeFragment := 'oddFunc(x)'
endif
else (* unsupported type *)
raiseCompileTimeError
endif
insert codeFragment
endm
Function PRED
Function PRED
returns the n-th predecessor of its operand. It accepts any ordinal type as operand type. The offset type may be any unsigned type. The offset n
may be omitted and if it is, a value of 1 is assumed as offset. The returned type is always the same as the operand. The function is defined as:
PROCEDURE PRED ( x : <AnyOrdinalType>;
(* OPTIONAL *) n : <anyUnsignedType> ) : <OperandType>;
(* returns the n-th predecessor of operand x *)
The semantics are defined as:
function macro PRED ( x : anyOrdinalType; optional n : anyUnsignedType ) : typeOf(x)
if isPresent(n) then
nValue := n
else (* default *)
nValue := 1
endif
insert (ORD(x) - ORD(nValue)) :: typeOf(x)
endm
Function SUCC
Function SUCC
returns the n-th successor of its operand. It accepts any ordinal type as operand type. The offset type may be any unsigned type. The offset n
may be omitted and if it is, a value of 1 is assumed as offset. The returned type is always the same as the operand. The function is defined as:
PROCEDURE SUCC ( x : <AnyOrdinalType>;
(* OPTIONAL *) n : <AnyUnsignedType> ) : <OperandType>;
(* returns the n-th sucessor of operand x *)
The semantics are defined as:
function macro SUCC ( x : anyOrdinalType; optional n : anyUnsignedType ) : typeOf(x)
if isPresent(n) then
nValue := n
else (* default *)
nValue := 1
endif
insert (ORD(x) + ORD(nValue)) :: typeOf(x)
endm
Function ORD
Function ORD
returns the ordinal value of its operand. It accepts any ordinal type as operand type. The returned type is coercible, it is always compatible with any numeric type. The function is defined as:
PROCEDURE ORD ( x : <AnyOrdinalType> ) : <AnyNumericType>;
(* returns the type coerced ordinal value of operand x *)
The semantics are defined as:
function macro ORD ( x : anyOrdinalType ) : zzType
insert x :: zzType
endm
function macro isOrdinalType ( T : typeIdentifier ) : boolean
if isPervasive(T) then
isOrdValue := symTabLookup(T, isOrdinal)
else (* non-pervasive *)
isOrdValue := boundIsOrdForType(T)
endif
insert isOrdValue
endm
Function CHR
Function CHR
returns the character whose code point is the function's operand. It accepts any cardinal type as operand type. For code points between 0 and 127 the returned type is CHAR
. For code points larger than 127, the return type is UNICHAR
. The function is defined as:
PROCEDURE CHR ( x : <AnyUnsignedType> ) : <CharacterType>;
(* returns the character whose code point is x *)
The semantics are defined as:
function macro CHR ( x : anyUnsignedType ) : coercible
if isCompileTimeExpr(x) then
if x <= 127 then
insert x :: CHAR
elsif ORD(x) <= ORD(TMAX(UNICHAR)) then
insert x :: UNICHAR
else (* out of range *)
raiseCompileTimeError
endif
else (* runtime expression *)
insert builtInChrFunc(x)
endif
endm
function builtInChrFunc ( x : anyUnsignedType ) : coercible
if x <= 127 then
return x :: CHAR
elsif ORD(x) <= ORD(TMAX(UNICHAR)) then
return x :: UNICHAR
else (* out of range *)
raiseRuntimeError
endif
endf
Function COUNT
Function COUNT
returns the number of items of its operand. It accepts any ordinal and any collection type as operand type but only variables may be passed in. The returned value is of type LONGCARD
. The function is defined as:
PROCEDURE COUNT ( v : <OrdinalOrCollectionType> ) : LONGCARD;
(* returns the number of items in variable v *)
Function SIZE
Function SIZE
returns the value of the allocated size of its operand. It accepts any type as operand type but only variables may be passed in. The returned value is of type LONGCARD
. The function is defined as:
PROCEDURE SIZE ( v : <AnyType> ) : LONGCARD;
(* returns the allocation size of variable v *)
The semantics are defined as:
function macro SIZE ( v : anyType ) : longcard
if isVariable(v) then
argType := typeOf(v)
if isDeterminateType(argType) then
insert TSIZE(argType)
else (* indeterminate type *)
determinant := symTabLookup(argType, determinantField, name)
elementType := symTabLookup(argType, indeterminateField, baseType)
insert TSIZE(argType) + valueOf(v.determinant) * TSIZE(elementType)
endif
else (* not a variable *)
raiseCompileTimeError
endif
endm
Function HIGH
Function HIGH
returns the highest subscript of its operand. It accepts any array type as operand type. The returned value is of type LONGCARD
. The function is defined as:
PROCEDURE HIGH ( a : <ArrayType> ) : LONGCARD;
(* returns the the highest subscript of array a *)
The semantics are defined as:
function macro HIGH ( a : anyType ) : longcard
argType := typeOf(a)
if isArray(argType) then
if isDeterminateType(argType) then
highValue := symTabLookup(argType, high)
codeFragment := highValue
else (* indeterminate type *)
determinant := symTabLookup(argType, determinantField, reference)
codeFragment := 'valueOf(determinant) - 1'
endif
else (* not an array *)
raiseCompileTimeError
endif
insert codeFragment
endm
Function LENGTH
The function LENGTH
returns the length of its operand. It accepts any character array type as operand type. The returned value is of type LONGCARD
. The function is defined as:
PROCEDURE LENGTH ( s : <CharacterArrayType> ) : LONGCARD;
(* returns the length of character string s *)
The semantics are defined as:
function macro LENGTH ( s : anyCharArrayType ) : longcard
if isCompileTimeExpr(s) then
lenValue := lengthOfString(s)
insert lenValue
else (* runtime expression *)
insert lengthOfString(s)
endif
endm
Function NEXTV
Function NEXTV
returns a pointer to the next variadic tuple within a variadic procedure or function. Each time the function is called the pointer is advanced to the next tuple in the variadic argument list. When no more variadic tuples are available the function returns NIL
. The returned type is always a pointer to the variadic tuple. The function is defined as:
PROCEDURE NEXTV ( v : <VariadicParameterType> ) : <VariadicTuplePointer>;
(* returns pointer to next variadic tuple v *)
Function TMIN
Function TMIN
returns the smallest value of its operand. It accepts any type identifier as operand. The returned type is always the operand itself. The function is defined as:
<*INLINE*> PROCEDURE TMIN ( T : <TypeIdentifier> ) : <T>;
(* returns the smallest value of type T *)
This function may be bound to by library defined ordered numeric type implementations.
CONST [TMIN] smallestValue : BCD;
(* defines the smallest value of type BCD, bound to pervasive function TMIN *)
The semantics are defined as:
function macro TMIN ( T : typeIdentifier ) : T
if isPervasiveType(T) then
tminFunc := builtinTminForType(T)
else
tminFunc := boundTminForType(T)
endif
if tminFunc # NIL then
tminValue := evaluate tminFunc
else (* unsupported type *)
raiseCompileTimeError
endif
insert tminValue
endm
Function TMAX
Function TMAX
returns the largest value of its operand. It accepts any type identifier as operand. The returned type is always the operand itself. The function is defined as:
<*INLINE*> PROCEDURE TMAX ( T : <TypeIdentifier> ) : <T>;
(* returns the largest value of type T *)
This function may be bound to by library defined ordered numeric type implementations.
CONST [TMAX] largestValue : BCD;
(* defines the largest value of type BCD, bound to pervasive function TMAX *)
The semantics are defined as:
function macro TMAX ( T : typeIdentifier ) : T
if isPervasiveType(T) then
tmaxFunc := builtinTmaxForType(T)
else
tmaxFunc := boundTmaxForType(T)
endif
if tmaxFunc # NIL then
tmaxValue := evaluate tmaxFunc
else (* unsupported type *)
raiseCompileTimeError
endif
insert tmaxValue
endm
Function TSIZE
Function TSIZE
returns the value of the allocation size required by its operand. It accepts any type identifier as operand. The returned type is of type LONGCARD
. The function is defined as:
<*INLINE*> PROCEDURE TSIZE( T : <TypeIdentifier> ) : LONGCARD;
(* returns the allocation size required for type T *)
The semantics are defined as:
function macro TSIZE ( T : typeIdentifier ) : longcard
tsizeValue := symTabLookup(T, size)
insert tsizeValue
endm
Function VAL
Function VAL
is equivalent to a type conversion expression where the first argument is the target type and the second argument is the operand. It accepts any type identifier as its first argument and any type as its second argument. The function is defined as:
<*INLINE*> PROCEDURE VAL ( T : <TypeIdentifier>; x : <AnyType> ) : <T>;
(* equivalent to type conversion expression x :: T *)
The semantics are defined as:
function macro VAL ( T : typeIdentifier; x : anyType ) : T
insert x :: T
endm
Macro MIN
Macro MIN
evaluates to the smallest value of its operands. It accepts a variable number of compile-time expression operands. All operands must be expression compatible and of a numeric type. The macro is defined as:
(* MACRO *) PROCEDURE MIN ( c1, c2, c3, ... : <NumericType> ) : <Constant>;
(* evaluates at compile time to the smallest value of the operand list *)
The semantics are defined as:
function macro MIN ( args : list of anyNumericType ) : baseTypeOf(args)
if isCompileTimeExpr(firstOf(args)) then
minValue := firstOf(args)
for c in remainderOf(args) do
if isCompileTimeExpr(c) then
if c < minValue then
minValue := c
endif
else (* runtime expression *)
raiseCompileTimeError
endif
endfor
else (* runtime expression *)
raiseCompileTimeError
endif
insert minValue
endm
Macro MAX
Macro MAX
evaluates to the largest value of its operands. It accepts a variable number of compile-time expression operands. All operands must be expression compatible and of a numeric type. The macro is defined as:
(* MACRO *) PROCEDURE MAX ( c1, c2, c3, ... : <NumericType> ) : <Constant>;
(* evaluates at compile time to the largest value of the operand list *)
The semantics are defined as:
function macro MAX ( args : list of anyNumericType ) : baseTypeOf(args)
if isCompileTimeExpr(firstOf(args)) then
maxValue := firstOf(args)
for c in remainderOf(args) do
if isCompileTimeExpr(c) then
if c > maxValue then
maxValue := c
endif
else (* runtime expression *)
raiseCompileTimeError
endif
endfor
else (* runtime expression *)
raiseCompileTimeError
endif
insert maxValue
endm