OADL - Object/Array Data Language

A dynamically-typed object-oriented language

Ross Cunniff



1. Introduction

OADL is released under the MIT public license - http://www.opensource.org/licenses/mit-license.php - which states in full:

Copyright (c) 1997 Ross Cunniff

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.

This means that anybody may do just about anything they want with this documentation and OADL source, as long as this copyright notice is retained. At this time, the OADL source itself has not been published.

OADL Overview

OADL - Object/Array Data Language - is an interpreted object-oriented language with dynamic typing and implicit memory management. It was designed for convenient implementation of applications with large numbers of pre-initialized objects (for example, a text adventure). OADL supports multiple inheritance, operator overloading, multi-dimensional array-valued expressions, and static and dynamic linking of OADL programs. OADL also implements an interactive desk calculator mode. Most of the examples in this documentation are intended to be used in this mode.

OADL was especially designed for embedded use in computer games; for example, it can be used:

This documentation presumes that the prospective OADL programmer has some familiarity with C, C++, and object-oriented programming in general.

This documentation is hosted at http://rcunniff.com/OADL/oadlnav.html. Several OADL test programs can be found at Tests/index.html . Actual adventure game sources written in OADL can be found at ADV/index.html . Documentation of the OADL command-line implementation can be found starting at MANPAGES/oadl.html. An index of all of the OADL man pages can be found at MANPAGES/manpages.html.

This reference is broken up into the following chapters:

  1. Introduction (this page)
  2. Lexical Elements
  3. OADL Program Syntax
  4. OADL Types
  5. Arrays, Lists, and Strings
  6. Dictionaries
  7. Classes
  8. Objects (Instances)
  9. Expressions
  10. Procedures
  11. Intrinsic Methods and Procedures
  12. External Procedures
  13. Input / Output
  14. OADL Format Specifiers
  15. Predefined Symbols
  16. Glossary
  17. OADL Implementation Notes
  18. Lex / Yacc Grammar


2. Lexical Elements

Character Set

OADL uses the UTF-8 (RFC 3629) input character encoding, which allows for minimum size for most uses (and is compatible with ASCII), but also allows for the use of the full 21-bit range of Unicode standard character encodings for identifiers, string literals and comments. In addition, OADL uses UTF-8 for text-based output. Although OADL accepts extended Unicode characters as elements of identifiers, only the ASCII digits '0' through '9' are allowed in numeric constants.

Note that illegal UTF-8 seqences in a source file will produce a compile-time error.

OADL is a token-based compiler. It uses a greedy algorithm to scan tokens; this means, for example, that the sequence of characters === is interpreted as the token == followed by the token = (which the compiler would then flag as a syntax error).

Whitespace (ASCII space, carriage return, line feed, form feed, horizontal tab, and vertical tab) is ignored, except as it separates tokens. Comments (delimited by /* and */) are considered whitespace, and otherwise ignored. End-line comments (delimited by //) are also ignored. For compatibility with some UTF-8 editors (i.e. Windows Notepad), the Unicode byte-order-mark 0xFEFF (or UTF-8 0xEF, 0xBB, 0xBF) is allowed at the beginning of an OADL source file and is treated as whitespace.

The following ASCII characters are recognized as whitespace:

ASCII code Character name
9 horizontal tab
10 line feed
11 vertical tab
12 form feed
13 carriage return
32 space

Tokens

Punctuation

An OADL compiler recognizes the following punctuation as single-character tokens:

& | ^ ~ + - * / %
. , : ; ! ( ) { }
[ ] < > = @ ? `

In addition, OADL recognizes the following two-character tokens:

## != == <= >= <<
>> += -= *= /= %=
&= |= ^= ++ -- =>
?= #= && || ~= ?#
:: ** \| \^ \& \<
\> \+ \- \* \/ \%
!- @@ #[ #( ?* ??
-> :=

OADL also recognizes the following three-character tokens:

<<= >>= <<< >>> ...
\== \#= \!= \<= \>=
\<< \>> \=> \~= \**


Character and String Constants

There are several composite token types. The first is a character constant token, expressed as a single character between two single quote marks, thus: 'x' A string constant token is lexically similar, expressed as zero or more characters between two double quote marks, thus: "abcdefg"

In both character constant tokens and string constant tokens, the character \ has special significance. Just as in C and C++, it is an "escape" character, which alters the interpretation of a number of characters following. Here is the complete list of escapes recognized by OADL:

Escape Meaning
\0 ASCII NUL character
\a ASCII bell character
\b ASCII backspace character
\f ASCII formfeed character
\n ASCII linefeed character
\r ASCII carriage return character
\t ASCII horizontal tab character
\v ASCII vertical tab character
\xHEX Hexadecimal character code (up to 8 digits)
\' Non-terminating single quote
\" Non-terminating double quote
\\ The backslash character
\any The given character

If a character constant or string constant token is immediately preceded by the character L the token is a wide character constant or wide string constant token. If any of the characters inside the token have an encoding greater than 127 (either due to specification via \xHEX or via UTF-8 sequences), then the constant is also considered to be a wide character constant or wide string constant token.

Integer Constants

In OADL, an integer constant token takes one of three forms:

The digits of an integer constant may be separated by an underscore _ for enhanced readability (the underscore must be between digits, not at the beginning or the end of the number). An integer constant may also have the one of the following suffixes to give it a type other than Int (the suffixes are case-independent):

Suffix Resulting type
B Byte (base-10 integer constants)
SB Byte (hexadecimal integer constants)
UB Ubyte
S Short
US Ushort
U Uint
L Long
UL Ulong

Here are some examples of integer constant tokens:

Token Description
0x1000 The number 4096, in hex
123 The number 123, in decimal
0x1FFF_FFFF The largest positive integer, in hex
0b111_1111b The largest Byte value, in binary


Floating Point Constants

A floating point constant token in OADL is distinguished from an integer constant token by one of two things: either it has an exponent part (the character e or E followed by a signed integer exponent), or it has a fractional part (the character . followed by the digits comprising the fraction), or it has both. A floating point constant may also have one of the following suffixes to give it a type other than Float (the suffixes are case-independent):

Suffix Resulting type
H Half
D Double

Hexadecimal floating point constants are supported; they are similar to hexadecimal integer constants but are distinguished from them by having an exponent part (the character p or P followed by a signed integer exponent signifying a power of two), or having a fractional part (the character . followed by the hexadecimal digits comprising the fraction), or both. A hexadecimal floating point constant may have one of the following suffixes to give it a type other than Float (the suffixes are case-independent):

Suffix Resulting type
H Half
L Double

Like integer constants, numeric digits of a floating point constant can be separated by the underscore _ (again, the underscore must be between two numeric digits, not at the beginning or the end of the string of digits).

Here are some examples of floating point constant tokens:

Token Description
3.14159_26535_89793_24d A Double approximation of π
1.e38 About the biggest Float representable
1e-38 About the smallest Float representable
.0h Zero as a Half
0x1p-1L The Double 0.5


Identifiers

OADL identifier tokens consist of a Unicode character with an alphabetic attribute or the character _ or $, followed by zero or more of:

Unicode characters with any of the following attributes are recognized as alphabetic when part of an identifier:

Attribute Abbreviation
Letter, upper case Lu
Letter, lower case Ll
Letter, title case Lt
Letter, other Lo

Unicode characters with any of the following attributes are recognized as numeric when part of an identifier:

Attribute Abbreviation
Number, decimal digit Nd
Number, letter Nl
Number, other No

Here are some example identifier tokens: Main $foo my_house x1 bißchen Note that OADL is case-sensitive; that is, the identifier tokens Main, main, mAIn, and MAIN are all unique.

OADL reserves several identifiers as keywords for syntactic purposes. This is the complete list:

assert break case catch
class const continue default
do else extern for
forall foreach if match
namespace new operator proc
protected public return static
switch throw try using
var while with

Keywords may not be used as user identifiers (variable names, procedure names, etc.) in OADL.

It is non-trivial to distinguish between the various integer constant, floating point constant, and identifier tokens. See the Token State Machine in the OADL Implementation Notes chapter for more information.

Local match arguments

In the context of a match statement, a match argument consisting of the character ? followed by one or more decimal digits may be used. It indicates the nth match result of the pattern:

    match ("123 45") {
    case "([0-9]+) ([0-9]+)" :
        "First: ", ?1, "; second: ", ?2, '\n';
    }
First: 123; second: 45

The number of match arguments present can be found by using the token ?# (note that the zero'th argument is always the entire string matched):

    match ("123 456 789") {
    case "([0-9]*) ([0-9]*) ([0-9]*)" :
        "Found ", ?#, " matches:\n";
        for (var i = 0; i < ?#; i++) {
            "", oadl::matchvec()[i], '\n';
        }
    }
Found 4 matches:
123 456 789
123
456
789

OADL Preprocessing

It is often convenient to break up a program into several source files. To enable this, the include statement is supported:

#include "filename"

Tokens are read from the given filename until it has been exhausted; at that point, lexical analysis returns to the current file. It is assumed that the filename will have a suffix of ".oah"; if so, it is not necessary to include the suffix in the #include statement. It is not required that files included have a ".oah" suffix, though.

It is implementation-dependent how many nested levels of includes are supported; however, all implementations will support at least 4 levels.

The OADL preprocessor supports macros. Macros are similar to those in C/C++; however, unlike C/C++, parenthesis and braces in a macro must match. Additionally, instead of escaping the end-of-line as in C/C++, multi-token OADL macro definitions are completely enclosed in matching braces. For example:

    #define foo(x) {
        x = x + 1
    }

    var a = 1
    foo(a)
    "a = ", a
a = 2

The matching braces are not included in the expansion of the macro. Unlike C/C++ there are no token pasting or tokenizing capabilities in OADL macros.

Macros may define and undefine other macros; for example:

    #define bar(x) {
        #ifdef(foo)
            #undef foo
        #endif
        #define foo(y) {x + y}
    }
    bar(3)
    foo(4)
7

    bar(5)
    foo(4)
9

Unlike C/C++, macros may not be redefined. Instead they must be undefined using the #undef statement:

    #define foo(a) {a+1}
    foo(1)
2
    #undef foo
    #define foo(a) {a+2}
    foo(1)
3

OADL also supports conditional compilation. The tokens #if, #ifdef, #else, #elif, and #endif are used for conditional compilation. As in C/C++, OADL conditional compilation statements may be nested. Unlike C/C++, OADL conditional compilation statements do not need to be on individual lines. This means that the condition must be enclosed in parentheses ( ):

    #ifdef(foo) "This statement is not printed"
    #elif(0) "Neither is this statement"
    #else "This statement is printed" #endif
This statement is printed

OADL also supports the #defined query which may be used in conditional compilation expressions as well as in regular OADL expressions:

    #define foo(a) {a+1}
    "Is foo defined? ", #defined(foo)
Is foo defined? true

    #if(0 || #defined(foo)) "Foo is still defined" #endif
Foo is still defined

Just as in C/C++, other than the conditional compilation tokens #if, #ifdef, #else, #elif, and #endif, tokens inside a non-compiled section of a conditional compilation statement are ignored, including #include, #define, and #undef tokens. Note that the input character stream is still processed as tokens; this can lead to subtle errors with unterminated comments:

    // Nothing is printed due to the unterminated comment inside
    // the #ifdef:
    #ifdef(foo) "This statement is not printed" /*
    #else "Neither is this one." */
    #endif

OADL reserves the following preprocessor keywords for future use:

#arg #args #nargs

OADL Unnamed Value Tokens

For unnamed non-numeric, non-array values, OADL accepts and prints the following special token sequences:

#OBJ(num) Unnamed object number num
#PRC(num) Unnamed proc number num
#PTR(num) System-specific pointer number num

Note that num must be a compile-time decimal integer constant.

For example,

    a = proc() {"Hello a!\n";}
    a
#PRC(7)

    b = #PRC(7)
    b()
Hello a!

    i = 7
    c = #PRC(i)
Decimal integer constant expected

OADL Desk Calculator Tokens

The OADL desk calculator accepts the following tokens for special use:

#classes #consts #defines #edit
#erase #externs #help #intrinsics
#list #load #namespaces #object
#procs #publics #quit #reset
#save #vars

OADL Program Syntax

At the outer global scope, an OADL programs may contain any or all of the following:

  1. Constant declarations
  2. Variable declarations and initialization
  3. External procedure declarations
  4. Procedure declarations and definition
  5. Class declarations and definition
  6. Object declarations and definition
  7. Public attribute declarations

These elements may be combined in any order. Not all are required; in fact, a procedural entry point named main is not even required. Any of these elements may be enclosed in a namespace declaration for better organization of symbols.

Constant Declarations

A constant declaration associates a name with a constant expression. The syntax for a constant declaration is:

const_decl      : 'const' consts ';'
                ;
consts          : name_init
                | consts ',' name_init
                ;
name_init       : IDENTIFIER '=' expr
                ;

where expr is defined in the Expressions chapter. Most expressions are valid constant initializers; these include scalar constants such as numbers; string constants; and even array and procedure constants. Dynamic values, such as variable references, procedure calls, and object references, are not allowed in constant expressions.

Here are some example constant declarations:

const
    pi = 3.141592653589,
    euler = 2.7182;

const
    three = '3';

const
    name = "Mary Smith";

const
    CardNames = {
        "A", "2", "3", "4", "5", "6", "7", "8",
        "9", "10", "J", "Q", "K"
    };

OADL predefines several constants for convenient use by the programmer. These constants include the floating point Type constants:

Float Half Double

...the integral Type constants:

Int Uint Byte Ubyte Short Ushort
Long Ulong

...the array Type constants:

PackInt PackUint PackLong PackUlong
PackShort PackUshort PackByte PackUbyte
PackChar PackWideChar String WideString
PackFloat PackDouble PackHalf PackBool
List Array

...various other Type constants:

Object Dict Proc Extern Public Pointer
Exception WideChar Char Null Class Type
Bool ArrayType Array[*] Enclosure File

...the predefined exceptions (found in namespace oadl):

TypeCheck RangeCheck ArgCheck AccessCheck AssertCheck
StackCheck ExternCheck ShapeCheck InterruptCheck FormatCheck
UnboundedCheck EndOfFile RegexCheck IoCheck MatchCheck
ProcCheck ExceptCheck NameCheck RedefinedCheck UTF8Check

...system configuration constants (found in namespace oadl):

JMP_SIZE MAXINT MAX_RANK

...various constants for use by OADL input/output routines (found in namespace io):

EOF ErrOut FMT_ADD_BLANK FMT_ADD_PLUS FMT_ADD_TYPE
FMT_ALIGN_ROWS FMT_CENTER FMT_IMMED_ROWS FMT_INTERNAT FMT_LEFT
FMT_NO_BOX_ARR FMT_THOUSANDS FMT_UNSIGNED FMT_UPPER_CASE Input
Output SEEK_CUR SEEK_END SEEK_SET

...and the Null, Bool, and Object constants:

nil true false self

Elements of constant arrays and strings may not be reassigned. For example, the following code with throw a runtime AccessCheck error:

const str = "string";
/* ... */
str[0] = 'f';

Variable Declarations

Variable declarations consist of the var keyword followed by one or more variable names. Variables may optionally have an initializer associated with them. Variables may also optionally have a type specifier associated with them.

An initializer is an expression (see the Expressions chapter). If no initializer is given, the variable is initialized to nil. Note that only procedure-local variables can be initialized to non-constant expressions; all other variables may only be initialized to constant expressions that can be evaluated at compile time.

A type specifier specifies that the given variable may only hold values of a given type. If no type specifier is given, then a variable may hold values of any type. The type specifier consists of a colon followed by an OADL type (Float, Int, Array, PackFloat[3], etc.). If a type specifier is given, assignments to the variable will be type-converted to that type before the value is stored. If type conversion is not possible, a TypeCheck exception will be thrown. See the chapter on OADL Types for more information on type specifiers.

The syntax of a variable declaration is:

var_decl        : 'var' vars ';'
                | 'static' vars ';'
                ;
vars            : var
                | vars ',' var
                ;
var             : qual_name 
                | qual_name ':' type
                | qual_name '=' expr
                | qual_name ':' type '=' expr
                ;

Variables of any scope (except arguments) may be initialized. The syntax is very similar to named constant declarations. For example:

var
    Weight = 82, Height : Int = 183;

Just as with constant declarations, the initializer may be an expression. Procedure-local variables may be initialized by any expression; all other variables must be initialized by constant expressions.

Variables can also be initialized to an unnamed procedure using the same syntax as constants:

var name = proc( args ) { statements };

The value of the unnamed procedure may be determined inside the body of the procedure by using the syntactic convention ( proc ), thus:

var fact = proc(n) { return (n < 2) ? 1 : n*(proc)(n-1); };

This is especially useful given the fact that unnamed lambda procedures do not have access to local variables of the enclosing procedures (see Identifier Scope, below, for more information).

Procedure local variables may be declared using the static keyword. If so, they are placed in the global variable area and retain their values from call to call. Otherwise, they are placed on the stack and have a lifetime only concurrent with the current execution instance of the procedure in which they are declared. For example:

    proc stat() {
        static entered = false;
        "", entered ? "Subsequent call" : "First call", '\n';
        entered = true;
    }

    stat()
First call

    stat()
Subsequent call

Note that, in OADL desk calculator mode, the var keyword may be omitted:

    a = 3
    a
3

Identifier Scope

Constant names, variable names, class names, object names, public names, and procedure names have a scope - a context in which they are valid. There are 5 possible identifier scopes in OADL:

Scope Identifiers allowed
Procedure block local Constants and variables
Procedure arguments Variables
Class Constants, variables, and procedures
Global Constants, variables, procedures, classes, and named objects
Public All public property names

The scopes are given in priority order. Identifiers are first looked for in the nested procedure block scopes, then in the procedure argument list, then in the enclosing class declaration, and finally in the global scope. The public scope is special; names immediately to the right of a . operator are looked for in the public scope, as are names explicitly looked up via the public::name syntax. The names of public and protected variables of class definitions are automatically placed in the public namespace.

Unlake Javascript, nested procedures have no access to names in the enclosing procedure's scope. This allows for a much simpler calling convention. For example, the following procedure will produce a compile-time error:

proc foo()
{
    var a = 1;
    var b = proc() {"a is: ", a, '\n';}
}

External Procedure Declarations

External procedures are system-dependent routines implemented by the OADL runtime or by OADL extension libraries. They are declared in an OADL program via the following syntax:

extern_decl     : 'extern' qual_names ';'
                ;

An external procedure can be defined as the default handler for non-object method calls via the following syntax:

default_public  : 'default' 'public' defpubs ';'
                ;

defpubs         : IDENTIFIER '=' qual_name
                | defpubs ',' IDENTIFIER '=' qual_name
                ;

Default handlers may not be redefined:

    #include "libstd"
    0.->sin()
0.

    default public cos = m ath::sin
Default public cos already defined

See the External Procedures chapter for further discussion.

Procedure Declarations

A procedure declaration either declares or defines a global procedure. The syntax for a procedure declaration is:

proc_decl       : 'proc' qual_name '(' args ')' proc_body
                | 'proc' qual_name '(' ')' proc_body
                | 'proc' STRING qual_name '(' args ')' proc_body
                | 'proc' STRING qual_name '(' ')' proc_body
                | 'proc' qual_names ';'
                ;

args            : /* NOTHING */
                | arg
                | args ',' arg
                ;

arg             : IDENTIFIER
                | IDENTIFIER ':' type
                ;

proc_body       : '{' statements '}'
                | ':' type '{' statements '}'
                ;

where qual_names is the same as in external procedure declarations, above. If no proc_body is provided, the statement merely declares the procedure but does not define the instructions. This is especially useful when linking multiple modules; the actual implementation of the procedure need not be exposed in a header file to be included via an #include statement.

The STRING is a hint to OADL about attributes of the procedure. Currently, the only supported attribute is the indexable attribute, "[]", which tells OADL that the byte code stream of the procedure may be examined by OADL programs. Each byte of the procedure is accessed by the OADL index operator, and the number of bytes in the procedure may be found by the OADL length intrinsic. Indexable procedures may be used in foreach expressions and forall statements. Attempting to access the byte code stream of non-indexable procedures will result in an AccessCheck exception.

For example:

    proc "[]" foo () {return nil;}
    foo.length()
19

    foo[0]
168

The type specifies a type for an argument of the procedure, or return type for the procedure. If no return type specifier is given, then the procedure may return values of any type. See the section on OADL Types for more information on type descriptors. If a type descriptor is used, return values will be type-converted to that type before the procedure returns. If type conversion is not possible, a TypeCheck exception to be thrown.

The statements production may be found in the Procedures chapter.

The following are examples of valid procedure declarations:

proc a, b, c;
proc fact(n : Int)
{
    if (n > 1) {
        return n * fact(n-1);
    }
    else {
        return 1;
    }
}

Class Declarations

A class declaration either declares or defines a class. A class is an abstract data type that includes data storage along with operations on the data. The syntax for a class declaration is:

class_decl      : 'class' qual_name '{' props '}'
                | 'class' qual_name '(' names ')' '{' props '}'
                | 'class' qual_names ';'
                ;
props           : /* NOTHING */
                | props prop
                ;
prop            : 'public' oneprop
                | 'protected' oneprop
                | 'operator' oper_decl
                | oneprop
                ;
oneprop         : var_decl
                | const_decl
                | proc_decl
                ;
oper_decl       : operator no_name_proc
                ;
operator        : '|'      | '^'     | '&'     | '<'         | '>'
                | '+'      | '-'     | '*'     | '/'         | '%'
                | '~'      | '!'     | '##'    | '=='        | '!='
                | '<='     | '>='    | '<<'    | '>>'        | '@'
                | '=>'     | '**'    | '++'    | '--'        | '#='
                | '\|'     | '\^'    | '\&'    | '\<'        | '\>'
                | '\+'     | '\-'    | '\*'    | '\/'        | '\%'
                | '\=='    | '\#='   | '\!='   | '\<='       | '\>='
                | '\<<'    | '\>>'   | '\=>'   | '\~='       | '\**'
                | '!-'     | '{' '}' | '[' ']' | '[' '=' ']' | '(' ')'
                | '#[' ']' | '#[' '=' ']'
                ;
no_name_proc    : '(' args ')' '{' statements '}'
                | '(' ')' '{' statements '}'
                ;

The args and statements productions may be found in the Procedures chapter. Further discussion of the semantics of classes and objects may be found in the Classes and Objects chapters.

The following are examples of valid class declarations:

class a, b, c;
class foo {
    public proc bar() {say("bar");}
}
class foobar(foo) {
    public proc bletch {say("bletch");}
}
class complex {
    protected var real, imag;
    public proc create(r, i) { real = r; imag = i; }
    operator + (rhs) {
        var res;
        if (rhs ?= complex) {
            res = new complex(real + rhs.real, imag + rhs.imag);
        }
        else {
            res = new complex(real + rhs, imag);
        }
        return res;
    }
    /*...*/
}

Object Declarations

An object declaration declares or defines an object. An object is an instance of a class. The syntax of an object declaration is:

/* Forward declarations and object definitions with no property
 * assignments
 */
obj_decl_list   : obj_decl_noprop
                | obj_decl ',' obj_decl_noprop
                ;
obj_decl_noprop : qual_name qual_name
                | qual_name qual_name '(' exprs ')'
                ;

/* Object definitions with property assignments */
obj_decl_props  : qual_name qual_name obj_proplist
                | qual_name qual_name '(' exprs ')' obj_proplist
                | '...' qual_name obj_proplist
                ;
obj_proplist    : '{' obj_props '}'
                | '{' obj_props '...' '}'
                ;
obj_props       : /* NOTHING */
                | obj_props prop_init
                ;
prop_init       : IDENTIFIER '=' expr
                ;
exprs           : /* NOTHING */
                | exprlist
                ;
exprlist        : expr
                | exprlist T_COMMA expr
                ;

Further discussion of the semantics of classes and objects may be found in the Classes and Objects chapters.

An example object declaration is:

box mybox {
    length = 10
    width = 5
    height = 4
}

Public Attribute Declarations

When creating an OADL module to be linked in by other programs, it is very useful to be able to declare classes and their public interfaces in a header file without specifying their full implementation. The public attribute declaration syntax declares an interface:

public_decl     : 'public' names ';'
                ;

An example using public attribute definitions is:

class box;
public length, width, height, draw, resize, setcolor;

The box class is (presumably) defined in an OADL source file which is to be separately compiled and linked in with the main OADL program.

Namespaces

Global identifiers may be grouped into namespaces for better management of identifier conflicts. By default, there are four namespaces that OADL defines: the anonymous global namespace, the public namespace, the io namespace, and the oadl namespace. The public namespace contains all names defined via public statements. All other global names are placed by default in the anonymous global namespace, unless a new named namespace is being constructed. This is similar to Java and C++ namespaces in syntax and concept. An OADL program may define a new namespace via the namespace declaration:

namespace_decl  : 'namespace' name '{' items '}'

qual_name       : name
                | name '::' name
                | '::' name
                ;

qual_names      : qual_name
                | qual_names ',' qual_name
                ;

The items in a namespace may refer to each other without qualification. Items outside the name space may only refer to items inside the namespace via the :: syntax or with the using statement:

using_stmt : 'using' one_using ';'
           | using_statmt ',' one_using ';'
           ;
one_using  : 'namespace' name
           | 'extern' string
           | name '::' name
           ;

If the program includes the using namespace statement, all of the symbols in the namespace may be used without qualification. Additionally, the program may selectively include only certain symbols via the using ns :: name syntax:

using statements may be placed at the global scope or the procedure block scope, but not the procedure argument scope or class scope. If a using statement is placed at the procedure block scope, the included names are only accessible until the end of the enclosing block.

Here is an example of a using statement that imports a single symbol into the global namespace:

#include "libstd.oah"

using math::cos;

The public namespace is implicitly used, and OADL will disambiguate names from the public namespace and the current namespace scope based on context - names immediately to the right of the . operator are assumed to be from the public namespace. To prevent this disambiguation, place parenthesis around the name to the right of the . operator:

var create = public::destroy;
obj.(create)(); // actually calls the "destroy" method

Names from the anonymous global namespace may be accessed via the ::name qualified name format:

var n = 1;
proc main()
{
    var n = 2;
    // Should print "n = 2; ::n = 1"
    "n = ", n, "; ::n = ", ::n, '\n';
}

The using extern syntax is used to interface an OADL program with an external procedure library; see the chapter on External Procedures for more information.


4. OADL Types

Most variables in OADL are dynamically typed - it is valid to store a string in a variable at one point, and then store an integer in it later. Despite this, OADL is a strongly typed language - there are several different types in OADL, and each represents different kinds of values, and the different types allow different kinds of operations on them.

Scalar types

There are 20 "scalar" object types in OADL - "scalar" in that only one value is stored:

Type Minimum Maximum Description
Null n/a n/a The type of nil. Every Null object is identical to every other Null object.
Bool false true Typically the result of boolean expressions
Type n/a n/a Typicaly returned by the typeof intrinsic
Exception n/a n/a Typically thrown by OADL's runtime error checking protocols
Char '\0' (or 0 => Char) '\x7F' Unsigned 7-bit character values. They may also be used in arithmetic expressions as integers with values from 0 to 127.
Byte -128 127 Signed 8-bit integers
Ubyte 0 255 Unsigned 8-bit integers
Short -32_768 32_767 Signed 16-bit integers
Ushort 0 65_535 Unsigned 16-bit integers
Half approx. ± 6.10e-5 approx. ± 6.55e+4 16-bit floating point numbers with approximately 3 decimal digits of precision
WideChar '\0'L '\x1FFFFF'L Unsigned 21-bit Unicode character values. They may also be used in arithmetic expressions as integers with values from 0 to 2,097,151
Public n/a n/a Associative indexes into Classes and Objects. They have no arithmetic value. Operators (such as operator +) are also of type Public.
Extern n/a n/a External procedure (typically a library procedure)
Uint 0U 0xFFFF_FFFFU Unsigned 32-bit integers with an approximate range from 0 to 4.3e9
Int -0x2000_0000 0x1FFF_FFFF Signed 30-bit integers with an approximate range of ± 5.4e8 see note
Float approx. ± 1.18e-38 approx. ± 3.40e+38 31-bit floating point numbers with approximately 7 decimal digits of precision see note
Long -0x2000_0000_0000_0000L 0x1FFF_FFFF_FFFF_FFFFL Signed 62-bit integers with an approximate range of ± 2.3e18
Ulong 0UL 0xFFFF_FFFF_FFFF_FFFFUL Unsigned 64-bit integers with an approximate range from 0 to 1.8e19
Pointer n/a n/a Strictly for use with external library procedures
Double approx. ± 2.23e-308D approx. ± 1.80e+308D 63-bit floating point numbers with approximately 16 decimal digits of precision

Note: On native 64-bit implementations, Int and Float objects are full 32-bit values. Int objects will have an approximate range of ± 2.1e9.

Dynamic types

There are 25 "dynamic" types in OADL - "dynamic" in that they refer to dynamically-allocated memory managed by the OADL machine.

Type Description
Class An OADL class. Mostly useful with the new operator.
Object An instance of a class. Only the public or protected constants, data, and procedures of the Object are accessible outside the scope of the Object
Dict An associative dictionary of key/value pairs
Proc A read-only executable byte stream of instructions.
Array A heterogeneous multi-dimensional ordered list of objects.
List A heterogenous single-dimensional list of objects
PackBool A packed homogeneous array of Bool objects
String A packed single-dimensional homogeneous array of Char objects
PackChar A packed multi-dimensional homogeneous array of Char objects
PackByte A packed homogeneous array of Byte objects
PackUbyte A packed homogeneous array of Ubyte objects
PackShort A packed homogeneous array of Short objects
PackUshort A packed homogeneous array of Ushort objects
PackHalf A packed homogeneous array of Half objects
WideString A packed single-dimensional homogeneous array of WideChar objects
PackWideChar A packed multi-dimensional homogeneous array of WideChar objects
PackInt A packed homogeneous array of Int objects
PackUint A packed homogeneous array of Uint objects
PackFloat A packed homogeneous array of Float objects
PackLong A packed homogeneous array of Long objects
PackUlong A packed homogeneous array of Ulong objects
PackDouble A packed homogeneous array of Double objects
Enclosure An array enclosed as a scalar via arr.enclose()
ArrayType An array type which includes shape information
File An opened file system file, for use with OADL I/O intrinsics

Packed arrays typically are more efficient than heterogeneous arrays, both in space and in execution efficiency. PackInt, PackFloat, PackLong, and PackDouble arrays have full 32- or 64-bit precision since the type information is not stored per-element.

Dynamic values in OADL are implicitly memory-managed. There is no need for an OADL programmer to keep track of which values are no longer in use and then free them. Instead, when OADL detects that there are no longer any references to a compound value, the value is freed. If the value is an Object, and if the Object has a destroy method, then the destroy method will be called at that time. The order in which compound values is freed is non-deterministic, and therefore destroy method calls may occur in any order.

There are some similarities between Object, Dict, and Array values. All contain a group of several other values - the elements. However, there are some key differences:

Type Access Time Private elems? Accessor Multi-index? Undef query? Undef assign?
Array O(1) No [ Num... ] Yes No No
Dict O(log(n)) No [ Any ] No Yes Yes
Object O(log(n)) Yes . Public No Yes No

Note that Array in this table encompasses all array types: PackInt, String, etc.

Access time refers to the typical time to access one of the elements of the compound value. Only Objects allow private elements - elements not accessible outside the class definition of the Object. An Array may only be accessed via (possibly multiple) numeric indexes and an Object may only be accessed via a Public index. Dict and Object variables allow queries of undefined elements - these queries return nil. And, finally, only Dict variables allow assignments to previously undefined values (this adds a new key/value pair into the dictionary if it is not full).

Type descriptors

The type of an OADL value may be queried by an OADL program. Additionally, variables and procedures may have a "type decoration" indicating that they only store / return values of the given type. Finally, the OADL I/O read() intrinsic can accept type descriptors to indicate the type of the items to be read. All of the type names described in this chapter may be used as type descriptors. In addition, array types may have a shape included as part of the descriptor; for example:

var aPak : PackInt[2,3];

The following tree describes the type hierarchy that OADL follows for type compatibility:

Type
  |
  +-------+-------+---    ...
  |       |       |
 Int    Float   Array[*]  ...
                  |
    +-------------+-------------+-------------+---------------+---       ...
    |             |             |             |               |
  List          Array        String        PackInt        PackFloat      ...
    |             |             |             |               |
  List[n]   Array[n,m,...]   String[n] PackInt[n,...]  PackFloat[n,...]  ...
    |             |             |             |               |
  new List()  new Array()    "hello"       [1,2,3]        [1.,2.,3.]     ...

When queried via oadl::typecheck(), each type in this tree will return true for values having the types of each of its children. For example:

    aList = {"one", "two", "three"} // A List

    oadl::typecheck(List, aList) // aList is, in fact, a List
true

    oadl::typecheck(List[3], aList) // aList is, in fact, a List with shape 3
true

    oadl::typecheck(Array, aList) // aList is *not* an Array of any kind
Illegal type

    aPak = [2,3].iterate() // A PackInt array

    oadl::typecheck(PackInt, aPak) // aPak is, in fact, a PackInt
true

    oadl::typecheck(PackInt[2,3], aPak) // aPak is a PackInt with shape [2,3]
true

    oadl::typecheck(Array, aPak) // aPak is not a heterogeneous Array
Illegal type

    // Both aList and aPak are, generically, arrays
    oadl::typecheck(Array[*], aList) && oadl::typecheck(Array[*], aPak)
true


5. Arrays, Lists, and Strings

There are many kinds of arrays in OADL:

Array List PackBool String PackChar
PackByte PackUbyte PackShort PackUshort PackHalf
WideString PackWideChar PackInt PackUint PackFloat
PackLong PackUlong PackDouble

Regardless of kind, all arrays are ordered lists of values, indexed by one or more numeric values. Arrays are a first-class types in OADL, in that they are dynamically allocated and assigned, and can participate in arithmetic operations as easily as scalars can. An array in OADL has three primary attributes: its shape, the type of its elements, and the elements themselves. The dimensionality of an array is known as its rank.

As mentioned, arrays are indexed by one or more numeric values. The indexes start at 0, and therefore the maximum index for a given dimension is the size of that dimension, minus one. Note that some of the array types actually only have one dimension; they are indistinguishable from the corresponding multi-dimensional type if only one dimension is specified:

Single-dimensional
type
Multi-dimensional
type
List Array
String PackChar
WideString PackWideChar

As mentioned before, array elements may be of any type. In the most general case, each element may be of a different type. This "generic" array will give a typeof() result of Array or List, depending on whether the array is multi- or single-dimensional. The new Array(dims) and new List(length) methods create generic arrays and lists.

However, it is more efficient in both space as well as execution speed if all the elements are of the same type and are packed together. OADL will create these packed arrays when the [ ] array creation syntax is used. It is a TypeCheck error to try to assign a non-convertable value to an element of a packed array:

    a = [1,2,3]
    a[1] = 2.5 // 2.5 will be converted to Int
    a[1] = "two" // "two" cannot be converted to Int
Illegal type

The pack() and unpack() methods can be used to make packed and unpacked copies of arrays, respectively. The array base type will be computed via the table shown under the Bracket syntax (packed arrays) section, below. For example:

    a = [1,2,3].unpack()
    a[1] = "two"
    a
1 two 3

    a = {1,2,3}
    typeof(a)
List

    a = a.pack()
    typeof(a)
PackInt

Array indexes

Elements of arrays may be referenced and changed using the indexing operator arr[indexes] Arrays in OADL always use zero-based indexing:

    a = new Array(3)
    for (var i = 0; i < 3; i++) {
        a[i] = i + 1;
    }
    a
1 2 3

The RangeCheck exception is thrown when an attempt is made to access a non-existent element:

    a = {1,2,3}
    a[3] = 4
Value out of range

Multi-dimensional arrays may be indexed by a list of numbers that can be as short as one number or as long as the number of dimensions of the array:

    a = [3,3,3].iterate()
    a[0]
0 1 2
3 4 5
6 7 8

    a[0,1]
3 4 5

    a[0,1,2]
4

    a[0,1,2,3]
Inconsistent array shape

If a partial list of indexes is given, a copy of the subarray is created. This can lead to subtle differences in program execution between fully specified indexes and partially- specified indexes:

    a[0,1,2] = 50
    a[0]
0 1  2
3 4 50
6 7  8

    // Note that a[0,1,2] will not be modified by this assignment
    a[0][1,2] = 500
    a[0]
0 1  2
3 4 50
6 7  8

Any of the indexes may specified as a contiguous range of indexes by using the : syntax. If the first index in a range is not given, 0 is assumed. If the last index in a range is not given, the last element in that dimension is assumed:

    str = "Hello world!"
    str[6:10]
world

    str[:4]
Hello

    str[6:]
world!

    a = [3,4,3].iterate()
    a[1,1:2,1] = 42 // Assign just a sub-portion of the array
    a[1]
12 13 14
15 42 17
18 42 20
21 22 23

Arrays may also be indexed by other arrays; in that case, the resulting shape is the concatenation of the shapes of all the indexes (with a scalar index not increasing the rank of the resulting array):

    a = [3,3,3].iterate()
    a
 0  1  2
 3  4  5
 6  7  8

 9 10 11
12 13 14
15 16 17

18 19 20
21 22 23
24 25 26

    a[[0,1],1,[1,2]]
 4  5
13 14

    a[2,[1,2],[1,2]] = 100
    a[2]
18  19  20
21 100 100
24 100 100

    // The consistency rules for array-valued-index assignment are the same
    // as those for arithmetic expressions
    a[2,[1,2],[1,2]] = [[22,23],[24,25]]
    a[2]
18 19 20
21 22 23
24 24 25

    a[2,[1,2],[1,2]] = [100,200]
Inconsistent array shape

Any array-valued indexing result is actually a new copy of the array subrange. Changing an element of the subrange will NOT change the corresponding element of the original array.

Although syntactically similar, there are subtle differences between using the arr[start:end] syntax and using an iterator as an index arr[[start:end]]. Internally, OADL can optimize the first form to create a copy-on-write reference to the array, reducing heap memory usage. Additionally, unbounded iterators cannot be used as array indexes:

    a = "Hello, world!"
    a[:]
Hello, world!

    a[[:]]
Unbounded iterator

A special indexing operator is the "flattened" indexing operator #[index]. It takes a single index (which may be an array) and interprets it as the offset, in elements, from the beginning of the array. This can be useful when writing algorithms that generally operate on arrays of any rank.

    a = "abcdefghi".reshape(3,3)
    a
abc
def
ghi

    a#[2]
c

    a#[4] = 'E'
    a
abc
dEf
ghi

Array properties

Various properties of arrays can be queried with the following intrinsic methods:

arr.shape()
Returns the shape (list of dimensions) of an array
arr.rank()
Returns the dimensionality of an array
arr.length()
Returns the number of elements in the first dimension of an array
arr.width()
Returns the number of elements in the last dimension of an array
arr.sizeof()
Returns the total number of elements in an array
arr.stride()
Returns the "stride" of each index of an array
arr.arrbase()
Returns the base type of an array, or Array for a heterogeneous array
arr.readonly()
Returns whether an array or object is read-only (constant) or changeable
arr.transient()
Returns whether an array or object is dynamically managed (transient) or permanent

Examples:

    arr = [2,3,4].iterate()
    arr.shape()
2 3 4

    arr.rank()
3

    arr.length()
2

    arr.width()
4

    arr.sizeof()
24

    arr.stride()
12 4 1

    arr.arrbase()
Int

    arr.readonly()
false

    arr.transient()
true

It is is not possible to change the shape of an array; however, it is possible to allocate a resized copy of an array by using the reshape() method.

    str = "Hello world!"
    hello = str.reshape(5)
    hello
Hello

    typeof(str)
String

    str = str.reshape(2,6)
    str
Hello
world!

    typeof(str)
PackedChar

Enclosures

An array or scalar may be enclosed. This creates a new Enclosure object which may be used as a scalar in arithmetic operations. Arrays may be enclosed along one of their axes; the result is a List or Array consisting of slices of the array along that axis:

    a = [2,3,4].iterate()
    a.enclose()
+-----------+
| 0  1  2  3|
| 4  5  6  7|
| 8  9 10 11|
|           |
|12 13 14 15|
|16 17 18 19|
|20 21 22 23|
+-----------+

    a.enclose(1) // Enclose along axis #1
   +-------+    +-------+   +--------+   +--------+
   |+-----+|    |+-----+|   |+------+|   |+------+|
   ||0 4 8||    ||1 5 9||   ||2 6 10||   ||3 7 11||
   |+-----+|    |+-----+|   |+------+|   |+------+|
   +-------+    +-------+   +--------+   +--------+
+----------+ +----------+ +----------+ +----------+
|+--------+| |+--------+| |+--------+| |+--------+|
||12 16 20|| ||13 17 21|| ||14 18 22|| ||15 19 23||
|+--------+| |+--------+| |+--------+| |+--------+|
+----------+ +----------+ +----------+ +----------+

    // The resulting Array has the shape of the remaining axes of the
    // original array
    a.enclose(1).shape
2 4

    [1,2,3,4]+[10,20].enclose()
+-------+ +-------+ +-------+ +-------+
|+-----+| |+-----+| |+-----+| |+-----+|
||11 21|| ||12 22|| ||13 23|| ||14 24||
|+-----+| |+-----+| |+-----+| |+-----+|
+-------+ +-------+ +-------+ +-------+

    // An enclosure may be (partially) reversed via the disclose() method
    a.enclose(1).disclose()
   +-----+    +-----+   +------+   +------+
   |0 4 8|    |1 5 9|   |2 6 10|   |3 7 11|
   +-----+    +-----+   +------+   +------+
+--------+ +--------+ +--------+ +--------+
|12 16 20| |13 17 21| |14 18 22| |15 19 23|
+--------+ +--------+ +--------+ +--------+


Array creation

Arrays can be created in several ways. These include:

Constant Strings

Strings are single-dimensional arrays of either Char or WideChar, and constant strings can be created with the double-quote syntax:

    str = "Hello!";
    lStr = L"Long String!";

Bracket syntax (packed arrays)

Arrays can be created and their contents initialized via the bracket syntax, which allows multi-dimensional constant arrays to be created:

    arr = [[1,'2', 3.0],[4,'5',6.0]]
    arr
1. 50. 3.
4. 53. 6.
    typeof(arr)
PackFloat
    arr.shape()
2 3

Note that packed arrays will be created if possible (as was shown in the previous example). The items between the brackets may be of different types, but must be compatible with each other for packing; this means one cannot mix String constants with scalar numeric values. The following table illustrates which types of constants may be present in a given packed array type. The cells highlighted in green indicate the types which force a promotion to the packed type on the left:

Bool Char Byte Ubyte Short Ushort Half WideChar Int Uint Float Long Ulong Double Other
PackBool Y
String2 Y
PackChar3 Y
PackByte Y Y
PackUbyte Y Y1 Y
PackShort Y Y Y Y
PackUshort Y Y1 Y Y1 Y
PackHalf Y Y Y Y Y Y
WideString2 Y Y1 Y Y1 Y Y
PackWideChar3 Y Y1 Y Y1 Y Y
PackInt Y Y Y Y Y Y Y
PackUint Y Y1 Y Y1 Y Y Y1 Y
PackFloat Y Y Y Y Y Y Y Y Y Y
PackLong Y Y Y Y Y Y Y Y Y
PackUlong Y Y1 Y Y1 Y Y Y1 Y Y1 Y
PackDouble Y Y Y Y Y Y Y Y Y Y Y Y Y
List2 Y Y Y Y Y Y Y Y Y Y Y Y Y Y Y
Array3 Y Y Y Y Y Y Y Y Y Y Y Y Y Y Y

1 Non-negative values only
2 Only one dimension
3 More than one dimension

Strings may be included in bracket-syntax packed arrays, but they must all have the same length. In bracket arrays, a string is syntactic sugar for a bracket with the list of individual characters in it:

    a = [["abc","def"],["ghi","jkl"]]
    a
abc
def

ghi
jkl

    a.parent
PackChar[2,2,3]

    // ['j','k','l'] has the same effect as "jkl" in a bracket-syntax array
    b = [["abc","def"],["ghi",['j','k','l']]]
    b.parent
PackChar[2,2,3]

    a == b
true

    // The characters in the string will be type-promoted according to
    // the table if mixed types are present in the bracket
    c = ["abc",[1,2,3]]
    c
97 98 99
 1  2  3

    c.parent
PackInt[2,3]

Brace syntax (Lists)

A heterogeneous List can be created using the brace syntax. Note that the new list will always have only one dimension; nested lists are supported, but they will be enclosed sub-lists:

    list = {1,"two",3.0}
    list
1 two 3.
    list = {{1,"two",3.0},{4,"five",6.0}}
    list
+--------+ +---------+
|1 two 3.| |4 five 6.|
+--------+ +---------+

Iterator syntax

The iterator syntax can be used to create single-dimensional packed arrays:

    iterator : '[' opt-expr ':' opt-expr ']'
             | '[' opt-expr ':' opt-expr ':' opt-expr ']'
             ;

The expressions in an iterator can be of any numeric or character type; the packed array will be of the appropriate type after potential type promotion. The first expression is the start element of the resulting array. If it is omitted, the first element will be a zero of the appropriate type.

The second expression specifies the end element of the resulting array. If it is present, then the array will be limited to the range of the start and end expressions, inclusive. Otherwise, the iterator is unbounded. Note that unbounded iterators can lead to UnboundedCheck errors if they are used in ways which would create unbounded memory allocations.

In the two-argument form, the iterator increment will be either 1 or -1 depending on whether the first expression is greater than or less than the second expression. In the three-argument form, the increment is the third expression, and the sign of the increment must be consistent with the order of the start and end elements.

Here are some examples of iterators:

    ['A':'Z']
ABCDEFGHIJKLMNOPQRSTUVWXYZ

    ['Z':'A']
ZYXWVUTSRQPONMLKJIHGFEDCBA

    [0:10:2]
0 2 4 6 8 10

    [0.:1.:0.05]
0. .05 .1 .15 .2 .25 .3 .35 .4 .45 .5 .55 .6 .65 .7 .75 .8 .85 .9 .95 1.

    a = [:] // Unbounded iterator; it cannot be printed
    a
Unbounded iterator

    a[10] // ...but it can be indexed
10

Array new syntax

The new arrType() syntax can create an array of any type and shape. The elements of the array are initialized to the appropriately typed zero:

    arr = new Array(10,10) // Create a 10x10 heterogeneous array
    str = new String(32) // Create a string that can hold 32 chars
    lst = new List(10) // Create a 10-element heterogeneous list
    cube = new PackFloat(2,2,2) // Create a 3-dimensional 2x2x2 cube of floats

Array creation with "foreach"

The foreach statement creates an appropriately-sized Array or List by evaluating an expression according to an array indexing template. The syntax of the foreach statement is:

foreach         : 'foreach' '(' arr-expr ')' '{' expr '}'

The arr-expr must be an array index expression. The indexes of arr-expr must be simple names. Each name will be implicitly declared as a local variable within the scope of the foreach body. The arr-expr dictates the shape of the resulting array. If a regular N-dimensional index is used, the shape of the resulting array is the first N elements of the shape of the source array. If a flattened index is used, then the shape of the resulting array is the same as the shape of the source array.

The expr may refer to the base array of arr-expr by using the ?* pseudo-constant. This is especially useful if the base array is an expression itself.

The foreach statement always creates a heterogeneous List or Array. Note that foreach is an expression - contrast it with forall, which is a statement. The definition of forall can be found in the Procedures chapter.

Example:

    a = [2,3].iterate()

    // A single index creates a 1-D result
    b = foreach (a[i]) { "Row " ## (i => String) }
    b
+-----+ +-----+
|Row 0| |Row 1|
+-----+ +-----+

    // Two indexes creates a 2-D result
    b = foreach (a[i,j]) { {i,j} }
    b
+---+ +---+ +---+
|0 0| |0 1| |0 2|
+---+ +---+ +---+
+---+ +---+ +---+
|1 0| |1 1| |1 2|
+---+ +---+ +---+

    // A flat index creates a result of the same shape as the source array
    b = foreach (a#[i]) { Char('a'+i) }
    b
a b c
d e f

    // Use the ?* constant to refer to the base array
    b = foreach ((a*10)[i,j]) { ?*[i,j] }
    b
 0 10 20
30 40 50

    // Attempting to access more elements than present in the array
    // throws a ShapeCheck error
    b = foreach(a[i,j,k]) { 1 }
Inconsistent array shape

Array creation intrinsics

There are a variety of intrinsic methods that create arrays. For example, two scalars may be concatentated, and the iterate() method may be used to create a packed homogeneous array filled with a sequence of Int values - a PackInt array - starting at zero:

    str = 'a' ## 'b'
    str
ab

    arr = [2,3].iterate()
    arr
0 1 2
3 4 5

See the chapter on Intrinsic Procedures and Methods for more information on the various OADL array intrinsic methods.

Array-valued expressions

Since arrays are first-class objects in OADL, they may be used in arithmetic expressions just like scalar (single-valued, non-array) values. A new array is created with its contents set to the element-by-element evaluation of the arithmetic expression.

Only values with consistent shapes can be used together in arithmetic statements. The rules regarding consistency are simple:

Note that an Enclosure (see above ) is considered to be a scalar. Here are some examples which illustrate these rules:

    a = [1,2,3]
    b = [4,5,6]
    a + b
5 7 9

    a + 1
2 3 4

    b = {4,{5,6},7}
    a + b
5 +---+ 10
  |7 8|   
  +---+ 

    b = [7,8].enclose()
    a + b
+---+ +----+ +-----+
|8 9| |9 10| |10 11|
+---+ +----+ +-----+

If an attempt is made to use inconsistent shapes together in an expression, the ShapeCheck exception is thrown:

    a = [1,2,3]
    b = [[4,5,6],[7,8,9]]
    a + b
Inconsistent array shape

In expressions involving both arrays and objects with overloaded operators, the operator overloading rules are followed first, followed by the array expression rules. This allows arrays to be passed to the overloaded operator methods. For example:

    class str {
        var sVal;
        public proc create(a) { sVal = a; }
        public proc get() { return sVal; }

        operator + (b) { // self is LHS of +
            switch (typeof(b)) {
            case String :
                return new str(sVal ## b);
            case Object :
                if (b.parent() == str) return new str(sVal ## b.get());
            }
            throw oadl::TypeCheck;
        }
        operator \+ (a) { // self is RHS of \+
            switch (typeof(a)) {
            case String :
                return new str(a ## sVal);
            case Object :
                if (a.parent() == str) return new str(a.get() ## sVal);
            }
            throw oadl::TypeCheck;
        }
    }

    a = new str("hello, ") {};
    b = a + "world";
    b.get()
hello, world


6. Dictionaries

A Dict is an associative dictionary which relates keys and values - the keys may be of any type. Dictionaries may be created in two ways. First, the new Dict() method may be used to create a dictionary with a given maximum size:

    d = new Dict(32) // Create a dictionary to hold 32 key/value pairs

Additionally, dictionaries can be created by using triple angle brackets, thus:

    d = <<< "red", [1.,0.,0.], "green", [0.,1.,0.], "blue", [0.,0.,1.]>>>

An even number of items must be specified between the triple angle brackets. The first of each pair is the key, and the second is the value associated with that key. Note that elements of a dictionary created with triple angle brackets may be replaced, but the dictionary may not grow beyond the number of pairs specified between the brackets. The reshape() method may be used to create a copy of a Dict which can hold a different number of items:

    // The dictionary from the previous example can hold 3 key/value pairs
    d.sizeof()
3

    // We need to store up to 10 pairs, so resize it
    d = d.reshape(10)
    d.sizeof()
10

    // It still only holds 3 key/value pairs
    d.length()
3

Dictionary insert, delete, and lookup

Dictionaries use the same bracket syntax as arrays to access and assign elements; however, dictionaries have only one "dimension". To insert a key/value pair into a dictionary, simply execute an array-like assignment:

    d["cyan"] = [0.,1.,1.]
    d.length()
4

The index expression is the key, and the right-hand side of the assignment is the value. Looking up a value in a dictionary is equally simple:

    "Red = ", d["red"]
Red = 1. 0. 0.

If the value is not found, the expression will evaluate to nil:

    "Purple = ", d["purple"]
Purple = nil

To delete an item from a dictionary, simply assign nil to the particular key:

    d.length()
4

    d["cyan"] = nil
    d.length()
3

Dictionaries have O(log(N)) complexity of insertions, lookups, and deletions. Additionally, although keys may be of any type, String and WideString keys are treated specially: the actual contents of the String or WideString is used as the key. Other Array-valued keys simply use the Array ID as the index for the dictionary. Finally, if the key stored in the dictionary or the key used for value lookup is a numeric value, the stored key and the lookup key are promoted to a compatible type according to the rules given in the Expressions chapter:

    d[1] = "two"
    d[1.0]
two


7. Classes

OADL classes are similar to C structs and C++ classes, but there are some important differences. Unlike C structs (but like C++ classes), OADL classes allow methods (public procedures) to be defined. Unlike C++ classes, though, all methods are essentially virtual.

Also like C++, classes may define properties which are either private (the default - not visible to other classes or external functions) or public. Because of OADL's dynamic typing, it is not necessary to include a complete class definition in a header file in order to use it or subclass it.

To declare a class (without defining it), use the class declaration:

class namelist;

To fully define a class and its attribute, use the class definition:

class name {
    proplist
}

The proplist is a sequence of constant, variable, and procedure definitions. See the OADL Program Syntax for a description of the syntax.

Public Elements

Only the public properties are visible outside the class. Public properties are declared using the public keyword:

public const constlist
public var varlist
public proc proc

Public properties may also be defined outside a class; however, the default association of a public property with an actual value can only be done inside a class definition. The syntax for declaring a public property or properties is:

public namelist;

There is not necessarily any association of those public properties with any particular class; this is simply a forward declaration of properties that might be part of some class. Referencing a non-existent public property of a class or object results in the value nil. Any attempt to assign a value to non-existent public property results in a RangeCheck exception.

A subset of public properties exist in OADL; these are protected properties. Protected properties may be referenced outside their class definition, just like a public property. However, they may only be assigned a new value inside a class-public or class-private procedure. The syntax is very similar to the syntax for public properties:

protected var varlist

Although OADL accepts the protected keyword for const and proc declarations, in those cases, the effect is exactly the same as the public keyword.

The public names exist in a separate namespace from other program objects. OADL attempts to use the proper namespace based on context, but the program may override its choice by using the public keyword as the namespace in an expression:

proc create()
{
    "pubname(create) = ", pubname(public::create), "\n";
}

Private Elements

The private elements of a class are those elements which are not visible or accessible to outside procedures. To declare private elements in a class, merely insert a const, var, or proc declaration inside the class definition scope; for example:

class box {
    const MyName = "Boxy";
    var position, size;
    proc PrintMyName() { say(MyName); }
}

Private elements are very useful if it is necessary to change the underlying implementation of a class. Since no other procedure can even know that private data exists in a class, changing that private data can in no way affect those other procedures. References to private elements inside the class declaration look exactly like normal variable or constant references; the compiler keeps track of what is meant by each name.

Public Constants

Public constants are constants which are visible to the outside world, but not modifiable. For example, suppose that boxes, by default have a weight which is meaningful for other objects to refer to:

class box {
    public const Weight = 60;
}

One special public constant is defined for all objects and classes in OADL: parent. It refers to the parent class of a class or object, and is handy when a class wants to enhance a public procedure with some extra code, but wants to use the parent same public procedure of the parent class as well to do something. Other procedures can refer to the public constant parent

switch (obj.parent) {
case box :      /* Do something boxy */
case sphere :   /* Do something spherical */
        /* and so on */
}

A class which was created without a parent has a parent public constant of nil.

Public Variables

Public variables are variables which are visible to and modifiable by outside procedures. If, for example, outside physical forces might move a box around without having to call a public box method, its position could be declared as a public variable:

class box {
    public var pos = [0,0];
}

Be very careful, though, when using public variables: the variable is exposed effectively as an interface to the class. This might cause trouble later if the class definition is changed. This risk may be somewhat reduced by annotating the public variable with a type decoration:

    class box {
        public var pos : PackInt[2] = [0,0];
    }

    box box1()
    box1.pos = [1,2]
    box1.pos = nil
Illegal type

    // OADL does type conversions for conformant array assignments
    box1.pos = [1.2, 2.2]
    box1.pos
1 2

Protected Variables

Protected variables are variables which are visible to outside procedures, but only modifiable by class-private and class-public procedures. If, for example, the temperature of an object may slowly approach room temperature in a well-defined way, but arbitrary code must not be allowed to change the temperature, a protected variable should be used:

class thermal {
    protected var temperature = 0;
    public proc create(initTemp) {
        temperature = initTemp;
    }
    public proc warmup(degrees) {
        temperature += degrees;
    }
}

In this example, the create() method modifies the temp variable; however, any attempt by an outside procedure to modify temp will result in a runtime AccessCheck error.

Note that a class may implement the assign operator ":=" which, if provided, will be called when an attempt is made to assign to a protected variable. For data integrity reasons, the assign operator may only be implemented if all parent classes of a class also implement it:

    // Demonstrate implemenation of an assign operator
    class assign {
        protected var a, b;
        operator := (prop, val) {
            switch (prop) {
            case public::a : self.(prop) = val;
            default : throw oadl::AccessCheck;
        }
    }

    assign x()
    x.a = 10
    x.b = 20
Access failure

    // Demonstrate restriction on overriding the assign
    // operator to gain access to protected variables
    class foo {
        protected var a;
    }
    class bar(foo) {
        operator := (prop, val) {}
Access failure

Public Procedures (Methods)

Public procedures are also known as methods. They are procedures which execute as if they were inside the class: they have access to all internal class constants, variables, and procedures. The better way to do the box position example above is to use a public procedure to move the box, so that its internal representation might change later:

class box {
    var pos = [0,0];
    public proc move(x, y) { pos[0] = x; pos[1] = y; }
}

The token -> may be used as a synonym for the . operator. This is useful when lexical confusion might otherwise occur (for example, when an integer is the target of the method call):

$ cat foo.oad
proc main()
{
    var a = 3.iterate();
}
$ oadl foo.oad
File foo.oad line 3: ';' expected
    var a = 3.iterate();
---------------------^
$ cat bar.oad
proc main()
{
    // Use the -> operator to avoid confusion between a floating-point
    // constant and the method call
    var a = 3->iterate();
    "", a, '\n';
}
$ oadl bar.oad
0 1 2

Create, Completion {}, and Destroy

All classes in OADL have two predefined methods, create() and destroy(), and one predefined operator, the completion operator { }. The create method is called when a dynamic object is created. The destroy method is called when OADL detects that no more references to an object exist, and is about to free that object (see the section on Zombie Objects for more details). The completion operator is called at the completion of static public variable initialiation (see below). The completion operator is also called at the completion of with statements (see the section on with statements in the Procedures chapter for more information).

The completion operator is called with several arguments. The first argument is either false (if the object is only partially completed due to use of the ... syntax) or true. The rest of the arguments are all of the public names that were assigned inside the current brace pair. For example:

    class a {
        public var b; 
        operator {} (compl) {
            using namespace oadl;
            var i;
            for (i = 1; i < nargs(); i++) {
                "Public ", arg(i), " was set to ",
                                self.(arg(i)), "\n";
            }
            if (compl) "Completed.\n";
        }
    }

    a() aa { b = "foo" }
Public b was set to foo
Completed.

The global pseudo-constant self refers to the current object that the current topmost method call applies to; this is handy if an object needs to reference itself to another routine. For example:

    proc ack() 
    {
        "self = ", oadl::objname(self), "\n";
    }

    class foo {
        public proc create() {
            ack();
        }
    }

    foo() bar
self = bar

Typically, classes do not need to provide their own destroy() implementation since the default one is generally sufficient. The main reason a class might have a destroy() method is if the class holds references to objects which are not tracked by OADL (for example, operating system objects).

Operator Overloading

OADL, like many other object-oriented languages, supports operator overloading. This allows classes to implement their own versions of standard OADL operators. All operators except logical AND &&, logical OR ||, and object public property reference . are overloadable. A class overloads an operator via the operator keyword, thus:

class complex {
    public var real, imag;
    public proc create(r, i) {
        real = r;
        imag = i;
    }
    operator + (rhs) {
        return new complex(real + rhs.real, imag + rhs.imag);
    }
    operator \+ (lhs) {
        return new complex(lhs.real + real, lhs.imag + imag);
    }
}

Binary operators are passed one argument - the other operand in the expression. If it is neccessary to distinguish the case where an object is the left operand from the case where an object is the right operand, "right-binding" versions of the operators are used. The names of each "right-binding" operator is the same as the name of the corresponding "left-binding" operator, but with a backslash in front of the operator:

\| \^ \& \< \> \+ \-
\* \/ \% \== \!= \<= \>=
\<< \>> \=> \~= \**

If no "right-binding" operator is present, both left- and right-operand overloaded operators call the normal operator method.

Unary operators (~ and -) are passed no arguments. Since the minus operator - is both a binary and a unary operator, a special operator name is provided for the unary version of minus. This name is !-. For example:

operator - (rhs) {
    return new complex(real - rhs.real, imag - rhs.imag);
}
operator \- (lhs) { // Right-binding version
    return new complex(lhs.real - real, lhs.imag - imag);
}
operator !- () () // Unary version
    return new complex(-real, -imag);
}

It is possible to call an overloaded operator method without using the default expression syntax. The name of an overloaded operator is operator op, where op is one of the possible overloaded operators. Since the ! operator can natively operate on expressions of any type, the "operator !" syntax is the only way this operator may be overloaded. As a shorthand, the backtick may be used instead:

    class factorial {
        operator ! (lhs) {
            if (lhs > 1) {
                return lhs * self.`!(lhs-1);
            }
            else {
                return lhs;
            }
        }
    }


    a = new factorial()
    "7! = ", a.`!(7), '\n'
7! = 5040
}

Procedure call overloading is a little different than general operator overloading. Instead of an explicit list of arguments the nargs() and arg() intrinsics must be used to access the arguments of the overloaded procedure:

    class procClass {
        public operator () () {
            var i;
            for(i = 0; i < oadl::nargs(); i++) {
                "arg(",i,") = ", oadl::arg(i), '\n';
            }
        }
    }
    a = new procClass()
    a(1,2,3)
arg(0) = 1
arg(1) = 2
arg(2) = 3

Array indexing overloading has two operators involved - index references, and indexed assignments. Therefore, there are two different operators: [] and [=]. The index reference operator [] works as might be expected - the argument list is the list of indexes to be looked up. The index assignment operator [=] takes at least two arguments. The last argument is the value that should be assigned. The remaining arguments are the multi-dimensional index:

    class arrClass {
        var arr;
        public proc create(n,m) { arr = [n,m].iterate(); }
        public operator [] (i0,i1) { return arr[i0,i1]; }
        public operator [=] (i0,i1,val) { arr[i0,i1] = val; }
        public proc print() { "", arr, '\n'; }
    }
    arrClass arr(4,5)
    arr[2,3] = 100
    arr[2,3]
100

    arr.print()
 0  1  2   3  4
 5  6  7   8  9
10 11 12 100 14
15 16 17  18 19

The flattened array index operators #[] and #[=] are supported in a similar way.

Inheritance

OADL fully supports class inheritance. Inheritance creates a new class derived from an existing one. The new class inherits all of its private constants, variables, and procedures, as well as all of its public properties. The new subclass may then change or add to that list to customize itself. To declare a class which inherits from another class, use the following syntax:

class name( parent ) {
    proplist
}

The proplist may change the initial value of variables, constants, and public properties, and it may add new ones. The proplist may not change an element to an element of a different kind; for example, the program may not change a const to a var, or a public property to a private element. Here is an example of inheritance:

class PhysObj {
    var
        Pos = { 0, 0, 0 },
        Mass = 1.0,
        Momementum = { 0, 0, 0 };
    public proc Accelerate( force )
    {
        Momentum[0] += force[0];
        Momentum[1] += force[1];
        Momentum[2] += force[2];
    }
    public proc Move( dT )
    {
        Pos[0] += dT * Momentum[0] / Mass;
        Pos[1] += dT * Momentum[1] / Mass;
        Pos[2] += dT * Momentum[2] / Mass;
    }
}

class SphereObj( PhysObj ) {
    var
        Radius = 1.0;
    public proc create( radius )
    {
        Radius = radius;
    }
}

The SphereObj is a subclass of PhysObj, and has all of its properties, including Pos, Mass, and Momentum, and all of its public properties. It defines a new property, Radius, and its create() method is called with the desired radius.

Multiple Inheritance

To solve certain problems (for example, in an adventure, to define a magical object which provides light and unlocks a door), it is often useful to have a class which is derived from more than one parent class. OADL supports a multiple inheritance capability which helps when these issues come up. To declare a class which inherits from multiple parents, simply list all of the parents in the class declaration, thus:

class litObjClass {
    public const lit = 1;
}

class keyObjClass {
    public const unlocks = 1;
}

class litKeyClass(litObjClass,keyObjClass) {}

In the example given, the class "litKeyClass" has the public and protected variables and constants from both litObjClass AND keyObjClass.

When creating classes with multiple inheritance, properties from parent classes later in the list of parent classes override those of earlier classes (except for the parent public property). For example:

    class Aclass {
        var a = 1;
        public proc Describe() { "a = ", a, "\n"; }
    }

    class Bclass {
        var b = 2;
        public proc Describe() { "b = ", b, "\n"; }
    }
    class ABclass(Aclass,Bclass) {}

    ABclass ab {}
    ab.Describe()
b = 2

In this example, the Describe public property from class Aclass was overidden by the Describe public property from Bclass. The reason for this is that, conceptually, inheriting from multiple classes is similar to inheriting from the first class in the list, and then adding the extra declarations. For example, the code above is very similar to this code:

    class Aclass {
        var a = 1;
        public proc Describe() { "a = ", a, "\n"; }
    }

    class ABclass(Aclass) {
        var b = 2;
        public proc Describe() { "b = ", b, "\n"; }
    }

    ABclass ab {}
    ab.Describe()
b = 2

The difference between this and multiple inheritance is that the Aclass and Bclass classes still exist as part of the ABclass. The following program is very hard to write with single inheritance, since the var a is in both Aclass and Bclass:

    class Aclass {
        var a = 1;
        public proc aDescribe() { "a = ", a, "\n"; }
    }
    class Bclass {
        var a = 2;
        public proc bDescribe() { "a = ", a, "\n"; }
    }
    class ABclass(Aclass,Bclass) {}

    ABclass ab {}

    ab.aDescribe()
a = 1
    ab.bDescribe()
a = 2

Dynamic Runtime Classes

Classes may be created dynamically at runtime. These classes do not have an inheritance tree - they always have a parent property of nil. A dynamic runtime class is created via the new Class(className, pubPropList) syntax. The className is the name of the new class. The pubPropList is a List of pub, value pairs. Each of the Public pub items is made a new public var of the new class. The corresponding value is used as the initial value of that variable in the class.

Accomanying dyamic runtime classes are dynamic runtime publics. These are created via the new Public(pubName) syntax. The pubName is the name of the new public.

An example of both dynamic publics and dynamic classes is:

public pub2;

proc main()
{
    // Create a couple of new publics
    var pub0 = new Public("pub0");
    var pub1 = new Public("pub1");
    // Create a new class using those, plus an existing public
    var cls = new Class("cls", {pub0, 123, pub1, "hello", pub2, 3.14});
    "New class:\n";
    forall (cls.(pub)) {
        "", pub, ": ", cls.(pub), '\n';
    }
    "\n";

    // Note that classes created with "new Class" are *not* readonly
    cls.(pub0) = 456;

    // Create an instance of that class
    var obj = new cls();
    "New instance:\n";
    forall (obj.(pub)) {
        "", pub, ": ", obj.(pub), '\n';
    }
}

The program above produces the following output:

New class:
parent: nil
pub2: 3.14
pub0: 123
pub1: hello

New instance:
parent: cls
pub2: 3.14
pub0: 456
pub1: hello

Dynamic classes are garbage collected when all references to them are removed. However, dynamic publics are not; they persist for the duration of program execution.


8. Objects (Instances)

To actually use the public properties defined in a class, that class must be instantiated in an object. This done in one of two ways: statically or dynamically. Static objects have a lifetime which extends over the entire life of the program (it is not possible to destroy a static object). Dynamic objects are allocated on the fly and are destroyed when the runtime detects that no more references to the object exist. The syntax by which static objects and dynamic objects are created is slightly different. Note that the create() method and {} completion operator of a static object are called before the main() procedure begins to run, whereas those of a dynamic object are called at the point in the code where the new dynamic object is created and initialized.

Static Objects

A static object is created in one of two ways: as a named static object, or as an unnamed static object which is assigned to a constant, a variable, or used in an expression. The syntax for creating a static object is nearly identical in both cases; the object name is simply omitted for the unnamed static object. Both static and dynamic objects may be created in one of two ways. The first way is this:

classname objname( create_args );

where classname is the name of a previously declared class, objname is the desired name of the object, and create_args are the arguments to be passed to the class's create() method. The objname and terminating semicolon are omitted for unnamed static objects.

To initialize any of the public variables, use the syntax:

classname objname( create_args ) {
    assignments
}

where assignments is a list of items of the form:

name = expr

Each name must be the name of a public variable in the class, and each expr must be a constant expression. For example, here's an adventure-language like construct:

room room1 {
    Lit = 1
    LDesc = proc() {say("You are in room 1.\n");}
    SDesc = proc() {say("Room 1");}
}

The object name is omitted for unnamed static objects. The named static object creation results in exactly the same behavior as using an unnamed static object as the initializer for a constant; for example, the following two statements result in identical behavior:

myClass myObj { myVar = 1; }
const myObj = myClass { myVar = 1; }

The following two statements are NOT identical to each other, since the compiler thinks the second one is just creating a constant with the same value as the given class:

myClass myObj {}
const myObj = myClass; // Does not create a static object!

If the create() method does not require arguments, then the parenthesis on the class name are optional. Forward references to static objects may be created by specifying the class name and the object name without any create() arguments or initializers; for example:

myClass myObj;

myObj is a forward reference to the object, and does not actually initialize the object (if a program with unresolved forward references is run a warning is generated).

Not all the properties of a static object need to be specified at the same point in the source file; it is often useful to split out similar functionality implemented in many objects into separate source regions (for example, in an adventure, it is convenient to have all of the room descriptions in one source file, and all of the room actions in another source file). To accomplish this, use the ellipsis ... syntax:

location room1 {
    lit = TRUE
    ...
}
location room2 {
    lit = FALSE
    ...
}

/* some time much later in the input file */
... room1 {
    sdesc = proc() {"Room 1";}
    ...
}
... room2 {
    sdesc = proc() {"Room 2";}
    ...
}

/* much later still in the input file */
... room1 {
    ldesc = proc() {"You are in room 1.\n";}
} // Since we did not use ..., the room is complete at this point
... room2 {
    ldesc = proc() {"You are in room 2.\n";}
} // Since we did not use ..., the room is complete at this point

If the last token before the closing brace of an object definition is the ellipsis, that indicates that the object will be continued. If the token before an object name is an ellipsis, it indicates that this is a continuing definition (and, if the object was not previously continued, an error is printed). Both the pre-ellipsis and post-ellipsis may be present, as shown by the middle example above.

Dynamic Objects

Dynamic objects do not have a lifetime which extends over the life of the program; instead, they are destroyed when OADL detects that there are no more existing references to them. They also do not have a name (the objname() intrinsic will return nil if called with a dynamic object).

To create a dynamic object, use the new operator, passing arguments to the create() method of the class, optionally specifying the value of public variables, and store the result in a variable:

var = new classname( create_args ) { public_assigns };

Here's the same example as above, but coded as a dynamic object:

var room1;
proc main()
{
    room1 = new room() {
        Lit = 1
        LDesc = proc() {"You are in room 1.\n";}
        SDesc = proc() {"Room 1.\n";}
    };
}

Zombie Objects

During object destruction with a destroy method, all references to non-constant dynamic values in the object are replaced with nil. The object itself is made read-only. A temporary "deleted" property of the object is set. Objects in this state are known as "zombie" objects. Zombie objects may be resurrected if a new visible reference to them is created during execution of the destroy method:

    z = nil
    resurrect = true

    class foo {
        public var a, b;
        public proc create(x) {
            a = @x; // a will be a non-static
            b = x;  // b may be static if x is static
            "foo.create - returning ", self, '\n';
        }
        public proc destroy() {
            "", self, ".destroy() {\n";
            "  self.readonly() = ", self.readonly(), '\n';
            "  oadl::deleted(self) = ", oadl::deleted(self), '\n';
            "  dynamic copy ", a, " vs static ref ", b, '\n';
            "}\n";
            if (resurrect) z = self;
        }
    }

    a = new foo("foo")
foo.create - returning #OBJ(1)
    a = nil

    // The deleted() intrinsic prints "true" for the zombie object.
    // Zombie objects are read-only.
    oadl::gc()
#OBJ(1).destroy() {
  self.readonly = true
  oadl::deleted(self) = true
  dynamic copy nil vs static ref foo
}
    // Note that, since resurrect is "true", the destroy
    // method stashed a copy of that zombie object in the
    // global variable z

    // Set z.b to a dynamic copy of the string - it will get deleted
    // next time around
    z.b = @z.b

    // Examinine resurrected zombie z
    "z = ", z, "; z.b = ", z.b, '\n'
z = #OBJ(1); z.b = foo

    "oadl::deleted(z) = ", oadl::deleted(z), '\n'
oadl::deleted(z) = false

    // Now, without resurrection, the objects really get deleted
    resurrect = false
    z = nil
    oadl::gc()
#OBJ(1).destroy() {
  self.readonly = true
  oadl::deleted(self) = true
  dynamic copy nil vs static ref nil
}

The order in which destroy methods is called is non- deterministic.


9. Expressions

Operators and Precedence

The operators defined by OADL are as follows (in precedence order):

Operator Description
. [ ] #[ ] ( ) #( ) Public ref, array indexing, flattened array indexing, function call, array call
~ ! - @ @@ ?? Bitwise NOT, logical NOT, negate, copy, deep copy, typeof
=> Type conversion
** Exponentiation
* / % Multiplication, division, modulus
+ - Addition, subtraction
<< >> Left shift, right shift
< > <= >= Less, Greater, Less or Equal, Greater or Equal
== != #= ?= ~= Equal, Not-equal, array component-wise equality, is_a, pattern match
& Bitwise AND
^ Bitwise XOR
| Bitwise OR
&& Logical AND (pseudo-op)
|| Logical OR (pseudo-op)
? : Conditional expression
## Concatenation of two values

See the chapter on Arrays, Lists, and Strings and the chapter on Dictionaries for discussion of the array indexing operators. See the chapter on Objects for discussion of the public reference operator. See the chapters on Arrays, Lists, and Strings and Classes for a more detailed discussion of how those object types work with arithmetic, bitwise, and comparison operators.

Arithmetic Operators

The following operators are considered arithmetic operators:

** * / % + -

These operators automatically do arithmetic type promotion on their operands. This is done according to the following arithmetic type promotion table:

Char Byte Ubyte Short Ushort Half WideChar Int Uint Float Long Ulong Double Enclosure Array Object
Char I I I I I F I I ui F L U D E A O
Byte I I I I I F I I ui F L U D E A O
Ubyte I I I I I F I I ui F L U D E A O
Short I I I I I F I I ui F L U D E A O
Ushort I I I I I F I I ui F L U D E A O
Half F F F F F F F F F F D D D E A O
WideChar I I I I I F I I ui F L U D E A O
Int I I I I I F I I ui F L U D E A O
Uint ui ui ui ui ui F ui ui ui F L U D E A O
Float F F F F F F F F F F D D D E A O
Long L L L L L D L L L D L U D E A O
Ulong U U U U U D U U U D U U D E A O
Double D D D D D D D D D D D D D E A O
Enclosure E E E E E E E E E E E E E E A O
Array A A A A A A A A A A A A A A A O
Object O O O O O O O O O O O O O O O O

The entries in the table may be decoded thus:

Table Entry Meaning
I Int
F Float
ui Uint
L Long
U Ulong
D Double
E Enclosure
A Array
O Object

Bitwise Operators

The following operators are considered bitwise operators:

& | ^ ~ << >>

They operate on integral or boolean types:

Char Byte Ubyte Short
Ushort WideChar Int Uint
Long Ulong Bool *
* Bool values are not allowed with the shift operators << and >>

They operate bit-by-bit on their operands. Integral operands of the bitwise operators are promoted according to the promotion table above.

The shift operators << and >> treat their operands as unsigned values. This means that the sign bit does NOT propagate through as a result of a right shift. Additionally, the shift count is clamped to the range [0..64] This means that a shift by a negative number is the same as no shift at all, and a shift of greater than 64 bits in the left hand operand will result in all the bits being shifted off (giving a result of zero).

Comparison Operators

The following operators are considered comparison operators:

== != #= < > <= >= ~=

The comparison operators == or != always return a scalar Bool result (unless operator overloading is involved). If both arguments are arrays, the result is a lexographic comparison of the contents of the two arrays, after type promotion:

    "Hello" == L"Hello"
true

    [1,2,3] == [1.,2.,3.]
true

Otherwise, standard arithmetic promotion is performed on scalar operands. Non-arithmetic values may be compared with the == and != operators:

    public foo
    public::foo == 3
false

If the operands of comparison operators <, <=, >, or >= are both String or WideString, a lexographic comparison is also performed:

    "123" < "124"
true

    "1234" > L"123"
true

Otherwise, standard arithmetic promotion and array conformance checks are performed on the operands:

    "123" > '2'
false false true

    [1,2,3] > 2.5
false false true

If a lexographic equality comparison is not wanted, use the #= component-wise equality operator:

    [1,2,3] == [1,2,4]
false

    [1,2,3] #= [1,2,4]
true true false

The ~= operator is the OADL string pattern matching operator. The left-hand side is a string-valued expression. The right hand side is a Perl-compatible regular expression. The operator returns true if the string matches the regular expression, and false otherwise. See also the match statement in the Procedures chapter.

Copy Operators

Since elements of constant arrays and strings may not be reassigned, and since it is cumbersome to type "str.copy()" to enable modification, the @ operator is implemented. It is shorthand syntax for the copy() intrinsic method. For example:

    a = "hello"
    a[0] = 'H'
Access failure

    a = @ a
    a[0] = 'H' // This will now succeed
    a
Hello

The @@ operator is similar to the @ operator, but it represents the deepcopy intrinsic method. For example:

    a = {"hello","world"}
    a[0][0] = 'H'
Access failure

    a = @@ a
    a[0][0] = 'H'
    a
Hello world

The @ and @@ operators are not allowed in constant initializers

Type Conversion Operator

The => operator is the OADL type conversion operator. It can be overloaded - which is a convenient way for classes to implement a class-to-string method. The left-hand side of the => operator is the value to be converted; the right-hand side of the => operator is the type (or class!) to be converted to. See the following example:

    a = 1.4;
    a => Int
1

    a => complex; // Assuming class complex properly overloads =>
(1.4,0)

    a => String
1.4

Type conversion may also be done via the call syntax; for example:

    Int(1.4)
1

    3 + Float(".1415927")
3.14159

Type Query Operators

The ?= operator is the same as the is_a() intrinsic method. It is used to evaluate the class hierarchy transitively. It returns true if the right hand side is one of the parent classes of the left hand side, and false otherwise.

The ?? operator is shorthand for the typeof intrinsic.

Logical (Short-circuit) Operators

The test ? expr1 : expr2 conditional operator evaluates the leftmost argument. If the test expression is logically TRUE then the result of the expression is the middle argument. Otherwise, the result of the expression is the right argument. For example, the following implements the signum function:

proc sgn(val)
{
    return (val < 0) ? -1 : ((val > 0) ? 1 : 0);
}

If the leftmost argument is logically TRUE, then the rightmost argument is not evaluated. If the leftmost argument is logically FALSE, then the middle argument is not evaluated. This is useful to prevent exceptions from being thrown; for example, this procedure will not index the array outside its bounds:

proc safeIdx(a, i)
{
    return (i < 0)
                ? nil
                : (i >= a.length())
                        ? nil
                        : a[i];
}

The complete list of logically FALSE values is:

false nil '\x0' '\x0'L 0B 0UB
0S 0US 0 0U 0L 0UL
0.H -0.H 0. -0. 0.D -0.D

Any other value is considered logically TRUE.

Logical AND and Logical OR are pseudo-ops; that is, they are not overloadable and both implement "short-circuit" semantics. Specifically:

This can be useful if an expression to be evaluated or a function to be called has an error condition that would be avoided by placing it in a short-circuit evaluator. The following code will not dereference the array a outside its bounds:

if ((i < 0) || (i >= length(a)) || (a[i] == 10)) {
    "a[i] == 10 (or i is out of range)\n";
}

Finally, the logical operators use the same list of logically FALSE values that the ? : operator uses. This can lead to different arithmetic results than bitwise AND and OR; for example,

    2 && 3
3

    2 & 3
2

A logical AND expression of op1 && op2 is equivalent to the conditional expression op1 ? op2 : op1, with the exception that each operand is evaluated only once. A logical OR expression of op1 || op2 is equivalent to the conditional expression op1 ? op1 : op2 with the same exception.

The ! operator performs the logical NOT operation according to the logically FALSE table above.

Expression Syntax

The following describes the syntax of expressions. The precedence of operators is encoded by the ordering of the productions.

expr            : cond_expr
                | expr '##' cond_expr
                ;

exprs           : /* NOTHING */
                | exprlist
                ;

exprlist        : expr
                | exprlist ',' expr
                ;

cond_expr       : logor_expr
                | logor_expr '?' expr ':' cond_expr
                ;

logor_expr      : logand_expr
                | logor_expr '||' logand_expr
                ;

logand_expr     : or_expr
                | logand_expr '&&' or_expr
                ;

or_expr         : excl_or_expr
                | or_expr '|' excl_or_expr
                ;

excl_or_expr    : and_expr
                | excl_or_expr '^' and_expr
                ;

and_expr        : equal_expr
                | and_expr '&' equal_expr
                ;

equal_expr      : rel_expr
                | equal_expr '==' rel_expr
                | equal_expr '!=' rel_expr
                | equal_expr '?=' rel_expr
                | equal_expr '~=' rel_expr
                | equal_expr '#=' rel_expr
                ;

rel_expr        : shift_expr
                | rel_expr '<' shift_expr
                | rel_expr '>' shift_expr
                | rel_expr '<=' shift_expr
                | rel_expr '>=' shift_expr
                ;

shift_expr      : add_expr
                | shift_expr '<<' add_expr
                | shift_expr '>>' add_expr
                ;

add_expr        : mult_expr
                | add_expr '+' mult_expr
                | add_expr '-' mult_expr
                ;

mult_expr       : pow_expr
                | mult_expr '*' pow_expr
                | mult_expr '/' pow_expr
                | mult_expr '%' pow_expr
                ;

// Note that '**' is right-associative
pow_expr        : cvt_expr
                | cvt_expr '**' pow_expr
                ;

cvt_expr        : unary_expr
                | cvt_expr '=>' unary_expr
                ;

unary_expr      : '~' unary_expr
                | '!' unary_expr
                | '-' unary_expr
                | '@' unary_expr
                | '@@' unary_expr
                | '??' unary_expr
                | '&' qual_name                 // Only for internal OADL use
                | term
                ;

indices         : index
                | indices ',' index
                ;

index           : expr
                | opt_expr ':' opt_expr
                ;

qual_name       : IDENTIFIER
                | IDENTIFIER '::' IDENTIFIER
                | '::' IDENTIFIER
                ;

term            : qual_name
                | 'public' '::' IDENTIFIER
                | '(' expr ')'
                | '(' 'proc' ')'                // ID of current proc
                | '{' exprs '}'                 // Inline List decl
                | '<<<' exprs '>>>'             // Inline Dict decl
                | '[' exprs ']'                 // Inline packed array decl
                | '[' iterator ']'
                | STRING
                | LSTRING
                | INTCON
                | FLOATCON
                | CHARCON
                | LCHARCON
                | MATCH_ARG
                | MATCH_COUNT
                | LOOPBASE
                | 'new' qual_name               // The create args are parsed...
                | 'new' '(' expr ')'            // ... by the call syntax below
                | 'proc' no_name_proc
                | 'proc' STRING no_name_proc
                | 'operator' operator
                | '`' operator
                | '`' IDENTIFIER                // Same as public::IDENTIFIER
                | term '(' exprs ')'            // The call syntax
                | term '[' '*' ']'              // For "Array[*]"
                | term '#( exprs ')'
                | term '.' public
                | term '[' indices ']'
                | term '#[' expr ']'
                | term '{' obj_props '}'        // For new and static objects
                | 'foreach' '(' expr ')' '{' expr '}'
                ;

iterator        : opt_expr ':' opt_expr
                | opt_expr ':' opt_expr ':' opt_expr
                ;

opt_expr        : /* NOTHING */
                | expr
                ;

public          : IDENTIFIER
                | '(' expr ')'
                | 'operator' operator
                | '`' operator
                | '`' IDENTIFIER
                ;

The no_name_proc and operator productions may be found in the OADL Program Syntax chapter.

Since procedures, classes, and objects are first-class types in OADL, they may also exist in expressions. For example, a program can put an unnamed procedure into an array:

a[3] = proc () {say("a[3]!\n");}

There is a subtle but significant difference between the static_obj and new_obj expression types. A static_obj creates a single, static object whose value persists over the entire duration of program execution. A new_obj creates a new dynamic object which will be deleted once all references to it are removed.

For more discussions of classes and objects, please see the Classes chapter.


10. Procedures

Overview

There are three scopes of OADL procedures: global procedures, class-private procedures, and class-public procedures (sometimes referred to as "methods"). Global procedures are declared outside the scope of any class declaration, and may be called by any other procedure. Class-private procedures are only directly visible from within a class definition. Public procedures are visible globally; however, they have special semantics with respect to object-oriented programming.

Procedures are constant; that is, given a declaration of a procedure, the instructions it executes never change. Variables may hold the address of a procedure, effectively giving a kind of "dynamic procedure".

Procedures are declared with the proc keyword. They may be defined at the same time, or they may be merely declared, with definition following later. This facilitates both top-down programming and circular recursion. Here is an example of a declaration without a definition:

proc foo;

If, at runtime, no definition of foo has been found, then a runtime error will be produced if a call to foo() is attempted.

The definition of a procedure consists of four parts: the name of the procedure, the arguments it takes, the return type, and the instructions comprising it. Any of these may be omitted under certain circumstances. Here is an example which has all four parts:

/* Procedure named fact, with one argument, n. Only works with Ints */
proc fact(n : Int) : Int
{
    /* Here come the instructions! */
    if (n > 1) {
        var next : Int = n - 1;
        return n * fact( next );
    }
    else {
        return 1;
    }
}

As this example indicates, procedures may return values, and they may call themselves recursively.

The name of the procedure may only be omitted when the procedure is a component of a constant expression. In this case, the name must be omitted. For example, the following statement assigns an unnamed procedure to a variable:

a = proc() {say( "Hi, mom!\n" );}

By default, procedures have no return type, and may return values of any type:

    proc het(t)
    {
        if (t == String) return "string";
        else if (t == Int) return 1;
        else return nil;
    }

    het(String)
string

    het(Int)
1

A return type may be specified. If so, the return value will be converted to the specified return type. If a conversion is not possible, a TypeCheck error will be thrown:

    proc ret(val) : Int
    {
        return val;
    }

    ret(1.4)
1

    ret("two")
Illegal type

The normal named procedure declaration is semantically identical with a constant initialized to an unnamed procedure; that is, the following two statements result in the same behavior:

proc a() {say( "Proc a\n" );}
const a = proc() {say( "Proc a\n" );}

The statements encountered inside a procedure are one of four things:

In order to call a procedure, merely place the name of the procedure (or an expression evaluating to a Proc object) followed by the (possibly empty) list of arguments enclosed in parentheses and separated by commas, thus:

foo( a, b, c );

The argument list is required, even if empty, since OADL won't recognize a statement like this in the body of a procedure:

foo;

Arguments

As in most languages, OADL procedures have arguments. To declare named arguments to a procedure, merely list them between the parentheses after the procedure name, thus:

proc foo( a, b, c )
{
}

It is valid to have a procedure which takes NO named arguments; for example:

proc foo()
{
}

The list of named arguments is specified only in the definition of the procedure, not in a declaration. That is, this declaration is illegal:

proc foo( a, b, c );

In OADL, procedure arguments are by-value. Note, however, that for dynamic values such as objects, strings, and arrays, it is the reference to the value that is passed. This means that the content of the composite value can be changed by the procedure. For example:

    proc modif(a) { a[0] = 'H'; }

    Name = @ "Sam";
    modif(Name);

    // The first character was modified by the call to modif
    Name
Ham

In contrast, the following program shows that the argument itself can not be modified:

    proc modif( a ) { a = "Ham"; }

    Name = "Sam";
    modif(Name);

    // Name will still be "Sam" since arguments are passed by-value
    Name
Sam

Procedure argument names hide anything with the same name outside the procedure; this can lead to difficult-to-find bugs. In this example, the three numbers "3 4 3" are printed in-order, since the modification of the argument named "num" in procedure foo won't affect the global variable of the same name:

    num = 3

    proc foo(num)
    {
        num = 4;
        say(num, '\n');
    }

    num
3

    foo(3)
4

    // num is still 3, since the global was hidden by foo's proc args
    num
3

The nargs() and arg() intrinsic procedures may be used to facilitate both argument checking as well as variable-length argument lists. Note that these are part of the oadl namespace. The nargs() intrinsic returns the number of arguments passed to the current procedure. The arg() intrinsic returns the value of the nth argument. As an example, the following procedure adds together a list of numbers:

proc addNums()
{
    var
        i, n, result;

    n = oadl::nargs();
    result = 0;
    for (i = 0; i < n; i++ ) {
        result += oadl::arg(i);
    }
    return result;
}

Similarly, the argvec() intrinsic procedure creates a new List containing the complete list of arguments. This is particularly useful if one needs to handle a variable number of input arguments, and also needs to pass that same variable number of input arguments to another procedure. This can be accomplished by using the #() array call syntax. This form of procedure call takes only one argument, a List of arguments to be extracted and passed as the arguments to the given procedure. Assuming the same addNums() procedure as the previous example, this example prints the list of arguments first then prints their sum:

proc printAddNums()
{
    var a = oadl::argvec();
    "Sum of ", a, " is ", addNums#(a), '\n';
}

The array call must have exactly one argument - the List containing the procedure arguments.

With either named or unnamed arguments, attempts to access an argument that was not actually passed to the procedure results in an ArgCount exception.

Local Variables and Constants

OADL procedures may also have local variables and constants. The most common are temporary locations used as intermediate values in calculations - their value is undefined as soon as the procedure exits. To declare local variables and constants, use the var or const keyword inside a procedure:

proc foo()
{
    const answer = 42;
    var a;
}

Local variables have no defined value until they're initialized. As a convenience, a local variable may be initialized with an expression, thus:

proc foo(a,i)
{
    var b = a[i];
}

Just like procedure arguments, local variables hide global items of the same name, leading to the same difficulties. It is an error to declare a local variable of the same name as one of the procedure arguments. The compiler typically produces a warning if a local variable name hides an outer declaration.

Local variables remain visible until the end of the block in which they were defined; for example, the following program is illegal since the variable b does not exist after the closing brace of the if statement:

proc foo()
{
    if (true) {
        var b;
        b = 3;
    }
    say(b);
}

Local constants and variables need not be the first statement in the block; the following is a legal code fragment:

proc foo()
{
    for (var i = 0; i < 10; i++) {
        say(i, '\n');
    }
}

OADL procedures may also have static local variables. The contents of these variables persist between procedure invocations. They are declared using the static keyword:

proc foo(n)
{
    static prevN = 0;
    say("Delta = ", n - prevN, "\n");
    prevN = n;
}

Variable Assignments

To change the value of a variable, an assignment statement must be executed. There are several kinds of assignment statements. First, simple assignment is of the form:

variable = value;

The variable may be a global variable, a local variable, an argument, or a public or private variable in the current class. In any case, the old value is discarded, and the new value put in its place. The value may be any expression, constant or otherwise.

Elements of arrays, strings, and dictionaries may be replaced using the syntax:

variable[index_list] = value;

Again, this discards the selected element (or elements, if index_list contains array-valued expressions) and replaces it with the given value. OADL arrays are indexed from 0, so in an N-element array, the maximum index is N-1. If the element at a given index is itself an array or string, double indexing is possible, and so on. For example:

    Table = @@ { "Mary", "Sam" }
    Table[1][0] = 'P'
    Table
Mary Pam

See the discussion in the Expressions chapter about the @ and @@ operators.

When dynamic objects (classes, objects, strings, arrays, and dictionaries) are used as the right-hand-side of a scalar assignment statement, only a pointer, or "handle", for the object is assigned. That is, it is possible to have more than one variable referring to a dynamic object. For example:

    Str1 = @ "Fred"
    Str2 = Str1
    Str2[0] = 'D'
    // The contents of Str1 were modified since Str2 and Str1
    // refer to the same string
    Str1
Dred

The exception to this rule is when an inline array or list is assigned. Inline arrays are created at runtime and are remade anew every time the statement containing the inline array is executed. For example:

    var val
    for (var i = 0; i < 3; i++) {
        val = { 1, 2, 3 };
        "{", val[0];
        val[0] = i;
        " ", val[0], "}\n";
    }
{1 0}
{1 1}
{1 2}

The first element in each line is 1, since it actually a reference to a new copy of the list {1, 2, 3} that is placed in the variable val.

Finally, public variables in other objects may be assigned to using the "dot" operator . or the with statement. See the Classes chapter for a full explanation:

    class foo {
        public var ack = 3;
    }

    foo bar()

    bar.ack = 4

As a convenience, OADL allows "shortcut" assignments, where the left-hand side is modified arithmetically by the right-hand side. The complete list of shortcut assignments is:

+= -= *= /= %=
&= |= ^= <<= >>=
++ --

For example, a program might increment a variable by one by stating i = i + 1;. It is equivalent to state: i += 1; or even i++;.

This is very useful if the left hand side has complicated addressing going on:

foo.bar[3].ack[9] += 5;

Shortcut assignments generally execute more efficiently than the equivalent longhand assignment statement. Additionally, portions of the left-hand side that have side effects are only executed once with a shortcut assignment:

    proc foo() {"Foo!\n"; return 0;}
    a = [1,2,3]
    a[foo()] = a[foo()] + 10
Foo!
Foo!
    a[foo()] += 10
Foo!

The ++ and -- shortcut assignments do not accept a right-hand side - it is implicitly assumed to be 1. Unlike C and C++, there is no pre-increment or pre-decrement equivalent, nor can these shortcut assignments be used inside expressions; they are merely shorthand for += 1 and -= 1, respectively.

Return Value

All OADL procedures return a value, whether or not an explicit return statement is included in them. If no return statement is given, the procedure returns the Null object, nil. To return a different value, execute the return statement with the desired return value:

return value

The value can be any expression (even nil). The procedure is immediately exited, and the calling context resumes execution. As discussed above, if the procedure has a specified return type, the return value will be converted to that type if possible. If not possible, a TypeCheck exception will be thrown.

If statement

The if statement executes the associated statement if and only if its condition is true. The syntax of the if statement is:

if (cond) statement

The statement may either be a semicolon-terminated single statement, or it may be multiple statements surrounded by { and }. The condition can be any expression. See the list of logically FALSE values in the Expressions chapter for the kind of zero values which are considered false. If you wish to have a different statement executed when a condition is false than when it is true, use the else clause of the if statement:

if (cond) statement else statement

Again, compount statements can be formed using { and }. An ambiguity potentially exists with nested if-else statements; in the construct:

if (cond1)
    if (cond2)
        statement1
    else
        statement2

...does the else belong to if (cond1) or if (cond2)? OADL resolves this ambiguity by binding the else clause to the immediately preceeding if statement, a common practice in programming languages.

Switch Statement

The switch statement evaluates an expression against multiple possible values, executing statements associated with the value which matches. The syntax of the switch statement is:

switch (expr) { cases }

The expr is any expression, and the cases are of the form:

case exprlist : statements

or of the form:

default : statements

The exprlist is a list of comma-separated constant expressions; the statements are a list of semicolon-terminated statements.

The expression in the switch is only evaluated once; this is only really important if there are side effects (for example, a procedure call which sets global state).

Arrays and strings, may be freely used in switch statements, and operate as might be expected:

    a = "Hello"
    switch (a) {
    case "World" : "Not reached\n";
    case "Hello" : "Hello, world!\n";
    }
Hello, world!

    a = [4,5,6];
    switch (a) {
    case [1,2,3] : "123\n";
    case [4,5,6] : "456\n";
    }
456

Unlike C and C++, multiple cases may be specified in a single case statement; for example

    switch (i) {
    case 1, 3, 5, 7, 9 : "i is odd\n";
    case 0, 2, 4, 6, 8 : "i is even\n";
    }

Also unlike C and C++ switch statements, "fallthrough" case statements can not occur, and therefore break terminations of cases are unnecessary. This allows a break in a switch statement to terminate loop execution.

Match Statement

OADL includes a powerful string pattern matching statement. The syntax is very similar to that of the switch statement:

match (expr) { cases }

The expr is any (string-valued) expression and cases are syntactically the same as switch-statement cases. The cases themselves must be strings which contain a Perl-compatible regular expression (see http://perldoc.perl.org/perlre.html for a detailed description of Perl-compatible regular expression syntax).

Multiple cases might contain a pattern which matches the expr. The statements which go with the first matching pattern in the match statement are the ones which will be executed.

Inside each pattern case, there are special variables which may be consulted to extract information from the match. These are the match count ?# and the match substrings ?N (where N is a positive integer).

For example:

    s ="Did we win?"

    match (s) {
    case "(w.n)" : "", ?1, "!\n";
    case "win" :   "We should not be here!\n";
    default :      "No match.\n";
    }
win!

The example printed "win!" since the first match will be the one executed. The implicit print statement will print the word "win" since the ?1 match substring matches the first substring matched in the pattern (which happens to be "win").

While Statement

The while statement is the simplest loop iterator in OADL. The syntax of the while statement is:

while( condition ) statement

Just like if/else, the statement may be a compound statement surrounded by { and }. The boolean true-or-false sense of the condition is evaluated exactly like an if statement, but it is done once at the start of each loop iteration. If it is necessary to terminate the loop early, use the break statement:

break

The break statement is usually contained in an if statement:

if (cond) break;

To skip the rest of the instructions in a loop, but go on with subsequent iterations, use the continue statement:

continue

Again, this is usually contained in an if statement:

if (cond) continue;

For Statement

The for statement is nearly identical to the C/C++ equivalent. It has a group of comma-separated initializations; a termination condition; and a group of comma-separated increment expressions. Any or all of these may be empty. If the condition is omitted, then the loop will never terminate (unless a break or return statement is executed inside the loop):

for (init; condition; incr) statement

The statement, again, can be multiple statements inside { and }. The condition follows the same rules as the if/else statement. Just like the while statement, break and continue alter the iteration of the loop. The incr statements will be executed if a continue is executed.

Do/While Statement

OADL provides the do/while statement to provide end-of-loop-structured loops. The syntax is:

do statement while (condition)

Multiple statements may be grouped with { and }. The condition follows the same rules as the if/else condition. The break and continue statements are allowed inside the do statement. A do/while loop always executes at least one time since the condition is evaluated after all of the statements.

Forall Statement

The forall statement allows an OADL programmer to iterate over all of the elements of an array, dictionary, or object. The syntax is very simple:

forall (expr) statement

However, further explanation of the expr is required. The expr must be either a simple indexing expression or an object public reference expression with a name enclosed in parentheses. The array indexes or public reference target are variable names that will be defined inside the forall statement. Here are a couple of examples:

    arr=[1,2,3]
    forall (arr[i]) {
        "arr[",i,"] = ", arr[i], '\n';
    }
arr[0] = 1
arr[1] = 2
arr[2] = 3

    class cls {public var a = 3, b = 4;}
    cls obj()
    forall (obj.(i)) {
        "obj.", i, " = ", obj.(i), '\n';
    }
obj.parent = cls
obj.a = 3
obj.b = 4

The loop will be executed for each element in the target array/dict/object. At each iteration, the index variable will be set to the next valid index. An unused slot in a dictionary will have both a key and a value of nil.

The order of iteration of the elements of objects and dictionaries is not deterministic (it may vary from compile-to-compile, and may even vary depending on the contents of the dictionary).

Assert Statement

OADL provides an assert statement that will throw the AssertCheck exception if the given expression does not evaluate to a logically-TRUE value:

assert expression

With Statement

In keeping with OADL's focus on simple management of object instances and their public data, OADL provides a with statement that allows the programmer to dynamically redefine public variables in an object instance:

with (obj) { assignments }

The obj must be an expression which evaluates to an object. The assignments are a list of items of the form:

name = expr

Each name must be the name of a public variable. There is no restriction on the type of each expr. These assignments are not separated by semicolons - this syntax echoes that of object creation. The completion operator {} will be called after all the public variable assignments are executed. Example:

// Same as:
//     obj.foo = 3;
//     obj.bar = 4;
//     obj.`{}(true, public::foo, public::bar);
with (obj) {
    foo = 3
    bar = 4
}

Implicit Print Statement

Since text output is such a frequent operation in console-oriented programs, OADL offers a short-cut print statement that eliminates the need to explicitly call the say external procedure. Any statement that begins with a string constant is considered an implicit print statement. Multiple items can be included in a print statement by separating them with commas:

// Same as say("Hello ", "world!\n");
"Hello ", "world!\n";

Exception Handling

OADL implements exception handling similarly to other languages such as Java and C++, with try / catch statements:

try statement catch (names) { statements }

OADL also implements throw statements:

throw expression;

Unlike those languages, there can only be one catch clause (since OADL variables are untyped). There are several predefined exceptions that OADL uses internally; these are:

Exception Meaning
TypeCheck An attempt was made to use an illegal type (for example, arithmetic on a string
RangeCheck An argument is out of range (for example, divide by zero)
ArgCheck An incorrect argument was specified (for example, with the intrinsic arg()
AccessCheck An attempt was made to assign a value to an element of a constant array, string, or class.
AssertCheck An assertion failed (this can also happen if hijinx have been performed on class method values)
StackCheck An internal stack overflow or underflow occurred
ExternCheck An attempt was made to use an undefined extern
ShapeCheck An attempt was made to use incompatible array shapes
InterruptCheck An interrupt occurred (for example, the user typed <ctrl>+C on the console)
FormatCheck At runtime, an invalid format string was used
UnboundedCheck An attempt was made to expand an unbounded iterator
EndOfFile An attempt was made read past the end of a File
RegexCheck At runtime, an invalid regular expression used
IoCheck An I/O error (other than end-of-file) occurred
MatchCheck An attempt was made to use match arguments outside of a match statement
ProcCheck An attempt was made to access an undefined procedure
ExceptCheck An unrecognized exception was thrown (typically an internal-only error)
NameCheck An attempt was made to convert an undefined name
RedefinedCheck An attempt was made to redefine an existing class
UTF8Check An illegal UTF-8 byte was read from a text-mode input file

Either one argument or three arguments must be named in the catch statement. If one argument is named in the catch statement, it will contain the thrown exception. If three arguments are named in the catch statement, the first argument is the thrown statement, the second argument is the OADL source file name from which the exception was thrown, and the third argument is the OADL source line number from which the exception was thrown. The file name and line number may not be valid if the OADL program was not compiled with debugging information.

Here is an example that shows catching the RangeCheck thrown by a divide-by-zero. This example also shows how exceptions may be passed back up the stack of exception handlers by themselves throwing an exception.

var i = 0, j;
try {
    j = 1 / i;
}
catch (n) {
    if (n == oadl::RangeCheck) {
        "Caught divide-by-zero\n";
    }
    else {
        throw n;
    }
}

Exceptions need not be of type Exception; any type of expression may be thrown. For example:

    try {
        throw "baseball";
        "Should not get here\n";
    }
    catch(n) {
        "Caught ", n, "\n";
    }
Caught baseball

The break, continue, and return statements execute as expected inside a catch clause:

    for (var i = 0; i < 3; i++) {
        try {
            assert i != 1;
        }
        catch() {
            continue;
        }
        "i = ", i, '\n';
    }
i = 0
i = 2

If a thrown exception is not caught, OADL will print a helpful error message and either continue (if the OADL desk calculator is being used) or exit (if a standalone OADL program is being run):

    throw oadl::TypeCheck
Illegal type
    throw "baseball"
Unhandled exception

Procedure Statement Syntax

The following is the complete syntax of statements allowed inside a procedure.

proc_body       : '{' stmts '}'
                ;

stmts           : /* NOTHING */
                | stmt stmts
                ;

stmt            : assign ';'            | call ';'
                | ifstmt                | whilestmt
                | dostmt ';'            | forstmt
                | forallstmt            | switchstmt
                | matchstmt             | withstmt
                | returnstmt ';'        | assertstmt ';'
                | trystmt               | throwstmt ';'
                | breakstmt ';'         | continuestmt ';'
                | var_decl              | const_decl
                | using                 | printstmt ';'
                ;

assign          : lhs '=' expr          | lhs '+=' expr
                | lhs '-=' expr         | lhs '*=' expr
                | lhs '/=' expr         | lhs '%=' expr
                | lhs '&=' expr         | lhs '|=' expr
                | lhs '^=' expr         | lhs '<<=' expr
                | lhs '>>=' expr        | lhs '++'
                | lhs '--'
                ;

call            : lhs '(' exprs ')'
                | lhs '#(' expr ')'
                ;

lhs             : qual_name
                | lhs '.' IDENTIFIER
                | lhs '.' '(' expr ')'
                | lhs '[' indices ']'
                | lhs '#[' expr ']'
                | '(' lhs ')'
                ;

ifstmt          : 'if' '(' expr ')' body
                | 'if' '(' expr ')' body 'else' body
                ;

whilestmt       : 'while' '(' expr ')' body
                ;

dostmt          : 'do' body 'while' '(' expr ')'
                ;

forstmt         : 'for' '(' alst ';' limit ';' alst ')' body
                ;

forallstmt      : 'forall' '(' expr ')' body
                ;

alst            : /* NOTHING */
                | assign_list
                ;

assign_list     : one_assign
                | assign_list ',' one_assign
                ;

one_assign      : assign
                | lhs
                | 'var' IDENTIFIER '=' expr
                | 'var' IDENTIFIER ':' type '=' expr
                | 'static' IDENTIFIER '=' expr
                | 'static' IDENTIFIER ':' type '=' expr
                ;

limit           : /* NOTHING */
                | expr
                ;

switchstmt      : 'switch' '(' expr ')' '{' cases '}'
                ;

matchstmt       : 'match' '(' expr ')' '{' cases '}'
                ;

cases           : /* NOTHING */
                | cases onecase
                ;

onecase         : 'case' exprlist ':' stmts
                | 'default' ':' stmts
                ;

returnstmt      : 'return' expr
                | 'return'
                ;

assertstmt      : 'assert' expr
                ;

withstmt        : 'with' '(' expr ')' '{' assignments '}'
                ;

assignments     : /* NOTHING */
                | assignments IDENTIFIER '=' expr
                ;

trystmt         : 'try' body 'catch' '(' names ')' proc_body
                ;

throwstmt       : 'throw' expr
                ;

breakstmt       : 'break'
                ;

continuestmt    : 'continue'
                ;

printstmt       : STRING
                | STRING ',' exprs
                | LSTRING
                | LSTRING ',' exprs
                ;

body            : stmt
                | '{' stmts '}'
                ;

The expr and exprs productions are defined in the Expressions chapter.


11. Intrinsic Procedures and Methods

Intrinsic Procedures

An OADL intrinsic procedure is one which is built-in to the OADL machine. It is not possible to place the address of an intrinsic procedure in a variable. Additionally, the number of arguments to intrinsic procedures is generally checked at compile-time. All OADL intrinsic procedures except for typeof are found in the oadl namespace.

Procedure Argument Intrinsic Procedures

These intrinsics deal with procedure arguments:

arg(n)
Returns the value of argument number n
nargs()
Returns the number of arguments passed to the current procedure.
argvec()
Returns a List containing all of the arguments to the current procedure.


Machine Execution Intrinsic Procedures

These intrinsics modify the execution of the OADL machine:

halt()
Immediately halts execution of the OADL virtual machine.
setjmp(arr)
Sets the target for a later longjmp() non-local jump
longjmp(arr, val)
Does a non-local jump to an enclosing procedure location where setjmp() was called
save(filename)
Saves the complete OADL state to a file
restore(filename)
Restores the complete OADL state from a file
restart()
Restarts the entire OADL machine


Memory Subsystem Intrinsic Procedures

These intrinsics manage various aspects of the dynamic memory subsystem:

gc()
Immediately performs a garbage collection cycle
protect(val)
Returns a new read-only copy of a value
readonly(val)
readonly(obj, pub)
Checks to see if a value is read-only
deleted(obj)
Returns true if the given obj has been marked for deletion
perm(val)
Creates a "permanent" copy of the given value
transient(val)
Check whether the given value is located in the default, dynamic memory pool


Type Checking Intrinsic Procedures

These intrinsics return information about the types of their arguments:

typeof(val)
Returns the type of a value; for example, Int, Null, Float, etc. Unlike all other intrinsic procedures, typeof() is found in the global namespace.
typecheck(typ, val)
Checks to ensure that the type of val is derived from typ. If not, a TypeCheck exception is thrown. Returns true if the type matches.
is_a(obj,cls)
Returns true if the class cls is a parent of the given object obj, and false otherwise. Same as the ?= comparison operator.

Input / Output Intrinsic Procedures

These procedures are all found in the global namespace. See the chapter on Input / Output for more information about them.

getchar()
getchar(file)
Get a single character of input
print(fmtstring, arg, ...)
print(file, fmtstring, arg, ...)
Print a formatted set of values
putchar(ch)
putchar(file, ch)
Puts a single character to a file
ungetc(ch)
ungetc(file, ch)
Returns a single character to a file's input buffer
read(fmtstring, typ, ...)
read(file, fmtstring, typ, ...)
read(string, fmtstring, typ, ...)
Reads a formatted set of values
readstr()
readstr(file)
Reads a string from a file
say(arg, arg, ...)
say(file, arg, arg, ...)
Prints a list of values with default formatting rules


Other Intrinsic Procedures

There are a couple of other miscellaneous intrinsic procedures supported by OADL:

matchvec()
Returns a List of all of the match pattern substrings ?1, ?2, etc.
format(fmtstring, arg, ...)
Create a string representation of the arg list given the format specifier fmtstring.

Standard Class Methods

Several methods are predefined for all OADL classes. They may be overridden by the OADL programmer. See the chapter on Classes for a detailed description of these methods:

obj.create()
Called when a new static or dynamic Object is created
obj.destroy()
Called if an object is to be destroyed during dynamic memory reclamation
obj.operator {}(args)
Object completion operator


Intrinsic Methods

Intrinsic methods are provided by OADL to perform a broad range of operations. Note that, unlike programmer-defined methods, OADL intrinsic methods can operate on values with types other than Object.

Type Query Intrinsic Methods

arr.arrbase()
Returns the base type of arr (for example, Char, Int, etc.) or Array if arr is a heterogeneous List or Array.
val.isarray()
Returns true if val is an array of any kind (List, String, PackInt, etc.) and false otherwise.
val.ischar()
Returns true if val is a scalar character of any kind (Char or WideChar) and false otherwise.
val.isfloat()
Returns true if val is a floating point scalar of any kind (Half, Float, or Double) and false otherwise.
val.isinteger()
Returns true if val is an integral scalar of any kind (Byte, Ubyte, Short, Ushort, Int, Uint, Long, or Ulong) and false otherwise.
val.isnumeric()
Returns true if val is a numeric scalar of any kind (Byte, Ubyte, Short, Ushort, Int, Uint, Long, Ulong, Half, Float, or Double) and false otherwise.
val.isstring()
Returns true if val is string of any kind (String or WideString) and false otherwise.
val.length()
Returns the number of elements along the first dimesion of an array, or the number of public properties of an object, or the number of currently defined key/value pairs in a dictionary.
typ.maxval()
Returns the maximum possible value of the given typ (Float, Int, etc.)
typ.minval()
Returns the minimum possible value of the given typ (Float, Int, etc.)
typ.packtype()
Returns the packed array type that corresponds to the scalar type typ (for example, Int.packtype() returns PackInt)
val0.promote(val1)
Returns the entry in the type promotion table from the Expressions chapter that corresponds to val0 and val1. If val0 or val1 is an OADL Type they are used directly. If they are not an OADL TYpe, their base types are used as the indexes into the table.
val.rank()
Returns the rank of val - the number of dimensions of the given array. The rank of a scalar is 0.
val.shape()
Returns a PackInt array which is the multi-dimensional shape of val. The shape of a scalar is the empty packed integer array 0->iterate()
val.sizeof()
Returns the total number of elements of array or dictionary val. The sizeof a scalar is 1.

Dynamic Value Management Intrinsic Methods

val.copy()
Creates a copy of the given array, string, or object. The elements of an array are NOT recursively copied. This is identical in effect to the @ operator. The new copy is neither permanent nor read-only regardless of whether val is permanent or read-only.
val.deepcopy()
Creates a copy of the given array, string, or object. The elements of an array ARE recursively copied. This is identical in effect to the @@ operator. The new copy is neither permanent nor read-only regardless of whether val is permanent or read-only.
val.readonly()
obj.readonly(pub)
The zero-argument form returns whether the given object or array value val is read-only. The one-argument form returns whether the public property pub of Object obj is read-only. A TypeCheck exception is thrown if val, obj, or pub is not of an appropriate type.
val.transient()
Returns true if the given val is located in dynamically maintained memory subject to garbage collection, and false otherwise. A TypeCheck exception is thrown if val is not of an appropriate type.

File Input / Output Intrinsic Methods

See the chapter on Input / Output for more information about these intrinsic methods.

file.binary()
Query whether a file was opened in binary-mode
file.clearerr()
Clear a file's error indicator
file.close()
file.close(disp)
Close a file
file.feof()
Query a file's end-of-file indicator
file.ferror()
Query a file's error indicator
file.fflush()
Flush pending output
file.fseek(offs, whence)
Change a file's read/write position
file.ftell()
Query a file's read/write position
file.getchar()
Read a single byte from a file
file.getswab()
Query a file's byte-swap indicator
file.ispipe()
Query whether a file is a pipe
file.print(fmtstr, arg, ...)
Print formatted values
file.putchar()
Put a byte into a file
file.read(typ, typ, ...)
file.read(fmtstr, typ, typ, ...)
string.read(fmtstr, typ, typ, ...)
Read values from a file
file.readonly()
Query whether a file was opened read-only
file.readstr()
Read a string from a file
file.rewind()
Move a file's read/write position to the beginning
file.say(arg, arg, ...)
Print values with default formats
file.setswab(bSwab)
Set a file's byte-swap flag
file.ungetc()
Push back a byte to a file's input stream
file.write(val, val, ...)
Write binary values to a file

Mathematical Intrinsic Methods

val.abs()
Computes the absolute value of val
val.clamp(lower, upper)
Compares val to the given lower and upper bounds, clamping it to those bounds and returning the new value.
val.fix2flt(typ)
Convert a value or array of values from 8- or 16-bit signed or unsigned integers to the specified floating point type
val.flt2fix(typ)
The inverse of fix2flt(). Convert a value or array of values from floating point to a specified 8- or 16-bit signed or unsigned fixed-point number.
val.lerp(lower, upper)
Linearly interpolates or extrapolates from given lower and upper bounds. If val is less than zero, it extrapolates below lower. If val is greater than one, it extrapolates above upper. Otherwise, it interpolates between lower and upper, returning the interpolated values. The interpolator val must be of a floating-point type. Appropriate type conversions are performed on the interpolants lower and upper.
val0.max(val1, val2, ...)
Computes the maximum of a set of values. Appropriate type conversions are performed between the values.
val0.min(val1, val2, ...)
Computes the minimum of a set of values. Appropriate type conversions are performed between the values.
val0.satadd(val1, lower, upper)
Computes val0 plus val1 and clamps the result to the given lower and upper bounds. Appropriate type conversions are performed between the values and the bounds.
val0.satsub(val1, lower, upper)
Computes val0 minus val1 and clamps the result to the given lower and upper bounds. Appropriate type conversions are performed between the values and the bounds.
val.signum()
Computes the signum of val, which is defined as -1 if val is less than minus zero, 1 if val is greater than zero, or 0 if val is equal to zero. The return type is the same type as that of val.

Array Manipulation Intrinsic Methods

Many of these methods were inspired by the programming language APL, which is an innovative interactive language developed in the 1960s to perform many array calculations and general-purpose computing tasks. There are a few conventions that should be noted:

Unlike APL, English names of the various array operations are used for the array intrinsic methods.

arr.accum(op)
arr.accum(op, axis)
Accumulate results of an operation across an axis. Similar to APL op \ arr and op \[axis] arr.
arr0.arrcmp(arr1)
Lexicographically compares two arrays or strings, returning -1, 0, or 1
a.concat(b, c, ...)
Concatenates several values, returning a new array or string. Exactly the same as the ## operator.
val0.decode(val1)
Convert non-uniform number bases, evaluate polynomials. Similar to APL val0 val1
arr.disclose()
Remove a level of nesting from an enclosure. Similar to APL val
arr.drop(num)
arr.drop(num, axis)
Similar to APL num arr and num ↓[axis] arr
val.enclose()
val.enclose(axis)
Enclose a value to make a scalar. Similar to APL val or ⊂[axis] val.
val0.encode(val1)
Similar to APL val0 val1
arr.flatten()
Completely flattens an array, including any nested elements
vec.increment(shp)
No direct APL comparison. Given a vector vec of the same length as vector shp (which is the shape of a multidimensional array), compute what the next vector index in row-major order would be. Returns nil if the next multi-dimensional index would step past the array bounds. This is useful with the "flattened" indexing operator, especially in combination with the arr.stride() intrinsic method:
    arr = "abcdef".reshape(2,3)
    arr
abc
def
    shp = arr.shape()
    idx = (0).reshape(arr.rank()) // Start with [0,0]
    strd = arr.stride()           // Needed to compute offset
    do {
        var n = idx.inner(`+,`*,strd); // Sum of products of idx and stride
        "arr[", idx, "] == ", arr#[n], '\n'; // Note: flattened index operator
        idx = idx.increment(shp); // Increment to next index in shape
    } while (idx != nil)
arr[0 0] == a
arr[0 1] == b
arr[0 2] == c
arr[1 0] == d
arr[1 1] == e
arr[1 2] == f
arr0.inner(op0, op1, arr1)
Similar to APL arr0 op0 . op1 arr1. The inner product is probably the most difficult operation to fully explain. In the simple case of two vectors, it is equivalent to:

(vec0 op1 vec1).reduce(op0)

In APL notation, the operation is defined as:

op0/¨(⊂[⍴⍴arr0]arr0)∘.op1⊂[1]arr1

Anybody who finds this definition helpful is already an APL expert and does not need the inner product explained further. However, a more readable algorithm is:
    // Enclose arr0 along the last axis
    var encl0 = arr0.enclose(-1);

    // Enclose arr1 along the first axis
    var encl1 = arr1.enclose(0);

    // Compute outer product of enclosed arrays with second operator
    var out = encl0.outer(op1,encl1);

    // For each element in the outer product, reduce it by the first operator
    var result = new Array(out.shape());
    forall (out#[i]) result#[i] = out#[i].disclose().reduce(op0);

    // Pack the result
    result = result.pack();

    // Convert single-element vector to scalar
    if (result.sizeof() == 1) result = result#[0];
vec.intersect(arr)
Similar to APL vec arr
val.iterate()
Creates a new multi-dimensional PackInt array with a shape of val, initialized to the numbers from 0 to n-1 inclusive, where n is the product of all of the elements of val. Note that val may also be a scalar; in this case, care must be taken to prevent OADL from interpreting the dot operator as part of a floating point constant. The normal convention is to place parentheses around the scalar in this case; e.g. (3).iterate().
arr0.laminate(arr1)
arr0.laminate(arr1, axis)
Similar to APL arr0 , arr1 and arr0 ,[axis] arr1
val.member(arr)
Similar to APL val arr
arr0.outer(op, arr1)
Similar to APL arr0 ∘. op arr1. The outer product takes corresponding elements from arr0 and arr1 and applies op to them. For vectors, this produces an operator table:
    x = [2,3,4]
    y = [1,2,3,4]
    x.outer(`*, y)
2 4  6  8
3 6  9 12
4 8 12 16

More generally, the destination array has a shape which is the concatenation of the shapes of arr0 and arr1. Each element of the destination array is assigned thus:

result[i00, i01, ..., i10, i11, ...] = arr0[i00, i01, ...] op arr1[i10, i11, ...]

arr.pack()
Attempt to create a new packed copy of the given array. Will always create a new array; however, arrays which are not packable will, obviously, not be packed.
vec.position(val)
Similar to APL vec val
arr.ravel()
arr.ravel(axis)
Similar to APL , arr and ,[axis] arr
arr.reduce(op)
arr.reduce(op, axis)
Similar to APL op / arr and op /[axis] arr. The reduce() method inserts the given operator op between each element of the array, along the specified axis. Note that the result is evaluated right-to-left. This is for consistency with APL. For example:
    arr=(10).iterate()
    arr.reduce(`-)
-5
    // Left-to-right reduce evaluation
    0-1-2-3-4-5-6-7-8-9
-45
    // Right-to-left reduce evaluation - per APL and OADL
    0-(1-(2-(3-(4-(5-(6-(7-(8-9))))))))
-5
arr.replicate(key)
arr.replicate(key, axis)
Similar to APL key / arr and key /[axis] arr and also similar to APL key \ arr and key
val.reshape(d0, d1, ...)
val.reshape(shp)
Creates a reshaped copy of the array or dictionary or scalar val specifying that the new array or dict will have a shape of [d0, d1, ...]. Note that the single-argument form can specificy a single-dimensional PackInt which will be the shape of the new array. Dictionaries may not be made smaller, only larger. Returns the new resized copy of val.
arr.reverse()
arr.reverse(axis)
Similar to APL arr and ⌽[axis] arr. Reverses the order of elements along the given axis. For example:
    a = [2,3].iterate()
    a.reverse()
2 1 0
5 4 3
    a.reverse(0)
3 4 5
0 1 2
arr.rotate(num)
arr.rotate(num, axis)
Similar to APL num arr and num ⌽[axis] arr. Rotates the elements of an array along the given axis by the given number of places. For example:
    arr = [4,4].iterate()
    // Rotate arr by 1 place along last axis
    arr.rotate(1)
 3  0  1  2
 7  4  5  6
11  8  9 10
15 12 13 14
    // Rotate arr by 2 places along last axis
    arr.rotate(2)
 2  3  0  1
 6  7  4  5
10 11  8  9
14 15 12 13
    // Rotate arr by 1 place along first axis
    arr.rotate(1,0)
12 13 14 15
 0  1  2  3
 4  5  6  7
 8  9 10 11
arr.sort()
arr.sort(cmp)
Returns a sorted copy of arr according to the optional cmp proc or operator. If cmp is not specified, operator < is assumed.
arr.stride()
No direct APL comparison. Returns a vector that indicates the number of elements between corresponding elements of the same axis of the source array. This is useful with the "flattened" indexing operator #[].
arr.subr(beg0, end0, beg1, end1, ... )
Returns the multi-dimensional substring or subarray from the given array starting at index beg0, beg1, ... up to and including index end0, end1, .... The data used by this substring or subarray is NOT part of the original string or array; therefore, modifying its contents will not modify the original object. If begn is nil the subrange starts at the beginning of that particular dimension. If endn is nil, then the subrange goes to the end of that particular dimension. If arr is not an array, or if any begn or endn is not an integer (or nil) then the TypeCheck exception is thrown. The subrange is clamped to the actual bounds of the array or string. If endn is less than begn the result is an empty array or string. This is closely related to the use of : in array indices.
arr.take(num)
arr.take(num, axis)
Similar to APL num arr and num ↑[axis] arr
arr.transpose()
arr.transpose(code)
Similar to APL arr and code arr. If no code is given, reverses the order of axes of an array. The code is a vector containing instructions on the order of axes. The length of the code must be the same as the rank of arr. Each element of the code is an axis from arr. If each element of code is unique, it simply specifies a new order for the result axes. If an element in code is repeated, then axes of the array are mapped together and the rank of the result will be less than the original array. Additionally, the maximum axis allowed to be present in code is reduced. If the axes that are mapped together are of different lengths, the shorter axis controls the number of elements for the destination array along that axis. In effect, repeated axes traverse a diagonal of the original array For example:
    arr = [2,3].iterate()
    arr.transpose()
0 3
1 4
2 5
    // 2 slabs of 3 rows by 4 columns
    arr = [2,3,4].iterate()
    arr
 0  1  2  3
 4  5  6  7
 8  9 10 11

12 13 14 15
16 17 18 19
20 21 22 23
    // Orig. axis 0 goes to new axis 1 (old slabs -> new rows)
    // Orig. axis 1 goes to new axis 0 (old rows -> new slabs)
    // Orig. axis 2 goes to new axis 2 (old cols -> new cols; NOP)
    arr.transpose([1,0,2])
 0  1  2  3
12 13 14 15

 4  5  6  7
16 17 18 19

 8  9 10 11
20 21 22 23
    // Orig. axis 0 goes to new axis 1 (old slabs -> new rows)
    // Orig. axis 1 goes to new axis 0 (old rows -> new slabs)
    // Orig. axis 2 ALSO goes to new axis 1 (old cols -> new rows ALSO)
    //    (The shorter of axis 0 and axis 2 is axis 0. The new
    //    columns are taken from arr[0,x,0] and arr[1,x,1])
    arr.transpose([1,0,1])
0 13
4 17
8 21
vec.union(arr)
Similar to APL vec arr
vec.unique()
Similar to APL vec
arr.unpack()
Create a new unpacked copy of the given array, resulting in either a List (for single-dimensional arrays) or an Array (for multi-dimensional arrays).
val.width()
Returns the number of elements along the last dimesion of an array
vec.without(arr)
Similar to APL vec ~ arr


12. External Procedures

External procedures are those which are implemented externally to the OADL machine. They may be called by OADL programs, but they are not an intrinsic part of the OADL machine.

OADL Predefined External Procedures

OADL pre-defines several external procedures. All of the OADL predefined external procedures are found in the oadl namespace.

str2var(str)
Convert a string value to an OADL value. The str can be numeric, one of the predefined OADL constants, or one of the user-defined named constants, procedures, classes, objects, etc. If str is not recognized, a NameCheck exception will be thrown.
wait(millis)
Causes a delay of millis milliseconds to occur. Useful when doing lots of output.
srandom()
srandom(opt-seed)
If the Int opt-seed is specified, sets the random number seed to opt-seed. If not, sets the random number seed to a number based on the current system clock.
random()
Returns a pseudo-random Float from 0.0 to 1.0
objname(obj)
Returns the name of the given obj as provided by the programmer in the original source file, or nil if the name cannot be determined. Note that obj need not be an Object; it can be a Proc, a named constant String, etc. Note, however, that if two named constants have the same value in the source program, objname() will return indeterminate results. Only global symbols will be able to have their objname() determined.
pubname(pub)
Returns the name of the given pub as provided by the programmer in the original source file, or nil if the name cannot be determined. Note that publics exist in a separate namespace from other program objects.
findobj(str)
Returns the global static value (a Class, Object, Proc, or other global named constant) whose name is str, or nil if no object was found.
findpub(str)
Returns the Public whose name is str or nil if it is not found

External Libraries

Non-predefined external functions are linked with the OADL program with the "using extern" statement:

using extern "libfoo"; // Implements foo::bar
extern foo::bar;
proc main()
{
    foo::bar();
}

See the chapter on OADL Implementation Notes for more information on implementing external procedure libraries.

Several standard external libraries are provided with OADL. These include:

libterm
Library for terminal I/O including cursor addressing, etc. Implements namespace term.
libstd
Provides similar functionality to libc / libm from C. Implements namespace std and namespace math.
libsys
Provides access to system-dependent functions such as file system operations and time queries. Implements namespace sys.
libglut
Library for OpenGL utilities, using glut. Implements namespace glut.
libgl1
Library that provides OpenGL ES 1.1 functionality, including emulation on full desktop OpenGL. Implements namespace gl1.
libgl2
Library that provides OpenGL ES 2.0 functionality, including emulation on full desktop OpenGL. Implements namespace gl2.
libo3d
Library that provides 3D graphics functionality. Implements namespace o3d.
libio
Library that provides functionality similar to C/C++ stdio. Implements namespace io.
libadv
stdadv
Libraries that assist the implementation of text adventure games. Implements namespace adv (libadv) and namespace stdadv (stdadv)


13. Input / Output

OADL has a full-featured file input/output feature set. It supports both text-mode and binary-mode I/O, and supports pipes as well if the host operating system supports them. A full set of support routines for handing file positioning and errors is implemented.

Files

The base for OADL I/O is the File, which is an OADL handle to either a file that resides in the host operating system's file system, or a pipe to an external program. OADL defines three Files for program use:

io::Input
The standard input File. It might refer to the input console, or it might refer to a file or pipe if the host operating system supports redirection
io::Output
The standard output File. It might refer to the output console, or it might refer to a file or pipe if the host operating system supports redirection
io::ErrOut
The standard error output File. Again, its actual destination depends on operating system support.

Other files are associated with external file system or program resources via the new syntax:

file = new File(name, mode)

where name is the name of the external file or external program, and mode is the file mode.

Various queries and state management methods are provided for File handles:

file.binary()
Query whether file was opened in binary mode
file.clearerr()
Clears any error conditions found on file
file.close()
file.close(disp)
Close the given file. It is an error to access it after it is closed.
file.feof()
Query whether file is at the end-of-file
file.ferror()
Returns the operating system error status associated with file
file.fflush()
Flush any pending buffered output to file
file.fseek(offs, whence)
Change the read/write position of file
file.ftell()
Query the read/write position of file
file.getswab()
Query whether file is in automatic byte-swap mode
file.ispipe()
Query whether file was opened as a pipe
file.readonly()
Query whether file was opened read-only
file.rewind()
Reset the read/write position of file to the beginning-of-file
file.setswab(bSwab)
Sets the automatic byte-swap mode of file.


Formatted Input / Output

OADL supports the formatting and printing of values to ouput files, and the reading of formatted values from input files. The files must be text-mode; the input/output strings are translated from or to streams of UTF-8 sequences. The following intrinsic procedures and method perform formatted input and output:

print(fmtstring, arg, ...)
print(file, fmtstring, arg, ...)
file.print(fmtstring, arg, ...)
Format and print several values
read(fmtstring, typ, ...)
read(file, fmtstring, typ, ...)
file.read(fmtstring, typ, ...)
Read a formatted set of values of the specified types from a file
say(val,val,...)
say(file,val,val,...)
file.say(val val,...)
Print out values to a file using a default format.


Streaming Input / Output

These intrinsic procedures and methods operate character-at-a-time on the input / output files. They support both text-mode and binary-mode files. If used with unformatted files, they operate byte-at-a-time, which can lead to unexpected effects with WideChar values.

getchar()
getchar(file)
file.getchar()
Get a single character of input from a file
putchar(ch)
putchar(file, ch)
file.putchar(ch)
Put a single character to a file
ungetc(ch)
ungetc(file, ch)
file.ungetc(ch)
Return a single character to the file input buffer
readstr()
readstr(file)
file.readstr()
Read a single line of input into a string


OADL supports unformatted reading and writing of values to files. These files must be opened in binary-mode. The values may be byte-swapped on read and write; see setswab and getswab for more information.

read(file, typ, typ, ...)
file.read(typ, typ, ...)
Read binary values from a file
write(file, val, val, ...)
file.write(val, val, ...)
Write binary values to a file


14. OADL Format Specifiers

An OADL Format Specifier is a string that contains one or more Format Descriptors, separated by commas. There are three types of Format Descriptors, Format Value Descriptors, Format Flag Descriptors, and Other Format Descriptors. Format Value Descriptors describe values to be printed or read. Format Flag Descriptors describe flags that control how values are printed and read. Other Format Descriptors cause input/output cursor control, literal items, and other commands.

Whitespace is ignored in a Format Specifier outside of embedded literals. Any Format Value Descriptor may be prefixed with an optional Repeat Count, which implies N identical Format Value Descriptors.

The following table describes the possible Format Value Descriptors (FVDs). In this table, the following definitions are used:

The Precision and Exponent Width are ignored for formatted reads.

The case of FVDs is significant only for the l, i, z, e, en, es, g, m, y and v FVDs. For them, a lower-case Descriptor causes the output characters to be entirely lower-case.

FVD Width Prec. Exp. Description
L opt Logical (boolean) format descriptor. If the field width is 5 or greater (or automatic), prints TRUE or FALSE. Otherwise, prints T or F.
A opt String format descriptor
I opt opt Integer format descriptor. Prints in base 10 unless a different radix is specified with the R format descriptor.
Z opt opt Hexadecimal integer format descriptor
O opt opt Octal integer format descriptor
B opt opt Binary integer format descriptor
F opt opt Floating point format descriptor
M opt opt Monetary floating point format descriptor
E opt opt opt Exponential floating point format descriptor
EN opt opt opt Engineering notation floating point format descriptor
ES opt opt opt Scientific notation floating point format descriptor
G opt opt opt Generalized floating point format descriptor
Y opt opt opt Hexadecimal floating point format descriptor
V opt opt opt Variable format descriptor. Print in L, I, G, or A format, depending on item type

For scalar values, each FVD correponds to a single item. For arrays, each FVD corresponds to a column of the array. All items in a column in an array will have the same field width; if the field width is omitted, the maximum field width will be calculated sufficient to hold all items in a column. All rows will be horizontally aligned, even between separate arrays. If this behavior is not desired, the | or S| Format Flag Descriptors may be used.

Output of nested arrays, enclosures, and strings with whitespace will cause a character-graphic box to be drawn around the item. If all of the characters of the output buffer are ASCII, the ASCII characters +-| will be used to draw the box. Otherwise, the following Unicode characters will be used to draw the box:

Code Char Descrption
0x250C Top left corner
0x2500 Horizontal line
0x2510 Top right corner
0x2502 Vertical line
0x2514 Bottom left corner
0x2518 Bottom right corner

To disable box output, use the SN# Format Flag Descriptor. To force Unicode box drawing characters to be used, use the SW Format Flag Descriptor.

The following table describes the possible Format Flag Descriptors (FFD):

FFD Description
SP Add '+' to positive numbers (disable with SNP or SS)
SB Add a single leading blank to positive numbers (disable with SS)
S# Enable box output around arrays (disable with SN#)
SU Treat integers as unsigned (disable with SNU)
SV Add type information prefix/suffix and quotes (disable with SNV)
ST Add thousands separator (disable with SNT)
S| Enable auto row break - don't align rows horizontally bewtween printed values (disable with SN|)
SL Left-justify output items in their field (disable with SR)
SC Center output items in their field (disable with SR)
SR Right-justify output items in their field (default)
SF'c' Set monetary fill character to c
SI Use international money symbols (disable with SNI)
S* Put single-line literals in all rows (disable with SN*)
SW Force WideChar output (cannot be disabled)
S or SN Same as SNP,SNB,SN#,SNU,SNV,SNT,SN|,SR,SNI,SN*

The following table describes the possible Other Format Descriptors (OFD):

OFD Description
count X Horizontal space. If the optional count is omitted, defaults to 1. Same as count TR.
radix R Radix control for the I format descriptor. If the optional radix is omitted, defaults to 10. Radixes from 2 to 36 may be specified.
rep (fmt) Nested format specifier. The repeat count rep is optional.
"literal" Prints the literal string literal. Two double-quotes adjacent to each other "" do not terminate the literal, but will print as an individual double-quote "
'literal' Prints the literal string literal. Two single-quotes adjacent to each other '' do not terminate the literal, but will print as an individual single-quote '
: Output terminator. If no more values remain to print, literals after the terminator will not print.
* Format reversion point. If there are more values to print than format descriptors, repeat the format descriptors starting at this point
$ Suppress newline
| Row break - don't align rows horizontally across this breakpoint
/, //, etc. Advance output rows. The number of slashes dictates the number of rows to advance.
T pos Absolute horizonal position
TL delta Relative horizontal position (toward the left)
TR delta Relative horizontal position (toward the right). Same as deltaX

As a historical note, OADL Format Specifiers are very similar to FORTRAN format statements. The differences include:

The following is the complete BNF description of OADL Format Specifiers:

format          : fmt_item
                | fmt_item ',' format
                ;

opt_int         : INT           // Repeat N times
                |               // No repeat
                ;

fmt_item        : INT rep_item
                | opt_int rep_fmt_char
                | opt_int '(' format ')'
                | non_rep_item
                ;

rep_fmt_char    : prec_fmt_char opt_int opt_digits
                | exp_fmt_char opt_int opt_digits opt_expon
                | 'L' opt_int           // Logical
                | 'A' opt_int           // String
                | 'X'                   // Space
                | 'R'                   // Radix control
                ;

opt_digits      : '.' INT
                |               // No digits
                ;

opt_expon       : 'E' INT
                | 'e' INT
                |               // No exponent
                ;

prec_fmt_char   : 'I' | 'Z' |'O' // Integer formats
                | 'i' | 'z'     // Ext. - lower case radix print
                | 'B'           // Ext. - integer binary (from Fortran 90)
                | 'F'           // Floating point format
                ;

exp_fmt_char    : 'E' | 'G'     // Exponential & Generic
                | 'e' | 'g'     // Extension - print lower-case
                | 'E' 'S' | 'e' 's' // Scientific notation
                | 'E' 'N' | 'e' 'n' // Extension - engineering (from F90)
                | 'Y' | 'y'     // Extension - like printf("%a")
                | 'V' | 'v'     // Extension - print according to var type
                | 'M'           // Extension - monetary float format
                ;

non_rep_item    : '\'' chars '\'' // Literal
                | '"' strchars '"' // Literal
                | ':'           // Terminate if no more items
                | '*'           // Reversion point
                | '$'           // Suppress newline
                | '|'           // Row break
                | advance       // Advance one or more output rows
                | 'S' | 'S' 'N' // Same as SNP,SNV,SNT,SN$,SJ
                | 'S' 'P'       // Add '+' to positive nums
                | 'S' 'S'       // Suppress '+' from positive nums
                | 'S' 'N' 'P'   // Extension - same as SS
                | 'S' 'B'       // Extension - same as printf("% d")
                | 'S' '#'       // Extension - enable box output around arrays
                | 'S' 'N' '#'   // Extension - disable box output around arrays
                | 'S' 'U'       // Extension - treat integers as unsigned
                | 'S' 'N' 'U'   // Extension - disable integers as unsigned
                | 'S' 'V'       // Extension - add type info pre/suf and quotes
                | 'S' 'N' 'V'   // Extension - disable type info pre/suf and quotes
                | 'S' 'T'       // Extension - add thousands separator
                | 'S' 'N' 'T'   // Extension - disable thousands separator
                | 'S' '|'       // Extension - enable auto row break
                | 'S' 'N' '|'   // Extension - disable auto row break
                | 'S' 'L'       // Extension - left-justified in field
                | 'S' 'C'       // Extension - center item in field (ign. field sign)
                | 'S' 'R'       // Extension - return to right-justified formatting
                | 'S' 'F' '\'' ch '\'' // Extension - set monetary fill char
                | 'S' 'I'       // Extension - use international monetary symbol
                | 'S' 'N' 'I'   // Extension - use national monetary symbol
                | 'S' '*'       // Extension - put single-line literals in all rows
                | 'S' 'N' '*'   // Extension - only put literals in first row
                | 'S' 'W'       // Extension - force wide char output (sticky)
                | 'T' INT       // Absolute horizontal position
                | 'T' 'L' INT   // Relative horizontal pos (toward left)
                | 'T' 'R' INT   // Relative horizontal pos (toward right)
                ;

advance         : '/'           // Advance one output row
                | advance '/'   // Advance multiple output rows
                ;

chars           : /* NOTHING */
                | chars CHAR
                | chars '\'' '\''
                ;

strchars        : /* NOTHING */
                | strchars CHAR
                | strchars '\"' '\"'
                ;


15. Predefined Symbols

This section lists the complete list of predefined OADL symbols.

Keywords:

assert break case catch
class const continue default
do else extern for
forall foreach if match
namespace new operator proc
protected public return static
switch throw try using
var while with

Built-in types (global namespace):

Array ArrayType Bool Byte
Char Class Dict Double
Enclosure Exception Extern File
Float Half Int List
Long Null Object PackBool
PackByte PackChar PackDouble PackFloat
PackHalf PackInt PackLong PackShort
PackUbyte PackUint PackUlong PackUshort
PackWideChar Pointer Proc Public
Short String Type Ubyte
Uint Ulong Ushort WideChar
WideString

Exceptions (namespace oadl):

TypeCheck RangeCheck ArgCheck AccessCheck
AssertCheck StackCheck ExternCheck ShapeCheck
InterruptCheck FormatCheck UnboundedCheck EndOfFile
RegexCheck IoCheck MatchCheck ProcCheck
ExceptCheck NameCheck RedfinedCheck UTF8Check

Global variables (namespace oadl):

ArgVec CalcPrompt1 CalcPrompt2 Editor
TermColumns TermRows TypePromote

Global variables (namespace io):

FieldWidth FltFormatChar FormatFlags IntFormatChar
IntRadix MonetaryFill NumDigits NumExponent

Constants (namespace oadl):

JMP_SIZE MAX_RANK MAXINT

Constants (namespace io):

EOF ErrOut FMT_ADD_BLANK FMT_ADD_PLUS
FMT_ADD_TYPE FMT_ALIGN_ROWS FMT_CENTER FMT_IMMED_ROWS
FMT_INTERNAT FMT_LEFT FMT_NO_BOX_ARR FMT_THOUSANDS
FMT_UNSIGNED FMT_UPPER_CASE Input Output
SEEK_CUR SEEK_END SEEK_SET

Intrinsic procedures (namespace oadl):

arg argvec deleted gc
halt is_a longjmp matchvec
nargs perm protect readonly
restart restore save setjmp
transient typecheck

Intrinsic procedures (global namespace):

format getchar print putchar
read readstr say typeof
ungetc

Intrinsic Public methods (in the public namespace):

abs accum arrbase arrcmp
binary clamp clearerr close
concat copy decode deepcopy
disclose drop enclose encode
feof ferror fflush fix2flt
flatten flt2fix fseek ftell
getchar getswab increment inner
intersect isarray ischar isfloat
isinteger isnumeric ispipe isstring
iterate laminate length lerp
max maxval member min
minval outer pack packtype
position print promote putchar
rank ravel read readonly
readstr reduce replicate reshape
reverse rewind rotate satadd
satsub say setswab shape
signum sizeof sort stride
subr take transient transpose
union unique ungetc unpack
width without write

Standard External Procedures (namespace oadl)

findobj findpub objname pubname
random srandom str2var wait

Predefined Public Properties:

create destroy parent

Preprocessor directives:

#define #defined #elif #else
#endif #if #ifdef #include
#undef

Reserved preprocessor directives:

#arg #args #nargs

Desk calculator directives:

#classes #consts #defines #erase
#externs #help #intrinsics #load
#namespaces #objects #procs #publics
#quit #reset #save #vars

Miscellaneous constants:

nil self true false


16. Glossary

argument
An argument is a value which is given to a procedure (or program) to operate on. For example, in the expression "say( a )", "a" is the only argument to the "say" procedure.
array
An array is a multi-dimensional list of values. In OADL, arrays need not contain values of all the same type. For example, the following is a valid OADL array: {1,2,"Hi",myClass}*
ASCII
American Standard Code for Information Interchange - the venerable 8-bit standard for the representation of characters. The ASCII table gives a numeric value for each possible character in the defined character set; for example, the letter 'a' has the ASCII value 97.
class
A class is a group of data elements and procedures and/or operators on those elements. Certain of the elements may be made public so that other classes/objects/contexts may use them.
constant
A constant is a value in an OADL program which may not be modified. Constants are found in many places in an OADL program, from simple constants like the number "1" to a complicated class declaration.
expression
An expression is a formula that mixes several operands with operators, returning a result. A typical arithmetic formula is an expression - for example, pi*r*r is an expression.
floating point
A floating point number can represent both fractional and whole numbers. Floating point numbers have a specific magnitude range and precision depending on their type. Single-precision numbers have a range of about 1e-38 to 3e38 and a precision of about 7 decimal digits. Double-precision numbers have a range of about 2e-308 to 2e308 and a precision of about 16 decimal digits. Half-precision numbers have a range of about 6e-5 to about 7e4 and a precision of about 3 decimal digits.
identifier
An identifier is a token in a programming language used to represent a variable, a named constant, named procedure, or other named item. Typically, identifiers start with an alphabetic character (as well as some characters such as "_" and "$") and are followed by any number of alphabetic characters and numbers
inheritance
Inheritance is the ability of classes and objects to be derived from another parent class. The derived class or instanced object inherits all of the attributes from its parent.
integer
An integer is a whole number whose range depends on the number of binary digits in the number. There about about 9 digits of precision for normal integers, about 3 digits of precision for 1-byte integers, about 5 digits of precision for 2-byte integers, and about 19 digits of precision for 8-byte integers.
method
A method is a public procedure interface to a class. A method is always called on an instance of that class, with the dot call syntax obj.method(args). During execution of the method, the self pseudo-variable can be used to find the Object instance of the class that the method was called with.
public
A public item in a class or object is one which is visible outside the class/object context. In addition, in OADL, a Public is a hash key index into an object which may be declared independently of any class.
multiple inheritance
Multiple inheritance is the ability of a class to derive attributes from more than one parent class. For example, a power drill might derive attributes from both a cutting tool (number of teeth, hardness, etc.) as well as from a power tool (spindle size, motor HP, etc.)
object
An object is an instance of a class. Classes are always non-modifiable; objects may be dynamic, with changes permitted to various attributes of the object.
operator
An operator is one of several mathematical operations, including +, -, and so on. Operators have one (monadic) or two (dyadic) operands. Operators may be overloaded by OADL classes.
procedure
A procedure is a sequence of instructions which tell a computer what to do. In addition, procedures typically have arguments - values that are given to the procedure to operate on - and a return value.
scalar
A scalar is a simple single-valued item. For example, the number 3 is a scalar. In OADL, for the purposes of array-valued expressions, everything that is not an array is a scalar.
token
A token is a sequence of characters which are grouped together according to a fixed set of rules. An identifier is a token, as is a string literal, and a floating point number.
Unicode
Unicode is the modern standard for encoding text in displayed output. It handles glyphs from most of the world's languages. OADL supports the UTF-8 encoding as well as direct 21-bit Unicode glyphs in a 32-bit field.
variable
A variable can be considered a "box" or holding cell which contains a value. In OADL, most variables have a dynamic type that may be changed by assigning a new value to the variable.


17. OADL Implementation Notes

Type System

In a 32-bit implementation, OADL objects are represented internally by 32-bit numbers. To maximize the precision of Float and Int variables, the type information for them is compressed. Float variables have 31 bits of value, and the type is indicated by having the least- significant bit set to '0'. Int variables have 30 bits of value, and the type is indicated by having the least-significant two bits set to '01' (or 1). The remaining types have up to 24 bits of value, six bits of type ID (from the table below), and the least-significant two bits are set to '11' (or 3).

Type Name ID Value
Float 0 (0x00) 31-bit single-precision IEEE float (the 32nd LSB is forced to 0)
Int 1 (0x01) 30-bit signed integer
Double 2 (0x02) 24-bit atom ID of 64-bit IEEE double-precision scalar
Long 3 (0x03) 24-bit atom ID of 62-bit signed integer
Ulong 4 (0x04) 24-bit atom ID of 64-bit unsigned integer
Uint 5 (0x05) 24-bit atom ID of 32-bit unsigned integer
Array 6 (0x06) 24-bit Array ID
Object 7 (0x07) 24-bit Object ID
ArrType 8 (0x08) 24-bit ArrType ID
Enclosure 9 (0x09) 24-bit Enclosure ID
Reserved 10-15 Reserved for future expansion
Pointer 16 (0x10) 24-bit atom ID of externally defined pointer
Dict 17 (0x11) 24-bit Dict ID
Proc 18 (0x12) 24-bit Proc ID
Extern 19 (0x13) 24-bit Extern ID
Public 20 (0x14) 24-bit Public ID
Exception 21 (0x15) 24-bit Exception ID
File 22 (0x16) 24-bit File ID
Reserved 23-31 Reserved for future expansion
Reserved 32-47 Reserved for OADL internal use
Reserved 48-53 Reserved for future expansion
WideChar 54 (0x36) 21-bit Unicode character
Half 55 (0x37) 16-bit half-precision float
Ushort 56 (0x38) 16-bit unsigned integer
Short 57 (0x39) 16-bit signed integer
Ubyte 58 (0x3A) 8-bit unsigned integer
Byte 59 (0x3B) 8-bit signed integer
Char 60 (0x3C) 7-bit character value (typically, an ASCII char)
Type 61 (0x3D) 6-bit unsigned value (one of the Type constants)
Bool 62 (0x3E) 1-bit boolean
Null 63 (0x3F) 0xFFFFFFFFu in C - the OADL nil* value

It is illegal for least-significant bits of '11' (or 3) to be combined with the type bits 2-7 of Float (0) or Int (1). Attempting to create an OADL value of this form will result in undefined behavior.

In a 64-bit implementation of OADL, the first few types are arranged differently:

Type Name ID Value
Double 0 63-bit IEEE double-precision float (the 64th LSB is forced to 0)
Long 1 62-bit signed integer
Float 2 32-bit IEEE single precision float
Int 3 32-bit signed integer

Additionally, in a 64-bit implementation, IDs and variable addresses are 32 bits rather than 24. The illegal type combinations are the least-significant bits of '11' (or 3) combined with Double (0) or Long (1) type bits 2-7. The value of nil is 0xFFFF_FFFF_FFFF_FFFFul (64 consecutive '1' bits).

There are several other dynamic types supported by OADL and returned by the typeof() intrinsic procedure; these types are synthized from a combination of OadlVar base type and information stored in the dynamic object referred to by the base value:

Type Name Base Type Indirect Base Type Other information
Class Object Class
PackDouble Array Double
PackUlong Array Ulong
PackLong Array Long
PackFloat Array Float
PackUint Array Uint
PackInt Array Int
PackHalf Array Half
PackUshort Array Ushort
PackShort Array Short
PackUbyte Array Ubyte
PackByte Array Byte
PackBool Array Bool
String Array Char One dimension
PackChar Array Char Multiple dimensions
WideString Array WideChar One dimension
PackWideChar Array WideChar Multiple dimensions
List Array Array One dimension
Array[*] Array Array Universal array type

These pictures document the actual bit layout of the various types in a 32-bit implementation:

Float - 0x0
S
31
Exponent:8
30 23
Mantissa:22
22 1
0
0

Int - 0x1
Value:30
31 2
0 1
1 0

24-bit variables - 0x02 through 0x1F
Value:24
31 8
0 t t t t t
7 2
1 1
1 0

WideChar - 0x36
n/a
31 29
Value:21
28 8
1 1 0 1 1 0
7 2
1 1
1 0

Half - 0x37
n/a
31 24
S
23
Exponent:5
22 18
Mantissa:10
17 8
1 1 0 1 1 1
7 2
1 1
1 0

Ushort, Short - 0x38, 0x39
n/a
31 24
Value:16
23 8
1 1 1 0 0 t
7 2
1 1
1 0

Ubyte, Byte - 0x3A, 0x3B
n/a
31 16
Value:8
15 8
1 1 1 0 1 t
7 2
1 1
1 0

Char, Type - 0x3C, 0x3D
n/a
31 15
Value:7
14 8
1 1 1 1 0 t
7 2
1 1
1 0

Bool - 0x3E
n/a
31 9
V
8
1 1 1 1 1 0
7 2
1 1
1 0

Null - 0x3F
0xFFFFFF
31 8
1 1 1 1 1 1
7 2
1 1
1 0

These pictures document the actual bit layout of the various types in a 64-bit implementation:

Double - 0x0
S
63
Exponent:11
62 52
MantHi:20
51 32
MantLo:31
31 1
0
0

Long - 0x1
ValueHi:32
63 32
ValueLo:30
31 2
0 1
1 0

Float - 0x2
S
63
Exponent:8
62 55
Mantissa:23
54 32
n/a
31 8
0 0 0 0 1 0
7 2
1 1
1 0

32-bit variables - 0x03 through 0x1F
Value:32
63 32
n/a
31 8
0 t t t t t
7 2
1 1
1 0

WideChar - 0x36
n/a
63 53
Value:21
52 32
n/a
31 8
1 1 0 1 1 0
7 2
1 1
1 0

Half - 0x37
n/a
63 48
S
47
Exponent:5
46 42
Mantissa:10
41 32
n/a
31 8
1 1 0 1 1 1
7 2
1 1
1 0

Ushort, Short - 0x38, 0x39
n/a
63 48
Value:16
47 32
n/a
31 8
1 1 1 0 0 t
7 2
1 1
1 0

Ubyte, Byte - 0x3A, 0x3B
n/a
63 40
Value:8
39 32
n/a
31 8
1 1 1 0 1 t
7 2
1 1
1 0

Char, Type - 0x3C, 0x3D
n/a
63 39
Value:7
38 32
n/a
31 8
1 1 1 1 0 t
7 2
1 1
1 0

Bool - 0x3E
n/a
63 33
V
32
n/a
31 8
1 1 1 1 1 0
7 2
1 1
1 0

Null - 0x3F
0xFFFFFFFF
63 32
0xFFFFFF
31 8
1 1 1 1 1 1
7 2
1 1
1 0

Several types refer to "IDs" - these are virtual indexes into a dynamic memory pool. Implementations must provide automatic garbage collection for these IDs, and all implementations must be able to distinguish read-only from writeable Array and Object contents.

Pointer values are provided only for the convenience of interfacing to system library routines. They are completely opaque to OADL programs. Pointer values are not saved to disk.

Generic arrays are arrays of 32-bit or 64-bit tagged values, as described above. Packed arrays are stored more efficiently, since the type of each element is homogeneous and stored as part of the array type.

Arguably, for Null values, one could store no data in a packed array. However, this is seen as an optimization of no value.

The type system is implemented in C at oadlvar.h .

OADL machine internals

In some cases, it can be useful to understand the OADL stack machine. Although it is not complete documentation, the opcodes are implemented in C at opcode.h and builtin.h and in OADL at oadlmach.oah . Additionally, note that some of the more complicated parts of OADL's machine are implemented in an extended form of OADL (extended by some intrinsics that are not supported for general use). See intrinsic.oad for more information.

External procedure libraries

External procedure libraries are typically implemented as dynamically loaded system libraries. These libraries are kept in a system-dependent location (frequently the syslib directory of the OADL installation location).

The dynamic library should implement an entry point named "OADL_libname" (where "libname" is the same as that used in the using extern statement). That entry point then performs callbacks to the OADL runtime to register external procedures, as well as to capture pointers to important OADL implementation functions. These callbacks are defined in oadlsys.h .

This entry point must be implemented with the following prototype (where "xxx" is the name of the dynamic library):

int OADL_xxx(void *ctx, OADL_FindProc_fp findProc);

The first argument passed to that entrypoint is a "context" pointer, which must be passed back to the findProc entry point. The second argument passed to the entry point is the findProc routine. This routine is used to find all the other OADL implementation procedures which may be needed by the utility library. The typedef for this function pointer is:

typedef int (*OADL_FindProc_fp)(void *ctx, const char *name,
                                int version, OADLproc *rProc);

The name is the name of the procedure that is desired (see the table below for the complete list). The OADL_SYS_VER constant must be given for version. The proc is returned in the rProc pointer. The OADLproc typedef exists only to provide a "generic" function pointer; the returned pointer should be typecast according to the table below before it is used.

The most important procedure which should be queried and used is the OADL_AddExtern() procedure. The utility library must use this procedure to define the Extern procs which are implemented by the library. The following fragment queries and calls the OADL_AddExtern procedure to implement an Extern named foo::bar"

OADL_AddExtern_fp OADL_AddExtern;
int foo_bar(void *ctx, OadlVar *pRes, int nargs, const OadlVar *args);

if (!findProc(ctx, "OADL_AddExtern",
               OADL_SYS_VER, (OADLproc *) &OADL_AddExtern))
{
    return 0;
}
if (!OADL_AddExtern(ctx, "foo::bar", foo_bar)) {
    return 0;
}

All Extern procs are implemented with the same function prototype:

typedef int (*OADL_Extern_fp)(void *ctx, OadlVar *pRes,
                              int nargs, const OadlVar *args);

The function returns 1 for success, and 0 if any error occurred (see ThrowError(), below, for how to raise an exception which will be handled after the function returns). The result OadlVar should be returned in the pRes pointer. nargs contains the number of arguments which were passed to the Extern, and args is an array containing all the arguments. See the oadlvar.h header file for the definition of the OadlVar structure. The ctx argument must be passed back to any callbacks called by this entry point.

The following is the complete list of functions that may be queried by findProc. Generally, these functions return 1 on success and 0 if any error occurred.

OADL_AddExtern
typedef int (*OADL_AddExtern_fp)(void *ctx, const char *name, OADL_Extern_fp proc);

Defines an Extern entry point (see above for more information)
OADL_GetProp
typedef int (*OADL_GetProp_fp)(void *ctx, OadlVar *pRes, int propNum);

Returns, in pRes, the object property of self at offset propNum. Note that the layout of OADL object properties is undefined, and can change from compile to compile. It is generally better to use the GetPublic/SetPublic routines, below.
OADL_SetProp
typedef int (*OADL_SetProp_fp)(void *ctx, int propNum, OadlVar val);

Sets property number propNum of self to val. See caveats in GetProc, above.
OADL_GetIndex
typedef int (*OADL_GetIndex_fp)(void *ctx, OadlVar *pRes, OadlVar v, int nIdx, int idx[]);

Returns, in pRes, the contents of v[idx0, idx1, ...].
OADL_SetIndex
typedef int (*OADL_SetIndex_fp)(void *ctx, OadlVar v, int nIdx, int idx[], OadlVar val);

Sets v[idx0, idx1, ...] to val. Note that OADL_SetIndex() can trigger a GC.
OADL_GetSubr
typedef int (*OADL_GetSubr_fp)(void *ctx, OadlVar *pRes, OadlVar v, int numSub, OadlVar *subrs);

The same as v.subr(subrs0, subrs1, ...) Creates a new subrange of the given var v. The subrange is returned in pRes.
OADL_ArrayInfo
The OADL_ArrayInfo struct contains information about an OADL array. It is used both for information queries as well as for allocation for newly created arrays. See OADL_GetArrayInfo() and OADL_CreateArray() for more information. Here is the structure and its associated flags:
#define OADL_ARRAY_READONLY     0x01    /* Do not modify contents */
#define OADL_ARRAY_PERMANENT    0x02    /* Versus dyamic / GC memory */
#define OADL_ARRAY_USER_DATA    0x04    /* Points to user data, not OADL data */
#define OADL_ARRAY_ITERATOR     0x08    /* Iterator - only if not expanded */

/* If the array is an iterator and the caller requested the parameters,
 * the ArrData is a pointer to an array of the following items (in the
 * type given by ArrType):
 */
#define OADL_ARR_ITER_PARAM_FIRST       0
#define OADL_ARR_ITER_PARAM_LAST        1
#define OADL_ARR_ITER_PARAM_INCR        2
#define OADL_ARR_ITER_PARAM_COUNT       3 // Total size of iterator param array

typedef struct {
    OADL_U32 ArrSize;                   /* Total size of array, in elements */
    OADL_U8 ArrType;                    /* One of OADL_VT_* */
    OADL_U8 ElemSize;                   /* Size of a single element, in bytes */
    OADL_U8 ArrRank;                    /* Rank - number of dimensions */
    OADL_U32 ArrFlags;                  /* Flags from OADL_ARRAY_*, above */
    OADL_U32 ArrShape[OADL_MAX_RANK];   /* Shape of the array */
    OADL_U32 ArrStrides[OADL_MAX_RANK]; /* Dimension strides, in elements */
    OadlVar ArrVar;                     /* Only if iter. expanded to heap */
    void *ArrData;                      /* Pointer to array data or params */
    void *ArrAlloc;                     /* Only if iter. expanded to malloc */
} OADL_ArrayInfo;

See caveats in OADL_WriteCopy() and OADL_GetGcCounter() regarding dereferencing the ArrData pointer.

OADL_GetArrayInfo
typedef int (*OADL_GetArrayInfo_fp)(void *ctx, OADL_ArrayInfo *pArr, OadlVar a, int flags);

Returns info about a in OADL_ArrayInfo structure *pArr. The flags are composed from the following bits:
#define OADL_AIF_ITERATOR_EXPANSION     0x00000007 // Mask for AIF_ITERATOR*
#define OADL_AIF_ITERATOR_HEAP          0x00000001 // ...expand into heap
#define OADL_AIF_ITERATOR_MALLOC        0x00000002 // ...expand into malloc
#define OADL_AIF_ITERATOR_SCRATCH       0x00000003 // ...expand into scratch
#define OADL_AIF_ITERATOR_PARAMS        0x00000004 // ...raw params in ArrData
OADL_GetGcCounter
typedef int (*OADL_GetGcCounter_fp)(void *ctx);

OADL keeps a count of how many times GC occurs. If the GC counter changes after calls to OADL_WriteCopy() or OADL_CreateArray() then a GC has occurred, and therefore OADL_GetArrayInfo() should be called again on all cached OADL_ArrayInfo structures.
OADL_WriteCopy
typedef int (*OADL_WriteCopy_fp)(void *ctx, int *pRes, OadlVar v);

To write directly into an array's data (i.e., instead of calling OADL_SetIndex()), a call to OADL_WriteCopy() must be made. The integer *pRes will be changed to 1 if a write copy was created and 0 otherwise. It is not necessary to call OADL_WriteCopy() on arrays created by the current Extern call. Note that OADL_WriteCopy() can trigger a GC.
OADL_Writeable
typedef int (*OADL_Writeable_fp)(void *ctx, int *pRes, OadlVar v);

Queries whether array v is writeable (that is, whether SetIndex may be called on it). The result of the query is returned in pRes.
OADL_TypeOf
typedef int (*OADL_TypeOf_fp)(void *ctx, int *pRes, OadlVar v);

Returns, in pRes, the abstract type of v - exactly the same as the typeof intrinsic.
OADL_FatalError
typedef int (*OADL_FatalError_fp)(void *ctx, int errNum)

Raises fatal exception errNum from oadlerr.h
OADL_ThrowError
typedef int (*OADL_ThrowError_fp)(void *ctx, int errNum);

Schedules the error errNum (from oadlerr.h for an exception handling event after the Extern function returns.
OADL_FindPublic
typedef int (*OADL_FindPublic_fp)(void *ctx, OadlVar *pRes, const char *name);

Find the Public named name and return its value in pRes.
OADL_FindExtern
typedef int (*OADL_FindExtern_fp)(void *ctx, OadlVar *pRes, const char *name);

Find the Extern named name and return its value in pRes.
OADL_FindObject
typedef int (*OADL_FindObject_fp)(void *ctx, OadlVar *pRes, const char *name);

Find the object named name and return its value in pRes. The name must be one located in global scope.
OADL_GetSelf
typedef int (*OADL_GetSelf_fp)(void *ctx, OadlVar *pSelf);

Returns self in pSelf
OADL_GetPublic
typedef int (*OADL_GetPublic_fp)(void *ctx, OadlVar *pRes, OadlVar obj, OadlVar pub);

Returns, in pRes, the value of public property pub of object obj
OADL_SetPublic
typedef int (*OADL_SetPublic_fp)(void *ctx, OadlVar obj, OadlVar pub, OadlVar v);

Sets the public property pub of object obj to v
OADL_FindGlobal
typedef int (*OADL_FindGlobal_fp)(void *ctx, OadlVar *pRes, const char *name);

Looks up name in the OADL global symbol talbe and returns the result in pRes
OADL_GetGlobal
typedef int (*OADL_GetGlobal_fp)(void *ctx, OadlVar *pRes, int idx);

Gets the global variable at index idx and puts it in pRes.
OADL_SetGlobal
typedef int (*OADL_SetGlobal_fp)(void *ctx, int idx, OadlVar val);

Sets the global variable at index idx to val.
OADL_AllocMach
typedef int (*OADL_AllocMach_fp)(void *ctx, void **pRes, int stackAlloc);

Creates an OADL Machine capable of calling procedures immediately. It allocates stackAlloc entries for the initial size of the execution stack.
OADL_CallProc
typedef int (*OADL_CallProc_fp)(void *ctx, OadlVar *pRes, int typ, void *mach, OadlVar obj, OadlVar proc, int nargs, const OadlVar *args);

Makes an immediate or deferred call to the OADL procedure whose value is proc, or to the method whose value is obj.proc if obj is not nil (proc must be of type Public in that case). Returns 1 on success and 0 on failure.

The typ parameter defines how the call will be executed:

If typ is OADL_CALL_IMMEDIATE, an immediate call is performed. The mach parameter must be a machine allocated by OADL_AllocMach(). OADL_CallProc() will not return until the OADL procedure returns. The return value of the immediate call will be placed in the OadlVar pointed to by the pRes parameter. Most OADL procedures allocate heap objects. This may trigger a GC cycle which will invalidate any cached heap pointers. The calling routine must revalidate any pointers to heap objects after OADL_CallProc() returns.

If typ is OADL_CALL_DEFERRED, a deferred call is scheduled. A deferred call is a call placed on the current executing machine's call stack. OADL_CallProc() will return immediately after scheduling the call. Note that deferred calls do not return any value to the calling context. This allows multiple deferred calls to be scheduled simultaneously without overflowing the stack with unused results. Since the call is deferred, no heap allocations will occur at the time of the OADL_CallProc() call. If an Extern proc implementation defers one or more calls, it must return OADL_CALL_DEFERRED to OADL.

If typ is OADL_CALL_CHAINED, a chained call is scheduled. A chained call is also a deferred call; however, its result is returned to the calling context (which means that only one call may be chained). An Extern proc implementation must return OADL_CALL_CHAINED to OADL if it schedules a chained call.
OADL_CreateArray
typedef int (*OADL_CreateArray_fp)(void *ctx, OadlVar *pRes, OADL_ArrayInfo *pArr);

Creates an array with parameters taken from OADL_ArrayInfo *pArr. Returns the resulting array in *pRes. This does allocate heap memory which could trigger a GC and invalidate any cached heap pointers.

Note that pArr->ArrData and pArr->ArrStrides are ignored unless OADL_ARRAY_USER_DATA is specified in pArr->ArrFlags.

pArr->ArrSize and pArr->ElemSize are always ignored, as they are calculated from the input in pArr->ArrType and pArr->ArrShape.

The pArr structure is updated with the actual array created.
OADL_MakePointer
typedef int (*OADL_MakePointer_fp)(void *ctx, OadlVar *pRes, void *ptr);

Creates a new Pointer value from the given native ptr
OADL_DelPointer
typedef int (*OADL_DelPointer_fp)(void *ctx, OadlVar v);

Deletes the native Pointer variable v
OADL_FindPointer
typedef int (*OADL_FindPointer_fp)(void *ctx, void **pRes, OadlVar v);

Returns the native pointer *pRes associated with the Pointer v
OADL_GetPubName
typedef int (*OADL_GetPubName_fp)(void *ctx, char **pRes, OadlVar v);

Returns the name of the Public v. Same as pubname(v)
OADL_GetExtName
typedef int (*OADL_GetExtName_fp)(void *ctx, char **pRes, OadlVar v);

Returns the name of the Extern v.
OADL_GetObjName
typedef int (*OADL_GetObjName_fp)(void *ctx, char **pRes, OadlVar v);

Returns the name of the object v. Same as objname(v)
OADL_fgets
typedef int (*OADL_fgets_fp)(void *ctx, OadlVar *pRes, OadlVar f);

Reads a string from the OADL file f returning the resulting OADL String or WideString object in *pRes
OADL_fgetc
typedef int (*OADL_fgetc_fp)(void *ctx, int *pRes, OadlVar f);

Reads a UTF8 character from the OADL file f and returns the character as *pRes (note - returns the int, not the OadlVar)
OADL_fputc
typedef int (*OADL_fputc_fp)(void *ctx, OadlVar f, int c);

Puts the (possibly wide) character c into OADL file f
OADL_fputs
typedef int (*OADL_fputs_fp)(void *ctx, OadlVar f, const char *s, int len);

Puts the ASCII character string s into OADL file f
OADL_wfputs
typedef int (*OADL_wfputs_fp)(void *ctx, OadlVar f, const OADL_U32 *s, int len);

Puts the 32-bit Unicode character string s into OADL file f
OADL_ungetc
typedef int (*OADL_ungetc_fp)(void *ctx, OadlVar f, int c);

Pushes the character c back onto OADL file f to be returned by subsequent UTF8 reads
OADL_fopen
typedef int (*OADL_fopen_fp)(void *ctx, OadlVar *pRes, const char *name, const char *access);

Opens a UTF8 stream and returns the File result in *pRes
OADL_fclose
typedef int (*OADL_fclose_fp)(void *ctx, OadlVar f);

Close the OADL file f
OADL_fflush
OADL_fseek
OADL_ftell
OADL_fread
OADL_fwrite
OADL_feof
OADL_ferror
OADL_clearerr
typedef int (*OADL_fflush_fp)(void *ctx, OadlVar f);
typedef OADL_64 (*OADL_fseek_fp)(void *ctx, OadlVar f, OADL_64 offs, int seekType);
typedef OADL_64 (*OADL_ftell_fp)(void *ctx, OadlVar f);
typedef int (*OADL_fread_fp)(void *ctx, void *p, int n, int s, OadlVar f);
typedef int (*OADL_fwrite_fp)(void *ctx, void *p, int n, int s, OadlVar f);
typedef int (*OADL_feof_fp)(void *ctx, OadlVar f);
typedef int (*OADL_ferror_fp)(void *ctx, OadlVar f);
typedef int (*OADL_clearerr_fp)(void *ctx, OadlVar f);

Other OADL equivalents to stdio routines. A program which uses OADL_fopen must use these instead of real stdio routines.
OADL_ucCharType
typedef int (*OADL_ucCharType_fp)(int wch)

Determines the Unicode Character Type from a given WideChar value between 0 and 0x11000, inclusive. Returns -1 on error. See unicode.h for possible character types.
OADL_ucToUpper(int wch)
OADL_ucToLower(int wch)
typedef int (*OADL_ucToUpper_fp)(int wch)
typedef int (*OADL_ucToLower_fp)(int wch)

Converts a WideChar value betwen 0 and 0x110000, inclusive. Returns the original character if no single-character conversion if found.
OADL_utf8_bytelen
typedef int (*OADL_utf8_bytelen_fp)(void *ctx, int *pRes, OADL_U32 *src, int n);

Returns the number of bytes that would be required to encode the 32-bit string src
OADL_utf8_strlen
typedef int (*OADL_utf8_strlen_fp)(void *ctx, int *pRes, unsigned char *src, int n);

Returns (in *pRes) the number of Unicode characters encoded by the n chars of UTF8 string src
OADL_utf8_strcpy
typedef int (*OADL_utf8_strcpy_fp)(void *ctx, unsigned char *dst, OADL_U32 *src, int n);

Copies the n-character 32-bit string src into the UTF8 string dst which must have enough space allocated to hold the complete string.
OADL_PushIntrinsic
typedef int (*OADL_PushIntrinsic_fp)(void *ctx)

Increments the intrinsic depth. Returns 1 on success, 0 if an error occurred.
OADL_PopIntrinsic
typedef int (*OADL_PopIntrinsic_fp)(void *ctx)

Decrements the intrinsic depth. Returns 1 on success, 0 if an error occurred.
OADL_AddProc
typedef int (*OADL_AddProc_fp)(void *ctx, OadlVar *pVar, const OADL_U8 instrs[], int numInst)

Adds a new intrinsic procedure based on the numInst OADL bytecodes found in the instrs array. The instrs / numInst parameters are typically obtained by using the cvtintr utility. The resulting intrinsic is returned in *pVar.
OADL_RegComp
typedef int (*OADL_RegComp_fp)(void *ctx, void **pRE, char *pattStr, int options);

Compiles the PCRE pattern pattStr into *pRE for subsequent use with OADL_RegEx(). Options are standard PCRE options, found in oadlpcre.h .
OADL_RegEx
typedef int (*OADL_RegEx_fp)(void *ctx, int *pRes, void *re, char *str, int first, int len, int options, int patOffs[], int patOffSize);

Executes the PCRE reg exp. machine with compiled expression RE. The matches are returned in patOffs. patOffs will be an array of begin,end+1 pairs indicating the captured substrings, with patOffs[0] and patOffs[1] indicating the entire match. first and len indicate the substring which is to be matched. Options are PCRE options, from the list found in oadlpcre.h . The number of pairs is returned in *pRes.
OADL_RegFree
typedef int (*OADL_RegFree_fp)(void *ctx, void *re);

Frees a PCRE regular expression previously created by OADL_RegComp()
OADL_malloc
OADL_realloc
OADL_free
typedef int (*OADL_malloc_fp)(void *ctx, void **pRes, int nBytes);
typedef int (*OADL_realloc_fp)(void *ctx, void **pRes, void *ptr, int nBytes);
typedef int (*OADL_free_fp)(void *ctx, void *ptr);

Just like libc malloc/realloc/free but with OADL debugging hooks. Also more likely to work despite any interesting details about how malloc pools are implemented with shared libraries.
OADL_AllocScratch
typedef int (*OADL_AllocScratch_fp)(void *ctx, void **pRes, int nBytes);

Allocates scratch space that is only valid until the next OADL_AllocScratch. There is no need to free this memory; it is recycled by clients of OADL_AllocScratch
OADL say() and read() replacement
typedef int (*OADL_GetChar_fp)(void *ctx, void *fp);
typedef void (*OADL_SayChar_fp)(void *ctx, int wch);
typedef void (*OADL_SayStr_fp)(void *ctx, char *s, int n);
typedef void (*OADL_SayLStr_fp)(void *ctx, OADL_U32 *s, int n);

These function pointers types are used by OADL built-in input and output routines, and can be updated via OADL_IoProcs(), below. Note that these functions are NOT queryable via the normal OADL_FindProc mechanism; use the OADL_GetIoProcs() function to get them instead.
OADL_IoProcs
typedef int (*OADL_IoProcs_fp)(void *ctx, OADL_GetChar_fp getChar, OADL_SayChar_fp sayChar, OADL_SayStr_fp sayStr, OADL_SayLStr_fp sayLStr);

If the extern library wants to hook/intercept say() and read(), it should call this routine with the four entry points specified.
OADL_GetIoProcs
typedef int (*OADL_GetIoProcs_fp)(void *ctx, OADL_GetChar_fp *pGetChar, OADL_SayChar_fp *pSayChar, OADL_SayStr_fp *pSayStr, OADL_SayLStr_fp *pSayLStr);

Retrieve the current IO procs
OADL_ArrayIncr
int OADL_ArrayIncr(int offs, int rank, const OADL_U32 strides[], const OADL_U32 shape[], OADL_U32 index[])

Increment a multidimensional array index and return the new offset to the current element. Note that a scalar may be aliased as an array by using a rank of 0. Note also that the proper offset to the next element (based on the contents of index[]) is computed if an offs of 0 is consistently provided in a loop over all elements.

Inputs:

offs - Current offset (start at 0)
rank - Rank (dimensionality) of array
strides[] - Array of strides, from OADL_ArrayInfo
shape[] - Shape of array, from OADL_ArrayInfo
index[] - Current indices of array (start at {0})

Note that this is not a function pointer which is queried from OADL; rather, it is an inline function. Updates the index[] array and returns an updated offs

Simple External Library Example

The following is a very simple external library implementation. It can be compiled and used with the using extern example from the chapter on External procedures. The example should be compiled as follows:

Linux .so
clang -x c++ --std=c++11 -fPIC -c libfoo.c -I../../INCLUDE
clang++ --std=c++11 -shared -Wl,-soname,libfoo.so.1 -o libfoo.so.1 libfoo.o
Cygwin .dll
gcc -x c++ --std=c++11 -c libfoo.c -I../../INCLUDE
g++ -shared -Wl,-soname,libfoo.so.1 -o libfoo.so.1 libfoo.o -lc
Windows .dll
cl /c libfoo.c /I../../INCLUDE /DWIN32
link /dll libfoo.obj /out:libfoo.dll
MacOS .dylib
clang -x c++ --std=c++11 -c libfoo.c -I../../INCLUDE
clang++ --std=c++11 -dynamiclib -o libfoo.dylib libfoo.o -lc++
/*
 * Copyright (c) 2024 Ross Cunniff
 *
 * Permission is hereby granted, free of charge, to any person obtaining a copy
 * of this software and associated documentation files (the "Software"), to deal
 * in the Software without restriction, including without limitation the rights
 * to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
 * copies of the Software, and to permit persons to whom the Software is
 * furnished to do so, subject to the following conditions:
 *
 * The above copyright notice and this permission notice shall be included in
 * all copies or substantial portions of the Software.
 *
 * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
 * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
 * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
 * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
 * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
 * OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
 * THE SOFTWARE.
 */

#ifdef WIN32
#include <windows.h>
#endif

#include <stdio.h>

#include "oadlvar.h"
#include "oadlsys.h"

static OADL_GetArrayInfo_fp OADL_GetArrayInfo;
static OADL_AddExtern_fp OADL_AddExtern;
static OADL_TypeOf_fp OADL_TypeOf;

static int foo_bar(void *ctx, OadlVar *pRes, int nargs, const OadlVar *args)
{
    printf("foo::bar!\n");
    *pRes = OADL_NIL;
    return 1;
}

/* tables of extern functions defined */
static struct {
    const char *name;
    OADL_Extern_fp func;
} funcList[] = {
    { "foo::bar",       foo_bar },
    { 0, 0 }
};

/* table of OADL exports needed */
static struct {
    const char *name;
    OADLproc *func;
} oadlCB[] = {
    { "OADL_AddExtern",    (OADLproc *) &OADL_AddExtern },
    { "OADL_TypeOf",       (OADLproc *) &OADL_TypeOf },
    { "OADL_GetArrayInfo", (OADLproc *) &OADL_GetArrayInfo },
    { 0, 0 }
};

#ifdef __cplusplus
extern "C" {
#endif

#ifdef WIN32
__declspec(dllexport)
#endif
int OADL_libfoo(void *ctx, OADL_FindProc_fp findProc)
{
    int i;

    /* Get the OADL exports needed to run */
    for (i = 0; oadlCB[i].name; i++) {
        if (!findProc(ctx, oadlCB[i].name, OADL_SYS_VER, oadlCB[i].func)) {
            return 0;
        }
    }

    /* Define the extern routines */
    for (i = 0; funcList[i].name; i++) {
        if (!OADL_AddExtern(ctx, funcList[i].name, funcList[i].func)) {
            return 0;
        }
    }

    return 1;
}

#ifdef __cplusplus
}
#endif

#ifdef WIN32
// DLL entry function (called on load, unload, ...)
BOOL APIENTRY DllMain(HANDLE hModule, DWORD dwReason, LPVOID lpReserved)
{
    return TRUE;
}
#endif

Token state machine

Although much of OADL lexical analysis can be implemented via simple switch statements and single-character lookahead, distinguishing identifiers (names), integer constants, hexadecimal constants, and floating point constants from each other is more complicated. The lex program given in this document does not implement it fully correctly - it does not handle embedded underscores in integer/hex/float constants. The following picture shows a complete deterministic finite-state automaton (DFA) which will recognize these tokens. States with double circles around them are legitimate final states (and each is labelled with the type of the token recognized at that state). Transitions are only labelled with upper-case letters; lower-case letters follow the same transitions. Finally, the character "u" represents the ASCII underline character '_'. The state numbers correlate exactly to the DFA in OADL's reference implementation. In non-terminal states, any other character than those given in the outbound transitions is a lexical error condition.

Picture of OADL token DFA

The token state machine is directly implemented in C by tokmach.h and tokmach.c . The state numbers correspond directly to the state diagram.


18. Lex / Yacc Grammar

gram.y

/*
 * Copyright (c) 1997 Ross Cunniff
 *
 * Permission is hereby granted, free of charge, to any person obtaining a copy
 * of this software and associated documentation files (the "Software"), to deal
 * in the Software without restriction, including without limitation the rights
 * to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
 * copies of the Software, and to permit persons to whom the Software is
 * furnished to do so, subject to the following conditions:
 *
 * The above copyright notice and this permission notice shall be included in
 * all copies or substantial portions of the Software.
 *
 * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
 * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
 * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
 * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
 * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
 * OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
 * THE SOFTWARE.
 */
%{
extern void yyerror(char *);
extern int yylex(void);
%}

/* Multicharacter reserved words */
%token T_ASSERT    T_BREAK    T_CASE     T_CATCH    T_CLASS
%token T_CONST     T_CONTINUE T_DEFAULT  T_DO       T_ELSE
%token T_EXTERN    T_FOR      T_FORALL   T_IF       T_MATCH
%token T_NAMESPACE T_NEW      T_OPERATOR T_PROC
%token T_PROTECTED T_PUBLIC   T_RETURN   T_SWITCH   T_THROW
%token T_TRY       T_USING    T_VAR      T_WHILE    T_WITH
%token T_STATIC    T_LOOPBASE

%token T_FOREACH

/* Preprocessor symbols */
%token T_DEFINE T_INCLUDE

/* Other multicharacter tokens */
%token T_NAME T_INTCON T_FLOATCON T_STRING T_CHARCON T_MATCH_ARG
%token T_LCHARCON T_LSTRING

/* Punctuation */
%token T_SEMI T_COMMA T_EQUALS T_LBRACE T_RBRACE T_LPAR T_RPAR T_OR T_XOR 
%token T_AND T_LT T_GT T_PLUS T_MINUS T_STAR T_SLASH T_PCT T_NOT T_BANG 
%token T_DOT T_LBRAK T_RBRAK T_COLON T_AT T_QUEST T_STARSTAR T_BACKTICK

/* Two-char punctuation */
%token T_CONCAT T_EQEQ T_NOTEQ T_LE T_GE T_PLUSEQ T_MINUSEQ T_STAREQ 
%token T_SLASHEQ T_PCTEQ T_ANDEQ T_OREQ T_XOREQ T_LSHIFT T_RSHIFT 
%token T_ANDAND T_OROR T_PLUSPLUS T_MINUSMINUS T_EQGT T_QUEST_EQ
%token T_MATCHES T_MATCH_COUNT T_COLON_COLON T_HASH_EQ T_AT_AT
%token T_HASH_LBRAK T_HASH_LPAR T_QUEST_QUEST T_COLON_EQUALS

/* Three-char punctuation */
%token T_LSHIFTEQ T_RSHIFTEQ T_LLL T_RRR T_DOTDOTDOT

/* "Reverse" punctuation */
%token T_OR_R T_XOR_R T_AND_R T_LT_R T_GT_R T_PLUS_R T_MINUS_R T_BANG_MINUS
%token T_STAR_R T_SLASH_R T_PCT_R T_POW_R T_EQEQ_R T_NOTEQ_R T_LE_R T_GE_R
%token T_LSHIFT_R T_RSHIFT_R T_EQGT_R T_MATCHES_R

/* End-of-file marker */
%token T_EOF 

/* Handle the dangling else shift/reduce conflict */
%nonassoc T_THEN
%nonassoc T_ELSE

/* Handle the dangling :: shift/reduce conflict */
%nonassoc T_NAME
%nonassoc T_COLON_COLON

%%

program         : prog T_EOF { return 0; }
                ;

prog            : decl
                | prog decl
                ;

decl            : class_decl
                | var_decl
                | proc_decl
                | const_decl
                | include
                | using
                | define
                | public_decl
                | default_public
                | extern_decl
                | obj_decl
                | T_NAMESPACE T_NAME T_LBRACE prog T_RBRACE
                ;

class_decl      : T_CLASS qual_name proplist
                | T_CLASS qual_name T_LPAR qual_names T_RPAR proplist
                | T_CLASS qual_names T_SEMI
                ;

proplist        : T_LBRACE props T_RBRACE
                ;

props           : /* NOTHING */
                | props prop
                ;

prop            : T_PUBLIC oneprop
                | T_PROTECTED oneprop
                | oneprop
                ;

oneprop         : var_decl
                | const_decl
                | proc_decl
                | T_OPERATOR oper_decl
                ;

var_decl        : T_VAR vars T_SEMI
                | T_STATIC vars T_SEMI
                ;

vars            : var
                | vars T_COMMA var
                ;

var             : qual_name
                | qual_name T_EQUALS expr
                | qual_name T_COLON type 
                | qual_name T_COLON type T_EQUALS expr
                ;

type            : T_NAME
                | T_NAME T_LBRAK exprlist T_RBRAK
                | T_NAME T_LBRAK T_STAR T_RBRAK
                ;

const_decl      : T_CONST consts T_SEMI
                ;

consts          : name_init
                | consts T_COMMA name_init
                ;

name_init       : qual_name T_EQUALS expr
                ;

oper_decl       : operator no_name_proc
                ;

operator        : T_OR | T_XOR | T_AND | T_LT | T_GT
                | T_PLUS | T_MINUS | T_STAR | T_SLASH | T_STARSTAR
                | T_PCT | T_NOT | T_CONCAT | T_EQEQ
                | T_NOTEQ | T_LE | T_GE | T_LSHIFT | T_RSHIFT
                | T_LBRACE T_RBRACE
                | T_LBRAK T_RBRAK | T_LBRAK T_EQUALS T_RBRAK
                | T_HASH_LBRAK T_RBRAK | T_HASH_LBRAK T_EQUALS T_RBRAK
                | T_LPAR T_RPAR | T_EQGT | T_MATCHES
                | T_PLUSPLUS | T_MINUSMINUS
                | T_OR_R | T_XOR_R | T_AND_R | T_LT_R | T_GT_R | T_PLUS_R
                | T_MINUS_R | T_BANG_MINUS | T_STAR_R | T_SLASH_R | T_PCT_R
                | T_POW_R | T_EQEQ_R | T_NOTEQ_R | T_LE_R | T_GE_R
                | T_LSHIFT_R | T_RSHIFT_R | T_EQGT_R | T_MATCHES_R
                | T_COLON_EQUALS
                ;

include         : T_INCLUDE T_STRING
                ;

using           : T_USING using_decls T_SEMI
                ;

using_decls     : one_use
                | using_decls T_COMMA one_use
                ;

one_use         : T_NAMESPACE T_NAME
                | T_EXTERN T_STRING
                | qual_name
                ;

define          : T_DEFINE T_NAME T_LPAR names T_RPAR T_LBRACE defn T_RBRACE
                | T_DEFINE T_NAME T_LPAR T_RPAR T_LBRACE defn T_RBRACE
                ;

defn            : /* NOTHING */
                | defn token
                | defn T_LPAR defn T_RPAR
                | defn T_LBRACE defn T_RBRACE
                | defn T_LBRAK defn T_RBRAK
                | defn T_HASH_LBRAK defn T_RBRAK
                | defn T_HASH_LPAR defn T_RBRAK
                ;

token           : T_CLASS | T_VAR | T_CONST | T_PUBLIC
                | T_PROC | T_IF | T_ELSE | T_WHILE
                | T_BREAK | T_RETURN | T_INCLUDE | T_SWITCH
                | T_CASE | T_DEFAULT | T_FOR | T_DO | T_FORALL
                | T_CONTINUE | T_NEW | T_OPERATOR | T_PROTECTED
                | T_TRY | T_CATCH | T_THROW | T_ASSERT
                | T_DEFINE | T_NAME | T_INTCON | T_FLOATCON
                | T_STRING | T_CHARCON | T_LSTRING | T_LCHARCON
                | T_SEMI | T_COMMA | T_EQUALS | T_OR
                | T_XOR | T_AND | T_LT | T_GT
                | T_PLUS | T_MINUS | T_STAR | T_SLASH | T_STARSTAR
                | T_PCT | T_NOT | T_BANG | T_DOT
                | T_COLON | T_AT | T_CONCAT | T_EQEQ
                | T_NOTEQ | T_LE | T_GE | T_PLUSEQ
                | T_MINUSEQ | T_STAREQ | T_SLASHEQ | T_PCTEQ
                | T_ANDEQ | T_OREQ | T_XOREQ | T_LSHIFT
                | T_RSHIFT | T_ANDAND | T_OROR | T_PLUSPLUS
                | T_MINUSMINUS | T_EQGT | T_QUEST_EQ | T_LSHIFTEQ
                | T_RSHIFTEQ  | T_MATCH | T_MATCHES | T_MATCH_ARG
                | T_MATCH_COUNT | T_USING | T_NAMESPACE
                | T_QUEST | T_COLON_COLON | T_WITH | T_EXTERN
                | T_HASH_EQ | T_AT_AT | T_QUEST_QUEST
                | T_OR_R | T_XOR_R | T_AND_R | T_LT_R | T_GT_R | T_PLUS_R
                | T_MINUS_R | T_BANG_MINUS | T_STAR_R | T_SLASH_R | T_PCT_R
                | T_POW_R | T_EQEQ_R | T_NOTEQ_R | T_LE_R | T_GE_R
                | T_LSHIFT_R | T_RSHIFT_R | T_EQGT_R | T_MATCHES_R
                | T_COLON_EQUALS
                ;

public_decl     : T_PUBLIC names T_SEMI
                ;

default_public  : T_DEFAULT T_PUBLIC consts T_SEMI
                ;

extern_decl     : T_EXTERN names T_SEMI
                ;

names           : T_NAME
                | names T_COMMA T_NAME
                ;

qual_names      : qual_name
                | qual_names T_COMMA qual_name
                ;

obj_decl        : obj_decl_list T_SEMI
                | obj_decl_props
                ;

obj_decl_list   : obj_decl_noprop
                | obj_decl T_COMMA obj_decl_noprop
                ;

obj_decl_noprop : qual_name qual_name
                | qual_name qual_name T_LPAR exprs T_RPAR
                ;

obj_decl_props  : qual_name qual_name obj_proplist
                | qual_name qual_name T_LPAR exprs T_RPAR obj_proplist
                | T_DOTDOTDOT qual_name obj_proplist
                ;

obj_proplist    : T_LBRACE obj_props T_RBRACE
                | T_LBRACE obj_props T_DOTDOTDOT T_RBRACE
                ;

obj_props       : /* NOTHING */
                | obj_props prop_init
                ;

prop_init       : T_NAME T_EQUALS expr
                ;

proc_decl       : T_PROC qual_name T_LPAR args T_RPAR proc_body
                | T_PROC qual_name T_LPAR T_RPAR proc_body
                | T_PROC T_STRING qual_name T_LPAR args T_RPAR proc_body
                | T_PROC T_STRING qual_name T_LPAR T_RPAR proc_body
                | T_PROC qual_names T_SEMI
                ;

args            : T_NAME
                | T_NAME T_COLON type
                | args T_COMMA T_NAME
                | args T_COMMA T_NAME T_COLON type
                ;

no_name_proc    : T_LPAR names T_RPAR proc_body
                | T_LPAR T_RPAR proc_body
                ;

proc_body       : T_LBRACE stmts T_RBRACE
                | T_COLON type T_LBRACE stmts T_RBRACE
                ;

stmts           : /* NOTHING */
                | stmt stmts
                ;

stmt            : assign T_SEMI
                | call T_SEMI
                | ifstmt
                | whilestmt
                | dostmt T_SEMI
                | forstmt
                | forallstmt
                | switchstmt
                | matchstmt
                | withstmt
                | returnstmt T_SEMI
                | assertstmt T_SEMI
                | trystmt
                | throwstmt T_SEMI
                | breakstmt T_SEMI
                | continuestmt T_SEMI
                | var_decl
                | const_decl
                | using
                | printstmt T_SEMI
                ;

assign          : lhs T_EQUALS expr
                | lhs T_PLUSEQ expr
                | lhs T_MINUSEQ expr
                | lhs T_STAREQ expr
                | lhs T_SLASHEQ expr
                | lhs T_PCTEQ expr
                | lhs T_ANDEQ expr
                | lhs T_OREQ expr
                | lhs T_XOREQ expr
                | lhs T_LSHIFTEQ expr
                | lhs T_RSHIFTEQ expr
                | lhs T_PLUSPLUS
                | lhs T_MINUSMINUS
                ;

call            : lhs T_LPAR exprs T_RPAR
                | lhs T_HASH_LPAR exprs T_RPAR
                ;

lhs             : qual_name
                | lhs T_DOT T_NAME
                | lhs T_DOT T_LPAR expr T_RPAR
                | lhs T_LBRAK indices T_RBRAK
                | lhs T_HASH_LBRAK indices T_RBRAK
                | T_LPAR lhs T_RPAR
                ;

ifstmt          : T_IF T_LPAR expr T_RPAR body                  %prec T_THEN
                | T_IF T_LPAR expr T_RPAR body T_ELSE body
                ;

whilestmt       : T_WHILE T_LPAR expr T_RPAR body
                ;

dostmt          : T_DO body T_WHILE T_LPAR expr T_RPAR
                ;

forstmt         : T_FOR T_LPAR alst T_SEMI limit T_SEMI alst T_RPAR body
                ;

forallstmt      : T_FORALL T_LPAR expr T_RPAR body
                ;

alst            : /* NOTHING */
                | assign_list
                ;

assign_list     : one_assign
                | assign_list T_COMMA one_assign
                ;

one_assign      : assign
                | lhs
                | T_VAR T_NAME T_EQUALS expr
                | T_VAR T_NAME T_COLON T_NAME T_EQUALS expr
                | T_STATIC T_NAME T_EQUALS expr
                | T_STATIC T_NAME T_COLON T_NAME T_EQUALS expr
                ;

limit           : /* NOTHING */
                | expr
                ;

switchstmt      : T_SWITCH T_LPAR expr T_RPAR T_LBRACE cases T_RBRACE
                ;

matchstmt       : T_MATCH T_LPAR expr T_RPAR T_LBRACE cases T_RBRACE
                ;

cases           : /* NOTHING */
                | cases onecase
                ;

onecase         : T_CASE exprlist T_COLON stmts
                | T_DEFAULT T_COLON stmts
                ;

returnstmt      : T_RETURN expr
                | T_RETURN
                ;

assertstmt      : T_ASSERT expr
                ;

withstmt        : T_WITH T_LPAR expr T_RPAR T_LBRACE obj_props T_RBRACE
                ;

trystmt         : T_TRY body T_CATCH T_LPAR names T_RPAR body
                ;

throwstmt       : T_THROW expr
                ;

breakstmt       : T_BREAK
                ;

continuestmt    : T_CONTINUE
                ;

printstmt       : T_STRING
                | T_STRING T_COMMA exprs
                | T_LSTRING
                | T_LSTRING T_COMMA exprs
                ;

body            : T_LBRACE stmts T_RBRACE
                | stmt
                ;

exprs           : /* NOTHING */
                | exprlist
                ;

exprlist        : expr
                | exprlist T_COMMA expr
                ;

expr            : cond_expr
                | expr T_CONCAT cond_expr
                ;

cond_expr       : logor_expr
                | logor_expr T_QUEST expr T_COLON cond_expr
                ;

logor_expr      : logand_expr
                | logor_expr T_OROR logand_expr
                ;

logand_expr     : or_expr
                | logand_expr T_ANDAND or_expr
                ;

or_expr         : excl_or_expr
                | or_expr T_OR excl_or_expr
                ;

excl_or_expr    : and_expr
                | excl_or_expr T_XOR and_expr
                ;

and_expr        : equal_expr
                | and_expr T_AND equal_expr
                ;

equal_expr      : rel_expr
                | equal_expr T_EQEQ rel_expr
                | equal_expr T_NOTEQ rel_expr
                | equal_expr T_QUEST_EQ rel_expr
                | equal_expr T_MATCHES rel_expr
                | equal_expr T_HASH_EQ rel_expr
                ;

rel_expr        : shift_expr
                | rel_expr T_LT shift_expr
                | rel_expr T_GT shift_expr
                | rel_expr T_LE shift_expr
                | rel_expr T_GE shift_expr
                ;

shift_expr      : add_expr
                | shift_expr T_LSHIFT add_expr
                | shift_expr T_RSHIFT add_expr
                ;

add_expr        : mult_expr
                | add_expr T_PLUS mult_expr
                | add_expr T_MINUS mult_expr
                ;

mult_expr       : pow_expr
                | mult_expr T_STAR pow_expr
                | mult_expr T_SLASH pow_expr
                | mult_expr T_PCT pow_expr
                ;

pow_expr        : cvt_expr
                | cvt_expr T_STARSTAR pow_expr
                ;

cvt_expr        : unary_expr
                | cvt_expr T_EQGT unary_expr
                ;

unary_expr      : T_NOT unary_expr
                | T_BANG unary_expr
                | T_MINUS unary_expr
                | T_AT unary_expr
                | T_AT_AT unary_expr
                | T_QUEST_QUEST unary_expr
                | T_AND T_NAME
                | term
                ;

indices         : index
                | indices T_COMMA index
                ;

index           : expr
                | opt_expr T_COLON opt_expr
                | opt_expr T_COLON opt_expr T_COLON expr
                ;

qual_name       : T_NAME
                | T_NAME T_COLON_COLON T_NAME
                | T_COLON_COLON T_NAME
                ;

term            : qual_name
                | T_PUBLIC T_COLON_COLON T_NAME
                | T_LPAR expr T_RPAR
                | T_LPAR T_PROC T_RPAR          /* ID of current proc */
                | T_LBRACE exprs T_RBRACE       /* Array decl */
                | T_LLL exprs T_RRR             /* Dict decl */
                | T_LBRAK exprs T_RBRAK         /* Packed array decl */
                | T_LBRAK iterator T_RBRAK      /* Iterator */
                | T_STRING
                | T_LSTRING
                | T_INTCON
                | T_FLOATCON
                | T_CHARCON
                | T_LCHARCON
                | T_MATCH_ARG
                | T_MATCH_COUNT
                | T_LOOPBASE
                | T_NEW qual_name               /* The create args are parsed */
                | T_NEW T_LPAR expr T_RPAR      /* by the CALL syntax below */
                | T_PROC no_name_proc
                | T_PROC T_STRING no_name_proc
                | T_OPERATOR operator
                | T_BACKTICK operator
                | T_BACKTICK T_NAME             /* Same as public::name */
                | term T_LPAR exprs T_RPAR      /* This is the CALL syntax */
                | term T_LBRAK T_STAR T_RBRAK     /* For "Array[*]" */
                | term T_HASH_LPAR exprs T_RPAR
                | term T_DOT public
                | term T_LBRAK indices T_RBRAK
                | term T_HASH_LBRAK indices T_RBRAK
                | term T_LBRACE obj_props T_RBRACE /* For new and static obj */
                | T_FOREACH T_LPAR expr T_RPAR T_LBRACE expr T_RBRACE
                ;

iterator        : opt_expr T_COLON opt_expr
                | opt_expr T_COLON opt_expr T_COLON opt_expr
                ;

opt_expr        : /* NOTHING */
                | expr
                ;

public          : T_NAME
                | T_LPAR expr T_RPAR
                | T_OPERATOR operator
                | T_BACKTICK operator
                | T_BACKTICK T_NAME
                ;

gram.l

The following lex / bison program properly tokenizes correct OADL programs:

/*
 * Copyright (c) 1997 Ross Cunniff
 *
 * Permission is hereby granted, free of charge, to any person obtaining a copy
 * of this software and associated documentation files (the "Software"), to deal
 * in the Software without restriction, including without limitation the rights
 * to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
 * copies of the Software, and to permit persons to whom the Software is
 * furnished to do so, subject to the following conditions:
 *
 * The above copyright notice and this permission notice shall be included in
 * all copies or substantial portions of the Software.
 *
 * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
 * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
 * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
 * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
 * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
 * OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
 * THE SOFTWARE.
 */

%{
#include "y.tab.h"
#define YY_NO_UNISTD_H
int line_num = 1;
%}

%x str
%x comment

/* This is a major hack. Rather than try to hand-enumerate all the possible
 * UTF-8 encodings of letter and digit characters, just assume that all
 * multibyte encodings are, effectively, letter characters. This
 * will accept valid programs but will not properly error on invalid
 * ones.
 */
U       [\x80-\xbf]
U2      [\xc2-\xdf]
U3      [\xe0-\xef]
U4      [\xf0-\xf7]

UANY    {U2}{U}|{U3}{U}{U}|{U4}{U}{U}{U}

ALPHA           [a-zA-Z$_]|{UANY}
ALNUM           [0-9a-zA-Z$_]|{UANY}

DIGIT           [0-9_]
HEXDIGIT        [0-9a-fA-F_]
ESCAPE          [0abfnrtv]
ISIZE           [ubslUBSL]
FSIZE           [hdHD]

%%

L\"                             BEGIN(str);
\"                              BEGIN(str);
<str>\"                         BEGIN(INITIAL); return T_STRING;
<str>\\[0-7]{1,3}
<str>\\0[xX]HEXDIGIT+
<str>\\(.|\n)
<str>[^\\\n\"]+

L\'.\'          return T_LCHARCON;
\'.\'           return T_CHARCON;
\'\\.\'         return T_CHARCON;


{DIGIT}+{ISIZE}*                        return T_INTCON;
"0"[xX]{HEXDIGIT}+{ISIZE}*              return T_INTCON;

{DIGIT}+"."{DIGIT}*{FSIZE}*                 return T_FLOATCON;
{DIGIT}*"."{DIGIT}+{FSIZE}*                 return T_FLOATCON;
{DIGIT}+"."{DIGIT}*[eE]{DIGIT}+{FSIZE}*     return T_FLOATCON;
{DIGIT}*"."{DIGIT}+[eE]{DIGIT}+{FSIZE}*     return T_FLOATCON;
{DIGIT}+"."{DIGIT}*[eE][+-]{DIGIT}+{FSIZE}* return T_FLOATCON;
{DIGIT}*"."{DIGIT}+[eE][+-]{DIGIT}+{FSIZE}* return T_FLOATCON;
{DIGIT}+[eE]{DIGIT}+{FSIZE}*                return T_FLOATCON;
{DIGIT}+[eE][+-]{DIGIT}+{FSIZE}*            return T_FLOATCON;

"?"{DIGIT}+                             return T_MATCH_ARG;

case            return T_CASE;
continue        return T_CONTINUE;
default         return T_DEFAULT;
do              return T_DO;
else            return T_ELSE;
extern          return T_EXTERN;
for             return T_FOR;
forall          return T_FORALL;
foreach         return T_FOREACH;
if              return T_IF;
return          return T_RETURN;
switch          return T_SWITCH;
while           return T_WHILE;
break           return T_BREAK;
class           return T_CLASS;
var             return T_VAR;
const           return T_CONST;
public          return T_PUBLIC;
proc            return T_PROC;
"#include"      return T_INCLUDE;
new             return T_NEW;
operator        return T_OPERATOR;
protected       return T_PROTECTED;
try             return T_TRY;
catch           return T_CATCH;
throw           return T_THROW;
assert          return T_ASSERT;
"#define"       return T_DEFINE;
match           return T_MATCH;
using           return T_USING;
namespace       return T_NAMESPACE;
with            return T_WITH;
static          return T_STATIC;

{ALPHA}{ALNUM}* return T_NAME;

";"     return T_SEMI;
","     return T_COMMA;
"="     return T_EQUALS;
"{"     return T_LBRACE;
"}"     return T_RBRACE;
"("     return T_LPAR;
")"     return T_RPAR;
"|"     return T_OR;
"^"     return T_XOR;
"&"     return T_AND;
"<"     return T_LT;
">"     return T_GT;
"+"     return T_PLUS;
"-"     return T_MINUS;
"*"     return T_STAR;
"/"     return T_SLASH;
"%"     return T_PCT;
"~"     return T_NOT;
"!"     return T_BANG;
"."     return T_DOT;
"["     return T_LBRAK;
"]"     return T_RBRAK;
":"     return T_COLON;
"@"     return T_AT;
"?"     return T_QUEST;
"`"     return T_BACKTICK;

"**"    return T_STARSTAR;
"##"    return T_CONCAT;
"=="    return T_EQEQ;
"!="    return T_NOTEQ;
"<="    return T_LE;
">="    return T_GE;
"+="    return T_PLUSEQ;
"-="    return T_MINUSEQ;
"*="    return T_STAREQ;
"/="    return T_SLASHEQ;
"%="    return T_PCTEQ;
"&="    return T_ANDEQ;
"|="    return T_OREQ;
"^="    return T_XOREQ;
"<<"    return T_LSHIFT;
">>"    return T_RSHIFT;
"&&"    return T_ANDAND;
"||"    return T_OROR;
"++"    return T_PLUSPLUS;
"--"    return T_MINUSMINUS;
"=>"    return T_EQGT;
"?="    return T_QUEST_EQ;
"??"    return T_QUEST_QUEST;
"~="    return T_MATCHES;
"?#"    return T_MATCH_COUNT;
"::"    return T_COLON_COLON;
"@@"    return T_AT_AT;
"#="    return T_HASH_EQ;
"#["    return T_HASH_LBRAK;
"#("    return T_HASH_LPAR;
"?*"    return T_LOOPBASE;
"!-"    return T_BANG_MINUS;
"->"    return T_DOT;
":="    return T_COLON_EQUALS;

"\\|"   return T_OR_R;
"\\^"   return T_XOR_R;
"\\&"   return T_AND_R;
"\\<"   return T_LT_R;
"\\>"   return T_GT_R;
"\\+"   return T_PLUS_R;
"\\-"   return T_MINUS_R;
"\\*"   return T_STAR_R;
"\\/"   return T_SLASH_R;
"\\%"   return T_PCT_R;
"\\**"  return T_POW_R;
"\\=="  return T_EQEQ_R;
"\\!="  return T_NOTEQ_R;
"\\<="  return T_LE_R;
"\\>="  return T_GE_R;
"\\<<"  return T_LSHIFT_R;
"\\>>"  return T_RSHIFT_R;
"\\=>"  return T_EQGT_R;
"\\~="  return T_MATCHES_R;

"<<="   return T_LSHIFTEQ;
">>="   return T_RSHIFTEQ;
"<<<"   return T_LLL;
">>>"   return T_RRR;
"..."   return T_DOTDOTDOT;

<<EOF>> return T_EOF;

"//".*\n                line_num++;
"/*"                    BEGIN(comment);
<comment>[^*\n]*
<comment>"*"+[^*/\n]*
<comment>\n             line_num++;
<comment>"*"+"/"        BEGIN(INITIAL);

"/*".*"*/"
[ \t\r]+
\n                      line_num++;

%%

extern int yydebug;
extern int yyparse(void);

int main(int argc, char **argv)
{
    if( (argc > 1) && (strcmp(argv[1], "-d") == 0) ) {
        yydebug = 1;
    }

    if( yyparse() == 0 ) {
        printf("success!\n");
    }
}

void yyerror(char *s)
{
    printf("failure at line %d\n", line_num);
    exit(1);
}

int yywrap(void)
{
    return 1;
}