loom/doc/docsrc/lang-ref.org

34 KiB
Raw Permalink Blame History

Loom Language Reference

This document explains the syntax and semantics of Loom and its implementation. It is very terse.

Since Loom is mostly library, you'll probably also want to keep the library reference handy as well.

Syntax

Loom syntax consists of some very basic expressions and a number of readability transformations (i.e. "syntactic sugar"). The latter are all simple enough to make it easy to intuit the resulting code.

I've described the syntax in a notation that Emacs's antlr-mode seems to recognize but is almost certainly not valid Antlr. Still, it should be enough to get the point across.

The individual elements of Loom syntax are mostly taken from C++. As a result, the language (semi-intentionally) looks a bit like sclang.

Basic syntax

Initial stuff

Whitespace is not significant.

Comments are delimited by either # or // and run to the end of the line.

Currently, only ASCII is supported. Fixing that is a to-do item.

Literals
  literal : number_literal | string_literal ;

  number_literal : '-'? ( [0-9]+ ('.' [0-9]+)? | 0x[0-9a-fA-F]+ | 0b[01]+ ) ;

  string_literal : '"' ('\"' | '\\' | '\x' [0-9a-fA-F]+ 
                   | '\' [abfnrtv] | [^"]+ )* '"' ;

Numeric literals are what you'd expect in a C-like language. Floating point values take the usual form while binary or hexadecimal integers begin with 0b or 0x respectively. There is no support for octal.

String literals are also C-like, with the backslash (\) used as an escape. The usual \xHH syntax (where H is a hex digit) works as it does in C, as do the \<letter> sequences defined above.

Examples:

123
420.69
0b101010
0xb00b1375

"This is a string.\n"

"This is also a \"string\".  With a '\\'.\n"

A minus sign in front of a numeric literal with no separating whitespace will always be considered part of the literal. This is important since the - operator can be combined with other operator-like character.

For example:

1+-2            # 1 + -2
1+- 2           # 1 +- 2
1-<+-+>-2       # 1 -<+-+> -2
Atomic Expressions
    atomic_expression : name | quote | literal ;

    name : [_a-zA-Z][_a-zA-Z0-9]* | '`' [^`]* '`' ;

    quote: ':' '(' expression ')' | ':' name ;

Names generally follow the C syntax rules; that is, alpha-numeric plus the underscore but may not begin with a number. As in C, names are case-sensitive.

In addition, a name may be delimited with backticks (`). Such a name may contain any character that is not a backtick or a whitespace character that is not a space. (For now, other whitespace characters may work but are not guaranteed to.)

Quotes (see below) are delimited by :( and ) and may contain any expression. As a special case, a name preceded by a : is equivalent to the full quote; this yields a Symbol.

Examples:


some_name
_bofa69
`!!! also a name!!!`

:( 2 + 3 )
:(a_symbol)

:a_symbol
:`also a symbol`
Message Expressions
    expression : atomic_expression | message_expression ;

    message_expression : expression '.' name '(' argument_list ? ')' ;

    argument_list : expression ( ',' expression )* ','?

This is the basic message send (i.e. "method invocation" or "member function call"). It looks like a typical C++ or Java method call. The object is to the left of the . and the method name is to the right. Arguments in in the parameter list. Loom tolerates a trailing comma.

Examples:


2.add(3).divide_by(42)
Top-level evaluation
    toplevel : /* nothing */ | expression (';'+ expression)* ';'*

The input stream is just a sequence of expressions separated by ;. Empty expressions and tailing semicolons are tolerated.

Transformations

Loom provides a number of syntactic constructs ("syntactic sugar") that make programming easier. All of them are expanded into Loom expressions in a fairly transparent way.

This section documents them.

Message Send Expression Cleanup

A number of transformations will normalize message send expressions in various ways, making the syntax more readable and forgiving.

  1. Empty argument lists may be omitted:

    thing.msg                   =>  thing.msg()
  2. Messages whose names are composed of one or more of the following "operator" characters and that are not = have special syntax:

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

    The '.' operator and trailing parentheses are both optional:

    2 + 3 + 4                   => 2.`+`(3).`+`(4)
    a + (b * c)                 => a.`+`(b.`*(c))
    2+-3                        => 2.`+`(-3)

    Note (as shown above) that an unparenthesized method call has the highest priority and so will receiver only the next complete expression.

    Note also that a minus sign immediately followed by a digit is considered part of that numeric literal and not a preceeding "operator" message.

  3. Trailing blocks (see below) that appear at the end of a message send are added to the argument list:

    thing.msg {thing}           => thing.msg({thing})
    thing.msg {thing} {thing2}  => thing.msg({thing}, {thing2})

    This mixes with parenthesized argument lists as well:

    thing.msg(1) {thing}        => thing,msg(1, {thing})
  4. If the message has no arguments and no empty parameter list and is followed by '=', this expands into a setter method call:

    thing.msg = i               => thing.msg_(i)

    That is, an underscore ("_") is added to the method name and the RHs expression becomes its argument.

Array-subscript-like methods

An expression followed by another expression in square brackets ("[" and "]") is expanded to the message at, with the inner expression converted into its argument:

thing[i]                    => thing.at(i)

If this expression is followed by the token "", it is instead turned into ~atPut~, with the expression following the "' token used as as the second argument:

thing[i] = j                => thing.atPut(i, j)

Note that the RHS is parsed greedily; the parser will continue to consume expression elements as long as possible:

1 + (v[3] = 2 + 3 * 5)      => 1.+(v.atPut(3,2.+(3).*(5)))
Name aliases

The following lowercase names are replaced with their uppercase equivalents:

= true false nil self here =

In addition, this is replaced by Self.

This is strictly a convenience thing. Loom constants are all capitalized but these values are commonly lower-case so the parser converts them to make them look like keywords.

Vector creation

  # Square-bracket-delimited lists expand to ~Vector.with(...)~ calls:
  [1, 2+3, 4]                 => Vector.with(1, 2+3, 4)

  # Note that ~Vector~ is the global object, *not* the name.  The
  # following still works as expected:
  {|Vector| [1,2,3]}.call(42) => Here.getglobal(:Vector).with(1,2,3)

  # (The actual implementation looks up the global ~Vector~ at "compile"
  # time and just uses it directly.)

  # Prefixing it with a colon quotes each element in turn:
  :[1, 2+3, foo]              => Vector.with(:(1),:(2.+(3)),:(foo))

  # This is different from quoting the array definition; that expands to
  # the first style but quotes the expression:
  :( [1, 2+3, foo] )          => :( Vector.with(1,2.+(3),foo) )
Variable Assignment

  # An expression prefixed with a bare word followed by ~=~ expands into
  # an assignment operation via ~Here.set~.  The name is quoted and
  # becomes the first ~set~ argument; the expression itself becomes the
  # second argument:
  total = 2 + count           => Here.set(:total, 2.`+`(count))
Return Statement

  # An expression beginning with the word ~return~ and containing an
  # optional expression expands to a call to ~return~ method the calling
  # method's (*NOT* block's) Here value.  This is done by first calling
  # ~Here.method_scope~.
  return n                    => Here.method_scope.return(n)

  # The expression following the ~return~ is essentially a toplevel
  # expression and can be arbitrarily complex.
  return 2+(n*3).sproing      => Here.method_scope.retur(2+(n*3).sproing)


  # If the trailing expression is omitted, ~self~ is implied:
  return                      => Here.method_scope().return(Self)
Global Definitions

  # The word 'def' followed by an assignment expression as defined above
  # defines the given name as a global variable.  (Upper-case names are
  # always constants.)
  def Thing = ThingClass.new    => Here.defglobal(:Thing, ThingClass.new,
                                                  "Thing")

The third argument is the name of the variable that is the target of the assignment. defglobal will set it to the value's annotation if the object supports it. This is how (e.g.) classes are able to know their own names.

ProtoMethods and Blocks

Block and method definitions are both built on ProtoMethod definitions. Since the latter are complex, I'm going to explain them first and then present the others in terms of that.

A ProtoMethod is a relatively simple class that holds all of the values needed to define a method or block. It is a slotted object with five readable fields:

  • args is a Vector of Symbols, possibly empty, containing the list of positional arguments. Capitalized names are allowed.
  • restvar is a symbol representing the name of the variadic argument (or nil, if not present). During a function call, all remaining actual arguments that are not bound to the formal arguments in args are put into a Vector which is assigned to restvar. restvar may be capitalized.
  • locals is a Vector of Symbols, possibly empty, containing the names of all non-argument local variables. Names should not be capitalized.
  • body is a Vector containing the function's body as sequence of Loom objects. (See 'Execution Model' below.)
  • annotation is either nil or a String. If it's a String, it is sometimes displayed in error messages or debugging text. Typically, it is set to the name of the method that this ProtoMethod will eventually create.

Actual Loom methods and blocks are opaque objects whose definition is implementation defined. ProtoMethod provides the methods for creating them.

Loom provides transformation for creating a ProtoMethod construction expression. This is probably the most complex transformation the language has.

Informal BNF is:

  protomethod :       ":{" block_body ;

  block_or_method :   "{" block_body ;

  block_body :        args_and_locals? body? "}" ;

  body :              expression (";" expression)* ";"? ;

  args_and_locals :   arg_list local_list? ;

  local_list :        "|" (name_list ","?) ? "|" ;

  arg_list :          local_list                      |
                      "|" "*" name "|"                |
                      "|" name_list "," "*" name "|"
                      ;

  name_list :         name ("," name)* ;

ProtoMethod transformations are used for actual ProtoMethods as well as Blocks and Methods. In the former case, the definition begins with :{ rather than just {.

(Note that for brevity in the examples below, I use square brackets to present vectors. The actual transformation expands into the full Vector.with(...) expression.)


  # Blocks with no arguments or locals can leave off the empty
  # declaration.
  :{42}                        => ProtoMethod.new([],nil,[],:[42],nil)

  # Block bodies consist of a sequence of expressions separated by
  # semicolons.  These are passed via argument 4 of ~ProtoMethod.new~:
  :{self.foo; self.bar}        => ProtoMethod.new([],nil,[],
                                                  :[Self.foo(),Self.bar()],nil)

  # Blocks with locals and arguments must declare them in two groups of
  # declarations, each delimited by ~|~.  Arguments and locals are passed
  # via arguments 1 and 3 respectively.
  :{|a| |b| b = a; a}          => ProtoMethod.new(:[a], nil, :[b],
                                                  :[Here.set(:(b),a)),a], nil)

  # Blocks with only arguments can omit the second declaration group but
  # blocks with only local variables need to provide an empty argument
  # list:
  :{|a| a+1}                   => ProtoMethod.new(:[a],nil,[],:[a.+(1)],nil)
  :{|| |a| a = 1}              => ProtoMethod.new(([],nil,:[a],
                                                  :[Here.set(:(a),1)],nil)

  # Variadic arguments are specified by prefixing the final argument
  # with an asterisk ('*').  This is passed via argument 2.
  :{|*a| a.size}               => ProtoMethod.new([],:a,[],:[a.size],nil)

Blocks (i.e. lambdas) differ only from ProtoMethod definitions by beginning with { instead of :{. The block expands exactly the same was as a ProtoMethod but the resulting ProtoMethod.new(...) expression has a make_block(Here) message appended.

  # Blocks are just ProtoMethod instantiations with an added call to
  # 'make_block'.
  {|a|a+1}                      => ProtoMethod
                                      .new(:[a], nil, [], :[a.+(1) ],nil)
                                      .make_block(Here)
Method Definitions

This is the basic shorthand for method definitions.


method_definition : name ("::" | "::*" ) name "=" block_or_method

The first element is the name of the class or object to extend. It is not any other kind of. It is looked up in the current context, however.


  # Inner method definition
  String::boing = {"boing! " + self .println }
      => String.inner_add_method(
          :boing,
          ProtoMethod.new(...)
              .make_method(String.slots)
              )

  # Outer method definition
  String::*new_boing = { return "boing" };
      => String.add_method(
            :new_boing,
            ProtoMethod.new(...).make_method(String.outer_slots())
            )

Execution model

A Loom function (i.e. a method or block) consists of a list of objects. They are evaluated from front to back.

Here is a notional (hypothetical) interpreter:

  LoomInterp::interp = { |context, body|
      |result|

      body.each {|expr|
          result = self.eval(context, expr);
      };

      // Methods return self rather than the last result
      self.is_method.if { result = self };
      return result;
  };

  LoomInterp::eval = {|context, expr|
      // Bare symbols are variables; we just look them up.
      expr.is_a(Symbol) .if { return context.get(expr) };

      // Quotes just yield the quoted value
      expr.is_a(Quote) .if { return expr.value };

      // MsgExpr must be evaluated.
      expr.is_a(MsgExpr) .if { ||
          |receiver, args, method, new_context|

          // Recursively evaluate the subexpressions
          receiver = self.eval(context, expr.receiver);
          args = expr.args.map{|arg| self.eval(context, arg) };

          // Find the method, create a new context for it and then run
          // it.  This is kind of a handwave.
          method = receiver.find_method(expr.message);
          new_context = Context.for_method(receiver, method, context);

          // And evaluate it
          return self.interp(new_context, method.body);
      };

      // Everything else just evaluates to itself.
      return expr;
  };

There's some detail missing here (as well as error detection), but this is the basic interpreter loop. Block evaluation isn't covered here but it mostly just boils down to Block::call invoking LoomInterp::interp.

I've also skipped over what happens if the message can't be found. (It just sends _does_not_understand with the message and arguments instead.)

Method lookup semantics are explained below.

Failure

When I talk about something failing, it means that it results in an exception being thrown.

This section is a placeholder for what that means, precisely.

Currently, it's an exception that can't be caught by Loom code (and so is fatal) but is caught by the REPL. So that's a helpful thing. Probably, there's going to be some rudimentary catch mechanism shortly.

Variables and Scopes

  1. Variables are names containing a reference to an object. They are not containers holding the value as in (e.g.) C structs. They are more like pointers to the actual object as in Lisp, Smalltalk, Ruby, or Python. Copying a variable does not copy the underlying object.
  2. Scoping is lexical. Name resolution is as follows:

    • current block
    • enclosing block(s), starting from the innermost and working outward.
    • current method's local variables
    • current object's (i.e. self's) instance variables (i.e. "slots"). (If self inherits instance variables from superclass(es), they are all in this namespace.)
    • the global scope
  3. Evaluating a variable (i.e. looking up its values) is done by the interpreter when it find an unquoted symbol as described above.
  4. Writing to variables is done exclusively via the current Context object Here via the following methods:

    • set, which follows the standard scoping rules.
    • setglobal, which skips directly to the global namespace.
  5. It is also possible to read variables via the Context:

    • get looks up a name in the usual way.
    • getglobal looks for the name in the global context.
    • has and hasglobal test for the existence of the variable in the same way.
  6. Variables must be declared before they are used.

    • Global variables are defined and initialized via Context::defglobal
    • slots are usually defined via the slots class method, but can also be added using the method add_slot.
    • local variables (block and method) are defined in the preceding ProtoMethod.new(...) expression. (This is usual done via the block syntax as described above).
    • Caveat: name checking happens when the code is defined. With Blocks inside of method bodies (which we use a lot), this doesn't happen until the outer method or function is actually invoked so in practice, it doesn't happen at "compile" time. (There's library code in place to do this, however.)
  7. Capitalized names are immutable; attempting to assign one to a different value will fail.

    • defglobal works as expected but the initial value is permanent.
    • Function (i.e. method or block) arguments may be capitalized; that makes them immutable.
    • capitalized slots or local variables may or may not be allowed. If they work, they will only ever have a value of nil. Don't use them. If you do, don't expect them to continue to work the way they do now.

Quoting

A Quote is an object which holds one other value. When evaluated by the (notional) interpreter, the result is the wrapped value. This allows us to pass around objects that would otherwise be evaluated.

Objects and Classes

The Loom object system is a class-based object system built on top of a prototype-based system. I did it this way because I suspect that it's easier to incrementally develop a system this way.

Objects

  1. Everything is an object. Everything is done by sending a message to an object. Message sends almost always result in invoking a corresponding method and returning its result. The term "method dictionary" refers to the set of named methods belonging to an object.
  2. Most objects contain slots (aka instance variables). These are named variables visible only to its methods and those of its delegates. (But see 'Fundamental Types' below.)
  3. Objects can contain methods which are invoked by the corresponding message send. They can also have one or more delegatesobjects which are searched for a method if it is not present.

    • Delegates must be traits. This is an arbitrary limitation that I put in, drunk with power, to encourage you to do class-based OOP.
  4. Traits are a special kind of object intended to help reuse code. They contain a second set of methods in a different namespace which we call "inner methods" in the "inner method dictionary". They are invoked only when the trait is another object's delegate and the method search has reached the trait.

    • When a trait is another object's delegate, the method search goes through the trait's inner methods only.
    • Traits also have inner delegates. These are searched in the usual way. As expected, inner delegates must also be traits and their inner methods and delegates are searched exclusively.
    • By extension, ordinary (non-inner) methods are called "outer methods".
    • Sending a message to a trait directly invokes the corresponding outer method, exactly as would happen with any other kind of object. Like other objects, traits may have outer delegates but these must be traits.

Method Lookup Semantics

When sending a message to an object,

  1. The object and its delegates are searched for a method with that name. If one is found, it is invoked with the arguments and the result is returned.

    • If the argument count does not match the number of expected arguments, it is an error.
  2. If there is no method with that name, the message _does_not_understand is sent instead with the the same argument list but with the message name prepended. If that succeeds, its result is returned instead.
  3. If no method named _does_not_understand is found, execution fails.

Method search happens as follows:

  1. The receiver's outer method is searched and if a method is found, it is used.
  2. Each of the receiver's outer delegates is searched in turn, depth-first. That is, We perform step 3 on each of these.
  3. For each delegate:

    • the inner method dictionary is searched for a matching name. If one is found, it is used.
    • otherwise, we perform step 3 on each of the inner delegates, quitting if we find a match.
    • if nothing is found, we go on to the next delegate.
  4. If nothing is found, the search has failed.
super_send

In addition, it is possible to start the search at the delegates of the class that owns the method that is initiating the search. (This is not necessarily self.) We care about this when we have overridden a superclass/delegate method but want to call it anyway.

This is done via the method Context::super_send, called on Here. It takes the message name and list of arguments and performs the message send.

Note that the method search stops at the method owner's delegates. It does not proceed to self's other delegates, if those exist.

(For example, if A delegates to B and C and both B and C implement method foo, if B::foo does a here.super_send(:foo), this will fail; it will not invoke C::foo.)

Classes

Philosophically, a class defines an object's type. In Smalltalk (as well as Ruby and Loom), it also acts as a repository for the object's code and perhaps acts as a factory that creates new objects of this type.

In Loom, the convention for classes is this. A class is a Trait which:

  1. Provides a factory method (typically called new) which creates a new object that has the class as its first delegate.
  2. Provides (possibly via delegation) an inner method named initialize, which is typically called by new and receives its arguments.
  3. Defines an outer method named slots that returns a (possibly empty) vector of symbols containing names in a consistent, well-defined order. A class's slots must return the result of its superclass's slots with its own slot names appended. slots is expected to always return the same value.

All of this is already implemented using Loom objects as follows:

  1. Most objects have a single outer delegate, which is their class. The common method 'class' returns this.
  2. Class objects have an inheritance heirarchy starting at Object. These are all traits; they inherit by making the superclass their first inner delegate. The inheritance heirarchy is pretty conventional. Object also provides a stub initialize method.
  3. Class objects are instances of (i.e. have as their first outer delegate) class Class. This provides the common interface:

    • slots and new, as expected.
    • subclass to create subclasses.
    • add_inner_method and friends, to access the inner method dictionary.
  4. Class-specific class methods are just outer methods of the class object.

As a result, using the class system is pretty simple and straightforward.

You create a class by sending subclass to its parent:

  def Complex = Object.subclass(:[real, imaginary]);

This creates a new Class instance with the correct new and slots methods. Since new takes a variadic argument list and passes it to initialize, we just need this

  Complex::initialize = {|r, i|
      real = r;
      imaginary = i;
  };

and now we can create instances with

  x = Complex.new(1, 1);

AddonTraits

AddonTraits are traits that can be added to classes as (non-class) delegates. They may not be a class's first delegate. An AddonTrait must:

  1. Contain only inner methods
  2. That do not directly reference any slots.

They may only interact with the object to which they belong by sending messages to self.

It's possible that in the future, some of these restrictions may be lifted.

Methods and Blocks

Loom has two kinds of functions (or procedures, if you want to be pedantic): methods and blocks.

Common Properties of Loom Procedures

Procedures (i.e. methods or blocks) have (optionally) local variables, formal arguments and a variadic argument list.

    {|a1, a2| |l1, l2| a1 = l1; a2 = l2 }

Formal arguments must match the number of arguments when called; otherwise, it is a runtime error.

Local variables are initialized to nil.

Variadic arguments are also supported:

    {|a1, a2, *rest| |l1| l1 = a1 + a2 + (rest.sum) }

The final argument is variadic if it is preceded by an asterisk ("*") (or is set as the restvar value of the corresponding ProtoMethod). When the procedure is invoked, it is set to a Vector containing all remaining arguments.

In addition to the declared local variables, a variable named Here (with here as a syntactic alias) is also present. This references to the current Context and is used to (among other things) write to variables.

Methods

Methods each belong to an object and have a name. They are invoked when the owning object (or a delegator) receives the corresponding message.

In addition to the locals above, methods have a local variable named Self (with self as a syntactic alias) that refers to the current object. This is the object that received the message, not (necessarily) the object that owns this method.

If Self has slots, they are visible to the method as variables.

Thing::do_it = {|a| self.combine(a, some_slot) };

By default, a method returns a reference to Self. To return a different value, you will need to use the return statement:

Thing::total = { return foo + bar + quux };

return is syntactic sugar for Here.method_scope.return(...). In the case above, this is equivalent to Here.return(...); however, when called inside a Block, this would return from the block instead. The Here.method_scope returns the Context object corresponding to the current method call scope (which may be Here if called from the method body directly).

This way, something like this will work as expected:

Thing::got_it = { it != nil .if { return true }; return false };

Primitive Methods

Primitive methods are methods that are part of the underlying language implementation and so are (typically) written in compiled native code. They are opaque objects but can otherwise be invoked or renamed in the same way as ordinary methods.

Primitives fail either by throwing a Loom exception or by exiting the process.

Blocks

Blocks are lambdas, by which I mean

  1. anonymous functions
  2. defined inside either a method or another block
  3. whose variable scope extends outward to the containing blocks and methods.

Blocks are also objects. They are invoked by calling their call method with the appropriate arguments.

Unlike methods, blocks return result of their last expression by default.

In this method,

  Thing::doot = {|a| |b| b = 42;
      {|c|
          {|d| return [a,b,c,d] }.call("d == this");
      }.call(123);
  };

the inner block can resolve varibles a, b and c defined in outer scopes:

> Thing.new.doot(:thing)
[:thing, 42, 123, "d == this"]

As with Smalltalk, Lisp and all other right-thinking languages, the outer context persists, so you can do stuff like this:

> def x = {|| |n| n = 0; { n = n + 1; n } }.call
Block(0,"x")
> x.call
1
> x.call
2
> x.call
3

In this example, we've defined a block that returns a second block and called it, storing the result (the inner block) in variable x. This block increments and then returns the value of n, which was defined and initialized by the outer block. This is because x is keeping the outer block's context alive and continues to manipulate it.

Blocks are also used to implement most of Loom's control flow.

The Lobby Object

When Loom evaluates an input expression from a source file or the REPL, these expressions are first turned into (unnamed(!)) temporary methods of an object named (via global variable) Lobby. This allows us to (e.g.) define a block in a top-level expression.

The Lobby is just an instance of class Object. It has several slots and more can be added if needed. In addition, it holds a small number of utility methods.

We can also use the Lobby to simulate procedural programming by defining outer methods in it and treating them as procedures:

> self::*greet = {"Hello, world!".println};
Method("(Unnamed Object).greet")
> self.greet
Hello, world!

Exceptions

Loom also has exceptions. They go thrown in at the last minute, but they're there and (probably) work.

We throw an exception with Context::throw():

here.throw("oopsie!");

The argument to throw must be a subinstance of class Object.

This will exit the current program if it is not caught. We catch exceptions with Block::catch():

{ self.do_thing() }.catch(String) {|e| "Error: " + e .println };

If the first block results in an exception being thrown and the corresponding object's type is an instance or subinstance of the class passed as the first argument to catch, the second block will be evaluated with the exception object as its parameter. It is perfectly fine to rethrow an exception from here.

This works with any object that's an instance of a Class. However, the system library also provides class Exception and several subclasses. You should only ever throw an instance of one of these so that we can reliably catch all exceptions as needed.

Layouts (i.e. fundamental types)

All of the classes in Loom that you will need to define are slotted classes. That is, they contain zero or more named instance variables. However, there are types that do not fit this model (e.g. strings, number, symbols, etc.) This is a common property of dynamic OOP languages.

The underlying semantics of these types (what I call the "layouts" here) are implementation details, and so it's common for languages in this space to treat them as a shameful secret, like that strange woman in certain pictures of Grandpa. And on one hand, this is reasonable. Implementation details are not part of the language specification.

However, these things can lead to wierd, quirky behaviours that make no sense unless you understand what's happening, but should never ever depend on. So in the spirit of healthy transparency, I'm going to document some of this stuff.

Caveat: this stuff is all in the "fun fact" category of documentation. The canonical description for what a class should or should not be able to do is in that class's documentation. (Assuming I'm doing this right. LOL.)

In the current implementation of Loom, these are C++ classes. Currently, the following are used:

  1. slotted - the default thing with named fields.
  2. vector - this holds instances of class Vector. It's a resizeable 1-dimensional array of object references. Currently implemented using the C++ class std::vector.
  3. nilobj - the type of the object nil.
  4. number - this holds instances of class Number; they can be an integer or floating-point value. Type promotion is handled internally.
  5. string - holds instances of class String; contains a C++ std::string.
  6. symbol - holds instances of class Symbol.
  7. trait - holds a second set of named methods. Instances of Class and AddonTrait have this layout.
  8. quotebox - holds instances of class Quote. Each one contains a reference to a single object. Their primary purpose is to delay evaluation of their contained object when interpreted. It could probably be done with a slotted layout, but this way it's easier for the interpreter to recognize a Quote.
  9. primitive_method - holds those instances of class Method that contain a C++ function.
  10. user_method - holds those instances of class Method that were defined in Loom code. Instances are usually created by methods of class ProtoMethod; explicitly creating one with new may or may not work.
  11. context - holds instances of class Context. These are created exclusively by the interpreter when a method or block is invoked.
  12. opaque - holds instances of class Opaque. Each one contains a pointer to a C++ object that is inaccessible from Loom code. This is used to pass values between primitive_method objects that are only useful to them.

Some of these could probably be eliminated easily enough and replaced with the slotted layout. Others could be done much more efficiently. Integers and symbols are both typically embedded in the pointer itself; that's something I should do.