[Joypy-announce] joypy/Joypy: 3 new changesets

Back to archive index
scmno****@osdn***** scmno****@osdn*****
Fri May 3 04:34:23 JST 2019


changeset 65141ee00abf in joypy/Joypy
details: http://hg.osdn.jp/view/joypy/Joypy?cmd=changeset;node=65141ee00abf
user: Simon Forman <sform****@hushm*****>
date: Thu May 02 08:38:15 2019 -0700
description: Minor cleanup.

Remove the pass0//2 DCG rule and unfold it in compile_program//2 rule.  Move init//0 to be with the rest of the state DCG code.
changeset 6273577778bb in joypy/Joypy
details: http://hg.osdn.jp/view/joypy/Joypy?cmd=changeset;node=6273577778bb
user: Simon Forman <sform****@hushm*****>
date: Thu May 02 10:18:58 2019 -0700
description: Make get//1 handle lists of pairs which it passes off to get//2.

(I could remove more punctuation by making the (key, value) pairs implicit.)

Move compile_program//2 to just under do//0.
changeset d6121ff8bf52 in joypy/Joypy
details: http://hg.osdn.jp/view/joypy/Joypy?cmd=changeset;node=d6121ff8bf52
user: Simon Forman <sform****@hushm*****>
date: Thu May 02 12:33:52 2019 -0700
description: Add some comments, minor rearrangement.

diffstat:

 thun/compiler.pl |  143 +++++++++++++++++++++++++++++++++++++++---------------
 1 files changed, 102 insertions(+), 41 deletions(-)

diffs (223 lines):

diff -r fb49f3d96c2d -r d6121ff8bf52 thun/compiler.pl
--- a/thun/compiler.pl	Wed May 01 21:55:46 2019 -0700
+++ b/thun/compiler.pl	Thu May 02 12:33:52 2019 -0700
@@ -1,6 +1,6 @@
 /*
 
-Copyright © 2018 Simon Forman
+Copyright © 2018-2019 Simon Forman
 
 This file is part of Thun
 
@@ -36,39 +36,29 @@
 compile_program(Program, Binary),
 write_binary('joy_asm.bin', Binary).
 
-% phrase(pass0(Program, AST), [], _),
-% write_canonical(AST),
-% phrase(⟐(AST), IR),
-% write_canonical(IR),
-% phrase(linker(IR), ASM),
-% write_canonical(ASM).
 
-pass0(Code, Program) --> init, ⦾(Code, Program).
+compile_program(Program, Binary) :-
+    phrase((init, ⦾(Program, IR)), [], _),
+    phrase(⟐(IR), ASM),
+    phrase(linker(ASM), EnumeratedASM),
+    phrase(asm(EnumeratedASM), Binary).
 
-init, [Context] -->
-    {empty_assoc(C), empty_assoc(Dictionary),
-     put_assoc(dictionary, C, Dictionary, Context)}.
+
+/*
+
+This first stage ⦾//2 converts the Joy description into a kind of intermediate
+representation that models the Joy interpreter on top of the machine but doesn't
+actually use assembly instructions.  It also manages the named registers and
+memory locations so thet don't appear in the program.
+
+The idea here is to extract the low-level "primitives" needed to define the Joy
+interpreter to make it easier to think about (and maybe eventually retarget other
+CPUs.)
+
+ */
 
 ⦾([], []) --> [].
 
-⦾([Body, ≡(NameAtom)|Terms], [defi(Name, B, Prev, I, SP, TOS)|Ts]) -->
-    get(dict, Prev), set(dict, Name), get(sp, SP), get(tos, TOS),
-    inscribe(NameAtom, Name), ⦾(Terms, Ts), lookup(i, I), lookup(Body, B).
-
-⦾([Body, ヮ(NameAtom)|Terms], [definition(Name, DONE, B, Prev)|Ts]) -->
-    get(dict, Prev), set(dict, Name), inscribe(NameAtom, Name),
-    get(done, DONE), ⦾([Body, Terms], [B, Ts]).
-
-⦾([Body, ワ(NameAtom)|Terms], [definition(Name, MAIN, B, Prev)|Ts]) -->
-    get(dict, Prev), set(dict, Name), inscribe(NameAtom, Name),
-    get(main, MAIN), ⦾([Body, Terms], [B, Ts]).
-
-⦾([P, T, E, ヰ|Terms], [br(Predicate, Then, Else)|Ts]) -->
-    ⦾([P, T, E, Terms], [Predicate, Then, Else, Ts]).
-
-⦾([P, B, ヱ|Terms], [repeat_until(Predicate, Body)|Ts]) -->
-    ⦾([P, B, Terms], [Predicate, Body, Ts]).
-
 ⦾([ヲ|Terms], Ts) -->  % Preamble.
     set(dict, 0), set(done, _DONE),
     set(temp0, 6), set(temp1, 7),
@@ -91,8 +81,8 @@
     set_reg_const(TERM, 0),
     asm(store_word(TOS, SP, 0))  % RAM[SP] := 0
     |Ts]) -->
-    get(dict_top, DICT_TOP), get(expr, EXPR),
-    get(sp, SP), get(term, TERM), get(tos, TOS),
+    get([(dict_top, DICT_TOP), (expr, EXPR),
+    (sp, SP), (term, TERM), (tos, TOS)]),
     ⦾(Terms, Ts), get(dict, LastWord).
 
 ⦾([メ|Terms], [  % Mainloop.
@@ -106,11 +96,29 @@
     label(DONE), write_ram(SP, TOS),   % RAM[SP] := TOS
     jump(MAIN)
     |Ts]) -->
-    get(done, DONE), get(main, MAIN), get(halt, HALT),
-    get(dict_ptr, DICT_PTR), get(dict_top, DICT_TOP), get(expr, EXPR),
-    get(sp, SP), get(term, TERM), get(tos, TOS),
+    get([(dict_ptr, DICT_PTR), (dict_top, DICT_TOP),
+    (done, DONE), (expr, EXPR), (halt, HALT), (main, MAIN),
+    (sp, SP), (term, TERM), (tos, TOS)]),
     ⦾(Terms, Ts).
 
+⦾([Body, ≡(NameAtom)|Terms], [defi(Name, B, Prev, I, SP, TOS)|Ts]) -->
+    get(dict, Prev), set(dict, Name), get(sp, SP), get(tos, TOS),
+    inscribe(NameAtom, Name), ⦾(Terms, Ts), lookup(i, I), lookup(Body, B).
+
+⦾([Body, ヮ(NameAtom)|Terms], [definition(Name, DONE, B, Prev)|Ts]) -->
+    get(dict, Prev), set(dict, Name), inscribe(NameAtom, Name),
+    get(done, DONE), ⦾([Body, Terms], [B, Ts]).
+
+⦾([Body, ワ(NameAtom)|Terms], [definition(Name, MAIN, B, Prev)|Ts]) -->
+    get(dict, Prev), set(dict, Name), inscribe(NameAtom, Name),
+    get(main, MAIN), ⦾([Body, Terms], [B, Ts]).
+
+⦾([P, T, E, ヰ|Terms], [br(Predicate, Then, Else)|Ts]) -->
+    ⦾([P, T, E, Terms], [Predicate, Then, Else, Ts]).
+
+⦾([P, B, ヱ|Terms], [repeat_until(Predicate, Body)|Ts]) -->
+    ⦾([P, B, Terms], [Predicate, Body, Ts]).
+
 ⦾([Term|Terms], [T|Ts]) --> ⦾(Term, T), ⦾(Terms, Ts).
 
 ⦾(∅, dw(0))                    --> [].
@@ -142,6 +150,23 @@
 ⦾(ナ, low_half(TEMP0, TOS))     --> get(temp0, TEMP0), get(tos, TOS).
 ⦾(ヶ, low_half(TOS, SP))        --> get(sp, SP), get(tos, TOS).
 
+
+/* 
+
+Context (state) manipulation for the ⦾//2 relation.
+
+Association lists are used to keep a kind of symbol table as well as a dictionary
+of name atoms to address logic variables for defined Joy functions.
+
+*/
+
+init, [Context] -->
+    {empty_assoc(C), empty_assoc(Dictionary),
+     put_assoc(dictionary, C, Dictionary, Context)}.
+
+get([]) --> !.
+get([(Key, Value)|Ts]) --> !, get(Key, Value), get(Ts).
+
 get(Key, Value) --> state(Context), {get_assoc(Key, Context, Value)}.
 set(Key, Value) --> state(ContextIn, ContextOut),
     {put_assoc(Key, ContextIn, Value, ContextOut)}.
@@ -159,6 +184,14 @@
 state(S), [S] --> [S].
 state(S0, S), [S] --> [S0].
 
+
+/*
+
+This second stage ⟐//1 converts the intermediate representation to assembly
+language.
+
+*/
+
 ⟐([]) --> [].
 ⟐([Term|Terms]) --> ⟐(Term), ⟐(Terms).
 
@@ -270,27 +303,50 @@
 
 ⟐(pop(Reg, TOS)) --> ⟐([split_word(Reg, TOS), deref(TOS)]).
 
+
+/* 
+
+Support for ⟐//1 second stage.
+
+The dexpr//2 DCG establishes a sequence of labeled expr_cell/2 pseudo-assembly
+memory locations as a linked list that encodes a Prolog list of Joy function
+labels comprising e.g. the body of some Joy definition.
+
+*/
+
 dexpr([], 0) --> [].
 dexpr([Func|Rest], ThisCell) -->
     [label(ThisCell), expr_cell(Func, NextCell)],
     dexpr(Rest, NextCell).
 
+/*
+
+The add_label/3 relation is a meta-logical construct that accepts a comparision
+predicate (e.g. if_zero/2) and "patches" it by adding the Label logic variable
+to the end.
+
+*/
+
 add_label(CmpIn, Label, CmpOut) :-
     CmpIn =.. F,
     append(F, [Label], G),
     CmpOut =.. G.
 
+/*
+
+Two simple masking predicates.
+
+*/
+
 high_half_word(I, HighHalf) :- HighHalf is I >> 16 /\ 0xFFFF.
 low_half_word( I,  LowHalf) :-  LowHalf is I       /\ 0xFFFF.
 
-compile_program(Program, Binary) :-
-    phrase(pass0(Program, IR), [], _),
-    phrase(⟐(IR), ASM),
-    phrase(linker(ASM), EnumeratedASM),
-    phrase(asm(EnumeratedASM), Binary).
 
+/*
 
-% Linker
+Linker
+
+*/
 
 linker(IntermediateRepresentation) --> enumerate_asm(IntermediateRepresentation, 0, _).
 
@@ -305,7 +361,12 @@
 align(N, Bytes, M) :- N mod 4 =:= 0, !, M is N + Bytes.
 align(N, Bytes, M) :- Padding is 4 - (N mod 4), M is N + Bytes + Padding.
 
-% Assembler
+
+/*
+
+Assembler
+
+*/
 
 asm([]) --> !, [].
 asm([      skip(Bits)|Rest]) --> !, skip(Bits),          asm(Rest).


More information about the Joypy-announce mailing list
Back to archive index