About rubber-lang

Nim programming language scripting macros bytecode interpreter

An experimental embeddable lisp-like statically-typed scripting language with support for value types and compile-time metaprogramming. Features a register-based bytecode interpreter, sweet sexp syntax, macros, fibers and more!

Work in progress -- rubber-lang still has lots of rough edges which make it unsuitable for general use. For example, it doesn't track source file line numbers and doesn't attempt to give good error messages at all.

Example

func fib(n i32,) i32:
  if n <= 1:
    n
  :else:
    fib(n - 1) + fib(n - 2)
vmEcho fib(10)

rubber playground

Screenshot of rubber playground
rubber playground running a wasm4-like game

Try out rubber-lang @ rubber playground directly in your web browser!

It implements support for a wasm4-like API, allowing games to be made using rubber-lang scripting!

Try out rubber-lang @ rubber playground

Features

Key Features include:

Other stuff:

Structs as value types

The biggest reason why rubber-lang exists is to fulfill my desire for having an embeddable statically-typed scripting language that supports structs as value types which can be allocated on the stack. This property is extremely important for game scripts that do a lot of vector math, as it helps to avoid lots of heap allocations, which greatly reduces pressure on the garbage collector. This means that rubber-lang doesn't need to have a sophisticated garbage collector to be performant either.

const Vec2i = tstruct: # define a struct type
  x i32
  y i32

# Use the makeStruct macro to construct struct values:
var a = makeStruct Vec2i:
  x = 10
  y = 20

var b = makeStruct Vec2i:
  x = 10
  y = 20

vmEcho(a == b) # true as values are equal (value semantics)
var c = b # copy `b` to `c`
c.x = 30 # modify `c`
vmEcho(a == b) # still true as `b` remains unmodified

Register-based bytecode interpreter

Inspired by Lua's virtual machine design, rubber implements a register-based bytecode interpreter. In comparison to stack-based interpreters, register-based interpreters can do more per bytecode instruction as they can load and store values to/from registers directly, thus increasing code density and program execution speed. This is important for rubber-lang which encourages an imperative programming style where values are frequently loaded and stored from local variables.

For example, this function squaredLength:

func squaredLength(x y f32,) f32:
  x * x + y * y

is compiled into the following register-based bytecode:

vopMulFloat32 r3, r1, r1
vopMulFloat32 r4, r2, r2
vopAddFloat32 r0, r3, r4

as opposed to this hypothetical stack-based bytecode which needs to perform more operations:

push_arg 0
push_arg 0
mul_float32
push_arg 1
push_arg 1
mul_float32
add_float32
set_return 0

Sweet sexp syntax

rubber-lang implements a base s-expression syntax, where instead of using parentheses it uses curly brackets instead:

A factorial function written in rubber-lang's raw sexp syntax
{func {factorial {n i32}} i32
  {if {<= n 1}
    1
  else
    {* n {factorial {- n 1}}}}}
{vmEcho {factorial 4}}

Inspired by the Readable Lisp S-Expressions Project, rubber-lang implements its own version of "Sweet S-Expressions" on top, as a form of syntactic sugar which brings its syntax closer towards more indentation-based mainstream programming languages, while keeping its underlying sexp list-based AST for straightforward AST manipulation via macros:

Equivalent factorial written in sweet sexp syntax
func factorial(n i32,) i32:
  if (n <= 1):
    1
  :else:
    n * factorial(n - 1)
vmEcho factorial(4)

Sweet s-expressions implement the following:

If needed, one can escape into raw sexps anywhere (although the reverse is not possible):

Equivalent factorial written in a mix of raw and sweet sexp syntax
func factorial({n i32}) i32:
  if (n <= 1):
    1
  :else:
    {* n {factorial {- n 1}}}
vmEcho factorial(4)

This is useful when it is clearer to write down the raw syntax tree structure itself instead of relying on the sweet sexp magic.

Compile-time evaluation and metaprogramming

The rubber-lang semmer is able to call into the rubber virtual machine when compiling scripts. This means it can perform compile-time evaluation. As it uses the exact same virtual machine that is used to run compiled scripts, this means that all features of rubber-lang are available without restriction (unless specifically restricted by the host).

Compile-time evaluation can be invoked using const in rubber-lang. This can be used, for example, to implement a hexToBytes() helper function that runs at compile time:

func hexToBytes(text pbuf(char),) pbuf(u8) _export_:
  var i = 0
  var dstIdx = 0
  var l = text.len
  var o = pbufAlloc(u8, l >> 1)
  loop:
    ifThen ((i + 1) >= l) break()
    var x0 = u32(text[i])
    var tmp0 = x0 >> 6
    var v0 = ((x0 & 15.u32) + tmp0 + (tmp0 << 3)) & 15.u32
    x0 = u32(text[i+1])
    tmp0 = x0 >> 6
    var v1 = ((x0 & 15.u32) + tmp0 + (tmp0 << 3)) & 15.u32
    o[dstIdx] = u8(v0 << 4 | v1)
    i = i + 2
    dstIdx = dstIdx + 1
  o

# usage
const HelloWorldBytes = hexToBytes "68656c6c6f20776f726c64"

vmEcho HelloWorldBytes # "hello world"

Such a helper function is useful for embedding binary data in a rubber script.

The virtual machine itself can call back into the semmer, which is used by rubber-lang to implement macros that can be used to perform compile-time metaprogramming.

Macros can examine the (typed or untyped) AST passed into them as arguments and transform them. For example, this is an implementation of a trace macro that transforms a statement block such that each source statement sexp is printed using vmEcho before running:

macro trace(body untyped,) untyped _varargs_:
  var bodylst = body.list
  var nstmts = bodylst.len
  var outbody = wbufAlloc(sexp, (nstmts << 1) + 1)
  outbody[0] = "block".sexpSym
  var i = 0
  loop:
    if not(i < nstmts) break()
    outbody[(i << 1) + 1] = sexpList("vmEcho".sexpSym, bodylst[i].repr.sexp)
    outbody[(i << 1) + 2] = bodylst[i]
    i = i + 1
  outbody.sexp

func gcd(a b i32,) i32:
  loop:
    trace:
      if not(b > 0) break()
      var c = a % b
      a = b
      b = c
  a

trace:
  var x = gcd(453, 849)
  vmEcho strJoin("gcd is ", x.str)

Macros are useful for statically-typed programming languages as their code generation capabilities allow the reduction of tedious boilerplate arising from satisfying the type checker.

The system module

The system module is implicitly imported into every module. It does the following:

Source of the system module
const (void () _builtin_("@TVoid") _export_)
const (i8 () _builtin_("@TInt8") _export_)
const (i16 () _builtin_("@TInt16") _export_)
const (i32 () _builtin_("@TInt32") _export_)
const (i64 () _builtin_("@TInt64") _export_)
const (u8 () _builtin_("@TUint8") _export_)
const (u16 () _builtin_("@TUint16") _export_)
const (u32 () _builtin_("@TUint32") _export_)
const (u64 () _builtin_("@TUint64") _export_)
const (char () _builtin_("@TChar") _export_)
const (f32 () _builtin_("@TFloat32") _export_)
const (f64 () _builtin_("@TFloat64") _export_)
const (bool () _builtin_("@TBool") _export_)
const (sexp () _builtin_("@TSexp") _export_)
const (word () _builtin_("@TWord") _export_)
const (typed () _builtin_("@TTyped") _export_)
const (untyped () _builtin_("@TUntyped") _export_)
const (undefined () _builtin_("@TUndefined") _export_)

const (true () _builtin_("@ELit" "@TBool" 1) _export_)
const (false () _builtin_("@ELit" "@TBool" 0) _export_)

macro tfn(rettyp untyped, argtyps untyped) void _varargs_ _builtin_("@TFn" rettyp argtyps) _export_
macro ttype(a typed,) typed _builtin_("@TType" a) _export_
macro pbuf(a typed,) typed _builtin_("@TBuffer" a) _export_
macro wbuf(a typed,) typed _builtin_("@TMlist" a) _export_
macro ptr(a typed,) typed _builtin_("@TPtr" a) _export_
macro wtr(a typed,) typed _builtin_("@TRef" a) _export_

const str () _export_ = pbuf(char)

func (pbufAlloc T)(t ttype(T), n i32) pbuf(T) _builtin_("@EAlloc" ("@TBuffer" T) n) _export_ _local_
macro (pbufMake T)(elems T,) pbuf(T) _varargs_ _builtin_("@EBuffer" ("@TBuffer" T) elems) _export_
macro (pbufMakeEmpty T)(t ttype(T),) pbuf(T) _builtin_("@EBuffer" ("@TBuffer" T)) _export_
macro (pbufMakeReadonly T)(elems T,) pbuf(T) _varargs_ _builtin_("@EString" ("@TBuffer" T) elems) _export_
macro (pbufMakeEmptyReadonly T)(t ttype(T),) pbuf(T) _builtin_("@EString" ("@TBuffer" T)) _export_

func (wbufAlloc T)(t ttype(T), n i32) wbuf(T) _builtin_("@EAlloc" ("@TMlist" T) n) _export_ _local_
macro (wbufMake T)(elems T,) wbuf(T) _varargs_ _builtin_("@EMlist" ("@TMlist" T) elems) _export_
macro (wbufMakeEmpty T)(t ttype(T),) wbuf(T) _builtin_("@EMlist" ("@TMlist" T)) _export_
macro (wbufMakeReadonly T)(elems T,) wbuf(T) _varargs_ _builtin_("@EList" ("@TMlist" T) elems) _export_
macro (wbufMakeEmptyReadonly T)(t ttype(T),) wbuf(T) _builtin_("@EList" ("@TMlist" T)) _export_
func (+ T)(a b T,) T _builtin_("@EAdd" T a b) _export_
func (- T)(a b T,) T _builtin_("@ESub" T a b) _export_
func (* T)(a b T,) T _builtin_("@EMul" T a b) _export_
func (/ T)(a b T,) T _builtin_("@EDiv" T a b) _export_
func (% T)(a b T,) T _builtin_("@EMod" T a b) _export_
func (& T)(a b T,) T _builtin_("@EBitAnd" T a b) _export_
func (| T)(a b T,) T _builtin_("@EBitOr" T a b) _export_
func (^ T)(a b T,) T _builtin_("@EBitXor" T a b) _export_
func {<< T S}(a T, b S) T _builtin_("@EBitShl" T a b) _export_
func {>> T S}(a T, b S) T _builtin_("@EBitAshr" T a b) _export_
func {>>> T S}(a T, b S) T _builtin_("@EBitShr" T a b) _export_
func (min T)(a b T,) T _builtin_("@EMin" T a b) _export_
func (max T)(a b T,) T _builtin_("@EMax" T a b) _export_
func (copysign T)(a b T,) T _builtin_("@ECopysign" T a b) _export_
func abs(a i32,) i32 _builtin_("@EAbs" i32 a) _export_ _local_
func abs(a f32,) f32 _builtin_("@EAbs" f32 a) _export_ _local_
func abs(a f64,) f64 _builtin_("@EAbs" f64 a) _export_ _local_
func (-)(a f32,) f32 _builtin_("@ENegate" f32 a) _export_ _local_
func (-)(a f64,) f64 _builtin_("@ENegate" f64 a) _export_ _local_
func ceil(a f32,) f32 _builtin_("@ECeil" f32 a) _export_ _local_
func ceil(a f64,) f64 _builtin_("@ECeil" f64 a) _export_ _local_
func floor(a f32,) f32 _builtin_("@EFloor" f32 a) _export_ _local_
func floor(a f64,) f64 _builtin_("@EFloor" f64 a) _export_ _local_
func trunc(a f32,) f32 _builtin_("@ETrunc" f32 a) _export_ _local_
func trunc(a f64,) f64 _builtin_("@ETrunc" f64 a) _export_ _local_
func nearest(a f32,) f32 _builtin_("@ENearest" f32 a) _export_ _local_
func nearest(a f64,) f64 _builtin_("@ENearest" f64 a) _export_ _local_
func sqrt(a f32,) f32 _builtin_("@ESqrt" f32 a) _export_ _local_
func sqrt(a f64,) f64 _builtin_("@ESqrt" f64 a) _export_ _local_
func cos(a f32,) f32 _builtin_("@ECos" f32 a) _export_ _local_
func cos(a f64,) f64 _builtin_("@ECos" f64 a) _export_ _local_
func sin(a f32,) f32 _builtin_("@ESin" f32 a) _export_ _local_
func sin(a f64,) f64 _builtin_("@ESin" f64 a) _export_ _local_
func (vmEcho T)(a T,) void _builtin_("@EEcho" a) _export_ _local_
func (== T)(a b T,) bool _builtin_("@EEq" T a b) _export_
func (!= T)(a b T,) bool _builtin_("@ELogicalNot" ("@EEq" T a b)) _export_
func (< T)(a b T,) bool _builtin_("@ELt" T a b) _export_
func (<= T)(a b T,) bool _builtin_("@ELtEq" T a b) _export_
func (> T)(a b T,) bool _builtin_("@EGt" T a b) _export_
func (>= T)(a b T,) bool _builtin_("@EGtEq" T a b) _export_

func (i8 T)(a T,) i8 _builtin_("@ENumConv" i8 a) _export_ _local_
func (i16 T)(a T,) i16 _builtin_("@ENumConv" i16 a) _export_ _local_
func (i32 T)(a T,) i32 _builtin_("@ENumConv" i32 a) _export_ _local_
func (i64 T)(a T,) i64 _builtin_("@ENumConv" i64 a) _export_ _local_
func (u8 T)(a T,) u8 _builtin_("@ENumConv" u8 a) _export_ _local_
func (u16 T)(a T,) u16 _builtin_("@ENumConv" u16 a) _export_ _local_
func (u32 T)(a T,) u32 _builtin_("@ENumConv" u32 a) _export_ _local_
func (u64 T)(a T,) u64 _builtin_("@ENumConv" u64 a) _export_ _local_
func (char T)(a T,) char _builtin_("@ENumConv" char a) _export_ _local_
func (bool T)(a T,) bool _builtin_("@ENumConv" bool a) _export_ _local_
func (f32 T)(a T,) f32 _builtin_("@ENumConv" f32 a) _export_ _local_
func (f64 T)(a T,) f64 _builtin_("@ENumConv" f64 a) _export_ _local_
func sexp(a i32,) sexp _builtin_("@ESexpI32" "@TSexp" a) _export_ _local_
func sexp(a f64,) sexp _builtin_("@ESexpF64" "@TSexp" a) _export_ _local_

func (&&)(a b bool,) bool _builtin_("@ELogicalAnd" a b) _export_ _local_
func (||)(a b bool,) bool _builtin_("@ELogicalOr" a b) _export_ _local_
func (!)(a bool,) bool _builtin_("@ELogicalNot" a) _export_ _local_
func not(a bool,) bool _builtin_("@ELogicalNot" a) _export_ _local_

func ([] T)(a pbuf(T),) T _builtin_("@EDeref" T a 0) _export_ _local_
func ([] T)(a pbuf(T), idx i32) T _builtin_("@EDeref" T a idx) _export_ _local_
func ([] T)(a ptr(T),) T _builtin_("@EDeref" T a 0) _export_ _local_
func ([] T)(a ptr(T), idx i32) T _builtin_("@EDeref" T a idx) _export_ _local_
func ([] T)(a wbuf(T),) T _builtin_("@EDeref" T a 0) _export_ _local_
func ([] T)(a wbuf(T), idx i32) T _builtin_("@EDeref" T a idx) _export_ _local_
func ([] T)(a wtr(T),) T _builtin_("@EDeref" T a 0) _export_ _local_
func ([] T)(a wtr(T), idx i32) T _builtin_("@EDeref" T a idx) _export_ _local_

func (len T)(p pbuf(T),) i32 _builtin_("@ELen" p) _export_ _local_
func (len T)(p wbuf(T),) i32 _builtin_("@ELen" p) _export_ _local_
func (byteLen T)(p pbuf(T),) i32 _builtin_("@EByteLen" p) _export_ _local_
func (wordLen T)(p wbuf(T),) i32 _builtin_("@EWordLen" p) _export_ _local_

func (dup T)(p ptr(T), len i32) pbuf(T) _builtin_("@EDup" ("@TBuffer" T) p len) _export_ _local_
func (dup T)(p wtr(T), len i32) wbuf(T) _builtin_("@EDup" ("@TMlist" T) p len) _export_ _local_
func (dupReadonly T)(p ptr(T), len i32) pbuf(T) _builtin_("@EDupReadonly" ("@TBuffer" T) p len) _export_ _local_
func (dupReadonly T)(p wtr(T), len i32) wbuf(T) _builtin_("@EDupReadonly" ("@TMlist" T) p len) _export_ _local_

func (memEq T)(a b ptr(T), len i32) bool _builtin_("@EMemEq" ("@TPtr" T) a b len) _export_ _local_

func (bulkCopy T)(dst src ptr(T), len i32) void _builtin_("@EBulkCopy" ("@TPtr" T) dst src len) _export_ _local_
func (bulkCopy T)(dst src wtr(T), len i32) void _builtin_("@EBulkCopy" ("@TRef" T) dst src len) _export_ _local_

func (sexp T)(p pbuf(T),) sexp _builtin_("@ESexpString" "@TSexp" p) _export_ _local_
func sexpSym(p str,) sexp _builtin_("@ESexpSym" "@TSexp" p) _export_ _local_
func sexp(p wbuf(sexp),) sexp _builtin_("@ESexpList" "@TSexp" p) _export_ _local_
macro sexpRaw(e untyped,) sexp _builtin_("@ESexpRaw" "@TSexp" e) _export_
func i32(p sexp,) i32 _builtin_("@ESexpUnwrap" i32 p) _export_ _local_
func f64(p sexp,) f64 _builtin_("@ESexpUnwrap" f64 p) _export_ _local_
func list(p sexp,) wbuf(sexp) _builtin_("@ESexpUnwrap" ("@TMlist" "@TSexp") p) _export_ _local_
func str(p sexp,) str _builtin_("@ESexpUnwrap" ("@TBuffer" "@TChar") p) _export_ _local_

macro sexpList(elems sexp,) sexp _varargs_ _export_:
  _builtin_ "@ESexpList" "@TSexp" ("@EList" ("@TMlist" "@TSexp") elems)

macro (addr T)(a T,) typed _builtin_("@EAddrOf" typed a) _export_
macro ifThen(a bool, body untyped) void _varargs_ _builtin_("@ECond" void a ("@EBlock" void () body) ()) _export_
macro loop(es untyped,) void _varargs_ _builtin_("@ELoop" __currLoop ("@EBlock" untyped () es)) _export_
macro break() undefined _builtin_("@EBreak" __currLoop) _export_
macro continue() undefined _builtin_("@EContinue" __currLoop) _export_
macro return(e untyped,) undefined _builtin_("@EReturn" e) _export_
macro return() undefined _builtin_("@EReturn" "@EVoid") _export_
func abort(msg str,) undefined _builtin_("@EAbort" msg) _export_ _local_
macro block(e0 body untyped,) untyped _varargs_ _export_ _builtin_("@EBlock" typed () e0 body)
func (wordCast T S)(t ttype(T), e S) T _export_ _builtin_("@EWordCast" T e)
func (numConv T S)(t ttype(T), e S) T _export_ _builtin_("@ENumConv" T e)

newtype SexpKind _export_ = i32
func sexpKind(v i32,) SexpKind _builtin_("@ENumConv" SexpKind v) _local_
const SEXP_I32 () _export_ = sexpKind(0)
const SEXP_F64 () _export_ = sexpKind(1)
const SEXP_STRING () _export_ = sexpKind(2)
const SEXP_LIST () _export_ = sexpKind(3)
const SEXP_SYM () _export_ = sexpKind(4)
const SEXP_NOMINAL () _export_ = sexpKind(5)
const SEXP_NOMINAL_GENERIC () _export_ = sexpKind(6)
const SEXP_TYPVAR () _export_ = sexpKind(7)
const SEXP_VAR () _export_ = sexpKind(8)
const SEXP_FN () _export_ = sexpKind(9)
const SEXP_FN_GENERIC () _export_ = sexpKind(10)
const SEXP_FN_EXTERN () _export_ = sexpKind(11)
const SEXP_MODULE () _export_ = sexpKind(12)

func kind(p sexp,) SexpKind _extern_("@compiler" "sexpKind") _export_
func symString(p sexp,) str _extern_("@compiler" "sexpSymString") _export_
func nomImpl(p sexp,) sexp _extern_("@compiler" "cnominalImpl") _export_
func typofExpr(p sexp,) sexp _extern_("@compiler" "typofExpr") _export_
func sexpTypWordCount(p sexp,) i32 _extern_("@compiler" "typWordCount") _export_

macro (wordSize T)(t ttype(T),) i32 _export_:
  sexpList "@ELit".sexpSym "@TInt32".sexpSym sexpTypWordCount(sexpRaw(T)).sexp

func fmtU32(dstBuf ptr(char), value u32) i32 _extern_("@systemfmt" "fmtU32") _export_
func fmtI32(dstBuf ptr(char), value i32) i32 _extern_("@systemfmt" "fmtI32") _export_
func fmtU64(dstBuf ptr(char), value u64) i32 _extern_("@systemfmt" "fmtU64") _export_
func fmtI64(dstBuf ptr(char), value i64) i32 _extern_("@systemfmt" "fmtI64") _export_
func fmtF32(dstBuf ptr(char), value f32) i32 _extern_("@systemfmt" "fmtF32") _export_
func fmtF64(dstBuf ptr(char), value f64) i32 _extern_("@systemfmt" "fmtF64") _export_

func str(value u32,) str _export_ _local_:
  var o = pbufAlloc(char, 10)
  var l = fmtU32(o[0].addr, value)
  dupReadonly(o[0].addr, l)
func str(value i32,) str _export_ _local_:
  var o = pbufAlloc(char, 11)
  var l = fmtI32(o[0].addr, value)
  dupReadonly(o[0].addr, l)
func str(value f32,) str _export_ _local_:
  var o = pbufAlloc(char, 65)
  var l = fmtF32(o[0].addr, value)
  dupReadonly(o[0].addr, l)
func str(value f64,) str _export_ _local_:
  var o = pbufAlloc(char, 65)
  var l = fmtF64(o[0].addr, value)
  dupReadonly(o[0].addr, l)

newtype StrBuilder _export_ = tstruct:
  e str
  l i32
  cap i32
func strBuilder(e str, l cap i32) StrBuilder _builtin_("@EStruct" StrBuilder e l cap) _export_ _local_
const EmptyString = ""
func strBuilder() StrBuilder _builtin_("@EStruct" StrBuilder EmptyString 0 0) _export_ _local_
func ensureAlloc(self StrBuilder, wantedCap i32) StrBuilder _export_:
  ifThen (wantedCap < self.cap) return(self)
  var newCap = max(max(self.cap * 3 / 2, 16), wantedCap)
  var newMem = pbufAlloc(char, newCap)
  bulkCopy(newMem[0].addr, self.e[0].addr, self.l)
  strBuilder(newMem, self.l, newCap)
func grow(self StrBuilder, addLen i32) StrBuilder _export_:
  ensureAlloc(self, self.l + addLen)
func add(self StrBuilder, mem ptr(char), len i32) StrBuilder _export_:
  self = grow(self, len)
  bulkCopy(self.e[self.l].addr, mem, len)
  self.l = self.l + len
  self
func add(self StrBuilder, mem str) StrBuilder _export_:
  add(self, mem[0].addr, mem.len)
func add(self StrBuilder, c char) StrBuilder _export_:
  self = grow(self, 1)
  self.e[self.l] = c
  self.l = self.l + 1
  self
func str(self StrBuilder,) str _export_ _local_:
  dupReadonly(self.e[0].addr, self.l)

func addRepr(self StrBuilder, value u32) StrBuilder _export_:
  self = ensureAlloc(self, self.l + 10)
  self.l = self.l + fmtU32(self.e[self.l].addr, value)
  self
func addRepr(self StrBuilder, value i32) StrBuilder _export_:
  self = ensureAlloc(self, self.l + 11)
  self.l = self.l + fmtI32(self.e[self.l].addr, value)
  self
func addRepr(self StrBuilder, value f32) StrBuilder _export_:
  self = ensureAlloc(self, self.l + 65)
  self.l = self.l + fmtF32(self.e[self.l].addr, value)
  self
func addRepr(self StrBuilder, value f64) StrBuilder _export_:
  self = ensureAlloc(self, self.l + 65)
  self.l = self.l + fmtF64(self.e[self.l].addr, value)
  self
func addRepr(self StrBuilder, value str) StrBuilder _export_:
  self = add(self, 34.char)
  self = add(self, value[0].addr, value.len)
  add(self, 34.char)

# Reify

func (__reify T)(tt ttype(T),) sexp _export_ _local_:
  _builtin_ "@ESexpRaw" "@TSexp" T

func __reify(v i32,) sexp _export_ _local_:
  sexpList "@ELit".sexpSym "@TInt32".sexpSym v.sexp
func __reify(v u16,) sexp _export_ _local_:
  sexpList "@ELit".sexpSym "@TUint16".sexpSym v.i32.sexp

func (__reify T)(s pbuf(T),) sexp _export_ _local_ (_mixin_ __reify):
  sexpList:
    sexpSym "@ELit"
    sexpList "@TBuffer".sexpSym __reify(T)
    sexp dupReadonly(s[0].addr, s.len)

func (__reify T)(s wbuf(T),) sexp _export_ _local_ (_mixin_ __reify):
  var listLen = s.len
  var o = wbufAlloc(sexp, listLen+2)
  o[0] = "@EListLit".sexpSym
  o[1] = sexpList "@TMlist".sexpSym __reify(T)
  var i = 0
  loop:
    ifThen not(i < listLen) break()
    o[i+2] = __reify(s[i])
    i = i + 1
  sexp o

func typUnroll(t sexp,) sexp _export_ _local_:
  loop:
    ifThen not(kind(t) == SEXP_NOMINAL) break()
    t = nomImpl(t)
  t

macro reifyFallbackImpl(tt v typed,) untyped:
  var origT = tt
  tt = typUnroll(tt)
  ifThen not(tt.kind == SEXP_LIST && tt.list.len > 0 && tt.list[0] == "@TStruct".sexpSym):
    return sexpList("abort".sexpSym, __reify "Type not supported by __reify fallback")
  var nfields = (tt.list.len - 1) / 2
  var o = wbufAlloc(sexp, nfields+3)
  o[0] = "wbufMakeReadonly".sexpSym
  o[1] = sexpList("sexpSym".sexpSym, __reify "@EStructLit")
  o[2] = sexpList("sexpRaw".sexpSym, origT)
  var i = 0
  loop:
    ifThen not(i < nfields) break()
    o[i+3] = sexpList("__reify".sexpSym, wbufMakeReadonly(".".sexpSym, v, tt.list[i*2+1]).sexp)
    i = i+1
  sexpList("sexp".sexpSym, o.sexp)

func (__reify T)(v T,) sexp _export_ _local_ (_mixin_ __reify):
  reifyFallbackImpl(T, v)

# fully compatible with RbSeq
newtype (wseq T) _export_ = tstruct:
  e wbuf(T)
  l i32
  cap i32

func (wseq T)(e wbuf(T), l cap i32) wseq(T) _export_:
  _builtin_ "@EStruct" (wseq T) e l cap
func (newWSeq T)(elemT ttype(T),) wseq(T) _export_:
  _builtin_ "@EStruct" (wseq T) ("@EList" ("@TMlist" T)) ("@ELit" "@TInt32" 0) ("@ELit" "@TInt32" 0)
func (ensureAlloc T)(self wseq(T), wantedCap i32) wseq(T) _export_:
  ifThen (wantedCap < self.cap) return(self)
  var newCap = max(max(self.cap * 3 / 2, 16), wantedCap)
  var newMem = wbufAlloc(T, newCap)
  bulkCopy(newMem[0].addr, self.e[0].addr, self.l)
  wseq(newMem, self.l, newCap)
func (add T)(self wseq(T), it T) wseq(T) _export_:
  self = ensureAlloc(self, self.l + 1)
  self.e[self.l] = it
  self.l = self.l + 1
  self
func (addUndefined T)(self wseq(T),) wseq(T) _export_:
  self = ensureAlloc(self, self.l + 1)
  self.l = self.l + 1
  self

# fully compatible with RbPodSeq
newtype (pseq T) _export_ = tstruct:
  e pbuf(T)
  l i32
  cap i32

func (pseq T)(e pbuf(T), l cap i32) pseq(T) _export_:
  _builtin_ "@EStruct" (pseq T) e l cap
func (newPSeq T)(elemT ttype(T),) pseq(T) _export_:
  _builtin_ "@EStruct" (pseq T) ("@EString" ("@TBuffer" T)) ("@ELit" "@TInt32" 0) ("@ELit" "@TInt32" 0)
func (ensureAlloc T)(self pseq(T), wantedCap i32) pseq(T) _export_:
  ifThen (wantedCap < self.cap) return(self)
  var newCap = max(max(self.cap * 3 / 2, 16), wantedCap)
  var newMem = pbufAlloc(T, newCap)
  bulkCopy(newMem[0].addr, self.e[0].addr, self.l)
  pseq(newMem, self.l, newCap)
func (add T)(self pseq(T), it T) pseq(T) _export_:
  self = ensureAlloc(self, self.l + 1)
  self.e[self.l] = it
  self.l = self.l + 1
  self
func (addUndefined T)(self pseq(T),) pseq(T) _export_:
  self = ensureAlloc(self, self.l + 1)
  self.l = self.l + 1
  self

# AST helpers

macro if(body untyped,) untyped _varargs_ _export_:
    var nrBranches = 1
    var branchStartIdx = 0
    var hasElse = false
    # 1. validate and count branches
    var i = 0
    var l = body.list.len
    loop:
        ifThen not(i < l) break()
        var e = body.list[i]
        ifThen (e == "elif".sexpSym):
            ifThen hasElse:
                abort "if: elif after else"
            ifThen ((i - branchStartIdx) < 2):
                abort "if: conditional branch must have condition and body"
            nrBranches = nrBranches + 1
            i = i + 1
            branchStartIdx = i
            continue()
        ifThen (e == "else".sexpSym):
            ifThen hasElse:
                abort "duplicate else after else"
            ifThen ((i - branchStartIdx) < 2):
                abort "if: conditional branch must have condition and body"
            hasElse = true
            i = i + 1
            branchStartIdx = i
            continue()
        i = i + 1
    ifThen ((not hasElse) && (i - branchStartIdx) < 2):
        abort "if: conditional branch must have condition and body"
    ifThen (hasElse && (i - branchStartIdx) < 1):
        abort "if: else branch must have body"

    # 2. Transform into @ECond
    var o = wbufAlloc(sexp, nrBranches * 2 + 3)
    o[0] = "@ECond".sexpSym
    o[1] = "@TUntyped".sexpSym
    o[2] = body.list[0]
    var dstIdx = 3
    i = 1
    branchStartIdx = 1 # this will now contain start of block
    loop:
        ifThen not(i < l) break()
        var e = body.list[i]
        ifThen (e == "elif".sexpSym || e == "else".sexpSym):
            # start of new branch; flush old branch
            var blk = wbufAlloc(sexp, i - branchStartIdx + 3)
            blk[0] = "@EBlock".sexpSym
            blk[1] = "@TUntyped".sexpSym
            blk[2] = sexpList()
            bulkCopy(blk[3].addr, body.list[branchStartIdx].addr, i - branchStartIdx)
            o[dstIdx] = blk.sexp
            dstIdx = dstIdx + 1
        ifThen (e == "elif".sexpSym):
            i = i + 1
            o[dstIdx] = body.list[i]
            dstIdx = dstIdx + 1
            i = i + 1
            branchStartIdx = i
            continue()
        ifThen (e == "else".sexpSym):
            branchStartIdx = i + 1
            break()
        i = i + 1
    # Gen last remaining branch
    var blk = wbufAlloc(sexp, l - branchStartIdx + 3)
    blk[0] = "@EBlock".sexpSym
    blk[1] = "@TUntyped".sexpSym
    blk[2] = sexpList()
    bulkCopy(blk[3].addr, body.list[branchStartIdx].addr, l - branchStartIdx)
    o[dstIdx] = blk.sexp
    dstIdx = dstIdx + 1
    # Fill in default else
    ifThen not(hasElse):
        o[dstIdx] = "@EVoid".sexpSym
    o.sexp

macro makeStruct(typ typed, body untyped,) untyped _varargs_ _export_:
    func findField(typStruct fieldName sexp,) i32:
        var i = 1
        var j = 2
        var l = typStruct.list.len
        loop:
            ifThen not(i < l) break()
            ifThen (typStruct.list[i] == fieldName) return(j)
            i = i + 2
            j = j + 1
        abort("makeStruct: Cannot find field!")

    var typStruct = typUnroll(typ)
    var fieldCount = (typStruct.list.len - 1) / 2
    var oExpr = wbufAlloc(sexp, fieldCount + 2)
    oExpr[0] = "@EStruct".sexpSym
    oExpr[1] = typ
    var i = 0
    var l = body.list.len
    loop:
        ifThen not(i < l) break()
        var eqExpr = body.list[i] # {= fieldName fieldValue}
        oExpr[findField(typStruct, eqExpr.list[1])] = eqExpr.list[2]
        i = i + 1
    sexp(oExpr)

func makeTTuple(typs wbuf(sexp),) sexp _local_:
  var nfields = typs.len
  var o = wbufAlloc(sexp, nfields * 2 + 1) # @TStruct _0 t0 _1 t1...
  o[0] = "@TStruct".sexpSym
  var i = 0
  var dstIdx = 1
  loop:
    ifThen not(i < nfields) break()
    o[dstIdx] = block:
      var sb = strBuilder()
      sb = add(sb, "_")
      sb = addRepr(sb, i)
      sb.str.sexpSym
    dstIdx = dstIdx + 1
    o[dstIdx] = typs[i]
    dstIdx = dstIdx + 1
    i = i + 1
  o.sexp

macro ttuple(typs typed,) typed _varargs_ _export_:
  makeTTuple typs.list

macro tuple(values typed,) typed _varargs_ _export_:
  var nvalues = values.list.len
  var typs = wbufAlloc(sexp, nvalues)
  var i = 0
  loop:
    ifThen not(i < nvalues) break()
    typs[i] = typofExpr(values.list[i])
    i = i + 1
  var o = wbufAlloc(sexp, nvalues+2)
  o[0] = "@EStruct".sexpSym
  o[1] = makeTTuple(typs)
  bulkCopy(o[2].addr, values.list[0].addr, nvalues)
  o.sexp

macro (@=)(dst untyped, srcE typed) void _export_:
  # block:
  #   var tmp = b
  #   a = b.firstField
  #   b = b.secondField
  # ...
  var srcTyp = typUnroll(typofExpr(srcE))
  ifThen not(srcTyp.kind == SEXP_LIST && srcTyp.list.len > 0 && srcTyp.list[0] == "@TStruct".sexpSym):
    abort "@= src unrolled typ is not TStruct"
  var fieldCount = (srcTyp.list.len - 1) / 2
  ifThen not(dst.list.len == fieldCount):
    abort "@= fieldCount mismatch"
  var o = wbufAlloc(sexp, fieldCount+4)
  o[0] = "@EBlock".sexpSym
  o[1] = "@TUntyped".sexpSym
  o[2] = sexpList()
  o[3] = sexpList("var".sexpSym, "_tmp".sexpSym, srcE)
  var i = 0
  loop:
    ifThen not(i < fieldCount) break()
    o[i+4] = sexpList("=".sexpSym, dst.list[i], sexpList(".".sexpSym, "_tmp".sexpSym, srcTyp.list[i*2+1]))
    i = i + 1
  o.sexp

macro strJoin(args str,) str _varargs_ _export_:
  # @EBlock str ():
  #   var `sb {strBuilder}
  #   {= `sb {add `sb arg}}
  #   {str `sb}
  var nargs = args.list.len
  var o = wbufAlloc(sexp, nargs+5)
  o[0] = "@EBlock".sexpSym
  o[1] = sexpList("@TBuffer".sexpSym, "@TChar".sexpSym)
  o[2] = sexpList()
  o[3] = sexpList("var".sexpSym, "__sb".sexpSym, sexpList("strBuilder".sexpSym))
  var i = 0
  var j = 4
  loop:
    ifThen not(i < nargs) break()
    o[j] = sexpList("=".sexpSym, "__sb".sexpSym, sexpList("add".sexpSym, "__sb".sexpSym, args.list[i]))
    i = i + 1
    j = j + 1
  o[j] = sexpList("str".sexpSym, "__sb".sexpSym)
  o.sexp

func addRepr(self StrBuilder, value sexp) StrBuilder _export_ _local_:
  var k = kind(value)
  if k == SEXP_I32:
    addRepr(self, value.i32)
  :elif k == SEXP_F64:
    addRepr(self, value.f64)
  :elif k == SEXP_STRING:
    addRepr(self, value.str)
  :elif k == SEXP_LIST:
    self = add(self, 123.char)
    var lst = value.list
    var l = lst.len
    var i = 0
    loop:
      ifThen not(i < l) break()
      ifThen not(i <= 0) (self = add(self, 32.char))
      self = addRepr(self, lst[i])
      i = i + 1
    add(self, 125.char)
  :elif k == SEXP_SYM:
    add(self, value.symString)
  :elif k == SEXP_NOMINAL:
    add(self, "<nominal>")
  :elif k == SEXP_NOMINAL_GENERIC:
    add(self, "<nominal_generic>")
  :elif k == SEXP_TYPVAR:
    add(self, "<typvar>")
  :elif k == SEXP_VAR:
    add(self, "<var>")
  :elif k == SEXP_FN:
    add(self, "<fn>")
  :elif k == SEXP_FN_GENERIC:
    add(self, "<fn_generic>")
  :elif k == SEXP_MODULE:
    add(self, "<module>")
  :else:
    abort "unsupported sexp kind"

func repr(value sexp,) str _export_ _local_:
  str(addRepr(strBuilder(), value))

The wasm4 module

The wasm4 module is available in the rubber playground and allows users to create games using a wasm4-like API.

Source of the wasm4 module
var DRAW_COLORS u16 _export__= 8738.u16

const BLIT_1BPP () _export_ = 0
const BLIT_2BPP () _export_ = 1
const BLIT_FLIP_X () _export_ = 2
const BLIT_FLIP_Y () _export_ = 4
const BLIT_ROTATE () _export_ = 8

const BUTTON_1 () _export_ = 1
const BUTTON_2 () _export_ = 2
const BUTTON_LEFT () _export_ = 16
const BUTTON_RIGHT () _export_ = 32
const BUTTON_UP () _export_ = 64
const BUTTON_DOWN () _export_ = 128

func setDrawColors(dc u16,) void _export_:
  DRAW_COLORS = dc
func setDrawColors(dc0 dc1 u8,) void _export_:
  DRAW_COLORS = u16(u32(dc0) & 15.u32 | (u32(dc1) & 15.u32) << 4)
func setDrawColors(dc0 dc1 dc2 dc3 u8,) void _export_:
  DRAW_COLORS = u16(u32(dc0) & 15.u32 | (u32(dc1) & 15.u32) << 4 | (u32(dc2) & 15.u32) << 8 | (u32(dc3) & 15.u32) << 12)

func clear() void _extern_("@wasm4" "clear") _export_
func myDrawHLine(x y l i32, dc u16) void _extern_("@wasm4" "drawHLine")
func myDrawVLine(x y l i32, dc u16) void _extern_("@wasm4" "drawVLine")
func myDrawRect(x y w h i32, dc u16) void _extern_("@wasm4" "drawRect")
func myDrawText(text ptr(char), textLen i32, x y i32, dc u16) void _extern_("@wasm4" "drawText")
func getGamepad() u8 _extern_("@wasm4" "getGamepad") _export_
func myBlit(sprite ptr(u8), spriteLen i32, x y width height srcX srcY stride flags i32, dc u16) void _extern_("@wasm4" "blit")

func drawHLine(x y l i32,) void _export_:
  myDrawHLine(x, y, l, DRAW_COLORS)

func drawVLine(x y l i32,) void _export_:
  myDrawVLine(x, y, l, DRAW_COLORS)

func drawRect(x y w h i32,) void _export_:
  myDrawRect(x, y, w, h, DRAW_COLORS)

func drawText(text ptr(char), textLen i32, x y i32) void _export_:
  myDrawText(text, textLen, x, y, DRAW_COLORS)

func drawText(text pbuf(char), x y i32) void _export_:
  myDrawText(text[0].addr, text.len, x, y, DRAW_COLORS)

func blit(sprite pbuf(u8), x y width height flags i32) void _export_:
  myBlit(sprite[0].addr, sprite.len, x, y, width, height, 0, 0, width, flags, DRAW_COLORS)

func blitSub(sprite pbuf(u8), x y width height srcX srcY stride flags i32) void _export_:
  myBlit(sprite[0].addr, sprite.len, x, y, width, height, srcX, srcY, stride, flags, DRAW_COLORS)

func hexToBytes(text pbuf(char),) pbuf(u8) _export_:
  var i = 0
  var dstIdx = 0
  var l = text.len
  var o = pbufAlloc(u8, l >> 1)
  loop:
    ifThen ((i + 1) >= l) break()
    var x0 = u32(text[i])
    var tmp0 = x0 >> 6
    var v0 = ((x0 & 15.u32) + tmp0 + (tmp0 << 3)) & 15.u32
    x0 = u32(text[i+1])
    tmp0 = x0 >> 6
    var v1 = ((x0 & 15.u32) + tmp0 + (tmp0 << 3)) & 15.u32
    o[dstIdx] = u8(v0 << 4 | v1)
    i = i + 2
    dstIdx = dstIdx + 1
  o