File:
[gforth] /
gforth /
glocals.fs
Revision
1.25:
download - view:
text,
annotated -
select for diffs
Mon Aug 26 10:07:18 1996 UTC (26 years, 9 months ago) by
anton
Branches:
MAIN
CVS tags:
HEAD
' and ['] now deliver an error for compile-only words.
renamed special- words into interpret/compile- words.
refactored some of the recent changes.
adapted see to the changes
added way to make a word that defines words with differring
interpretation and compilation code.
1: \ A powerful locals implementation
2:
3: \ Copyright (C) 1995 Free Software Foundation, Inc.
4:
5: \ This file is part of Gforth.
6:
7: \ Gforth is free software; you can redistribute it and/or
8: \ modify it under the terms of the GNU General Public License
9: \ as published by the Free Software Foundation; either version 2
10: \ of the License, or (at your option) any later version.
11:
12: \ This program is distributed in the hope that it will be useful,
13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15: \ GNU General Public License for more details.
16:
17: \ You should have received a copy of the GNU General Public License
18: \ along with this program; if not, write to the Free Software
19: \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
20:
21:
22: \ More documentation can be found in the manual and in
23: \ http://www.complang.tuwien.ac.at/papers/ertl94l.ps.gz
24:
25: \ Local variables are quite important for writing readable programs, but
26: \ IMO (anton) they are the worst part of the standard. There they are very
27: \ restricted and have an ugly interface.
28:
29: \ So, we implement the locals wordset, but do not recommend using
30: \ locals-ext (which is a really bad user interface for locals).
31:
32: \ We also have a nice and powerful user-interface for locals: locals are
33: \ defined with
34:
35: \ { local1 local2 ... }
36: \ or
37: \ { local1 local2 ... -- ... }
38: \ (anything after the -- is just a comment)
39:
40: \ Every local in this list consists of an optional type specification
41: \ and a name. If there is only the name, it stands for a cell-sized
42: \ value (i.e., you get the value of the local variable, not it's
43: \ address). The following type specifiers stand before the name:
44:
45: \ Specifier Type Access
46: \ W: Cell value
47: \ W^ Cell address
48: \ D: Double value
49: \ D^ Double address
50: \ F: Float value
51: \ F^ Float address
52: \ C: Char value
53: \ C^ Char address
54:
55: \ The local variables are initialized with values from the appropriate
56: \ stack. In contrast to the examples in the standard document our locals
57: \ take the arguments in the expected way: The last local gets the top of
58: \ stack, the second last gets the second stack item etc. An example:
59:
60: \ : CX* { F: Ar F: Ai F: Br F: Bi -- Cr Ci }
61: \ \ complex multiplication
62: \ Ar Br f* Ai Bi f* f-
63: \ Ar Bi f* Ai Br f* f+ ;
64:
65: \ There will also be a way to add user types, but it is not yet decided,
66: \ how. Ideas are welcome.
67:
68: \ Locals defined in this manner live until (!! see below).
69: \ Their names can be used during this time to get
70: \ their value or address; The addresses produced in this way become
71: \ invalid at the end of the lifetime.
72:
73: \ Values can be changed with TO, but this is not recomended (TO is a
74: \ kludge and words lose the single-assignment property, which makes them
75: \ harder to analyse).
76:
77: \ As for the internals, we use a special locals stack. This eliminates
78: \ the problems and restrictions of reusing the return stack and allows
79: \ to store floats as locals: the return stack is not guaranteed to be
80: \ aligned correctly, but our locals stack must be float-aligned between
81: \ words.
82:
83: \ Other things about the internals are pretty unclear now.
84:
85: \ Currently locals may only be
86: \ defined at the outer level and TO is not supported.
87:
88: require search-order.fs
89: require float.fs
90:
91: : compile-@local ( n -- ) \ gforth compile-fetch-local
92: case
93: 0 of postpone @local0 endof
94: 1 cells of postpone @local1 endof
95: 2 cells of postpone @local2 endof
96: 3 cells of postpone @local3 endof
97: ( otherwise ) dup postpone @local# ,
98: endcase ;
99:
100: : compile-f@local ( n -- ) \ gforth compile-f-fetch-local
101: case
102: 0 of postpone f@local0 endof
103: 1 floats of postpone f@local1 endof
104: ( otherwise ) dup postpone f@local# ,
105: endcase ;
106:
107: \ the locals stack grows downwards (see primitives)
108: \ of the local variables of a group (in braces) the leftmost is on top,
109: \ i.e. by going onto the locals stack the order is reversed.
110: \ there are alignment gaps if necessary.
111: \ lp must have the strictest alignment (usually float) across calls;
112: \ for simplicity we align it strictly for every group.
113:
114: slowvoc @
115: slowvoc on \ we want a linked list for the vocabulary locals
116: vocabulary locals \ this contains the local variables
117: ' locals >body ' locals-list >body !
118: slowvoc !
119:
120: create locals-buffer 1000 allot \ !! limited and unsafe
121: \ here the names of the local variables are stored
122: \ we would have problems storing them at the normal dp
123:
124: variable locals-dp \ so here's the special dp for locals.
125:
126: : alignlp-w ( n1 -- n2 )
127: \ cell-align size and generate the corresponding code for aligning lp
128: aligned dup adjust-locals-size ;
129:
130: : alignlp-f ( n1 -- n2 )
131: faligned dup adjust-locals-size ;
132:
133: \ a local declaration group (the braces stuff) is compiled by calling
134: \ the appropriate compile-pushlocal for the locals, starting with the
135: \ righmost local; the names are already created earlier, the
136: \ compile-pushlocal just inserts the offsets from the frame base.
137:
138: : compile-pushlocal-w ( a-addr -- ) ( run-time: w -- )
139: \ compiles a push of a local variable, and adjusts locals-size
140: \ stores the offset of the local variable to a-addr
141: locals-size @ alignlp-w cell+ dup locals-size !
142: swap !
143: postpone >l ;
144:
145: : compile-pushlocal-f ( a-addr -- ) ( run-time: f -- )
146: locals-size @ alignlp-f float+ dup locals-size !
147: swap !
148: postpone f>l ;
149:
150: : compile-pushlocal-d ( a-addr -- ) ( run-time: w1 w2 -- )
151: locals-size @ alignlp-w cell+ cell+ dup locals-size !
152: swap !
153: postpone swap postpone >l postpone >l ;
154:
155: : compile-pushlocal-c ( a-addr -- ) ( run-time: w -- )
156: -1 chars compile-lp+!
157: locals-size @ swap !
158: postpone lp@ postpone c! ;
159:
160: : create-local ( " name" -- a-addr )
161: \ defines the local "name"; the offset of the local shall be
162: \ stored in a-addr
163: create
164: immediate restrict
165: here 0 , ( place for the offset ) ;
166:
167: : lp-offset ( n1 -- n2 )
168: \ converts the offset from the frame start to an offset from lp and
169: \ i.e., the address of the local is lp+locals_size-offset
170: locals-size @ swap - ;
171:
172: : lp-offset, ( n -- )
173: \ converts the offset from the frame start to an offset from lp and
174: \ adds it as inline argument to a preceding locals primitive
175: lp-offset , ;
176:
177: vocabulary locals-types \ this contains all the type specifyers, -- and }
178: locals-types definitions
179:
180: : W: ( "name" -- a-addr xt ) \ gforth w-colon
181: create-local
182: \ xt produces the appropriate locals pushing code when executed
183: ['] compile-pushlocal-w
184: does> ( Compilation: -- ) ( Run-time: -- w )
185: \ compiles a local variable access
186: @ lp-offset compile-@local ;
187:
188: : W^ ( "name" -- a-addr xt ) \ gforth w-caret
189: create-local
190: ['] compile-pushlocal-w
191: does> ( Compilation: -- ) ( Run-time: -- w )
192: postpone laddr# @ lp-offset, ;
193:
194: : F: ( "name" -- a-addr xt ) \ gforth f-colon
195: create-local
196: ['] compile-pushlocal-f
197: does> ( Compilation: -- ) ( Run-time: -- w )
198: @ lp-offset compile-f@local ;
199:
200: : F^ ( "name" -- a-addr xt ) \ gforth f-caret
201: create-local
202: ['] compile-pushlocal-f
203: does> ( Compilation: -- ) ( Run-time: -- w )
204: postpone laddr# @ lp-offset, ;
205:
206: : D: ( "name" -- a-addr xt ) \ gforth d-colon
207: create-local
208: ['] compile-pushlocal-d
209: does> ( Compilation: -- ) ( Run-time: -- w )
210: postpone laddr# @ lp-offset, postpone 2@ ;
211:
212: : D^ ( "name" -- a-addr xt ) \ gforth d-caret
213: create-local
214: ['] compile-pushlocal-d
215: does> ( Compilation: -- ) ( Run-time: -- w )
216: postpone laddr# @ lp-offset, ;
217:
218: : C: ( "name" -- a-addr xt ) \ gforth c-colon
219: create-local
220: ['] compile-pushlocal-c
221: does> ( Compilation: -- ) ( Run-time: -- w )
222: postpone laddr# @ lp-offset, postpone c@ ;
223:
224: : C^ ( "name" -- a-addr xt ) \ gforth c-caret
225: create-local
226: ['] compile-pushlocal-c
227: does> ( Compilation: -- ) ( Run-time: -- w )
228: postpone laddr# @ lp-offset, ;
229:
230: \ you may want to make comments in a locals definitions group:
231: ' \ alias \ immediate
232: ' ( alias ( immediate
233:
234: forth definitions
235:
236: \ the following gymnastics are for declaring locals without type specifier.
237: \ we exploit a feature of our dictionary: every wordlist
238: \ has it's own methods for finding words etc.
239: \ So we create a vocabulary new-locals, that creates a 'w:' local named x
240: \ when it is asked if it contains x.
241:
242: also locals-types
243:
244: : new-locals-find ( caddr u w -- nfa )
245: \ this is the find method of the new-locals vocabulary
246: \ make a new local with name caddr u; w is ignored
247: \ the returned nfa denotes a word that produces what W: produces
248: \ !! do the whole thing without nextname
249: drop nextname
250: ['] W: >name ;
251:
252: previous
253:
254: : new-locals-reveal ( -- )
255: true abort" this should not happen: new-locals-reveal" ;
256:
257: create new-locals-map ( -- wordlist-map )
258: ' new-locals-find A, ' new-locals-reveal A,
259:
260: vocabulary new-locals
261: new-locals-map ' new-locals >body cell+ A! \ !! use special access words
262:
263: variable old-dpp
264:
265: \ and now, finally, the user interface words
266: : { ( -- addr wid 0 ) \ gforth open-brace
267: dp old-dpp !
268: locals-dp dpp !
269: also new-locals
270: also get-current locals definitions locals-types
271: 0 TO locals-wordlist
272: 0 postpone [ ; immediate
273:
274: locals-types definitions
275:
276: : } ( addr wid 0 a-addr1 xt1 ... -- ) \ gforth close-brace
277: \ ends locals definitions
278: ] old-dpp @ dpp !
279: begin
280: dup
281: while
282: execute
283: repeat
284: drop
285: locals-size @ alignlp-f locals-size ! \ the strictest alignment
286: set-current
287: previous previous
288: locals-list TO locals-wordlist ;
289:
290: : -- ( addr wid 0 ... -- ) \ gforth dash-dash
291: }
292: [char] } parse 2drop ;
293:
294: forth definitions
295:
296: \ A few thoughts on automatic scopes for locals and how they can be
297: \ implemented:
298:
299: \ We have to combine locals with the control structures. My basic idea
300: \ was to start the life of a local at the declaration point. The life
301: \ would end at any control flow join (THEN, BEGIN etc.) where the local
302: \ is lot live on both input flows (note that the local can still live in
303: \ other, later parts of the control flow). This would make a local live
304: \ as long as you expected and sometimes longer (e.g. a local declared in
305: \ a BEGIN..UNTIL loop would still live after the UNTIL).
306:
307: \ The following example illustrates the problems of this approach:
308:
309: \ { z }
310: \ if
311: \ { x }
312: \ begin
313: \ { y }
314: \ [ 1 cs-roll ] then
315: \ ...
316: \ until
317:
318: \ x lives only until the BEGIN, but the compiler does not know this
319: \ until it compiles the UNTIL (it can deduce it at the THEN, because at
320: \ that point x lives in no thread, but that does not help much). This is
321: \ solved by optimistically assuming at the BEGIN that x lives, but
322: \ warning at the UNTIL that it does not. The user is then responsible
323: \ for checking that x is only used where it lives.
324:
325: \ The produced code might look like this (leaving out alignment code):
326:
327: \ >l ( z )
328: \ ?branch <then>
329: \ >l ( x )
330: \ <begin>:
331: \ >l ( y )
332: \ lp+!# 8 ( RIP: x,y )
333: \ <then>:
334: \ ...
335: \ lp+!# -4 ( adjust lp to <begin> state )
336: \ ?branch <begin>
337: \ lp+!# 4 ( undo adjust )
338:
339: \ The BEGIN problem also has another incarnation:
340:
341: \ AHEAD
342: \ BEGIN
343: \ x
344: \ [ 1 CS-ROLL ] THEN
345: \ { x }
346: \ ...
347: \ UNTIL
348:
349: \ should be legal: The BEGIN is not a control flow join in this case,
350: \ since it cannot be entered from the top; therefore the definition of x
351: \ dominates the use. But the compiler processes the use first, and since
352: \ it does not look ahead to notice the definition, it will complain
353: \ about it. Here's another variation of this problem:
354:
355: \ IF
356: \ { x }
357: \ ELSE
358: \ ...
359: \ AHEAD
360: \ BEGIN
361: \ x
362: \ [ 2 CS-ROLL ] THEN
363: \ ...
364: \ UNTIL
365:
366: \ In this case x is defined before the use, and the definition dominates
367: \ the use, but the compiler does not know this until it processes the
368: \ UNTIL. So what should the compiler assume does live at the BEGIN, if
369: \ the BEGIN is not a control flow join? The safest assumption would be
370: \ the intersection of all locals lists on the control flow
371: \ stack. However, our compiler assumes that the same variables are live
372: \ as on the top of the control flow stack. This covers the following case:
373:
374: \ { x }
375: \ AHEAD
376: \ BEGIN
377: \ x
378: \ [ 1 CS-ROLL ] THEN
379: \ ...
380: \ UNTIL
381:
382: \ If this assumption is too optimistic, the compiler will warn the user.
383:
384: \ Implementation: migrated to kernal.fs
385:
386: \ THEN (another control flow from before joins the current one):
387: \ The new locals-list is the intersection of the current locals-list and
388: \ the orig-local-list. The new locals-size is the (alignment-adjusted)
389: \ size of the new locals-list. The following code is generated:
390: \ lp+!# (current-locals-size - orig-locals-size)
391: \ <then>:
392: \ lp+!# (orig-locals-size - new-locals-size)
393:
394: \ Of course "lp+!# 0" is not generated. Still this is admittedly a bit
395: \ inefficient, e.g. if there is a locals declaration between IF and
396: \ ELSE. However, if ELSE generates an appropriate "lp+!#" before the
397: \ branch, there will be none after the target <then>.
398:
399: \ explicit scoping
400:
401: : scope ( compilation -- scope ; run-time -- ) \ gforth
402: cs-push-part scopestart ; immediate
403:
404: : endscope ( compilation scope -- ; run-time -- ) \ gforth
405: scope?
406: drop
407: locals-list @ common-list
408: dup list-size adjust-locals-size
409: locals-list ! ; immediate
410:
411: \ adapt the hooks
412:
413: : locals-:-hook ( sys -- sys addr xt n )
414: \ addr is the nfa of the defined word, xt its xt
415: DEFERS :-hook
416: last @ lastcfa @
417: clear-leave-stack
418: 0 locals-size !
419: locals-buffer locals-dp !
420: 0 locals-list !
421: dead-code off
422: defstart ;
423:
424: : locals-;-hook ( sys addr xt sys -- sys )
425: def?
426: 0 TO locals-wordlist
427: 0 adjust-locals-size ( not every def ends with an exit )
428: lastcfa ! last !
429: DEFERS ;-hook ;
430:
431: ' locals-:-hook IS :-hook
432: ' locals-;-hook IS ;-hook
433:
434: \ The words in the locals dictionary space are not deleted until the end
435: \ of the current word. This is a bit too conservative, but very simple.
436:
437: \ There are a few cases to consider: (see above)
438:
439: \ after AGAIN, AHEAD, EXIT (the current control flow is dead):
440: \ We have to special-case the above cases against that. In this case the
441: \ things above are not control flow joins. Everything should be taken
442: \ over from the live flow. No lp+!# is generated.
443:
444: \ !! The lp gymnastics for UNTIL are also a real problem: locals cannot be
445: \ used in signal handlers (or anything else that may be called while
446: \ locals live beyond the lp) without changing the locals stack.
447:
448: \ About warning against uses of dead locals. There are several options:
449:
450: \ 1) Do not complain (After all, this is Forth;-)
451:
452: \ 2) Additional restrictions can be imposed so that the situation cannot
453: \ arise; the programmer would have to introduce explicit scoping
454: \ declarations in cases like the above one. I.e., complain if there are
455: \ locals that are live before the BEGIN but not before the corresponding
456: \ AGAIN (replace DO etc. for BEGIN and UNTIL etc. for AGAIN).
457:
458: \ 3) The real thing: i.e. complain, iff a local lives at a BEGIN, is
459: \ used on a path starting at the BEGIN, and does not live at the
460: \ corresponding AGAIN. This is somewhat hard to implement. a) How does
461: \ the compiler know when it is working on a path starting at a BEGIN
462: \ (consider "{ x } if begin [ 1 cs-roll ] else x endif again")? b) How
463: \ is the usage info stored?
464:
465: \ For now I'll resort to alternative 2. When it produces warnings they
466: \ will often be spurious, but warnings should be rare. And better
467: \ spurious warnings now and then than days of bug-searching.
468:
469: \ Explicit scoping of locals is implemented by cs-pushing the current
470: \ locals-list and -size (and an unused cell, to make the size equal to
471: \ the other entries) at the start of the scope, and restoring them at
472: \ the end of the scope to the intersection, like THEN does.
473:
474:
475: \ And here's finally the ANS standard stuff
476:
477: : (local) ( addr u -- ) \ local paren-local-paren
478: \ a little space-inefficient, but well deserved ;-)
479: \ In exchange, there are no restrictions whatsoever on using (local)
480: \ as long as you use it in a definition
481: dup
482: if
483: nextname POSTPONE { [ also locals-types ] W: } [ previous ]
484: else
485: 2drop
486: endif ;
487:
488: : >definer ( xt -- definer )
489: \ this gives a unique identifier for the way the xt was defined
490: \ words defined with different does>-codes have different definers
491: \ the definer can be used for comparison and in definer!
492: dup >code-address [ ' spaces >code-address ] Literal =
493: \ !! this definition will not work on some implementations for `bits'
494: if \ if >code-address delivers the same value for all does>-def'd words
495: >does-code 1 or \ bit 0 marks special treatment for does codes
496: else
497: >code-address
498: then ;
499:
500: : definer! ( definer xt -- )
501: \ gives the word represented by xt the behaviour associated with definer
502: over 1 and if
503: swap [ 1 invert ] literal and does-code!
504: else
505: code-address!
506: then ;
507:
508: :noname
509: ' dup >definer [ ' locals-wordlist >definer ] literal =
510: if
511: >body !
512: else
513: -&32 throw
514: endif ;
515: :noname
516: 0 0 0. 0.0e0 { c: clocal w: wlocal d: dlocal f: flocal }
517: ' dup >definer
518: case
519: [ ' locals-wordlist >definer ] literal \ value
520: OF >body POSTPONE Aliteral POSTPONE ! ENDOF
521: [ comp' clocal drop >definer ] literal
522: OF POSTPONE laddr# >body @ lp-offset, POSTPONE c! ENDOF
523: [ comp' wlocal drop >definer ] literal
524: OF POSTPONE laddr# >body @ lp-offset, POSTPONE ! ENDOF
525: [ comp' dlocal drop >definer ] literal
526: OF POSTPONE laddr# >body @ lp-offset, POSTPONE 2! ENDOF
527: [ comp' flocal drop >definer ] literal
528: OF POSTPONE laddr# >body @ lp-offset, POSTPONE f! ENDOF
529: -&32 throw
530: endcase ;
531: interpret/compile: TO ( c|w|d|r "name" -- ) \ core-ext,local
532:
533: : locals|
534: \ don't use 'locals|'! use '{'! A portable and free '{'
535: \ implementation is compat/anslocals.fs
536: BEGIN
537: name 2dup s" |" compare 0<>
538: WHILE
539: (local)
540: REPEAT
541: drop 0 (local) ; immediate restrict
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>