5babf09388d23517af2374852eb899fcfecdfb78
[scheme.forth.jl.git] / src / scheme.4th
1 vocabulary scheme
2 scheme definitions
3
4 include term-colours.4th
5 include defer-is.4th
6 include catch-throw.4th
7 include float.4th
8
9 include debugging.4th
10
11 defer read
12 defer eval
13 defer print
14
15 defer collect-garbage
16
17 \ ---- Types ---- {{{
18
19 variable nexttype
20 0 nexttype !
21 : make-type
22     create nexttype @ ,
23     1 nexttype +!
24     does> @ ;
25
26 make-type fixnum-type
27 make-type flonum-type
28 make-type boolean-type
29 make-type character-type
30 make-type string-type
31 make-type nil-type
32 make-type none-type
33 make-type pair-type
34 make-type symbol-type
35 make-type primitive-proc-type
36 make-type compound-proc-type
37 make-type fileport-type
38 : istype? ( obj type -- obj bool )
39     over = ;
40
41 \ }}}
42
43 \ ---- Exceptions ---- {{{
44
45 variable nextexception
46 1 nextexception !
47 : make-exception 
48     create nextexception @ ,
49     1 nextexception +!
50     does> @ ;
51
52 make-exception recoverable-exception
53 make-exception unrecoverable-exception
54
55 : display-exception-msg ( addr count -- )
56     bold fg red
57     ." Exception: "
58     type
59     reset-term ;
60
61 : throw" immediate 
62     [compile] s"
63
64     ['] rot , ['] dup ,
65
66     [compile] if
67         ['] -rot ,
68         ['] display-exception-msg ,
69     [compile] then
70
71     ['] throw ,
72 ;
73
74 \ }}}
75
76 \ ---- List-structured memory ---- {{{
77
78 10000 constant scheme-memsize
79
80 create car-cells scheme-memsize allot
81 create car-type-cells scheme-memsize allot
82 create cdr-cells scheme-memsize allot
83 create cdr-type-cells scheme-memsize allot
84
85 create nextfrees scheme-memsize allot
86 :noname
87     scheme-memsize 0 do
88         i 1+ nextfrees i + !
89     loop
90 ; execute
91         
92 variable nextfree
93 0 nextfree !
94
95 : inc-nextfree
96     nextfrees nextfree @ + @
97     nextfree !
98
99     nextfree @ scheme-memsize >= if
100         collect-garbage
101     then
102
103     nextfree @ scheme-memsize >= if
104         unrecoverable-exception throw s" Out of memory!"
105     then
106 ;
107
108 : cons ( car-obj cdr-obj -- pair-obj )
109     cdr-type-cells nextfree @ + !
110     cdr-cells nextfree @ + !
111     car-type-cells nextfree @ + !
112     car-cells nextfree @ + !
113
114     nextfree @ pair-type
115     inc-nextfree
116 ;
117
118 : car ( pair-obj -- car-obj )
119     drop
120     dup car-cells + @ swap
121     car-type-cells + @
122 ;
123
124 : cdr ( pair-obj -- car-obj )
125     drop
126     dup cdr-cells + @ swap
127     cdr-type-cells + @
128 ;
129
130 : set-car! ( obj pair-obj -- )
131     drop dup
132     rot swap  car-type-cells + !
133     car-cells + !
134 ;
135
136 : set-cdr! ( obj pair-obj -- )
137     drop dup
138     rot swap  cdr-type-cells + !
139     cdr-cells + !
140 ;
141
142 : nil 0 nil-type ;
143 : nil? nil-type istype? ;
144
145 : none 0 none-type ;
146 : none? none-type istype? ;
147
148 : objvar create nil swap , , ;
149
150 : value@ ( objvar -- val ) @ ;
151 : type@ ( objvar -- type ) 1+ @ ;
152 : value! ( newval objvar -- ) ! ;
153 : type! ( newtype objvar -- ) 1+ ! ;
154 : obj! ( newobj objvar -- ) dup rot swap 1+ ! ! ; 
155 : obj@ ( objvar -- obj ) dup @ swap 1+ @ ; 
156
157 : objeq? ( obj obj -- bool )
158     rot = -rot = and ;
159
160 : 2rot ( a1 a2 b1 b2 c1 c2 -- b1 b2 c1 c2 a1 a2 )
161     >R >R ( a1 a2 b1 b2 )
162     2swap ( b1 b2 a1 a2 )
163     R> R> ( b1 b2 a1 a2 c1 c2 )
164     2swap
165 ;
166
167 : -2rot ( a1 a2 b1 b2 c1 c2 -- c1 c2 a1 a2 b1 b2 )
168     2swap ( a1 a2 c1 c2 b1 b2 )
169     >R >R ( a1 a2 c1 c2 )
170     2swap ( c1 c2 a1 a2 )
171     R> R>
172 ;
173
174 \ }}}
175
176 \ ---- Port I/O ----  {{{
177
178 : fileport>fid ( fileport -- fid )
179     drop ;
180
181 : fid>fileport ( fid -- fileport )
182     fileport-type ;
183
184 : open-input-file ( addr n -- fileport )
185     r/o open-file drop fid>fileport
186 ;
187
188 : close-port ( fileport -- )
189     fileport>fid close-file drop
190 ;
191
192 objvar console-i/o-port
193 0 fileport-type console-i/o-port obj!
194
195 objvar current-input-port
196 console-i/o-port obj@ current-input-port obj!
197
198 : read-port ( fileport -- obj )
199     current-input-port obj!
200     read ;
201
202 : read-console ( -- obj )
203     console-i/o-port obj@ read-port ;
204
205 \ }}}
206
207 \ ---- Pre-defined symbols ---- {{{
208
209 objvar symbol-table
210
211 : duplicate-charlist ( charlist -- copy )
212     nil? false = if
213         2dup car 2swap cdr recurse cons
214     then ;
215
216 : charlist-equiv ( charlist charlist -- bool )
217
218     2over 2over
219
220     \ One or both nil
221     nil? -rot 2drop
222     if
223         nil? -rot 2drop
224         if
225             2drop 2drop true exit
226         else
227             2drop 2drop false exit
228         then
229     else
230         nil? -rot 2drop
231         if
232             2drop 2drop false exit
233         then
234     then
235
236     2over 2over
237
238     \ Neither nil
239     car drop -rot car drop = if
240             cdr 2swap cdr recurse
241         else
242             2drop 2drop false
243     then
244 ;
245
246 : charlist>symbol ( charlist -- symbol-obj )
247
248     symbol-table obj@
249
250     begin
251         nil? false =
252     while
253         2over 2over
254         car drop pair-type
255         charlist-equiv if
256             2swap 2drop
257             car
258             exit
259         else
260             cdr
261         then
262     repeat
263
264     2drop
265     drop symbol-type 2dup
266     symbol-table obj@ cons
267     symbol-table obj!
268 ;
269
270
271 : cstr>charlist ( addr n -- charlist )
272     dup 0= if
273         2drop nil
274     else
275         2dup drop @ character-type 2swap
276         swap 1+ swap 1-
277         recurse
278
279         cons
280     then
281 ;
282
283 : create-symbol ( -- )
284     bl word
285     count
286
287     cstr>charlist
288     charlist>symbol
289
290     create swap , ,
291     does> dup @ swap 1+ @
292 ;
293
294 create-symbol quote             quote-symbol
295 create-symbol quasiquote        quasiquote-symbol
296 create-symbol unquote           unquote-symbol
297 create-symbol unquote-splicing  unquote-splicing-symbol
298 create-symbol define            define-symbol
299 create-symbol define-macro      define-macro-symbol
300 create-symbol set!              set!-symbol
301 create-symbol ok                ok-symbol
302 create-symbol if                if-symbol
303 create-symbol lambda            lambda-symbol
304 create-symbol Î»                 Î»-symbol
305 create-symbol begin             begin-symbol
306
307 \ }}}
308
309 \ ---- Environments ---- {{{
310
311 : enclosing-env ( env -- env )
312     cdr ;
313
314 : first-frame ( env -- frame )
315     car ;
316
317 : make-frame ( vars vals -- frame )
318     cons ;
319
320 : frame-vars ( frame -- vars )
321     car ;
322
323 : frame-vals ( frame -- vals )
324     cdr ;
325
326 : add-binding ( var val frame -- )
327     2swap 2over frame-vals cons
328     2over set-cdr!
329     2swap 2over frame-vars cons
330     2swap set-car!
331 ;
332
333 : extend-env ( vars vals env -- env )
334     >R >R
335     make-frame
336     R> R>
337     cons
338 ;
339
340 objvar vars
341 objvar vals
342
343 : get-vars-vals-frame ( var frame -- bool )
344     2dup frame-vars vars obj!
345     frame-vals vals obj!
346
347     begin
348         vars obj@ nil objeq? false =
349     while
350         2dup vars obj@ car objeq? if
351             2drop true
352             exit
353         then
354
355         vars obj@ cdr vars obj!
356         vals obj@ cdr vals obj!
357     repeat
358
359     2drop false
360 ;
361
362 : get-vars-vals ( var env -- vars? vals? bool )
363
364     begin
365         nil? false =
366     while
367         2over 2over first-frame
368         get-vars-vals-frame if
369             2drop 2drop
370             vars obj@ vals obj@ true
371             exit
372         then
373
374         enclosing-env
375     repeat
376
377     2drop 2drop
378     false
379 ;
380
381 hide vars
382 hide vals
383
384 : lookup-var ( var env -- val )
385     get-vars-vals if
386         2swap 2drop car
387     else
388         recoverable-exception throw" Tried to read unbound variable."
389     then
390 ;
391
392 : set-var ( var val env -- )
393     >R >R 2swap R> R> ( val var env )
394     get-vars-vals if
395         2swap 2drop ( val vals )
396         set-car!
397     else
398         recoverable-exception throw" Tried to set unbound variable."
399     then
400 ;
401
402 objvar env
403
404 : define-var ( var val env -- )
405     env obj! 
406
407     2over env obj@ ( var val var env )
408     get-vars-vals if
409         2swap 2drop ( var val vals )
410         set-car!
411         2drop
412     else
413         env obj@
414         first-frame ( var val frame )
415         add-binding
416     then
417 ;
418
419 hide env
420
421 : make-procedure ( params body env -- proc )
422     nil
423     cons cons cons
424     drop compound-proc-type
425 ;
426
427 objvar global-env
428 nil nil nil extend-env
429 global-env obj!
430
431 \ }}}
432
433 \ ---- Primitives ---- {{{
434
435 : make-primitive ( cfa -- )
436     bl word
437     count
438
439     cstr>charlist
440     charlist>symbol
441   
442     rot primitive-proc-type ( var prim )
443     global-env obj@ define-var
444 ;
445
446 : ensure-arg-count ( args n -- )
447     dup 0= if
448         drop nil objeq? false = if
449             recoverable-exception throw" Too many arguments for primitive procedure."
450         then
451     else
452         -rot nil? if
453             recoverable-exception throw" Too few arguments for primitive procedure."
454         then
455         
456         cdr rot 1- recurse
457     then
458 ;
459
460 : ensure-arg-type-and-count ( tn tn-1 ... t2 t1 args n -- )
461     dup 0= if
462         drop nil objeq? false = if
463             recoverable-exception throw" Too many arguments for primitive procedure."
464         then
465     else
466         -rot nil? if
467             recoverable-exception throw" Too few arguments for primitive procedure."
468         then
469
470         2dup cdr 2swap car ( ... t1 n args' arg1 )
471         2rot 1- swap 2swap rot ( ... args' n-1 arg1 t1 )
472         istype? false = if
473             recoverable-exception throw" Incorrect type for primitive procedure."
474         then
475
476         2drop recurse
477     then
478
479 ;
480
481 : push-args-to-stack ( args -- arg1 arg2 ... argn )
482     begin
483         nil? false =
484     while
485         2dup car 2swap cdr
486     repeat
487
488     2drop
489 ;
490
491 : add-fa-checks ( cfa n -- cfa' )
492     here current @ 1+ dup @ , !
493     0 ,
494     here -rot
495     docol ,
496     ['] 2dup , ['] lit , , ['] ensure-arg-count ,
497     ['] push-args-to-stack ,
498     ['] lit , , ['] execute ,
499     ['] exit ,
500 ;
501
502 : add-fa-type-checks ( cfa t1 t2 ... tn n -- cfa' )
503     here current @ 1+ dup @ , !
504     0 ,
505     here >R
506     docol ,
507     ['] 2dup ,
508     ['] >R , ['] >R ,
509
510     dup ( cfa t1 t2 ... tn n m )
511     
512     begin
513         ?dup 0>
514     while
515         rot ['] lit , , ( cfa t1 t2 ... tn-1 n m )
516         1-
517     repeat
518
519     ['] R> , ['] R> ,
520
521     ['] lit , , ['] ensure-arg-type-and-count ,
522
523     ['] push-args-to-stack ,
524     ['] lit , , ['] execute ,
525     ['] exit ,
526
527     R>
528 ;
529
530 : make-fa-primitive ( cfa n -- )
531     add-fa-checks make-primitive ;
532
533 : make-fa-type-primitive ( cfa t1 t2 ... tn n -- )
534     add-fa-type-checks make-primitive ;
535
536 : arg-type-error
537             bold fg red ." Incorrect argument type." reset-term cr
538             abort
539 ;
540
541 : ensure-arg-type ( arg type -- arg )
542     istype? false = if
543         recoverable-exception throw" Incorrect argument type for primitive procedure."
544     then
545 ;
546
547
548 \ }}}
549
550 \ ---- Macros ---- {{{
551
552 objvar macro-table
553
554 ( Look up macro in macro table. Returns nil if
555   no macro is found. )
556 : lookup-macro ( name_symbol -- proc )
557     macro-table obj@
558
559     begin
560         nil? false =
561     while
562         2over 2over
563         car car objeq? if
564             2swap 2drop
565             car cdr
566             exit
567         then
568
569         cdr
570     repeat
571
572     2swap 2drop
573 ;
574
575 : make-macro ( name_symbol params body env -- )
576     make-procedure
577
578     2swap ( proc name_symbol )
579
580     macro-table obj@
581
582     begin
583         nil? false =
584     while
585         2over 2over ( proc name table name table )
586         car car objeq? if
587             2swap 2drop ( proc table )
588             car ( proc entry )
589             set-cdr!
590             exit
591         then
592
593         cdr
594     repeat
595
596     2drop
597
598     2swap cons
599     macro-table obj@ cons
600     macro-table obj!
601 ;
602
603 \ }}}
604
605 \ ---- Read ---- {{{
606
607 variable parse-idx
608 variable stored-parse-idx
609 create parse-str 161 allot
610 variable parse-str-span
611
612 create parse-idx-stack 10 allot 
613 variable parse-idx-sp
614 parse-idx-stack parse-idx-sp !
615
616 : push-parse-idx
617     parse-idx @ parse-idx-sp @ !
618     1 parse-idx-sp +!
619 ;
620
621 : pop-parse-idx
622     parse-idx-sp @ parse-idx-stack <= abort" Parse index stack underflow."
623
624     1 parse-idx-sp -!
625
626     parse-idx-sp @ @ parse-idx ! ;
627
628
629 : append-newline
630     '\n' parse-str parse-str-span @ + !
631     1 parse-str-span +! ;
632
633 : append-eof
634     4 parse-str parse-str-span @ + !
635     1 parse-str-span +!  ;
636
637 : empty-parse-str
638     0 parse-str-span !
639     0 parse-idx ! ;
640
641 : getline
642     current-input-port obj@ console-i/o-port obj@ objeq? if
643         parse-str 160 expect cr
644         span @ parse-str-span !
645     else
646         parse-str 160 current-input-port obj@ fileport>fid read-line
647         drop swap parse-str-span !
648
649         parse-str-span @ 0= and if append-eof then
650     then
651     append-newline
652     0 parse-idx ! ;
653
654 : inc-parse-idx
655     1 parse-idx +! ;
656
657 : dec-parse-idx
658     1 parse-idx -! ;
659
660 : charavailable? ( -- bool )
661     parse-str-span @ parse-idx @ > ;
662
663 : nextchar ( -- char )
664     charavailable? false = if getline then
665     parse-str parse-idx @ + @ ;
666
667 : '\t' 9 ;
668 : whitespace? ( -- bool )
669     nextchar BL = 
670     nextchar '\n' =
671     nextchar '\t' =
672     or or ;
673
674 : EOF 4 ; 
675 : eof? ( -- bool )
676     nextchar EOF = ;
677
678 : delim? ( -- bool )
679     whitespace?
680     nextchar [char] ( = or
681     nextchar [char] ) = or
682 ;
683
684 : commentstart? ( -- bool )
685     nextchar [char] ; = ;
686
687 : eatspaces
688
689     false \ Indicates whether or not we're eating a comment
690
691     begin
692         dup whitespace? or commentstart? or
693     while
694         dup nextchar '\n' = and if
695             invert \ Stop eating comment
696         else
697             dup false = commentstart? and if   
698                 invert \ Begin eating comment
699             then
700         then
701
702         inc-parse-idx
703     repeat
704     drop
705 ;
706
707 : digit? ( -- bool )
708     nextchar [char] 0 >=
709     nextchar [char] 9 <=
710     and ;
711
712 : minus? ( -- bool )
713     nextchar [char] - = ;
714
715 : plus? ( -- bool )
716     nextchar [char] + = ;
717
718 : fixnum? ( -- bool )
719     minus? plus? or if
720         inc-parse-idx
721
722         delim? if
723             dec-parse-idx
724             false exit
725         else
726             dec-parse-idx
727         then
728     else
729         digit? false = if
730             false exit
731         then
732     then
733
734     push-parse-idx
735     inc-parse-idx
736
737     begin digit? while
738         inc-parse-idx
739     repeat
740
741     delim? pop-parse-idx
742 ;
743
744 : flonum? ( -- bool )
745     push-parse-idx
746
747     minus? plus? or if
748         inc-parse-idx
749     then
750
751     \ Record starting parse idx:
752     \ Want to detect whether any characters (following +/-) were eaten.
753     parse-idx @
754
755     begin digit? while
756             inc-parse-idx
757     repeat
758
759     [char] . nextchar = if
760         inc-parse-idx
761         begin digit? while
762                 inc-parse-idx
763         repeat
764     then
765
766     [char] e nextchar = [char] E nextchar = or if
767         inc-parse-idx
768
769         minus? plus? or if
770             inc-parse-idx
771         then
772
773         digit? invert if
774             drop pop-parse-idx false exit
775         then
776
777         begin digit? while
778                 inc-parse-idx
779         repeat
780     then
781
782     \ This is a real number if characters were
783     \ eaten and the next characer is a delimiter.
784     parse-idx @ < delim? and
785
786     pop-parse-idx
787 ;
788
789 : boolean? ( -- bool )
790     nextchar [char] # <> if false exit then
791
792     push-parse-idx
793     inc-parse-idx
794
795     nextchar [char] t <>
796     nextchar [char] f <>
797     and if pop-parse-idx false exit then
798
799     inc-parse-idx
800     delim? if
801         pop-parse-idx
802         true
803     else
804         pop-parse-idx
805         false
806     then
807 ;
808
809 : str-equiv? ( str -- bool )
810
811     push-parse-idx
812
813     true -rot
814
815     swap dup rot + swap
816
817     do
818         i @ nextchar <> if
819             drop false
820             leave
821         then
822
823         inc-parse-idx
824     loop
825
826     delim? false = if drop false then
827
828     pop-parse-idx
829 ;
830
831 : character? ( -- bool )
832     nextchar [char] # <> if false exit then
833
834     push-parse-idx
835     inc-parse-idx
836
837     nextchar [char] \ <> if pop-parse-idx false exit then
838
839     inc-parse-idx
840
841     S" newline" str-equiv? if pop-parse-idx true exit then
842     S" space" str-equiv? if pop-parse-idx true exit then
843     S" tab" str-equiv? if pop-parse-idx true exit then
844
845     charavailable? false = if pop-parse-idx false exit then
846
847     pop-parse-idx true
848 ;
849
850 : pair? ( -- bool )
851     nextchar [char] ( = ;
852
853 : string? ( -- bool )
854     nextchar [char] " = ;
855
856 : readfixnum ( -- fixnum )
857     plus? minus? or if
858         minus?
859         inc-parse-idx
860     else
861         false
862     then
863
864     0
865
866     begin digit? while
867         10 * nextchar [char] 0 - +
868         inc-parse-idx
869     repeat
870
871     swap if negate then
872
873     fixnum-type
874 ;
875
876 : readflonum ( -- flonum )
877     readfixnum drop
878     dup 0< swap abs i->f
879
880     [char] . nextchar = if
881         inc-parse-idx
882
883         10.0 ( f exp )
884
885         begin digit? while
886             nextchar [char] 0 - i->f ( f exp d )
887             over f/ rot f+ ( exp f' )
888             swap 10.0 f* ( f' exp' )
889             inc-parse-idx
890         repeat
891
892         drop
893     then
894
895     [char] e nextchar = [char] E nextchar = or if
896         inc-parse-idx
897         10.0
898         readfixnum drop i->f
899         f^ f*
900     then
901
902     swap if
903         -1.0 f*
904     then
905
906     flonum-type
907 ;
908
909 : readbool ( -- bool-obj )
910     inc-parse-idx
911     
912     nextchar [char] f = if
913         false
914     else
915         true
916     then
917
918     inc-parse-idx
919
920     boolean-type
921 ;
922
923 : readchar ( -- char-obj )
924     inc-parse-idx
925     inc-parse-idx
926
927     S" newline" str-equiv? if 7 parse-idx +! '\n' character-type exit then
928     S" space" str-equiv? if 5 parse-idx +! bl character-type exit then
929     S" tab" str-equiv? if 3 parse-idx +! 9 character-type exit then
930
931     nextchar character-type
932
933     inc-parse-idx
934 ;
935
936 : readstring ( -- charlist )
937     nextchar [char] " = if
938         inc-parse-idx
939
940         delim? false = if
941             bold fg red
942             ." No delimiter following right double quote. Aborting." cr
943             reset-term abort
944         then
945
946         dec-parse-idx
947
948         0 nil-type exit
949     then
950
951     nextchar [char] \ = if
952         inc-parse-idx
953         nextchar case
954             [char] n of '\n' endof
955             [char] " of [char] " endof
956             [char] \
957         endcase
958     else
959         nextchar
960     then
961     inc-parse-idx character-type
962
963     recurse
964
965     cons
966 ;
967
968 : readsymbol ( -- charlist )
969     delim? if nil exit then
970
971     nextchar inc-parse-idx character-type
972
973     recurse
974
975     cons
976 ;
977
978 : readpair ( -- pairobj )
979     eatspaces
980
981     \ Empty lists
982     nextchar [char] ) = if
983         inc-parse-idx
984
985         delim? false = if
986             bold fg red
987             ." No delimiter following right paren. Aborting." cr
988             reset-term abort
989         then
990
991         dec-parse-idx
992
993         0 nil-type exit
994     then
995
996     \ Read first pair element
997     read
998
999     \ Pairs
1000     eatspaces
1001     nextchar [char] . = if
1002         inc-parse-idx
1003
1004         delim? false = if
1005             bold fg red
1006             ." No delimiter following '.'. Aborting." cr
1007             reset-term abort
1008         then
1009
1010         eatspaces read
1011     else
1012         recurse
1013     then
1014
1015     eatspaces
1016
1017     cons
1018 ;
1019
1020 \ Parse a scheme expression
1021 :noname ( -- obj )
1022
1023     eatspaces
1024
1025     fixnum? if
1026         readfixnum
1027         exit
1028     then
1029
1030     flonum? if
1031         readflonum
1032         exit
1033     then
1034
1035     boolean? if
1036         readbool
1037         exit
1038     then
1039
1040     character? if
1041         readchar
1042         exit
1043     then
1044
1045     string? if
1046         inc-parse-idx
1047
1048         readstring
1049         drop string-type
1050
1051         nextchar [char] " <> if
1052             bold red ." Missing closing double-quote." reset-term cr
1053             abort
1054         then
1055
1056         inc-parse-idx
1057
1058         exit
1059     then
1060
1061     pair? if
1062         inc-parse-idx
1063
1064         eatspaces
1065
1066         readpair
1067
1068         eatspaces
1069
1070         nextchar [char] ) <> if
1071             bold red ." Missing closing paren." reset-term cr
1072             abort
1073         then
1074
1075         inc-parse-idx
1076
1077         exit
1078     then
1079
1080     nextchar [char] ' = if
1081         inc-parse-idx
1082         quote-symbol recurse nil cons cons exit
1083     then
1084
1085     nextchar [char] ` = if
1086         inc-parse-idx
1087         quasiquote-symbol recurse nil cons cons exit
1088     then
1089
1090     nextchar [char] , = if
1091         inc-parse-idx
1092         nextchar [char] @ = if
1093             inc-parse-idx
1094             unquote-splicing-symbol recurse nil cons cons exit
1095         else
1096             unquote-symbol recurse nil cons cons exit
1097         then
1098     then
1099
1100     eof? if
1101         EOF character-type
1102         inc-parse-idx
1103         exit
1104     then
1105
1106     \ Anything else is parsed as a symbol
1107     readsymbol charlist>symbol
1108
1109     \ Replace Î» with lambda
1110     2dup Î»-symbol objeq? if
1111         2drop lambda-symbol
1112     then
1113     
1114
1115 ; is read
1116
1117 \ }}}
1118
1119 \ ---- Eval ---- {{{
1120
1121 : self-evaluating? ( obj -- obj bool )
1122     boolean-type istype? if true exit then
1123     fixnum-type istype? if true exit then
1124     flonum-type istype? if true exit then
1125     character-type istype? if true exit then
1126     string-type istype? if true exit then
1127     nil-type istype? if true exit then
1128     none-type istype? if true exit then
1129
1130     false
1131 ;
1132
1133 : tagged-list? ( obj tag-obj -- obj bool )
1134     2over 
1135     pair-type istype? false = if
1136         2drop 2drop false
1137     else
1138         car objeq?
1139     then ;
1140
1141 : quote? ( obj -- obj bool )
1142     quote-symbol tagged-list?  ;
1143
1144 : quote-body ( quote-obj -- quote-body-obj )
1145     cdr car ;
1146
1147 : quasiquote? ( obj -- obj bool )
1148     quasiquote-symbol tagged-list? ;
1149
1150 : unquote? ( obj -- obj bool )
1151     unquote-symbol tagged-list? ;
1152
1153 : unquote-splicing? ( obj -- obj bool )
1154     unquote-splicing-symbol tagged-list? ;
1155
1156 : eval-unquote ( env obj -- res )
1157     cdr ( env args )
1158
1159     nil? if
1160         recoverable-exception throw" no arguments to unquote."
1161     then
1162
1163     2dup cdr
1164     nil? false = if
1165         recoverable-exception throw" too many arguments to unquote."
1166     then
1167
1168     2drop car 2swap eval
1169 ;
1170
1171 ( Create a new list from elements of l1 consed on to l2 )
1172 : join-lists ( l2 l1 -- l3 )
1173     nil? if 2drop exit then
1174
1175     2dup car
1176     -2rot cdr
1177     recurse cons
1178 ;
1179
1180 defer eval-quasiquote-item
1181 : eval-quasiquote-pair ( env obj -- res )
1182     2over 2over ( env obj env obj )
1183
1184     cdr eval-quasiquote-item
1185
1186     -2rot car ( cdritem env objcar )
1187
1188     unquote-splicing? if
1189         eval-unquote ( cdritems caritem )
1190
1191         2swap nil? if
1192             2drop
1193         else
1194             2swap join-lists
1195         then
1196     else
1197         eval-quasiquote-item ( cdritems caritem )
1198         2swap cons
1199     then
1200
1201 ;
1202
1203 :noname ( env obj )
1204     nil? if
1205         2swap 2drop exit
1206     then
1207
1208     unquote? if
1209         eval-unquote exit
1210     then
1211
1212     pair-type istype? if
1213         eval-quasiquote-pair exit
1214     then
1215
1216     2swap 2drop
1217 ; is eval-quasiquote-item
1218
1219 : eval-quasiquote ( obj env -- res )
1220     2swap cdr ( env args )
1221
1222     nil? if
1223         recoverable-exception throw" no arguments to quasiquote."
1224     then
1225
1226     2dup cdr ( env args args-cdr )
1227     nil? false = if
1228         recoverable-exception throw" too many arguments to quasiquote."
1229     then
1230
1231     2drop car ( env arg )
1232
1233     eval-quasiquote-item
1234 ;
1235
1236 : variable? ( obj -- obj bool )
1237     symbol-type istype? ;
1238
1239 : definition? ( obj -- obj bool )
1240     define-symbol tagged-list? ;
1241
1242 : make-lambda ( params body -- lambda-exp )
1243     lambda-symbol -2rot cons cons ;
1244
1245 ( Handles iterative expansion of defines in
1246   terms of nested lambdas. Most Schemes only
1247   handle one iteration of expansion! )
1248 : definition-var-val ( obj -- var val )
1249
1250     cdr 2dup cdr 2swap car ( val var )
1251
1252     begin
1253         symbol-type istype? false =
1254     while
1255         2dup cdr 2swap car ( val formals var' )
1256         -2rot 2swap ( var' formals val )
1257         make-lambda nil cons ( var' val' )
1258         2swap ( val' var' )
1259     repeat
1260
1261     2swap car
1262 ;
1263
1264 : eval-definition ( obj env -- res )
1265     2dup 2rot ( env env obj )
1266     definition-var-val ( env env var val )
1267     2rot eval  ( env var val )
1268
1269     2rot ( var val env )
1270     define-var
1271
1272     ok-symbol
1273 ;
1274
1275 : assignment? ( obj -- obj bool )
1276     set!-symbol tagged-list? ;
1277
1278 : assignment-var ( obj -- var )
1279     cdr car ;
1280     
1281 : assignment-val ( obj -- val )
1282     cdr cdr car ;
1283
1284 : eval-assignment ( obj env -- res )
1285     2swap 
1286     2over 2over ( env obj env obj )
1287     assignment-val 2swap ( env obj valexp env )
1288     eval  ( env obj val )
1289     
1290     2swap assignment-var 2swap ( env var val )
1291
1292     2rot ( var val env )
1293     set-var
1294
1295     ok-symbol
1296 ;
1297
1298 : macro-definition? ( obj -- obj bool )
1299     define-macro-symbol tagged-list? ;
1300
1301 : macro-definition-name ( exp -- mname )
1302     cdr car car ;
1303
1304 : macro-definition-params ( exp -- params )
1305     cdr car cdr ;
1306
1307 : macro-definition-body ( exp -- body )
1308     cdr cdr ;
1309
1310 objvar env
1311 : eval-define-macro ( obj env -- res )
1312     env obj!
1313
1314     2dup macro-definition-name 2swap ( name obj )
1315     2dup macro-definition-params 2swap ( name params obj )
1316     macro-definition-body ( name params body )
1317
1318     env obj@ ( name params body env )
1319
1320     make-macro
1321
1322     ok-symbol
1323 ;
1324 hide env
1325
1326 : if? ( obj -- obj bool )
1327     if-symbol tagged-list? ;
1328
1329 : if-predicate ( ifobj -- pred )
1330     cdr car ;
1331
1332 : if-consequent ( ifobj -- conseq )
1333     cdr cdr car ;
1334
1335 : if-alternative ( ifobj -- alt|none )
1336     cdr cdr cdr
1337     nil? if
1338         2drop none
1339     else
1340         car
1341     then ;
1342
1343 : false? ( boolobj -- boolean )
1344     boolean-type istype? if
1345         false boolean-type objeq?
1346     else
1347         2drop false
1348     then
1349 ;
1350
1351 : true? ( boolobj -- bool )
1352     false? invert ;
1353
1354 : lambda? ( obj -- obj bool )
1355     lambda-symbol tagged-list? ;
1356
1357 : lambda-parameters ( obj -- params )
1358     cdr car ;
1359
1360 : lambda-body ( obj -- body )
1361     cdr cdr ;
1362
1363 : begin? ( obj -- obj bool )
1364     begin-symbol tagged-list? ;
1365
1366 : begin-actions ( obj -- actions )
1367     cdr ;
1368
1369 : eval-sequence ( explist env -- finalexp env )
1370     ( Evaluates all bar the final expressions in
1371       an an expression list. The final expression
1372       is returned to allow for tail optimization. )
1373
1374     2swap ( env explist )
1375
1376     \ Abort on empty list
1377     nil? if
1378         2drop none
1379         2swap exit
1380     then
1381
1382     begin
1383         2dup cdr ( env explist nextexplist )
1384         nil? false =
1385     while
1386         -2rot car 2over ( nextexplist env exp env )
1387         eval
1388         2drop \ discard result
1389         2swap ( env nextexplist )
1390     repeat
1391
1392     2drop car 2swap ( finalexp env )
1393 ;
1394
1395 : application? ( obj -- obj bool )
1396     pair-type istype? ;
1397
1398 : operator ( obj -- operator )
1399     car ;
1400
1401 : operands ( obj -- operands )
1402     cdr ;
1403
1404 : nooperands? ( operands -- bool )
1405     nil objeq? ;
1406
1407 : first-operand ( operands -- operand )
1408     car ;
1409
1410 : rest-operands ( operands -- other-operands )
1411     cdr ;
1412
1413 : list-of-vals ( args env -- vals )
1414     2swap
1415
1416     2dup nooperands? if
1417         2swap 2drop
1418     else
1419         2over 2over first-operand 2swap eval
1420         -2rot rest-operands 2swap recurse
1421         cons
1422     then
1423 ;
1424
1425 : procedure-params ( proc -- params )
1426     drop pair-type car ;
1427
1428 : procedure-body ( proc -- body )
1429     drop pair-type cdr car ;
1430
1431 : procedure-env ( proc -- body )
1432     drop pair-type cdr cdr car ;
1433
1434 ( Ensure terminating symbol arg name is handled
1435   specially to allow for variadic procedures. )
1436 : flatten-proc-args ( argvals argnames -- argvals' argnames' )
1437     nil? if
1438         2over nil? false = if
1439             recoverable-exception throw" Too many arguments for compound procedure."
1440         else
1441             2drop
1442         then
1443         exit
1444     then
1445
1446     symbol-type istype? if
1447         nil cons
1448         2swap
1449         nil cons
1450         2swap
1451         exit
1452     then
1453
1454     2over
1455     nil? if
1456         recoverable-exception throw" Too few arguments for compound procedure."
1457     else
1458         cdr
1459     then
1460
1461     2over cdr
1462
1463     recurse ( argvals argnames argvals'' argnames'' )
1464     2rot car 2swap cons  ( argvals argvals'' argnames' )
1465     2rot car 2rot cons ( argnames' argvals' )
1466     2swap
1467 ;
1468
1469 : apply ( proc argvals -- result )
1470         2swap dup case
1471             primitive-proc-type of
1472                 drop execute     
1473             endof
1474
1475             compound-proc-type of
1476                 2dup procedure-body ( argvals proc body )
1477                 -2rot 2dup procedure-params ( body argvals proc argnames )
1478                 -2rot procedure-env ( body argnames argvals procenv )
1479
1480                 -2rot 2swap
1481                 flatten-proc-args
1482                 2swap 2rot
1483
1484                 extend-env ( body env )
1485
1486                 eval-sequence
1487
1488                 R> drop ['] eval goto-deferred  \ Tail call optimization
1489             endof
1490
1491             recoverable-exception throw" Object not applicable."
1492         endcase
1493 ;
1494
1495 ( Simply evaluates the given procedure with expbody as its argument. )
1496 : macro-expand ( proc expbody -- result )
1497     2swap
1498     2dup procedure-body ( expbody proc procbody )
1499     -2rot 2dup procedure-params ( procbody expbody proc argnames )
1500     -2rot procedure-env ( procbody argnames expbody procenv )
1501     
1502     -2rot 2swap
1503     flatten-proc-args
1504     2swap 2rot
1505
1506     extend-env eval-sequence eval
1507 ;
1508
1509 :noname ( obj env -- result )
1510     2swap
1511
1512     self-evaluating? if
1513         2swap 2drop
1514         exit
1515     then
1516
1517     quote? if
1518         quote-body
1519         2swap 2drop
1520         exit
1521     then
1522
1523     quasiquote? if
1524         2swap eval-quasiquote
1525         exit
1526     then
1527
1528     variable? if
1529         2swap lookup-var
1530         exit
1531     then
1532
1533     definition? if
1534         2swap eval-definition
1535         exit
1536     then
1537
1538     assignment? if
1539         2swap eval-assignment
1540         exit
1541     then
1542
1543     macro-definition? if
1544         2swap eval-define-macro
1545         exit
1546     then
1547
1548     if? if
1549         2over 2over
1550         if-predicate
1551         2swap eval 
1552
1553         true? if
1554             if-consequent
1555         else
1556             if-alternative
1557         then
1558
1559         2swap
1560         ['] eval goto-deferred
1561     then
1562
1563     lambda? if
1564         2dup lambda-parameters
1565         2swap lambda-body
1566         2rot make-procedure
1567         exit
1568     then
1569
1570     begin? if
1571         begin-actions 2swap
1572         eval-sequence
1573         ['] eval goto-deferred
1574     then
1575
1576     application? if
1577
1578         2over 2over ( env exp env exp )
1579         operator ( env exp env opname )
1580
1581         2dup lookup-macro nil? false = if
1582              \ Macro function evaluation
1583
1584             ( env exp env opname mproc )
1585             2swap 2drop -2rot 2drop cdr ( env mproc body )
1586
1587             macro-expand
1588
1589             2swap
1590             ['] eval goto-deferred
1591         else
1592            \ Regular function application
1593
1594             2drop ( env exp env opname )
1595
1596             2swap eval ( env exp proc )
1597
1598             -2rot ( proc env exp )
1599             operands 2swap ( proc operands env )
1600             list-of-vals ( proc argvals )
1601
1602             apply
1603             exit
1604         then
1605     then
1606
1607     recoverable-exception throw" Tried to evaluate object with unknown type."
1608 ; is eval
1609
1610 \ }}}
1611
1612 \ ---- Print ---- {{{
1613
1614 : printfixnum ( fixnum -- ) drop 0 .R ;
1615
1616 : printflonum ( flonum -- ) drop f. ;
1617
1618 : printbool ( bool -- )
1619     drop if
1620         ." #t"
1621     else
1622         ." #f"
1623     then
1624 ;
1625
1626 : printchar ( charobj -- )
1627     drop
1628     case
1629         9 of ." #\tab" endof
1630         bl of ." #\space" endof
1631         '\n' of ." #\newline" endof
1632         
1633         dup ." #\" emit
1634     endcase
1635 ;
1636
1637 : (printstring) ( stringobj -- )
1638     nil? if 2drop exit then
1639
1640     2dup car drop dup
1641     case
1642         '\n' of ." \n" drop endof
1643         [char] \ of ." \\" drop endof
1644         [char] " of [char] \ emit [char] " emit drop endof
1645         emit
1646     endcase
1647
1648     cdr recurse
1649 ;
1650 : printstring ( stringobj -- )
1651     [char] " emit
1652     (printstring)
1653     [char] " emit ;
1654
1655 : printsymbol ( symbolobj -- )
1656     nil-type istype? if 2drop exit then
1657
1658     2dup car drop emit
1659     cdr recurse
1660 ;
1661
1662 : printnil ( nilobj -- )
1663     2drop ." ()" ;
1664
1665 : printpair ( pairobj -- )
1666     2dup
1667     car print
1668     cdr
1669     nil-type istype? if 2drop exit then
1670     pair-type istype? if space recurse exit then
1671     ."  . " print
1672 ;
1673
1674 : printprim ( primobj -- )
1675     2drop ." <primitive procedure>" ;
1676
1677 : printcomp ( primobj -- )
1678     2drop ." <compound procedure>" ;
1679
1680 : printnone ( noneobj -- )
1681     2drop ." Unspecified return value" ;
1682
1683 : printport ( port -- )
1684     2drop ." <port>" ;
1685
1686 :noname ( obj -- )
1687     fixnum-type istype? if printfixnum exit then
1688     flonum-type istype? if printflonum exit then
1689     boolean-type istype? if printbool exit then
1690     character-type istype? if printchar exit then
1691     string-type istype? if printstring exit then
1692     symbol-type istype? if printsymbol exit then
1693     nil-type istype? if printnil exit then
1694     pair-type istype? if ." (" printpair ." )" exit then
1695     primitive-proc-type istype? if printprim exit then
1696     compound-proc-type istype? if printcomp exit then
1697     none-type istype? if printnone exit then
1698
1699     recoverable-exception throw" Tried to print object with unknown type."
1700 ; is print
1701
1702 \ }}}
1703
1704 \ ---- Garbage Collection ---- {{{
1705
1706 variable gc-enabled
1707 false gc-enabled !
1708
1709 variable gc-stack-depth
1710
1711 : enable-gc
1712     depth gc-stack-depth !
1713     true gc-enabled ! ;
1714
1715 : disable-gc
1716     false gc-enabled ! ;
1717
1718 : gc-enabled?
1719     gc-enabled @ ;
1720
1721 : pairlike? ( obj -- obj bool )
1722     pair-type istype? if true exit then
1723     string-type istype? if true exit then
1724     symbol-type istype? if true exit then
1725     compound-proc-type istype? if true exit then
1726
1727     false
1728 ;
1729
1730 : pairlike-marked? ( obj -- obj bool )
1731     over nextfrees + @ 0=
1732 ;
1733
1734 : mark-pairlike ( obj -- obj )
1735         over nextfrees + 0 swap !
1736 ;
1737
1738 : gc-unmark ( -- )
1739     scheme-memsize 0 do
1740         1 nextfrees i + !
1741     loop
1742 ;
1743
1744 : gc-mark-obj ( obj -- )
1745
1746     pairlike? invert if 2drop exit then
1747     pairlike-marked? if 2drop exit then
1748
1749     mark-pairlike
1750
1751     drop pair-type 2dup
1752
1753     car recurse
1754     cdr recurse
1755 ;
1756
1757 : gc-sweep
1758     scheme-memsize nextfree !
1759     0 scheme-memsize 1- do
1760         nextfrees i + @ 0<> if
1761             nextfree @ nextfrees i + !
1762             i nextfree !
1763         then
1764     -1 +loop
1765 ;
1766
1767 \ Following a GC, this gives the amount of free memory
1768 : gc-count-marked
1769     0
1770     scheme-memsize 0 do
1771         nextfrees i + @ 0= if 1+ then
1772     loop
1773 ;
1774
1775 \ Debugging word - helps spot memory that is retained
1776 : gc-zero-unmarked
1777     scheme-memsize 0 do
1778         nextfrees i + @ 0<> if
1779             0 car-cells i + !
1780             0 cdr-cells i + !
1781         then
1782     loop
1783 ;
1784
1785 :noname
1786     \ ." GC! "
1787
1788     gc-unmark
1789
1790     symbol-table obj@ gc-mark-obj
1791     macro-table obj@ gc-mark-obj
1792     global-env obj@ gc-mark-obj
1793
1794     depth gc-stack-depth @ do
1795         PSP0 i + 1 + @
1796         PSP0 i + 2 + @
1797
1798         gc-mark-obj
1799     2 +loop
1800
1801     gc-sweep
1802
1803     \ ." (" gc-count-marked . ." pairs marked as used.)" cr
1804 ; is collect-garbage
1805
1806 \ }}}
1807
1808 \ ---- Loading files ---- {{{
1809
1810 : charlist>cstr ( charlist addr -- n )
1811
1812     dup 2swap ( origaddr addr charlist )
1813
1814     begin 
1815         nil? false =
1816     while
1817         2dup cdr 2swap car 
1818         drop ( origaddr addr charlist char )
1819         -rot 2swap ( origaddr charlist addr char )
1820         over !
1821         1+ -rot ( origaddr nextaddr charlist )
1822     repeat
1823
1824     2drop ( origaddr finaladdr ) 
1825     swap -
1826 ;
1827
1828 : load ( addr n -- finalResult )
1829     open-input-file
1830
1831     empty-parse-str
1832
1833     ok-symbol ( port res )
1834
1835     begin
1836         2over read-port ( port res obj )
1837
1838         2dup EOF character-type objeq? if
1839             2drop 2swap close-port
1840             exit
1841         then
1842
1843         2swap 2drop ( port obj )
1844
1845         global-env obj@ eval ( port res )
1846     again
1847 ;
1848
1849 \ }}}
1850
1851 \ ---- Standard Library ---- {{{
1852
1853     include scheme-primitives.4th
1854
1855     s" scheme-library.scm" load 2drop
1856     
1857 \ }}}
1858
1859 \ ---- REPL ----
1860
1861 ( REPL calls REPL-BODY in a loop until repl-body returns true. )
1862 : repl-body ( -- bool )
1863     cr bold fg green ." > " reset-term
1864
1865     read-console
1866
1867     2dup EOF character-type objeq? if
1868         2drop
1869         bold fg blue ." Moriturus te saluto." reset-term cr
1870         true exit
1871     then
1872
1873     global-env obj@ eval
1874
1875     fg cyan ." ; " print reset-term
1876
1877     false
1878 ;
1879
1880 : repl
1881     cr ." Welcome to scheme.forth.jl!" cr
1882        ." Use Ctrl-D to exit." cr
1883
1884     empty-parse-str
1885
1886     enable-gc
1887
1888     begin
1889         ['] repl-body catch
1890         case
1891             recoverable-exception of false endof
1892             unrecoverable-exception of true endof
1893
1894             throw false
1895         endcase
1896     until
1897 ;
1898
1899 forth definitions
1900
1901 \ vim:fdm=marker