rebirth: Extract steps into separate source files

It's nice being able to do this now.

This starts to pave the path toward ultimately sharing code with Ulambda.

* build-aux/bootstrap/rebirth.scm: Extract steps 0--2 into separate source
    files.
* build-aux/bootstrap/rebirth/es.scm: New file containing step 2.
* build-aux/bootstrap/rebirth/macro.scm: New file containing step 1.
* build-aux/bootstrap/rebirth/relibprebirth.scm: New file contaiing step 0.
master
Mike Gerwitz 2018-02-03 01:06:02 -05:00
parent 203d468b83
commit 9eb8355e22
Signed by: mikegerwitz
GPG Key ID: 8C917B7F5DC51BA2
4 changed files with 674 additions and 606 deletions

View File

@ -60,613 +60,13 @@
;;; used, so those appear at the top of this file, despite their definitions
;;; not being supported until future passes.
;;;
;;; So, to begin, go to `==STEP 0=='.
;; ==Step 2== (don't start here; see Step 0 below)
;;
;; Did you read the other steps first? If not, you're out of order; skip
;; down to Step 0 first and then come back here.
;;
;; Back? Good!
;;
;; Now that we have macro support, we can start to refactor parts of the
;; compiler into macros---rather than maintaining features as part of the
;; compiler itself, we maintain them as a library used alongside the
;; program. This also has another important benefit: additional compiler
;; features resulting from these definitions do not require another Rebirth
;; compilation pass (that is, Re⁽ⁿ⁺¹⁾birth) before they are available to
;; use.
;;
;; To make sure that these macros are not thwarted by the existing `fnmap'
;; definitions, `fnmap' has been refactored to remove the respective
;; definitions using `cond-expand'; see `fnmap-premacro'.
;;
;; These are by no means meant to be solid implementations; strong
;; deficiencies exist, and don't expect this to work properly in every
;; case. They will be replaced with proper R7RS implementations in the
;; future.
;;
;; These macros have references to `_env', representing the current
;; environment. It is at this point that we also add primitive environment
;; support---this is essential as we move forward into purely macro-based
;; compilation passes, since we need to be able to have discrete
;; environments to run each of those passes in. More on that later.
;;
;; Scheme creates a new environment for every level of scope. Each
;; environment inherits the one above it, which produces the familiar
;; lexical scoping. As it turns out, this structure is represented
;; perfectly by ECMAScript's prototype model---a reference to a key on a
;; prototype chain is transparently proxied up the chain until it is
;; found. Therefore, environments are chained using a simple
;; `Object.create'. For now, anyway---that's the easy solution for now, but
;; in the future (Ulambda) we're likely to have a heap instead, once we have
;; static analysis.
;;
;; Initially, everything here was a near-exact copy of the `fnmap-premacro'
;; forms, re-arranged as needed for compilation (see limitations of
;; `cdfn-macro'), so all changes are clearly visible in the repository
;; history.
;;; So, to begin, goto STEP 0! ----------------,
;;; V
(cond-expand
(cdfn-macro
(define-macro (%es:native-apply fn . args)
(`quote
(string->es
(unquote (string-append
(token-value fn)
"(" (join "," (map sexp->es args)) ")")))))
(define-macro (es:console . args)
(`quote (%es:native-apply console.log (unquote@ args))))
(define-macro (es:error . args)
(`quote (%es:native-apply console.error (unquote@ args))))
(define-macro (es:raw . body)
(`quote
(string->es (unquote@ body))))
;; Expand the body BODY into a new environment inherited from the current
;; environment. Environments are currently handled by the ES runtime, so
;; this is easy.
(define-macro (es:envf . body)
(`quote
(string-append
"(function(_env){"
"return "
(unquote@ body)
"})(Object.create(_env))")))
(define-macro (define-es-macro decl . body)
(quasiquote
(define-macro (unquote decl)
(list
(quote string->es)
(string-append (unquote@ body))))))
;; Reference to current environment object.
(define-es-macro (%es:env) "_env")
;; Don't worry---basic tail call support (at least for recursion) is
;; nearing, and then we can get rid of this ugly thing.
(define-es-macro (es:while pred . body)
"(function(__whilebrk){"
"while (" (sexp->es pred) "){\n"
(body->es body #f) " if (__whilebrk) break;\n"
"}\n"
"})(false)")
(define-es-macro (es:break)
"__whilebrk=true")
(define-es-macro (lambda fnargs . body)
(es:envf
"function(" (join ", " (map tparam->es fnargs)) "){\n"
(env-params fnargs)
(body->es body #t)
"}"))
(define-es-macro (let* bindings . body)
"(function(){\n"
(join "" (map (lambda (binding)
(string-append
"let " (tparam->es (car binding)) ; TODO: BC; remove
" = " (env-ref (car binding))
" = " (sexp->es (cadr binding)) ";\n"))
bindings))
(body->es body #t) "\n"
" })()")
(define-es-macro (let bindings . body)
(let* ((params (map car bindings))
(fparams (join ", " (map tparam->es params)))
(args (map cadr bindings))
(fargs (map sexp->es args)))
(string-append (es:envf
"(function(" fparams "){\n"
(env-params params)
(body->es body #t) "\n"
"})(" fargs ")"))))
(define-es-macro (and . args)
"(function(__and){\n"
(join "" (map (lambda (expr)
(string-append
"__and = " (sexp->es expr) "; "
"if (!_truep(__and)) return false;\n"))
args))
"return __and;})()")
(define-es-macro (or . args)
"(function(__or){\n"
(join "" (map (lambda (expr)
(string-append
"__or = " (sexp->es expr) "; "
"if (_truep(__or)) return __or;\n"))
args))
"return false;})()")
(define-es-macro (if pred t . rest)
(let ((f (and (pair? rest)
(car rest))))
(string-append
"(function(){"
"if (_truep(" (sexp->es pred) ")){return " (sexp->es t) ";}"
(or (and (pair? f)
(string-append "else{return " (sexp->es f) ";}"))
"")
"})()")))
(define-es-macro (case key . clauses)
"(function(){const _key=" (sexp->es key) ";\n"
"switch (_key){\n"
(join ""
(map (lambda (data exprs)
(string-append
(if (and (token? data)
(string=? "else" (token-lexeme data)))
"default:\n"
(join ""
(map (lambda (datum)
(string-append
"case " (sexp->es datum) ":\n"))
data)))
(body->es exprs #t) "\n"))
(map car clauses)
(map cdr clauses)))
"}})()")
;; We unfortunately have to worry about environment mutability in the
;; current implementation. Since variables within environments are
;; implemented using ECMAScript's prototype chain, any sets affect the
;; object that the assignment is performed _on_, _not_ the prototype that
;; contains the key being set. Therefore, we have to traverse up the
;; prototype chain until we find the correct value, and set it on that
;; object.
;;
;; There are other ways to accomplish this. For example, we should
;; define setters for each variable and then not worry about
;; traversing. However, since set! is rare, we wouldn't want to incur a
;; performance hit for every single variable.
(define (%es:has-own-prop o id)
(string->es "Object.hasOwnProperty.call($$o, $$id)"))
(define (%es:proto-of o)
(string->es "Object.getPrototypeOf($$o)"))
(define (%es:envobj-for env id)
(if (and (string=? (es:typeof env) "object")
(not (es:null? env)))
(if (%es:has-own-prop env id)
env
(%es:envobj-for (%es:proto-of env) id))
(error (string-append "unknown variable: `" id "'"))))
(define (%es:setenv env id val)
(let ((envo (%es:envobj-for env id)))
(string->es "$$envo[$$id] = $$val")))
;; set! is then a simple application of `%es:setenv'.
(define-macro (set! varid val)
(`quote
(%es:setenv (%es:env)
(unquote (tname->id (token-lexeme varid)))
(unquote val))))))
;; ==STEP 0== (start here)
;;
;; The first step in the Rebirth process is to liberate ourselves from
;; libprebirth.
;;
;; Here we define the libprebirth primitives. When we first compile
;; Rebirth with Birth, `string->es' is not yet available, because it is
;; only implemented in Rebirth. Further, Birth includes libprebirth in
;; its output, so we cannot blindly redefine the procedures without
;; producing an error.
;;
;; Once Rebirth is compiled with Birth, Rebirth can then compile
;; itself. Since Rebirth _does_ implement `string->es', and further _does
;; not_ include libprebirth in its output, we can define the libprebirth
;; primitives ourselves in Rebirth Lisp. Cut the cord.
;;
;; Some of these definitions aren't valid: variable arguments, for
;; example, aren't represented _at all_---the `define' form will be
;; properly implemented in the future to correct this.
(cond-expand
(string->es
(define #t (string->es "true"))
(define #f (string->es "false"))
;; _truep is used only internally and is still defined as a JS function
;; for brevity
(string->es "const _truep = x => x !== false")
;; intended for whether a procedure is defined, mostly
(define (es:defined? x)
(let ((id (tname->id x)))
(string->es "eval('typeof ' + $$id) !== 'undefined'")))
(define (es:null? x)
(string->es "$$x === null"))
(define (es:typeof x)
(string->es "typeof $$x"))
(define (symbol=? x y)
(and (string=? (es:typeof x) "symbol")
(eq? x y)))
(define (es:arg->arr args)
(string->es "Array.prototype.slice.call($$args)"))
(define (list . xs) xs)
;; warning: only compares two values
(define (= x y)
(string->es "+$$x === +$$y"))
(define (> x y)
(string->es "+$$y > +$$x"))
(define (< x y)
(string->es "+$$y < +$$x"))
;; warning: doesn't verify that it's a pair
(define (length xs)
(string->es "$$xs.length"))
(define (es:array? xs)
(string->es "Array.isArray($$xs)"))
(define (es:-assert-list xs)
(or (es:array? xs)
(error "expecting list")))
(define (es:-assert-pair xs)
(es:-assert-list xs)
(if (= 0 (length xs))
(error "expecting pair")
#t))
;; ignore obj for now
(define (error msg obj)
(string->es "throw Error($$msg)")
#f) ; prevent above from being in tail position and prefixing "return"
;; warning: these only operate on arrays
(define (cons obj1 obj2)
(es:-assert-list obj2)
(string->es "[$$obj1].concat($$obj2)"))
(define (car pair)
(es:-assert-pair pair)
(string->es "$$pair[0]"))
(define (cdr pair)
(es:-assert-pair pair)
(string->es "$$pair.slice(1)"))
(define (append . args)
(fold (lambda (x xs)
(es:-assert-list x)
(string->es "$$xs.concat($$x)"))
(list)
args))
;; warning: these two are wholly inadequate
(define (list? xs)
(string->es "Array.isArray($$xs)"))
(define (pair? xs)
(and (list? xs)
(> 0 (length xs))))
;; R7RS string
(define (substring s start end)
(string->es "$$s.substring($$start, $$end)"))
(define (string-length s)
(string->es "$$s.length"))
(define (string=? s1 s2)
(string->es "typeof $$s1 === 'string' && $$s1 === $$s2"))
(define (string-ref s i)
(string->es "$$s[$$i] || $$error(`value out of range: ${$$i}`)"))
(define (string-append . xs)
(string->es "$$xs.join('')"))
(define (eq? x y)
(string->es "$$x === $$y"))
;; R7RS math
(define (+ . xs)
(fold (lambda (y x)
(string->es "$$x + $$y"))
0
xs))
(define (- . xs)
(fold (lambda (y x)
(string->es "$$x - $$y"))
(car xs)
(cdr xs)))
(define (zero? x)
(eq? x 0))
;; SRFI-1
;; warning: fold here only supports one list
(define (fold f init xs)
(string->es "$$xs.reduce((prev, x) => $$f(x, prev), $$init)"))
;; warning: map here uses the length of the first list, not the shortest
(define (map f . xs)
(string->es
"$$xs[0].map((_, i) => $$f.apply(null, $$xs.map(x => x[i])))"))
(define (es:regexp s opts)
(string->es "new RegExp($$s, $$opts)"))
(define (es:match r s)
(string->es "$$s.match($$r) || false"))
(define (es:replace r repl s)
(string->es "$$s.replace($$r, $$repl)"))
(define *fsdata*
(if (string->es "typeof __fsinit === 'undefined'")
(string->es "{}")
(string->es "__fsinit")))
(define *fs*
(if (string->es "typeof require === 'undefined'")
(string->es
"{
readFileSync(path)
{
throw Error(`Cannot load ${path} (no fs module)`);
},
}")
(string->es "require('fs')")))
;; so that we do not have to modify existing compiler output (which would
;; break the first round of compilation before these are defined)
(string->es "const fsdata = $$$k$fsdata$k$")
(string->es "const fs = $$$k$fs$k$")
(define (es:file->string path)
(if (string->es "fsdata[$$path] === undefined")
(string->es
"fsdata[$$path] = fs.readFileSync($$path).toString()")
(string->es "fsdata[$$path]")))))
;; ==STEP 1== (see Step 0 above)
;;
;; Without macro support, anything that involves producing code with
;; variable structure at compile-time must be hard-coded in the
;; compiler. Perhaps the greatest power in Lisp is the ability to extend
;; the language through its own facilities---its ability to parse itself
;; and treat itself as data.
;;
;; So we need to introduce macro support.
;;
;; This is not a trivial task: RⁿRS has a rich and powerful system that
;; would be quite a bit of work upfront to implement. Instead, we're
;; going to focus on traditional Lisp macros, which are conceptually
;; rather simple---they produce a list that, when expanded, is treated as
;; Lisp code as if the user had typed it herself.
;;
;; Macros hold the full power of Lisp---macro expansion _is_
;; compilation. This means that we need to compile macro expansions as
;; their own separate programs during the normal compilation process and
;; splice in the result. But to execute the macro, we need to execute
;; ECMAScript code that we just generated. In other words: the evil eval.
;;
;; ECMAScript has two ways of evaluating ES code contained in a string:
;; through the `eval' function and by instantiating `Function' with a
;; string argument representing the body of the function (or something
;; that can be cast into a string). Good thing, otherwise we'd find
;; ourselves painfully writing a Lisp interpreter in Rebirth Lisp.
;;
;; This implementation is very simple---there's very little code but a great
;; deal of comments. They describe important caveats and hopefully
;; enlighten the curious reader.
(cond-expand
(string->es
(define (cdfn-macro sexp)
(define (%make-macro-proc sexp)
;; The syntax for a macro definition is the same as a procedure
;; definition. In fact, that's exactly what we want, since a macro is
;; a procedure that, when applied, produces a list. But we want an
;; anonymous function, so override the id to the empty string.
(let* ((proc-es (cdfn-proc sexp "")))
;; Rather than outputting the generated ES function, we're going to
;; immediately evaluate it. This is a trivial task, but how we do
;; it is important: we need to maintain lexical scoping. This
;; means that we must use `eval'---`new Function' does not create a
;; closure.
;;
;; The only thing we need to do to ensure that eval returns a
;; function is to enclose the function definition in
;; parenthesis. This results in something along the lines of:
;; eval("(function(args){...})")
;;
;; If you're confused by the execution environment (compiler
;; runtime vs. compiler output), don't worry, you're not
;; alone. We're actually dealing with a number of things here:
;;
;; 1. Use `string->es' below to produce _compiler output_ for the
;; next version of a Rebirth Lisp compiler that will be
;; responsible for actually running the `eval'.
;; 2. That next version of the compiler will then compile
;; ECMAScript function definition from macro procedure source
;; using `cdfn-proc' as above.
;; 3. This will then be run by the compiler _at runtime_ by
;; running the `eval' statement below (which is part of the
;; program just as if it were Lisp).
;; 4. The result will be the procedure `proc-es' available to the
;; compiler at runtime rather than produced as compiler output.
;;
;; There's a lot of words here for so little code! We currently
;; lack the language features necessary to produce the types of
;; abstractions that would make this dissertation unnecessary.
(string->es "eval('(' + $$proc$_$es + ')')")))
;; We then store the macro by name in memory in `_env.macros'. When
;; invoked, it will apply the result of the above generated procedure
;; to `macro-compile-result' (defined below), which will produce the
;; ECMAScript code resulting from the macro application.
;;
;; There are consequences to this naive implementation. Rebirth is a
;; dumb transpiler that relies on features of ECMAScript to do its
;; job. In particular, we don't have any dependency graph or lexical
;; scoping or any of those necessary features---we let ECMAScript take
;; care of all of that. That means that we have no idea what is
;; defined or even what has been compiled; we just transpile and move
;; on blindly. Any errors resulting from undefined procedures, for
;; example, occur at runtime in the compiled output.
;;
;; These are features that will be implemented in Gibble Lisp; that's
;; not something to distract ourselves with now.
;;
;; So there are some corollaries:
;;
;; 1. Macros must be defined _before_ they are called. Order
;; matters.
;; 2. Macros can only make use of what is defined in the compiler
;; runtime environment---if a procedure is defined, it won't be
;; available to macros until the next compilation pass. This is
;; because we have no dependency graph and cannot automatically
;; eval dependencies so that they are available in the execution
;; context.
;; - To work around that, procedures can be defined within the
;; macro body. Of course, then they're encapsulated within it,
;; which is not always desirable.
;;
;; While this implementation is crippled, it does still provide good
;; foundation with which we can move forward. Our use of recursive
;; Reⁿbirth passes and `cond-expand' makes this less of an issue as
;; well, since we're recursing anyway.
(let ((macro-proc (%make-macro-proc sexp))
(macro-id (token-value (caadr sexp)))) ; XXX
(string->es
"_env.macros[$$macro$_$id] = function(){
return $$macro$_$compile$_$result(
$$macro$_$proc.apply(this,arguments))};")
;; Because the macro procedure was evaluated at runtime, it would
;; never actually itself be output. This makes debugging difficult,
;; so we'll output it as a comment. This is admittedly a little bit
;; dangerous, as we're assuming that no block comments will ever
;; appear in `macro-proc'. But at the time of writing, this
;; assumption is perfectly valid.
(string-append "/*macro " macro-id ": " macro-proc "*/")))
;; Compile the S-expression resulting from the macro application into
;; ECMAScript.
;;
;; This simply converts the given S-expression SEXP into an AST and
;; compiles it using the same procedures that we've been using for all
;; other code. See below for details.
(define (macro-compile-result sexp)
(sexp->es (list->ast sexp)))
;; Produce a Rebirth List AST from an internal list form.
;;
;; Up until this point, the only way to represent Rebirth Lisp was using
;; a typical Lisp form. With macros, however, we have bypassed that
;; source form---we're working with our own internal representation of a
;; list.
;;
;; The structure of the AST is already done---it mirrors that of the list
;; itself. What we need to do is map over the list, recursively, and
;; convert each item into a token.
;;
;; Consider the tokens processed by `toks->ast': comments,
;; opening/closing delimiters, strings, and symbols. We don't need to
;; worry about comments since we aren't dealing with source code. We
;; also don't need to worry about opening/closing delimiters since we
;; already have our list. This leaves only two token types to worry
;; about: strings and symbols.
;;
;; And then there's the fascinating case of macro arguments. When a
;; macro or procedure application are encountered during compilation, the
;; arguments are represented as tokens (see `apply-proc-or-macro'). As
;; just mentioned, the end goal is to convert our list SEXP into tokens
;; for the AST. But the arguments are _already_ tokens, so they need no
;; additional processing---we just splice them in as-is! This trivial
;; operation yields the powerful Lisp macro ability we're looking for:
;; the ability to pass around chunks of the AST.
;;
;; Consequently, we have Rebirth-specific syntax to deal with when
;; processing the AST within macros. Up until this point, in place of
;; macros, we have used `fnmap', which operates on tokens. That is the
;; case here as well: if a macro wishes to assert on or manipulate any
;; syntax it is given, it must use the Rebirth token API that the rest of
;; the system uses. For example, say we have a macro `foo' that asserts
;; on its first argument as a string:
;;
;; (foo "moo") => "cow"
;; (foo "bar") => "baz"
;;
;; This will _not_ work:
;;
;; (define-macro (foo x)
;; (if (string=? x "moo") "cow" "baz"))
;;
;; The reason is that `x' is not a string---it is a `token?'. Instead,
;; we must do this:
;;
;; (define-macro (foo x)
;; (if (string=? (token-value x) "moo") "cow" "baz"))
;;
;; Of course, if you do not need to make that determination at
;; compile-time, you can defer it to runtime instead and use `string=?':
;;
;; (define-macro (foo x)
;; (quasiquote (if (string=? (unquote x) "moo") "cow" "baz")))
;;
;; Simple implementation, complex consequences. Scheme uses syntax
;; objects; we'll provide that abstraction over our implementation at
;; some point.
;;
;; Okay! That's trivial enough, isn't it?
(define (list->ast sexp)
;; Anything that is not a string is considered to be a symbol
;; token. But note that a symbol token does not necessarily mean an
;; ECMAScript Symbol object.
(define (%list-item item)
(case (es:typeof item)
(("string")
(list "string" item))
(("symbol")
(list "symbol" (string->es "Symbol.keyFor($$item)")))
(else
(list "symbol" (string->es "''+$$item")))))
;; Recursively create tokens for each item. Note that we will not have
;; any useful source code or source location information---just use the
;; empty string and 0 for them, respectively.
;;
;; The lexeme will simply be the item converted into a string, whatever
;; that happens to be.
(if (token? sexp)
sexp
(if (list? sexp)
(map list->ast sexp)
(let* ((item-parts (%list-item sexp))
(type (car item-parts))
(lexeme (cadr item-parts)))
(car (make-token type lexeme "" 0))))))))
;; (go to Step 2 above)
(include
(include "rebirth/es.scm") ;; STEP 2 (start at STEP 0) <--,
(include "rebirth/relibprebirth.scm") ;; STEP 0 (start here) /
(include "rebirth/macro.scm"))) ;; STEP 1 (then go to STEP 2) -`
;; pair selection

View File

@ -0,0 +1,227 @@
;;; ECMAScript Target Compiler Macros for Rebirth Lisp
;;;
;;; Copyright (C) 2017, 2018 Mike Gerwitz
;;;
;;; This file is part of Gibble.
;;;
;;; Gibble is free software: you can redistribute it and/or modify
;;; it under the terms of the GNU Affero General Public License as
;;; published by the Free Software Foundation, either version 3 of the
;;; License, or (at your option) any later version.
;;;
;;; This program is distributed in the hope that it will be useful,
;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
;;; GNU General Public License for more details.
;;;
;;; You should have received a copy of the GNU Affero General Public License
;;; along with this program. If not, see <http://www.gnu.org/licenses/>.
;;;
;;; THIS IS BOOTSTRAP CODE INTENDED FOR USE ONLY IN REBIRTH.
;;;
;;;
;;; === STEP 2 ===
;;;
;;; Did you read the other steps first? If not, you're out of order; go to
;;; Step 0 first and then come back here; see `rebirth.scm'.
;;;
;;; Back? Good!
;;;
;;; Now that we have macro support, we can start to refactor parts of the
;;; compiler into macros---rather than maintaining features as part of the
;;; compiler itself, we maintain them as a library used alongside the
;;; program. This also has another important benefit: additional compiler
;;; features resulting from these definitions do not require another Rebirth
;;; compilation pass (that is, Re⁽ⁿ⁺¹⁾birth) before they are available to
;;; use.
;;;
;;; To make sure that these macros are not thwarted by the existing `fnmap'
;;; definitions, `fnmap' has been refactored to remove the respective
;;; definitions using `cond-expand'; see `fnmap-premacro'.
;;;
;;; These are by no means meant to be solid implementations; strong
;;; deficiencies exist, and don't expect this to work properly in every
;;; case. They will be replaced with proper R7RS implementations in the
;;; future.
;;;
;;; These macros have references to `_env', representing the current
;;; environment. It is at this point that we also add primitive environment
;;; support---this is essential as we move forward into purely macro-based
;;; compilation passes, since we need to be able to have discrete
;;; environments to run each of those passes in. More on that later.
;;;
;;; Scheme creates a new environment for every level of scope. Each
;;; environment inherits the one above it, which produces the familiar
;;; lexical scoping. As it turns out, this structure is represented
;;; perfectly by ECMAScript's prototype model---a reference to a key on a
;;; prototype chain is transparently proxied up the chain until it is
;;; found. Therefore, environments are chained using a simple
;;; `Object.create'. For now, anyway---that's the easy solution for now, but
;;; in the future (Ulambda) we're likely to have a heap instead, once we have
;;; static analysis.
;;;
;;; Initially, everything here was a near-exact copy of the `fnmap-premacro'
;;; forms, re-arranged as needed for compilation (see limitations of
;;; `cdfn-macro'), so all changes are clearly visible in the repository
;;; history.
(cond-expand
(cdfn-macro
(define-macro (%es:native-apply fn . args)
(`quote
(string->es
(unquote (string-append
(token-value fn)
"(" (join "," (map sexp->es args)) ")")))))
(define-macro (es:console . args)
(`quote (%es:native-apply console.log (unquote@ args))))
(define-macro (es:error . args)
(`quote (%es:native-apply console.error (unquote@ args))))
(define-macro (es:raw . body)
(`quote
(string->es (unquote@ body))))
;; Expand the body BODY into a new environment inherited from the current
;; environment. Environments are currently handled by the ES runtime, so
;; this is easy.
(define-macro (es:envf . body)
(`quote
(string-append
"(function(_env){"
"return "
(unquote@ body)
"})(Object.create(_env))")))
(define-macro (define-es-macro decl . body)
(quasiquote
(define-macro (unquote decl)
(list
(quote string->es)
(string-append (unquote@ body))))))
;; Reference to current environment object.
(define-es-macro (%es:env) "_env")
;; Don't worry---basic tail call support (at least for recursion) is
;; nearing, and then we can get rid of this ugly thing.
(define-es-macro (es:while pred . body)
"(function(__whilebrk){"
"while (" (sexp->es pred) "){\n"
(body->es body #f) " if (__whilebrk) break;\n"
"}\n"
"})(false)")
(define-es-macro (es:break)
"__whilebrk=true")
(define-es-macro (lambda fnargs . body)
(es:envf
"function(" (join ", " (map tparam->es fnargs)) "){\n"
(env-params fnargs)
(body->es body #t)
"}"))
(define-es-macro (let* bindings . body)
"(function(){\n"
(join "" (map (lambda (binding)
(string-append
"let " (tparam->es (car binding)) ; TODO: BC; remove
" = " (env-ref (car binding))
" = " (sexp->es (cadr binding)) ";\n"))
bindings))
(body->es body #t) "\n"
" })()")
(define-es-macro (let bindings . body)
(let* ((params (map car bindings))
(fparams (join ", " (map tparam->es params)))
(args (map cadr bindings))
(fargs (map sexp->es args)))
(string-append (es:envf
"(function(" fparams "){\n"
(env-params params)
(body->es body #t) "\n"
"})(" fargs ")"))))
(define-es-macro (and . args)
"(function(__and){\n"
(join "" (map (lambda (expr)
(string-append
"__and = " (sexp->es expr) "; "
"if (!_truep(__and)) return false;\n"))
args))
"return __and;})()")
(define-es-macro (or . args)
"(function(__or){\n"
(join "" (map (lambda (expr)
(string-append
"__or = " (sexp->es expr) "; "
"if (_truep(__or)) return __or;\n"))
args))
"return false;})()")
(define-es-macro (if pred t . rest)
(let ((f (and (pair? rest)
(car rest))))
(string-append
"(function(){"
"if (_truep(" (sexp->es pred) ")){return " (sexp->es t) ";}"
(or (and (pair? f)
(string-append "else{return " (sexp->es f) ";}"))
"")
"})()")))
(define-es-macro (case key . clauses)
"(function(){const _key=" (sexp->es key) ";\n"
"switch (_key){\n"
(join ""
(map (lambda (data exprs)
(string-append
(if (and (token? data)
(string=? "else" (token-lexeme data)))
"default:\n"
(join ""
(map (lambda (datum)
(string-append
"case " (sexp->es datum) ":\n"))
data)))
(body->es exprs #t) "\n"))
(map car clauses)
(map cdr clauses)))
"}})()")
;; We unfortunately have to worry about environment mutability in the
;; current implementation. Since variables within environments are
;; implemented using ECMAScript's prototype chain, any sets affect the
;; object that the assignment is performed _on_, _not_ the prototype that
;; contains the key being set. Therefore, we have to traverse up the
;; prototype chain until we find the correct value, and set it on that
;; object.
;;
;; There are other ways to accomplish this. For example, we should
;; define setters for each variable and then not worry about
;; traversing. However, since set! is rare, we wouldn't want to incur a
;; performance hit for every single variable.
(define (%es:has-own-prop o id)
(string->es "Object.hasOwnProperty.call($$o, $$id)"))
(define (%es:proto-of o)
(string->es "Object.getPrototypeOf($$o)"))
(define (%es:envobj-for env id)
(if (and (string=? (es:typeof env) "object")
(not (es:null? env)))
(if (%es:has-own-prop env id)
env
(%es:envobj-for (%es:proto-of env) id))
(error (string-append "unknown variable: `" id "'"))))
(define (%es:setenv env id val)
(let ((envo (%es:envobj-for env id)))
(string->es "$$envo[$$id] = $$val")))
;; set! is then a simple application of `%es:setenv'.
(define-macro (set! varid val)
(`quote
(%es:setenv (%es:env)
(unquote (tname->id (token-lexeme varid)))
(unquote val))))))

View File

@ -0,0 +1,244 @@
;;; Macro support for Rebirth Lisp
;;;
;;; Copyright (C) 2017, 2018 Mike Gerwitz
;;;
;;; This file is part of Gibble.
;;;
;;; Gibble is free software: you can redistribute it and/or modify
;;; it under the terms of the GNU Affero General Public License as
;;; published by the Free Software Foundation, either version 3 of the
;;; License, or (at your option) any later version.
;;;
;;; This program is distributed in the hope that it will be useful,
;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
;;; GNU General Public License for more details.
;;;
;;; You should have received a copy of the GNU Affero General Public License
;;; along with this program. If not, see <http://www.gnu.org/licenses/>.
;;;
;;; THIS IS BOOTSTRAP CODE INTENDED FOR USE ONLY IN REBIRTH.
;;;
;;;
;;; === STEP 1 ===
;;;
;;; Did you read Step 0 first? If not, start there; see `rebirth.scm'.
;;;
;;; Without macro support, anything that involves producing code with
;;; variable structure at compile-time must be hard-coded in the
;;; compiler. Perhaps the greatest power in Lisp is the ability to extend
;;; the language through its own facilities---its ability to parse itself
;;; and treat itself as data.
;;;
;;; So we need to introduce macro support.
;;;
;;; This is not a trivial task: RⁿRS has a rich and powerful system that
;;; would be quite a bit of work upfront to implement. Instead, we're
;;; going to focus on traditional Lisp macros, which are conceptually
;;; rather simple---they produce a list that, when expanded, is treated as
;;; Lisp code as if the user had typed it herself.
;;;
;;; Macros hold the full power of Lisp---macro expansion _is_
;;; compilation. This means that we need to compile macro expansions as
;;; their own separate programs during the normal compilation process and
;;; splice in the result. But to execute the macro, we need to execute
;;; ECMAScript code that we just generated. In other words: the evil eval.
;;;
;;; ECMAScript has two ways of evaluating ES code contained in a string:
;;; through the `eval' function and by instantiating `Function' with a
;;; string argument representing the body of the function (or something
;;; that can be cast into a string). Good thing, otherwise we'd find
;;; ourselves painfully writing a Lisp interpreter in Rebirth Lisp.
;;;
;;; This implementation is very simple---there's very little code but a
;;; great deal of comments. They describe important caveats and hopefully
;;; enlighten the curious reader.
(cond-expand
(string->es
(define (cdfn-macro sexp)
(define (%make-macro-proc sexp)
;; The syntax for a macro definition is the same as a procedure
;; definition. In fact, that's exactly what we want, since a macro is
;; a procedure that, when applied, produces a list. But we want an
;; anonymous function, so override the id to the empty string.
(let* ((proc-es (cdfn-proc sexp "")))
;; Rather than outputting the generated ES function, we're going to
;; immediately evaluate it. This is a trivial task, but how we do
;; it is important: we need to maintain lexical scoping. This
;; means that we must use `eval'---`new Function' does not create a
;; closure.
;;
;; The only thing we need to do to ensure that eval returns a
;; function is to enclose the function definition in
;; parenthesis. This results in something along the lines of:
;; eval("(function(args){...})")
;;
;; If you're confused by the execution environment (compiler
;; runtime vs. compiler output), don't worry, you're not
;; alone. We're actually dealing with a number of things here:
;;
;; 1. Use `string->es' below to produce _compiler output_ for the
;; next version of a Rebirth Lisp compiler that will be
;; responsible for actually running the `eval'.
;; 2. That next version of the compiler will then compile
;; ECMAScript function definition from macro procedure source
;; using `cdfn-proc' as above.
;; 3. This will then be run by the compiler _at runtime_ by
;; running the `eval' statement below (which is part of the
;; program just as if it were Lisp).
;; 4. The result will be the procedure `proc-es' available to the
;; compiler at runtime rather than produced as compiler output.
;;
;; There's a lot of words here for so little code! We currently
;; lack the language features necessary to produce the types of
;; abstractions that would make this dissertation unnecessary.
(string->es "eval('(' + $$proc$_$es + ')')")))
;; We then store the macro by name in memory in `_env.macros'. When
;; invoked, it will apply the result of the above generated procedure
;; to `macro-compile-result' (defined below), which will produce the
;; ECMAScript code resulting from the macro application.
;;
;; There are consequences to this naive implementation. Rebirth is a
;; dumb transpiler that relies on features of ECMAScript to do its
;; job. In particular, we don't have any dependency graph or lexical
;; scoping or any of those necessary features---we let ECMAScript take
;; care of all of that. That means that we have no idea what is
;; defined or even what has been compiled; we just transpile and move
;; on blindly. Any errors resulting from undefined procedures, for
;; example, occur at runtime in the compiled output.
;;
;; These are features that will be implemented in Gibble Lisp; that's
;; not something to distract ourselves with now.
;;
;; So there are some corollaries:
;;
;; 1. Macros must be defined _before_ they are called. Order
;; matters.
;; 2. Macros can only make use of what is defined in the compiler
;; runtime environment---if a procedure is defined, it won't be
;; available to macros until the next compilation pass. This is
;; because we have no dependency graph and cannot automatically
;; eval dependencies so that they are available in the execution
;; context.
;; - To work around that, procedures can be defined within the
;; macro body. Of course, then they're encapsulated within it,
;; which is not always desirable.
;;
;; While this implementation is crippled, it does still provide good
;; foundation with which we can move forward. Our use of recursive
;; Reⁿbirth passes and `cond-expand' makes this less of an issue as
;; well, since we're recursing anyway.
(let ((macro-proc (%make-macro-proc sexp))
(macro-id (token-value (caadr sexp)))) ; XXX
(string->es
"_env.macros[$$macro$_$id] = function(){
return $$macro$_$compile$_$result(
$$macro$_$proc.apply(this,arguments))};")
;; Because the macro procedure was evaluated at runtime, it would
;; never actually itself be output. This makes debugging difficult,
;; so we'll output it as a comment. This is admittedly a little bit
;; dangerous, as we're assuming that no block comments will ever
;; appear in `macro-proc'. But at the time of writing, this
;; assumption is perfectly valid.
(string-append "/*macro " macro-id ": " macro-proc "*/")))
;; Compile the S-expression resulting from the macro application into
;; ECMAScript.
;;
;; This simply converts the given S-expression SEXP into an AST and
;; compiles it using the same procedures that we've been using for all
;; other code. See below for details.
(define (macro-compile-result sexp)
(sexp->es (list->ast sexp)))
;; Produce a Rebirth List AST from an internal list form.
;;
;; Up until this point, the only way to represent Rebirth Lisp was using
;; a typical Lisp form. With macros, however, we have bypassed that
;; source form---we're working with our own internal representation of a
;; list.
;;
;; The structure of the AST is already done---it mirrors that of the list
;; itself. What we need to do is map over the list, recursively, and
;; convert each item into a token.
;;
;; Consider the tokens processed by `toks->ast': comments,
;; opening/closing delimiters, strings, and symbols. We don't need to
;; worry about comments since we aren't dealing with source code. We
;; also don't need to worry about opening/closing delimiters since we
;; already have our list. This leaves only two token types to worry
;; about: strings and symbols.
;;
;; And then there's the fascinating case of macro arguments. When a
;; macro or procedure application are encountered during compilation, the
;; arguments are represented as tokens (see `apply-proc-or-macro'). As
;; just mentioned, the end goal is to convert our list SEXP into tokens
;; for the AST. But the arguments are _already_ tokens, so they need no
;; additional processing---we just splice them in as-is! This trivial
;; operation yields the powerful Lisp macro ability we're looking for:
;; the ability to pass around chunks of the AST.
;;
;; Consequently, we have Rebirth-specific syntax to deal with when
;; processing the AST within macros. Up until this point, in place of
;; macros, we have used `fnmap', which operates on tokens. That is the
;; case here as well: if a macro wishes to assert on or manipulate any
;; syntax it is given, it must use the Rebirth token API that the rest of
;; the system uses. For example, say we have a macro `foo' that asserts
;; on its first argument as a string:
;;
;; (foo "moo") => "cow"
;; (foo "bar") => "baz"
;;
;; This will _not_ work:
;;
;; (define-macro (foo x)
;; (if (string=? x "moo") "cow" "baz"))
;;
;; The reason is that `x' is not a string---it is a `token?'. Instead,
;; we must do this:
;;
;; (define-macro (foo x)
;; (if (string=? (token-value x) "moo") "cow" "baz"))
;;
;; Of course, if you do not need to make that determination at
;; compile-time, you can defer it to runtime instead and use `string=?':
;;
;; (define-macro (foo x)
;; (quasiquote (if (string=? (unquote x) "moo") "cow" "baz")))
;;
;; Simple implementation, complex consequences. Scheme uses syntax
;; objects; we'll provide that abstraction over our implementation at
;; some point.
;;
;; Okay! That's trivial enough, isn't it?
(define (list->ast sexp)
;; Anything that is not a string is considered to be a symbol
;; token. But note that a symbol token does not necessarily mean an
;; ECMAScript Symbol object.
(define (%list-item item)
(case (es:typeof item)
(("string")
(list "string" item))
(("symbol")
(list "symbol" (string->es "Symbol.keyFor($$item)")))
(else
(list "symbol" (string->es "''+$$item")))))
;; Recursively create tokens for each item. Note that we will not have
;; any useful source code or source location information---just use the
;; empty string and 0 for them, respectively.
;;
;; The lexeme will simply be the item converted into a string, whatever
;; that happens to be.
(if (token? sexp)
sexp
(if (list? sexp)
(map list->ast sexp)
(let* ((item-parts (%list-item sexp))
(type (car item-parts))
(lexeme (cadr item-parts)))
(car (make-token type lexeme "" 0))))))))

View File

@ -0,0 +1,197 @@
;;; libprebirth Replacement for Rebirth Lisp
;;;
;;; Copyright (C) 2017, 2018 Mike Gerwitz
;;;
;;; This file is part of Gibble.
;;;
;;; Gibble is free software: you can redistribute it and/or modify
;;; it under the terms of the GNU Affero General Public License as
;;; published by the Free Software Foundation, either version 3 of the
;;; License, or (at your option) any later version.
;;;
;;; This program is distributed in the hope that it will be useful,
;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
;;; GNU General Public License for more details.
;;;
;;; You should have received a copy of the GNU Affero General Public License
;;; along with this program. If not, see <http://www.gnu.org/licenses/>.
;;;
;;; THIS IS BOOTSTRAP CODE INTENDED FOR USE ONLY IN REBIRTH.
;;;
;;;
;;; === STEP 0 ===
;;;
;;; The first step in the Rebirth process is to liberate ourselves from
;;; libprebirth.
;;;
;;; Here we define the libprebirth primitives. When we first compile
;;; Rebirth with Birth, `string->es' is not yet available, because it is
;;; only implemented in Rebirth. Further, Birth includes libprebirth in
;;; its output, so we cannot blindly redefine the procedures without
;;; producing an error.
;;;
;;; Once Rebirth is compiled with Birth, Rebirth can then compile
;;; itself. Since Rebirth _does_ implement `string->es', and further _does
;;; not_ include libprebirth in its output, we can define the libprebirth
;;; primitives ourselves in Rebirth Lisp. Cut the cord.
;;;
;;; Some of these definitions aren't valid: variable arguments, for
;;; example, aren't represented _at all_---the `define' form will be
;;; properly implemented in the future to correct this.
(cond-expand
(string->es
(define #t (string->es "true"))
(define #f (string->es "false"))
;; _truep is used only internally and is still defined as a JS function
;; for brevity
(string->es "const _truep = x => x !== false")
;; intended for whether a procedure is defined, mostly
(define (es:defined? x)
(let ((id (tname->id x)))
(string->es "eval('typeof ' + $$id) !== 'undefined'")))
(define (es:null? x)
(string->es "$$x === null"))
(define (es:typeof x)
(string->es "typeof $$x"))
(define (symbol=? x y)
(and (string=? (es:typeof x) "symbol")
(eq? x y)))
(define (es:arg->arr args)
(string->es "Array.prototype.slice.call($$args)"))
(define (list . xs) xs)
;; warning: only compares two values
(define (= x y)
(string->es "+$$x === +$$y"))
(define (> x y)
(string->es "+$$y > +$$x"))
(define (< x y)
(string->es "+$$y < +$$x"))
;; warning: doesn't verify that it's a pair
(define (length xs)
(string->es "$$xs.length"))
(define (es:array? xs)
(string->es "Array.isArray($$xs)"))
(define (es:-assert-list xs)
(or (es:array? xs)
(error "expecting list")))
(define (es:-assert-pair xs)
(es:-assert-list xs)
(if (= 0 (length xs))
(error "expecting pair")
#t))
;; ignore obj for now
(define (error msg obj)
(string->es "throw Error($$msg)")
#f) ; prevent above from being in tail position and prefixing "return"
;; warning: these only operate on arrays
(define (cons obj1 obj2)
(es:-assert-list obj2)
(string->es "[$$obj1].concat($$obj2)"))
(define (car pair)
(es:-assert-pair pair)
(string->es "$$pair[0]"))
(define (cdr pair)
(es:-assert-pair pair)
(string->es "$$pair.slice(1)"))
(define (append . args)
(fold (lambda (x xs)
(es:-assert-list x)
(string->es "$$xs.concat($$x)"))
(list)
args))
;; warning: these two are wholly inadequate
(define (list? xs)
(string->es "Array.isArray($$xs)"))
(define (pair? xs)
(and (list? xs)
(> 0 (length xs))))
;; R7RS string
(define (substring s start end)
(string->es "$$s.substring($$start, $$end)"))
(define (string-length s)
(string->es "$$s.length"))
(define (string=? s1 s2)
(string->es "typeof $$s1 === 'string' && $$s1 === $$s2"))
(define (string-ref s i)
(string->es "$$s[$$i] || $$error(`value out of range: ${$$i}`)"))
(define (string-append . xs)
(string->es "$$xs.join('')"))
(define (eq? x y)
(string->es "$$x === $$y"))
;; R7RS math
(define (+ . xs)
(fold (lambda (y x)
(string->es "$$x + $$y"))
0
xs))
(define (- . xs)
(fold (lambda (y x)
(string->es "$$x - $$y"))
(car xs)
(cdr xs)))
(define (zero? x)
(eq? x 0))
;; SRFI-1
;; warning: fold here only supports one list
(define (fold f init xs)
(string->es "$$xs.reduce((prev, x) => $$f(x, prev), $$init)"))
;; warning: map here uses the length of the first list, not the shortest
(define (map f . xs)
(string->es
"$$xs[0].map((_, i) => $$f.apply(null, $$xs.map(x => x[i])))"))
(define (es:regexp s opts)
(string->es "new RegExp($$s, $$opts)"))
(define (es:match r s)
(string->es "$$s.match($$r) || false"))
(define (es:replace r repl s)
(string->es "$$s.replace($$r, $$repl)"))
(define *fsdata*
(if (string->es "typeof __fsinit === 'undefined'")
(string->es "{}")
(string->es "__fsinit")))
(define *fs*
(if (string->es "typeof require === 'undefined'")
(string->es
"{
readFileSync(path)
{
throw Error(`Cannot load ${path} (no fs module)`);
},
}")
(string->es "require('fs')")))
;; so that we do not have to modify existing compiler output (which would
;; break the first round of compilation before these are defined)
(string->es "const fsdata = $$$k$fsdata$k$")
(string->es "const fs = $$$k$fs$k$")
(define (es:file->string path)
(if (string->es "fsdata[$$path] === undefined")
(string->es
"fsdata[$$path] = fs.readFileSync($$path).toString()")
(string->es "fsdata[$$path]")))))