Kho tháng 3/2020
Thứ ba, 31 Tháng 3 năm 2020 21:03:10 ICT
I locked myself out of the network by essentially shutting it down
... again! Never ever test network configuration over SSH.
Chủ nhật, 29 Tháng 3 năm 2020 10:53:22 ICT
Highlight countries will no COVID-19 cases
URL=https://upload.wikimedia.org/wikipedia/commons/2/26/COVID-19_Outbreak_World_Map.svg
curl $URL | sed 's/#e0e0e0/#00ff00/g' > map.svg
It's beautiful. The current one is this, still many countries in Africa and lots in Occenia.
Thứ bảy, 28 Tháng 3 năm 2020 08:48:58 ICT
Spin and Dragon's Egg
Both has the time difference, though probably more realistic in Dragon's Egg. Humans in two cases are on the "slow time" side. Though at least in Dragon's Egg, humans are seen as Gods to those litte cheelas.
Cập nhật 1 lần. Lần cuối: Thu Aug 25 14:40:58+0003 2022
Thứ sáu, 27 Tháng 3 năm 2020 17:36:42 ICT
Steam mini browser
Smaller, less memory hungry.
steam -no-browser steam://open/minigameslist
Cập nhật 1 lần. Lần cuối: Fri Aug 26 00:20:24+0003 2022
Thứ năm, 19 Tháng 3 năm 2020 16:31:33 ICT
Compile comp.. inline
Compare this
$ ./gosh -ftest -fno-inline
gosh$ ((with-module gauche.internal compile-p1)
...... '(begin
...... (define c 1)
...... (define (a b)
...... (if (zero? b)
...... b
...... (+ (a (- b 1) 1 c))))))
($seq
($define () user#c
($const 1))
($define () user#a
($lambda[a.0] (b.3)
($if ($call ($gref user#zero?)
($lref b.3))
($lref b.3)
($call ($gref user#+)
($call ($gref user#a)
($call ($gref user#-)
($lref b.3)
($const 1))
($const 1)
($gref user#c)))))))
#<undef>
and this
$ ./gosh -ftest
gosh$ ((with-module gauche.internal compile-p1)
...... '(begin
...... (define c 1)
...... (define (a b)
...... (if (zero? b)
...... b
...... (+ (a (- b 1) 1 c))))))
($seq
($define () user#c
($const 1))
($define () user#a
($lambda[a.0] (b.4)
($if ($asm (NUMEQ2)
($lref b.4)
($const 0))
($lref b.4)
($call ($gref user#+)
($call ($gref user#a)
($asm (NUMSUB2)
($lref b.4)
($const 1))
($const 1)
($gref user#c)))))))
The difference without -fno-inline
is zero?
and -
are no longer
ordinary calls. They are VM instructions.
Most of this is in compile-i.scm
, which registers inline versions
for many Gauche builtins. They must be marked inlineable with
%mark-binding-inlinable!
. The inline transformation procedure must
be saved with %procedure-inliner
.
In pass 1, inlineble symbols are detected by global-call-type
. If
it's "inline", pass1/expand-inliner
will handle the rest, which
involves getting the inliner from %procedure-inliner
and letting it
do all the work, probably.
Thứ tư, 18 Tháng 3 năm 2020 19:06:47 ICT
Compile compile.. before the.. macros
There isn't much left to say about pass1 because it basically turns a Scheme expression to an (still nested) IForm expression, which is annotated with some more information such as source code, and is a bit more normalized (i.e. most syntax errors should be caught here).
The biggest part done at this pass is macro/syntax expansion (and
inlining, which could be seen as "expansion"). And we have looked at a
procedure call previously. Let's try a couple other syntaxes. Since
all syntaxes are defined with define-pass1-syntax
in this file, it's
not that hard to find them.
(define-pass1-syntax (define-constant form cenv) :gauche
(pass1/define form form '(const) #t (cenv-module cenv) cenv))
This is a Gauche form, which pass const
as one of the flags to
pass1/define
. Not much else to see (unless you want to go through
pass1/define
looking for constant optimization in there).
(define-pass1-syntax (define-in-module form cenv) :gauche
(pass1/define `(_ . ,rest) form '() #t
(ensure-module module 'define-in-module #f)
cenv)]
This one is also Gauche's and it passes a different module to
pass1/define
. The rest is obvious.
(define-pass1-syntax (if form cenv) :null
(match form
[(_ test then else)
($if form (pass1 test (cenv-sans-name cenv))
(pass1 then cenv) (pass1 else cenv))]
[(_ test then)
($if form (pass1 test (cenv-sans-name cenv))
(pass1 then cenv) ($const-undef))]
[_ (error "syntax-error: malformed if:" form)]))
This form comes up a lot in articles about writing an interpreter or a
compiler. Here the transformation is very simple (of course), it
essentially just converts it to $if
form, compiling all the test and
if/else clauses.
let
form is probably more interesting (but not that much after
define
). Unnamed let is quite simple:
(define-pass1-syntax (let form cenv) :null
(match form
[(_ ((var expr) ...) body ...)
(let* ([lvars (imap make-lvar+ var)]
[newenv (cenv-extend cenv (%map-cons var lvars) LEXICAL)])
($let form 'let lvars
(map (^[init lvar]
(rlet1 iexpr
(pass1 init (cenv-add-name cenv (lvar-name lvar)))
(lvar-initval-set! lvar iexpr)))
expr lvars)
(pass1/body body newenv)))]
We basically create a new environment that has new lexical bindings. Named let is a bit more complicated, left for the reader to explore.
(define-pass1-syntax (define-module form cenv) :gauche
(check-toplevel form cenv)
(match form
[(_ name body ...)
(let* ([mod (ensure-module name 'define-module #t)]
[newenv (make-bottom-cenv mod)])
($seq (imap (cut pass1 <> newenv) body)))]
[_ (error "syntax-error: malformed define-module:" form)]))
define-module
is not that different than define-in-module
except
that by passing #t
as create?
to ensure-module
we may create a
new module object.
(define-pass1-syntax (export form cenv) :gauche
(%export-symbols (cenv-module cenv) (cdr form))
($values0))
export
form may be interesting because well... it exports stuff, via
Scm_ExportSymbols()
. These symbols are kept in the "external" hash
table of the module.
import
is similar. The syntax parsing/transforming is not much to
write about. It'll end up in Scm_ImportModule()
. We don't
immediately import all symbols from the imported module to the target
module. We just make a note about the imported module in the
imported
linked list of the target module. find-binding
(or
Scm_FindBinding()
) may look through these modules and return a gloc
for the found symbol.
include
form reads the entire file in as a list of Scheme expression
and converts it to ((begin Sexp...) . Filename)
. The entire thing is
passed to pass1 again, so this special form must be recognized
somehow.
That's it. The commit 108fa909f (merged changes from NVM0_8_3 branch, 2005-04-12) may be intersting because it's the first time that this Scheme-based compiler enters Git. Less features, so easier to understand.
Next time (hopefully), macros.
Thứ năm, 12 Tháng 3 năm 2020 20:30:36 ICT
Compile compile compile... lambda
From the last time we're at handling (op . args)
form inside a
lambda. This is kinda like the main body in pass1.
(define (pass1/body-rec exprs mframe vframe cenv)
(match exprs
[(((op . args) . src) . rest)
(or (and-let* ([head (pass1/lookup-head op cenv)])
(cond
[(lvar? head) ...]
[(macro? head) ...] ; locally defined macro
[(syntax? head) ...] ; when (let-syntax ((xif if)) (xif ...)) etc.
[(and (pair? head) (eq? (car head) :rec)) ...]
[(or (global-identifier=? head define.)
(global-identifier=? head define-inline.)
(global-identifier=? head r5rs-define.))
...]
[(global-identifier=? head define-syntax.) ...] ; internal syntax definition
[(global-identifier=? head begin.) ...] ;intersperse forms
[(global-identifier=? head include.) ...]
[(global-identifier=? head include-ci.) ...]
[(wrapped-identifier? head) ...]
We do head lookup like before to determine the type of the head so we can do the right thing. If it's a local variable, hmm... If it's either a syntax or macro, do macro/syntax transformation (with some more tricky stuff because of local scopes).
If it's global define
form, looks like we treat it as defining new
nested procedures (and defining global variables again is not
accepted). All these something.
are global identifiers, to make sure
that the code refers to the vanilla ones. If somebody rebinds define
for example, "head" would not be the same as define.
.
In the end if it's an indentifer inserted by macro expansion, do mysterious stuff...
Let's look at the lvar?
case, which calls the same function as when
you evaluate a simple variable inside a lambda (the match condition
after (((op . args)...
).
(define (pass1/body-finish exprs mframe vframe cenv)
(if (not mframe)
(pass1/body-rest exprs cenv)
;; Replace dummy bindings to the real one
(let* ([intdefs. (reverse (cdr vframe))]
[vars (map car intdefs.)]
[lvars (imap make-lvar+ vars)])
(set-cdr! vframe (%map-cons vars lvars))
($let #f 'rec* lvars
(imap2 (cut pass1/body-init <> <> cenv) lvars (map cddr intdefs.))
(pass1/body-rest exprs cenv)))))
Well, let's assume "mframe" (macro frames, the "vframe" is for
variables) is #f
since that's the easy case. We'll go to
(define (pass1/body-rest exprs cenv)
(match exprs
[() ($seq '())]
[(expr&src) (pass1/body-1 expr&src cenv)]
[_ (let1 stmtenv (cenv-sans-name cenv)
($seq (let loop ([exprs exprs] [r '()])
(if (null? (cdr exprs))
(reverse (cons (pass1/body-1 (car exprs) cenv) r))
(loop (cdr exprs)
(cons (pass1/body-1 (car exprs) stmtenv) r))))))]))
We should hit the (expr&src)
case, so here we go...
(define (pass1/body-1 expr&src cenv)
(let1 src (cdr expr&src)
(if (string? src)
(pass1 (car expr&src) (cenv-swap-source cenv src))
(pass1 (car expr&src) cenv))))
This basically brings us back to the main pass1
compile
procedure. Probably the main difference here is we're already in a
lambda scope instead of a global one. For variable reference, we
should hit the bottom part of pass1
when we detect that it's a local
reference:
(define (pass1 program cenv)
(cond
[(pair? program) ... ] ; (op . args)
[(identifier? program) ; variable reference
(let1 r (cenv-lookup-variable cenv program)
(cond [(lvar? r) ($lref r)]))]))
which helps transform to $lref
IForm. Similarly, a procedure call
will hit pass1/call
in either of these cases, the first one calling
a local lambda/define, the second evaluates the op
expression before
calling further.
(define (pass1 program cenv)
(cond
[(pair? program) ; (op . args)
(cond
[(pass1/lookup-head (car program) cenv)
=> (^h (cond
[(lvar? h) (pass1/call program ($lref h) (cdr program) cenv)]))]
[else (pass1/call program (pass1 (car program) (cenv-sans-name cenv))
(cdr program) cenv)])]))
Not sure how a global call is made,.. Maybe global definitions are heavy identifiers too?
Anyway... the meat is in pass1/call
(define-inline (pass1/call program proc args cenv)
(cond
[(has-tag? proc $LAMBDA) ; immediate lambda
(expand-inlined-procedure program proc (imap (cut pass1 <> cenv) args))]
[(null? args) ($call program proc '())] ; fast path
[else (let1 cenv (cenv-sans-name cenv)
($call program proc (imap (cut pass1 <> cenv) args)))]))
The first "immediate lambda" case, I'm not sure. But the next too look
simple. For a procedure call with no argument, we can produce $call
IForm directly. If the procedure takes arguments, of course we have to
evaluate them first by running them through pass1
again. Evaluation
order is determined by imap
defined in compile-0.scm
, and they are
evaluated from left to right.
$call
form will be transformed in pass5 to produce a bunch of pushes
to save arguments in the (Scheme) stack, then depending on the
procedure we have an appropriate call instruction.
Anyway pass1 result looks like this
gosh$ ((with-module gauche.internal compile-p1) '(begin (define (a) #t) (a 1)))
($seq
($define () user#a
($lambda[a.0] ()
($const #t)))
($call ($gref user#a)
($const 1)))
#<undef>
Cập nhật 1 lần. Lần cuối: Sun Mar 29 04:09:24+0011 2020
Thứ tư, 11 Tháng 3 năm 2020 19:30:13 ICT
Compile compile compile... going global
Let's have a look at how you define new "things" in this compiler. Things here are global variables or procedures. Local bindings are probably quite different...
All special forms are defined in compile-1.scm with
define-pass1-syntax1
macro, you have, for example:
(define-pass1-syntax (define form cenv) :null
(pass1/define form form '() #f (cenv-module cenv) cenv))
which tells the compiler how to handle a define
form. All these
syntaxes are kept in cenv
and they are probably looked up by
pass1/lookup-head
we mentioned earlier:
(define (pass1 program cenv)
(cond
[(pair? program) ; (op . args)
(cond
[(pass1/lookup-head (car program) cenv)
=> (^h (cond
[(syntax? h);; locally rebound syntax
(call-syntax-handler h program cenv)]
So. pass1/define
takes two form arguments, some flags, the current
module we're compiling in and the compiled environment. This procedure
covers all define variants, including non-standard ones such as
define-constant
or define-inline
. But we'll look at defining
variables only for now:
(define (pass1/define form oform flags extended? module cenv)
(match form
[(_ name expr)
(let1 cenv (cenv-add-name cenv (variable-name name))
;; Hygiene alert
;; If NAME is an identifier, it is inserted by macro expander; we
;; can't simply place it in $define, since it would insert a toplevel
;; definition into the toplevel of macro-definition environment---
;; we don't want a mere macro call would modify different module.
;; We rename it to uninterned symbol, so, even the binding itself
;; is into the macro-definiting module, it won't be visible from
;; other code except the code generated in the same macro expansion.
;; A trick - we directly modify the identifier, so that other forms
;; referring to the same (eq?) identifier can keep referring it.
(let1 id (if (wrapped-identifier? name)
(%rename-toplevel-identifier! name)
(make-identifier name module '()))
;; Insert dummy binding at compile time, if we don't have one yet.
;; This matters when we compile multiple modules at once, and
;; one need to import from another with qualifiers.
(unless (vm-compiler-flag-is-set? SCM_COMPILE_LEGACY_DEFINE)
(%insert-binding module (unwrap-syntax name)
(%uninitialized) '(fresh)))
($define oform flags id (pass1 expr cenv))))]
So we have a name
, an expr
that should evaluate to some value, and
we convert that to the $define
intermediate form. This is, according
to compile.scm, the global definition, which binds some result to an
identifier.
Before pass1/define
takes two forms. The first one could be
transformed recursively by pass1/define itself for easy
processing. The second "original form" is the unmodified one, and we
pass it to $define
. This is probably to show the source form when
something goes wrong, basically troubleshooting purposes only.
The third argument to $define
is id
, which is a new identifier
associated with the module we want to define it in:
(make-identifier name module '())
Let's ignore the (if (wrapped-identifier?
part, which will be
revisited when we come to macro handling.
The last argument to $define
is the "value" (in terms of IForm) the
variable is set to. Of course we need to recursively call pass1
on
the entire expression and let it compiles that to some IForm.
Also note that we have a new compiler environment now when we call
this pass1
:
(let1 cenv (cenv-add-name cenv (variable-name name))
This new environment contains the new variable (or at least its name, so basically we know the name is occupied, probably, but not more).
What does it look like after compiled into VM instructions? Nothing surprising:
gosh$ ((with-module gauche.internal compile-p15) '(define a #t))
=== main_code (name=%toplevel, cc=0x7f174d2a7780, codevec=0x7f174d930900, size=5, const=1 stack=0):
signatureInfo: #f
0 CONST #t
2 DEFINE(0) #<identifier user#a.4d972680>; (define a #t)
We push the evaluated value #t
here on the stack, then we issue
DEFINE
instruction to probably add a new binding in the current
module the identifier belongs to (remember the identifer has a module
reference, when we create it).
The exact implementation of DEFINE
is like this:
(define-insn DEFINE 1 obj #f
(let* ([var] [val VAL0])
(FETCH-OPERAND var)
(VM_ASSERT (SCM_IDENTIFIERP var))
(SCM_FLONUM_ENSURE_MEM val)
INCR-PC
(let* ([id::ScmIdentifier* (Scm_OutermostIdentifier (SCM_IDENTIFIER var))]
[mod::ScmModule* (-> id module)]
[name::ScmSymbol* (SCM_SYMBOL (-> id name))])
(case (SCM_VM_INSN_ARG code) ;flag
[(0) (Scm_MakeBinding mod name val 0)]
[(1 SCM_BINDING_CONST) (Scm_MakeBinding mod name val SCM_BINDING_CONST)]
[(SCM_BINDING_INLINABLE)(Scm_MakeBinding mod name val SCM_BINDING_INLINABLE)])
($result (SCM_OBJ name)))))
and the meat is probably in Scm_MakeBinding
in module.c. That
function can be summarized in a few important lines:
ScmGloc *Scm_MakeBinding(ScmModule *module, ScmSymbol *symbol,
ScmObj value, int flags)
{
ScmObj v = Scm_HashTableRef(module->internal, SCM_OBJ(symbol), SCM_FALSE);
/* NB: this function bypasses check of gloc setter */
if (SCM_GLOCP(v)) {
g = SCM_GLOC(v);
if (Scm_GlocConstP(g)) prev_kind = SCM_BINDING_CONST;
else if (Scm_GlocInlinableP(g)) prev_kind = SCM_BINDING_INLINABLE;
oldval = g->value;
} else {
g = SCM_GLOC(Scm_MakeGloc(symbol, module));
Scm_HashTableSet(module->internal, SCM_OBJ(symbol), SCM_OBJ(g), 0);
/* If module is marked 'export-all', export this binding by default */
if (module->exportAll && SCM_SYMBOL_INTERNED(symbol)) {
Scm_HashTableSet(module->external, SCM_OBJ(symbol), SCM_OBJ(g), 0);
}
}
g->value = value;
return g;
In other words, we try to find the symbol in the module's symbol table. If found, it must be a global location (gloc), we are redefining, so we just assign a new value to it. Otherwise we create a new gloc, add it to the table, and assign again.
Simple!
What is a gloc then? A global location is just an object that has:
- a name (symbol)
- a module (that it belongs to)
- a value (anything the variable holds)
- optionally setter and getter hooks
So you can say it's essentially a "global variable".
What about the top-level procedure define form then? It's essentially the same as the variable definition form, we just need some preprocessing...
(define (pass1/define form oform flags extended? module cenv)
(match form
[(_ (name . args) body ...)
(pass1/define `(define ,name
,(with-original-source
`(,(if extended? lambda. r5rs-lambda.) ,args ,@body)
oform))
oform flags extended? module cenv)]
Here we transform the define
form back to the variable one, or in
pure Scheme terms, we transform
(define (a b) body)
to
(define a (lambda (b) body))
Not really fancy. lambda
syntax will have to produce a closure that
we can put in the value field of a gloc.
That's probably about it for defining stuff at top level. So let's go local. Anything local starts with a lambda form (though probably the let form is more important because it defines a new local binding environment)
A lambda is defined in the compiler the same way other syntaxes are:
(define-pass1-syntax (lambda form cenv) :null ;RnRS lambda
(match form
[(_ formals . body)
(receive (reqs rest)
(let loop ((xs formals) (ys '()))
(cond [(null? xs) (values (reverse ys) #f)]
[(identifier? xs) (values (reverse ys) xs)]
[(pair? xs)
(loop (cdr xs) (cons (car xs) ys))]))
(pass1/vanilla-lambda (add-arg-info form formals)
(if rest (append reqs (list rest)) reqs)
(length reqs)
(if rest 1 0)
body cenv))]
We basically need to parse the formals
aka procedure arguments part,
then pass everything in pass1/vanilla-lambda
(define (pass1/vanilla-lambda form formals nreqs nopts body cenv) ; R7RS lambda
(let* ([lvars (imap make-lvar+ formals)]
[intform ($lambda form (cenv-exp-name cenv) nreqs nopts lvars #f #f)]
[newenv (cenv-extend/proc cenv (%map-cons formals lvars)
LEXICAL intform)])
(vector-set! intform 6 (pass1/body body newenv))
intform))
Here things probably get more interesting. We create local variables
(or something like that) from formals
, make a new $lambda
IForm
that will can put stuff in later, make a new compiler environment that
contains the lvar arguments we just made. Now we're ready to handle
the lambda body.
Before going into the body, keep in mind the input we have:
- an
$lambda
iform - a compiler environment frame that contains all procedure arguments
- the current module, kept inside cenv, which gives us access to all global references
Before going in (again) there's this comment before pass/body
that's
worth mentioning
;; To avoid unnecessary allocation, we adopt somewhat convoluted strategy
;; that delays frame allocation until needed, and once allocated, we
;; "grow" the frame as new definition appears. This is an exception of
;; the general principle that cenv is immutable.
Okay... now this is self explanatory
(define (pass1/body exprs cenv)
;; First, we pair up each expr with dummy source info '(). Some of expr
;; may be an 'include' form and expanded into the content of the file,
;; in which case we keep the source file info in each cdr of the pair.
(pass1/body-rec (map list exprs) #f #f cenv))
The fun thing starts in pass1/body-rec
. The first part is really
really big and scary
(define (pass1/body-rec exprs mframe vframe cenv)
(match exprs
[(((op . args) . src) . rest) ...]
which probably just means that "for each statement" in the body. Phew... until next time.
Thứ ba, 10 Tháng 3 năm 2020 19:33:56 ICT
Compile compile compile... paaaaaiiii...
Let's start from the top of Gauche's compiler. In this compiler it's called pass one which, given a compile environment "cenv", transforms a program (as an s-expression) to IForm.
The the whole thing is in compile-1.scm, but you can still access it via some hidden procedures meant for testing compiler, e.g.
gosh$ ((with-module gauche.internal compile-p1) '(define a 1))
($define () user#a
($const 1))
#<undef>
compile-p1
is pretty simple, it prepares a compile environment for
you, then pretty print the IForm:
(define (compile-p1 program :optional (env (vm-current-module)))
(pp-iform (pass1 program (make-bottom-cenv env))))
So let's dig in. Scheme program is modeled after lambda calculus so it's pretty simple:
- A "variable" evaluates to its value
(proc ...)
evaluates as a procedure call, all arguments are also evaluated(macro ...)
performs macro expansion recursively, then go back to the first two points. Special forms such as define, let or lambda could probably fail into this category.
The main pass1
body is kinda like that
(define (pass1 program cenv)
...
;; main body of pass1
(cond
[(pair? program) ; (op . args)
(cond
[(pass1/lookup-head (car program) cenv)
=> (^h (cond
[(wrapped-identifier? h) (pass1/global-call h)]
[(lvar? h) (pass1/call program ($lref h) (cdr program) cenv)]
[(macro? h) ;; local macro
(pass1 (call-macro-expander h program cenv) cenv)]
[(syntax? h);; locally rebound syntax
(call-syntax-handler h program cenv)]
[else (error "[internal] unknown resolution of head:" h)]))]
...)]
[(identifier? program) ; variable reference
...]
pass1/lookup-head
looks up (car program)
in the current compile
environment. Which is basically this (ignoring the (with-module ...)
exceptio).
(define-inline (pass1/lookup-head head cenv)
(and (identifier? head)
(cenv-lookup-syntax cenv head)))
Note that identifier?
can match either a symbold or a disjoint
identifier type. In the normal case here it should be just a plain
symbol. Let's ignore how symbol lookup is done for now.
So back to the main body above, if it's a wrapped-identifier (aka the
disjoint identifier mentioned in Gauche reference), it can only be
inserted by a macro, or it's imported from another module. Which means
it's either a global call or macro expansion, pass1/global-call (local
calls are handled in lvar?
block right next to it)
If it's a local variable (lvar?
) we perform a normal procedure call
via pass1/call
. The argument list (cdr program)
is passed in of
course.
If it's a macro (including both Gauche macros and syntax-rules), we
call the associated macro expander to transform program
. This
probably should happen until nothing is left to expand and pass1
called again on the final result.
If if a syntax, which is kinda like builtin macros, call the syntax handler for it. Syntax handlers and macro transformers take the same input. Syntax handlers return IForm while macro transformers return another sexp that could in turn be macro expanded.
Let's stick to the most simple thing in this compiler, handling variable references
[(identifier? program) ; variable reference
(let1 r (cenv-lookup-variable cenv program)
(cond [(lvar? r) ($lref r)]
[(wrapped-identifier? r)
(or (and-let* ([const (find-const-binding r)]) ($const const))
($gref r))]
[else (error "[internal] cenv-lookup returned weird obj:" r)]))]
We look up the variable in the compile environment (which includes the current module that contains the list of all bindings). If it's a local variable, return an IForm
($lref r)
These intermediate tree forms are defined (and also described) in
compile.scm. The $lref
form contains a local variable reference
(there's also $lref
VM instruction but probably should ignore that
for now).
If it's an identifier (real one, not Scheme symbol), we find the
global binding with $gref
instead. That's it. A variable is compiled
to either $lref
and $gref
. We can try out with gosh
gosh$ ((with-module gauche.internal compile-p1) 'a)
($gref user#a)
Local variables are harder to create, the result is also more complex
but the key point here is the ($lref b.1)
in the end.
gosh$ ((with-module gauche.internal compile-p1) '(define (a) (let ((b #f)) b)))
($define () user#a
($lambda[a.0] ()
($let ([b.1 ($const #f)])
($lref b.1))))
It would be fun to turn these IForms to VM instructions (pass 5) but
compile-p5
is not really made for this because it will run all
passes to optimize, and there seems no easy way to inject a new
procedure in there, so let's add a new one to compile.scm and rebuild
gosh:
(define (compile-p15 program :optional (env (vm-current-module)))
(let1 cenv (make-bottom-cenv env)
(vm-dump-code (pass5 (pass1 program cenv)
(make-compiled-code-builder 0 0 '%toplevel #f #f)
'() 'tail))))
Now we can have some fun
gosh$ ((with-module gauche.internal compile-p15) 'a)
=== main_code (name=%toplevel, cc=0x7f1d5ed70ba0, codevec=0x7f1d5eb0b9e0, size=3, const=1 stack=0):
signatureInfo: #f
0 GREF #<identifier user#a.5ed3bf00>; a
2 RET
#<undef>
Here we see the gref iform is translated straight to gref instruction,
which looks it up and probably puts the result in VAL0
register,
or on stack (Gauche VM is basically a stack based one with very few
registers)
gosh$ ((with-module gauche.internal compile-p15) 'a)
=== main_code (name=%toplevel, cc=0x7f1d5eb0a720, codevec=0x7f1d5f220960, size=5, const=2 stack=0):
signatureInfo: #f
0 CLOSURE #<lambda 0> ; (lambda () (let ((b #f)) b))
2 DEFINE(0) #<identifier user#a.5ec46fe0>; (define (a) (let ((b #f)) b))
4 RET
=== closure:0 (name=a, cc=0x7f1d5eb0a6c0, codevec=0x7f1d5eb0be60, size=3, const=0 stack=4):
signatureInfo: ((a))
0 CONSTF-PUSH
1 LOCAL-ENV(1) ; (let ((b #f)) b)
2 LREF0-RET ; b
#<undef>
The lambda example looks a lot more complicated. The last instruction
is a fused one, a combination of LREF0
and RET
. They probably look
up slot 0 in the local frame, the return it in VAL0. The local frame
(of one slot) should be set up by the LOCAL-ENV
instruction above
So that's it for a very simple and small piece of the compiler. Next we'll see how to define a global variable, probably.
Cập nhật 2 lần. Lần cuối: Sun Mar 29 04:09:24+0011 2020