1: \ CROSS.FS The Cross-Compiler 06oct92py
2: \ Idea and implementation: Bernd Paysan (py)
3:
4: \ Copyright (C) 1995,1996,1997,1998,1999,2000 Free Software Foundation, Inc.
5:
6: \ This file is part of Gforth.
7:
8: \ Gforth is free software; you can redistribute it and/or
9: \ modify it under the terms of the GNU General Public License
10: \ as published by the Free Software Foundation; either version 2
11: \ of the License, or (at your option) any later version.
12:
13: \ This program is distributed in the hope that it will be useful,
14: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
15: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16: \ GNU General Public License for more details.
17:
18: \ You should have received a copy of the GNU General Public License
19: \ along with this program; if not, write to the Free Software
20: \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
21:
22: 0
23: [IF]
24:
25: ToDo:
26: - Crossdoc destination ./doc/crossdoc.fd makes no sense when
27: cross.fs is used seperately. jaw
28: - Do we need this char translation with >address and in branchoffset?
29: (>body also affected) jaw
30:
31: [THEN]
32:
33: s" compat/strcomp.fs" included
34:
35: hex
36:
37: \ debugging for compiling
38:
39: \ print stack at each colon definition
40: \ : : save-input cr bl word count type restore-input throw .s : ;
41:
42: \ print stack at each created word
43: \ : create save-input cr bl word count type restore-input throw .s create ;
44:
45:
46: \ \ ------------- Setup Vocabularies
47:
48: \ Remark: Vocabulary is not ANS, but it should work...
49:
50: Vocabulary Cross
51: Vocabulary Target
52: Vocabulary Ghosts
53: Vocabulary Minimal
54: only Forth also Target also also
55: definitions Forth
56:
57: : T previous Ghosts also Target ; immediate
58: : G Ghosts ; immediate
59: : H previous Forth also Cross ; immediate
60:
61: forth definitions
62:
63: : T previous Ghosts also Target ; immediate
64: : G Ghosts ; immediate
65:
66:
67: : >cross also Cross definitions previous ;
68: : >target also Target definitions previous ;
69: : >minimal also Minimal definitions previous ;
70:
71: H
72:
73: >CROSS
74:
75: \ Test against this definitions to find out whether we are cross-compiling
76: \ may be usefull for assemblers
77: 0 Constant gforth-cross-indicator
78:
79: \ find out whether we are compiling with gforth
80:
81: : defined? bl word find nip ;
82: defined? emit-file defined? toupper and \ drop 0
83: [IF]
84: \ use this in a gforth system
85: : \GFORTH ; immediate
86: : \ANSI postpone \ ; immediate
87: [ELSE]
88: : \GFORTH postpone \ ; immediate
89: : \ANSI ; immediate
90: [THEN]
91:
92: \ANSI : [IFUNDEF] defined? 0= postpone [IF] ; immediate
93: \ANSI : [IFDEF] defined? postpone [IF] ; immediate
94: 0 \ANSI drop 1
95: [IF]
96: : \G postpone \ ; immediate
97: : rdrop postpone r> postpone drop ; immediate
98: : name bl word count ;
99: : bounds over + swap ;
100: : scan >r BEGIN dup WHILE over c@ r@ <> WHILE 1 /string REPEAT THEN rdrop ;
101: : linked here over @ , swap ! ;
102: : alias create , DOES> @ EXECUTE ;
103: : defer ['] noop alias ;
104: : is state @
105: IF ' >body postpone literal postpone !
106: ELSE ' >body ! THEN ; immediate
107: : 0>= 0< 0= ;
108: : d<> rot <> -rot <> or ;
109: : toupper dup [char] a [char] z 1+ within IF [char] A [char] a - + THEN ;
110: Variable ebuf
111: : emit-file ( c fd -- ior ) swap ebuf c! ebuf 1 chars rot write-file ;
112: 0a Constant #lf
113: 0d Constant #cr
114:
115: [IFUNDEF] Warnings Variable Warnings [THEN]
116:
117: \ \ Number parsing 23feb93py
118:
119: \ number? number 23feb93py
120:
121: Variable dpl
122:
123: hex
124: Create bases 10 , 2 , A , 100 ,
125: \ 16 2 10 character
126:
127: \ !! protect BASE saving wrapper against exceptions
128: : getbase ( addr u -- addr' u' )
129: over c@ [char] $ - dup 4 u<
130: IF
131: cells bases + @ base ! 1 /string
132: ELSE
133: drop
134: THEN ;
135:
136: : sign? ( addr u -- addr u flag )
137: over c@ [char] - = dup >r
138: IF
139: 1 /string
140: THEN
141: r> ;
142:
143: : s>unumber? ( addr u -- ud flag )
144: over [char] ' =
145: IF \ a ' alone is rather unusual :-)
146: drop char+ c@ 0 true EXIT
147: THEN
148: base @ >r dpl on getbase
149: 0. 2swap
150: BEGIN ( d addr len )
151: dup >r >number dup
152: WHILE \ there are characters left
153: dup r> -
154: WHILE \ the last >number parsed something
155: dup 1- dpl ! over c@ [char] . =
156: WHILE \ the current char is '.'
157: 1 /string
158: REPEAT THEN \ there are unparseable characters left
159: 2drop false
160: ELSE
161: rdrop 2drop true
162: THEN
163: r> base ! ;
164:
165: \ ouch, this is complicated; there must be a simpler way - anton
166: : s>number? ( addr len -- d f )
167: \ converts string addr len into d, flag indicates success
168: sign? >r
169: s>unumber?
170: 0= IF
171: rdrop false
172: ELSE \ no characters left, all ok
173: r>
174: IF
175: dnegate
176: THEN
177: true
178: THEN ;
179:
180: : s>number ( addr len -- d )
181: \ don't use this, there is no way to tell success
182: s>number? drop ;
183:
184: : snumber? ( c-addr u -- 0 / n -1 / d 0> )
185: s>number? 0=
186: IF
187: 2drop false EXIT
188: THEN
189: dpl @ dup 0< IF
190: nip
191: ELSE
192: 1+
193: THEN ;
194:
195: : number? ( string -- string 0 / n -1 / d 0> )
196: dup >r count snumber? dup if
197: rdrop
198: else
199: r> swap
200: then ;
201:
202: : number ( string -- d )
203: number? ?dup 0= abort" ?" 0<
204: IF
205: s>d
206: THEN ;
207:
208: [THEN]
209:
210: \ this provides assert( and struct stuff
211: \GFORTH [IFUNDEF] assert1(
212: \GFORTH also forth definitions require assert.fs previous
213: \GFORTH [THEN]
214:
215: >CROSS
216:
217: hex \ the defualt base for the cross-compiler is hex !!
218: \ Warnings off
219:
220: \ words that are generaly useful
221:
222: : KB 400 * ;
223: : >wordlist ( vocabulary-xt -- wordlist-struct )
224: also execute get-order swap >r 1- set-order r> ;
225:
226: : umax 2dup u< IF swap THEN drop ;
227: : umin 2dup u> IF swap THEN drop ;
228:
229: : string, ( c-addr u -- )
230: \ puts down string as cstring
231: dup c, here swap chars dup allot move ;
232:
233: : ," [char] " parse string, ;
234:
235: : SetValue ( n -- <name> )
236: \G Same behaviour as "Value" if the <name> is not defined
237: \G Same behaviour as "to" if <name> is defined
238: \G SetValue searches in the current vocabulary
239: save-input bl word >r restore-input throw r> count
240: get-current search-wordlist
241: IF drop >r
242: \ we have to set current to be topmost context wordlist
243: get-order get-order get-current swap 1+ set-order
244: r> ['] to execute
245: set-order
246: ELSE Value THEN ;
247:
248: : DefaultValue ( n -- <name> )
249: \G Same behaviour as "Value" if the <name> is not defined
250: \G DefaultValue searches in the current vocabulary
251: save-input bl word >r restore-input throw r> count
252: get-current search-wordlist
253: IF bl word drop 2drop ELSE Value THEN ;
254:
255: hex
256:
257: \ FIXME delete`
258: \ 1 Constant Cross-Flag \ to check whether assembler compiler plug-ins are
259: \ for cross-compiling
260: \ No! we use "[IFUNDEF]" there to find out whether we are target compiling!!!
261:
262: \ FIXME move down
263: : comment? ( c-addr u -- c-addr u )
264: 2dup s" (" str=
265: IF postpone (
266: ELSE 2dup s" \" str= IF postpone \ THEN
267: THEN ;
268:
269: : X ( -- <name> )
270: \G The next word in the input is a target word.
271: \G Equivalent to T <name> but without permanent
272: \G switch to target dictionary. Used as prefix e.g. for @, !, here etc.
273: bl word count [ ' target >wordlist ] Literal search-wordlist
274: IF state @ IF compile, ELSE execute THEN
275: ELSE -1 ABORT" Cross: access method not supported!"
276: THEN ; immediate
277:
278: \ Begin CROSS COMPILER:
279:
280: \ debugging
281:
282: 0 [IF]
283:
284: This implements debugflags for the cross compiler and the compiled
285: images. It works identical to the has-flags in the environment.
286: The debugflags are defined in a vocabluary. If the word exists and
287: its value is true, the flag is switched on.
288:
289: [THEN]
290:
291: >CROSS
292:
293: Vocabulary debugflags \ debug flags for cross
294: also debugflags get-order over
295: Constant debugflags-wl
296: set-order previous
297:
298: : DebugFlag
299: get-current >r debugflags-wl set-current
300: SetValue
301: r> set-current ;
302:
303: : Debug? ( adr u -- flag )
304: \G return true if debug flag is defined or switched on
305: debugflags-wl search-wordlist
306: IF EXECUTE
307: ELSE false THEN ;
308:
309: : D? ( <name> -- flag )
310: \G return true if debug flag is defined or switched on
311: \G while compiling we do not return the current value but
312: bl word count debug? ;
313:
314: : [d?]
315: \G compile the value-xt so the debug flag can be switched
316: \G the flag must exist!
317: bl word count debugflags-wl search-wordlist
318: IF compile,
319: ELSE -1 ABORT" unknown debug flag"
320: \ POSTPONE false
321: THEN ; immediate
322:
323: : symentry ( adr len taddr -- )
324: \G Produce a symbol table (an optional symbol address
325: \G map) if wanted
326: [ [IFDEF] fd-symbol-table ]
327: base @ swap hex s>d <# 8 0 DO # LOOP #> fd-symbol-table write-file throw base !
328: s" :" fd-symbol-table write-file throw
329: fd-symbol-table write-line throw
330: [ [ELSE] ]
331: 2drop drop
332: [ [THEN] ] ;
333:
334:
335: \ \ -------------------- source file
336:
337: decimal
338:
339: Variable cross-file-list
340: 0 cross-file-list !
341: Variable target-file-list
342: 0 target-file-list !
343: Variable host-file-list
344: 0 host-file-list !
345:
346: cross-file-list Value file-list
347: 0 Value source-desc
348:
349: \ file loading
350:
351: : >fl-id 1 cells + ;
352: : >fl-name 2 cells + ;
353:
354: Variable filelist 0 filelist !
355: Create NoFile ," #load-file#"
356:
357: : loadfile ( -- adr )
358: source-desc ?dup IF >fl-name ELSE NoFile THEN ;
359:
360: : sourcefilename ( -- adr len )
361: loadfile count ;
362:
363: \ANSI : sourceline# 0 ;
364:
365: \ \ -------------------- path handling from kernel/paths.fs
366:
367: \ paths.fs path file handling 03may97jaw
368:
369: \ -Changing the search-path:
370: \ fpath+ <path> adds a directory to the searchpath
371: \ fpath= <path>|<path> makes complete now searchpath
372: \ seperator is |
373: \ .fpath displays the search path
374: \ remark I:
375: \ a ./ in the beginning of filename is expanded to the directory the
376: \ current file comes from. ./ can also be included in the search-path!
377: \ ~+/ loads from the current working directory
378:
379: \ remark II:
380: \ if there is no sufficient space for the search path increase it!
381:
382:
383: \ -Creating custom paths:
384:
385: \ It is possible to use the search mechanism on yourself.
386:
387: \ Make a buffer for the path:
388: \ create mypath 100 chars , \ maximum length (is checked)
389: \ 0 , \ real len
390: \ 100 chars allot \ space for path
391: \ use the same functions as above with:
392: \ mypath path+
393: \ mypath path=
394: \ mypath .path
395:
396: \ do a open with the search path:
397: \ open-path-file ( adr len path -- fd adr len ior )
398: \ the file is opened read-only; if the file is not found an error is generated
399:
400: \ questions to: wilke@jwdt.com
401:
402: [IFUNDEF] +place
403: : +place ( adr len adr )
404: 2dup >r >r
405: dup c@ char+ + swap move
406: r> r> dup c@ rot + swap c! ;
407: [THEN]
408:
409: [IFUNDEF] place
410: : place ( c-addr1 u c-addr2 )
411: 2dup c! char+ swap move ;
412: [THEN]
413:
414: \ if we have path handling, use this and the setup of it
415: [IFUNDEF] open-fpath-file
416:
417: create sourcepath 1024 chars , 0 , 1024 chars allot \ !! make this dynamic
418: sourcepath value fpath
419:
420: : also-path ( adr len path^ -- )
421: >r
422: \ len check
423: r@ cell+ @ over + r@ @ u> ABORT" path buffer too small!"
424: \ copy into
425: tuck r@ cell+ dup @ cell+ + swap cmove
426: \ make delimiter
427: 0 r@ cell+ dup @ cell+ + 2 pick + c! 1 + r> cell+ +!
428: ;
429:
430: : only-path ( adr len path^ -- )
431: dup 0 swap cell+ ! also-path ;
432:
433: : path+ ( path-addr "dir" -- ) \ gforth
434: \G Add the directory @var{dir} to the search path @var{path-addr}.
435: name rot also-path ;
436:
437: : fpath+ ( "dir" ) \ gforth
438: \G Add directory @var{dir} to the Forth search path.
439: fpath path+ ;
440:
441: : path= ( path-addr "dir1|dir2|dir3" ) \ gforth
442: \G Make a complete new search path; the path separator is |.
443: name 2dup bounds ?DO i c@ [char] | = IF 0 i c! THEN LOOP
444: rot only-path ;
445:
446: : fpath= ( "dir1|dir2|dir3" ) \ gforth
447: \G Make a complete new Forth search path; the path separator is |.
448: fpath path= ;
449:
450: : path>counted cell+ dup cell+ swap @ ;
451:
452: : next-path ( adr len -- adr2 len2 )
453: 2dup 0 scan
454: dup 0= IF 2drop 0 -rot 0 -rot EXIT THEN
455: >r 1+ -rot r@ 1- -rot
456: r> - ;
457:
458: : previous-path ( path^ -- )
459: dup path>counted
460: BEGIN tuck dup WHILE repeat ;
461:
462: : .path ( path-addr -- ) \ gforth
463: \G Display the contents of the search path @var{path-addr}.
464: path>counted
465: BEGIN next-path dup WHILE type space REPEAT 2drop 2drop ;
466:
467: : .fpath ( -- ) \ gforth
468: \G Display the contents of the Forth search path.
469: fpath .path ;
470:
471: : absolut-path? ( addr u -- flag ) \ gforth
472: \G A path is absolute if it starts with a / or a ~ (~ expansion),
473: \G or if it is in the form ./*, extended regexp: ^[/~]|./, or if
474: \G it has a colon as second character ("C:..."). Paths simply
475: \G containing a / are not absolute!
476: 2dup 2 u> swap 1+ c@ [char] : = and >r \ dos absoulte: c:/....
477: over c@ [char] / = >r
478: over c@ [char] ~ = >r
479: \ 2dup S" ../" string-prefix? r> or >r \ not catered for in expandtopic
480: S" ./" string-prefix?
481: r> r> r> or or or ;
482:
483: Create ofile 0 c, 255 chars allot
484: Create tfile 0 c, 255 chars allot
485:
486: : pathsep? dup [char] / = swap [char] \ = or ;
487:
488: : need/ ofile dup c@ + c@ pathsep? 0= IF s" /" ofile +place THEN ;
489:
490: : extractpath ( adr len -- adr len2 )
491: BEGIN dup WHILE 1-
492: 2dup + c@ pathsep? IF EXIT THEN
493: REPEAT ;
494:
495: : remove~+ ( -- )
496: ofile count s" ~+/" string-prefix?
497: IF
498: ofile count 3 /string ofile place
499: THEN ;
500:
501: : expandtopic ( -- ) \ stack effect correct? - anton
502: \ expands "./" into an absolute name
503: ofile count s" ./" string-prefix?
504: IF
505: ofile count 1 /string tfile place
506: 0 ofile c! sourcefilename extractpath ofile place
507: ofile c@ IF need/ THEN
508: tfile count over c@ pathsep? IF 1 /string THEN
509: ofile +place
510: THEN ;
511:
512: : compact.. ( adr len -- adr2 len2 )
513: \ deletes phrases like "xy/.." out of our directory name 2dec97jaw
514: over swap
515: BEGIN dup WHILE
516: dup >r '/ scan 2dup s" /../" string-prefix?
517: IF
518: dup r> - >r 4 /string over r> + 4 -
519: swap 2dup + >r move dup r> over -
520: ELSE
521: rdrop dup 1 min /string
522: THEN
523: REPEAT drop over - ;
524:
525: : reworkdir ( -- )
526: remove~+
527: ofile count compact..
528: nip ofile c! ;
529:
530: : open-ofile ( -- fid ior )
531: \G opens the file whose name is in ofile
532: expandtopic reworkdir
533: ofile count r/o open-file ;
534:
535: : check-path ( adr1 len1 adr2 len2 -- fd 0 | 0 <>0 )
536: 0 ofile ! >r >r ofile place need/
537: r> r> ofile +place
538: open-ofile ;
539:
540: : open-path-file ( addr1 u1 path-addr -- wfileid addr2 u2 0 | ior ) \ gforth
541: \G Look in path @var{path-addr} for the file specified by @var{addr1 u1}.
542: \G If found, the resulting path and an open file descriptor
543: \G are returned. If the file is not found, @var{ior} is non-zero.
544: >r
545: 2dup absolut-path?
546: IF rdrop
547: ofile place open-ofile
548: dup 0= IF >r ofile count r> THEN EXIT
549: ELSE r> path>counted
550: BEGIN next-path dup
551: WHILE 5 pick 5 pick check-path
552: 0= IF >r 2drop 2drop r> ofile count 0 EXIT ELSE drop THEN
553: REPEAT
554: 2drop 2drop 2drop -38
555: THEN ;
556:
557: : open-fpath-file ( addr1 u1 -- wfileid addr2 u2 0 | ior ) \ gforth
558: \G Look in the Forth search path for the file specified by @var{addr1 u1}.
559: \G If found, the resulting path and an open file descriptor
560: \G are returned. If the file is not found, @var{ior} is non-zero.
561: fpath open-path-file ;
562:
563: fpath= ~+
564:
565: [THEN]
566:
567: \ \ -------------------- include require 13may99jaw
568:
569: >CROSS
570:
571: : add-included-file ( adr len -- adr )
572: dup >fl-name char+ allocate throw >r
573: file-list @ r@ ! r@ file-list !
574: r@ >fl-name place r> ;
575:
576: : included? ( c-addr u -- f )
577: file-list
578: BEGIN @ dup
579: WHILE >r 2dup r@ >fl-name count str=
580: IF rdrop 2drop true EXIT THEN
581: r>
582: REPEAT
583: 2drop drop false ;
584:
585: false DebugFlag showincludedfiles
586:
587: : included1 ( fd adr u -- )
588: \ include file adr u / fd
589: \ we don't use fd with include-file, because the forth system
590: \ doesn't know the name of the file to get a nice error report
591: [d?] showincludedfiles
592: IF cr ." Including: " 2dup type ." ..." THEN
593: rot close-file throw
594: source-desc >r
595: add-included-file to source-desc
596: sourcefilename
597: ['] included catch
598: r> to source-desc
599: throw ;
600:
601: : included ( adr len -- )
602: cross-file-list to file-list
603: open-fpath-file throw
604: included1 ;
605:
606: : required ( adr len -- )
607: cross-file-list to file-list
608: open-fpath-file throw \ 2dup cr ." R:" type
609: 2dup included?
610: IF 2drop close-file throw
611: ELSE included1
612: THEN ;
613:
614: : include bl word count included ;
615:
616: : require bl word count required ;
617:
618: 0 [IF]
619:
620: also forth definitions previous
621:
622: : included ( adr len -- ) included ;
623:
624: : required ( adr len -- ) required ;
625:
626: : include include ;
627:
628: : require require ;
629:
630: [THEN]
631:
632: >CROSS
633: hex
634:
635: \ \ -------------------- Error Handling 05aug97jaw
636:
637: \ Flags
638:
639: also forth definitions \ these values may be predefined before
640: \ the cross-compiler is loaded
641:
642: false DefaultValue stack-warn \ check on empty stack at any definition
643: false DefaultValue create-forward-warn \ warn on forward declaration of created words
644:
645: previous >CROSS
646:
647: : .dec
648: base @ decimal swap . base ! ;
649:
650: : .sourcepos
651: cr sourcefilename type ." :"
652: sourceline# .dec ;
653:
654: : warnhead
655: \G display error-message head
656: \G perhaps with linenumber and filename
657: .sourcepos ." Warning: " ;
658:
659: : empty? depth IF .sourcepos ." Stack not empty!" THEN ;
660:
661: stack-warn [IF]
662: : defempty? empty? ;
663: [ELSE]
664: : defempty? ; immediate
665: [THEN]
666:
667: \ \ -------------------- Compiler Plug Ins 01aug97jaw
668:
669: >CROSS
670:
671: \ Compiler States
672:
673: Variable comp-state
674: 0 Constant interpreting
675: 1 Constant compiling
676: 2 Constant resolving
677: 3 Constant assembling
678:
679: : compiling? comp-state @ compiling = ;
680:
681: : pi-undefined -1 ABORT" Plugin undefined" ;
682:
683: : Plugin ( -- : pluginname )
684: Create
685: \ for normal cross-compiling only one action
686: \ exists, this fields are identical. For the instant
687: \ simulation environment we need, two actions for each plugin
688: \ the target one and the one that generates the simulation code
689: ['] pi-undefined , \ action
690: ['] pi-undefined , \ target plugin action
691: 8765 , \ plugin magic
692: DOES> perform ;
693:
694: Plugin DummyPlugin
695:
696: : 'PI ( -- addr : pluginname )
697: ' >body dup 2 cells + @ 8765 <> ABORT" not a plugin" ;
698:
699: : plugin-of ( xt -- : pluginname )
700: dup 'PI 2! ;
701:
702: : action-of ( xt -- : plunginname )
703: 'PI cell+ ! ;
704:
705: : TPA ( -- : plugin )
706: \ target plugin action
707: \ executes current target action of plugin
708: 'PI cell+ POSTPONE literal POSTPONE perform ; immediate
709:
710: Variable ppi-temp 0 ppi-temp !
711:
712: : pa:
713: \g define plugin action
714: ppi-temp @ ABORT" pa: definition not closed"
715: 'PI ppi-temp ! :noname ;
716:
717: : ;pa
718: \g end a definition for plugin action
719: POSTPONE ; ppi-temp @ ! 0 ppi-temp ! ; immediate
720:
721:
722: Plugin dlit, ( d -- ) \ compile numerical value the target
723: Plugin lit, ( n -- )
724: Plugin alit, ( n -- )
725:
726: Plugin branch, ( target-addr -- ) \ compiles a branch
727: Plugin ?branch, ( target-addr -- ) \ compiles a ?branch
728: Plugin branchmark, ( -- branch-addr ) \ reserves room for a branch
729: Plugin ?branchmark, ( -- branch-addr ) \ reserves room for a ?branch
730: Plugin ?domark, ( -- branch-addr ) \ reserves room for a ?do branch
731: Plugin branchto, ( -- ) \ actual program position is target of a branch (do e.g. alignment)
732: ' NOOP plugin-of branchto,
733: Plugin branchtoresolve, ( branch-addr -- ) \ resolves a forward reference from branchmark
734: Plugin branchtomark, ( -- target-addr ) \ marks a branch destination
735:
736: Plugin colon, ( tcfa -- ) \ compiles call to tcfa at current position
737: Plugin prim, ( tcfa -- ) \ compiles primitive invocation
738: Plugin colonmark, ( -- addr ) \ marks a colon call
739: Plugin colon-resolve ( tcfa addr -- )
740:
741: Plugin addr-resolve ( target-addr addr -- )
742: Plugin doer-resolve ( ghost res-pnt target-addr addr -- ghost res-pnt )
743:
744: Plugin ncontrols? ( [ xn ... x1 ] n -- ) \ checks wheter n control structures are open
745: Plugin if, ( -- if-token )
746: Plugin else, ( if-token -- if-token )
747: Plugin then, ( if-token -- )
748: Plugin ahead,
749: Plugin begin,
750: Plugin while,
751: Plugin until,
752: Plugin again,
753: Plugin repeat,
754: Plugin cs-swap ( x1 x2 -- x2 x1 )
755:
756: Plugin case, ( -- n )
757: Plugin of, ( n -- x1 n )
758: Plugin endof, ( x1 n -- x2 n )
759: Plugin endcase, ( x1 .. xn n -- )
760:
761: Plugin do, ( -- do-token )
762: Plugin ?do, ( -- ?do-token )
763: Plugin for, ( -- for-token )
764: Plugin loop, ( do-token / ?do-token -- )
765: Plugin +loop, ( do-token / ?do-token -- )
766: Plugin next, ( for-token )
767: Plugin leave, ( -- )
768: Plugin ?leave, ( -- )
769:
770: Plugin ca>native \ Convert a code address to the processors
771: \ native address. This is used in doprim, and
772: \ code/code: primitive definitions word to
773: \ convert the addresses.
774: \ The only target where we need this is the misc
775: \ which is a 16 Bit processor with word addresses
776: \ but the forth system we build has a normal byte
777: \ addressed memory model
778:
779: Plugin doprim, \ compiles start of a primitive
780: Plugin docol, \ compiles start of a colon definition
781: Plugin doer,
782: Plugin fini, \ compiles end of definition ;s
783: Plugin doeshandler,
784: Plugin dodoes,
785:
786: Plugin colon-start
787: ' noop plugin-of colon-start
788: Plugin colon-end
789: ' noop plugin-of colon-end
790:
791: Plugin ]comp \ starts compilation
792: ' noop plugin-of ]comp
793: Plugin comp[ \ ends compilation
794: ' noop plugin-of comp[
795:
796: Plugin t>body \ we need the system >body
797: \ and the target >body
798:
799: >TARGET
800: : >body t>body ;
801:
802:
803: \ Ghost Builder 06oct92py
804:
805: >CROSS
806: hex
807: \ Values for ghost magic
808: 4711 Constant <fwd> 4712 Constant <res>
809: 4713 Constant <imm> 4714 Constant <do:>
810: 4715 Constant <skip>
811:
812: \ Bitmask for ghost flags
813: 1 Constant <unique>
814: 2 Constant <primitive>
815:
816: \ FXIME: move this to general stuff?
817: : set-flag ( addr flag -- )
818: over @ or swap ! ;
819:
820: : reset-flag ( addr flag -- )
821: invert over @ and swap ! ;
822:
823: : get-flag ( addr flag -- f )
824: swap @ and 0<> ;
825:
826:
827: Struct
828:
829: \ link to next ghost (always the first element)
830: cell% field >next-ghost
831:
832: \ type of ghost
833: cell% field >magic
834:
835: \ pointer where ghost is in target, or if unresolved
836: \ points to the where we have to resolve (linked-list)
837: cell% field >link
838:
839: \ execution semantics (while target compiling) of ghost
840: cell% field >exec
841:
842: \ compilation action of this ghost; this is what is
843: \ done to compile a call (or whatever) to this definition.
844: \ E.g. >comp contains the semantic of postpone s"
845: \ whereas >exec-compile contains the semantic of s"
846: cell% field >comp
847:
848: \ Compilation sematics (while parsing) of this ghost. E.g.
849: \ "\" will skip the rest of line.
850: \ These semantics are defined by Cond: and
851: \ if a word is made immediate in instant, then the >exec2 field
852: \ gets copied to here
853: cell% field >exec-compile
854:
855: \ Additional execution semantics of this ghost. This is used
856: \ for code generated by instant and for the doer-xt of created
857: \ words
858: cell% field >exec2
859:
860: cell% field >created
861:
862: \ the xt of the created ghost word itself
863: cell% field >ghost-xt
864:
865: \ pointer to the counted string of the assiciated
866: \ assembler label
867: cell% field >asm-name
868:
869: \ mapped primitives have a special address, so
870: \ we are able to detect them
871: cell% field >asm-dummyaddr
872:
873: \ for builder (create, variable...) words
874: \ the execution symantics of words built are placed here
875: \ this is a doer ghost or a dummy ghost
876: cell% field >do:ghost
877:
878: cell% field >ghost-flags
879:
880: cell% field >ghost-name
881:
882: End-Struct ghost-struct
883:
884: Variable ghost-list
885: 0 ghost-list !
886:
887: Variable executed-ghost \ last executed ghost, needed in tcreate and gdoes>
888: \ Variable last-ghost \ last ghost that is created
889: Variable last-header-ghost \ last ghost definitions with header
890:
891: \ space for ghosts resolve structure
892: \ we create ghosts in a sepearte space
893: \ and not to the current host dp, because this
894: \ gives trouble with instant while compiling and creating
895: \ a ghost for a forward reference
896: \ BTW: we cannot allocate another memory region
897: \ because allot will check the overflow!!
898: Variable cross-space-dp
899: Create cross-space 250000 allot here 100 allot align
900: Constant cross-space-end
901: cross-space cross-space-dp !
902: Variable cross-space-dp-orig
903:
904: : cross-space-used cross-space-dp @ cross-space - ;
905:
906: : >space ( -- )
907: dp @ cross-space-dp-orig !
908: cross-space-dp @ dp ! ;
909:
910: : space> ( -- )
911: dp @ dup cross-space-dp !
912: cross-space-end u> ABORT" CROSS: cross-space overflow"
913: cross-space-dp-orig @ dp ! ;
914:
915: \ this is just for debugging, to see this in the backtrace
916: : execute-exec execute ;
917: : execute-exec2 execute ;
918: : execute-exec-compile execute ;
919:
920: : NoExec
921: executed-ghost @ >exec2 @
922: ?dup
923: IF execute-exec2
924: ELSE true ABORT" CROSS: Don't execute ghost, or immediate target word"
925: THEN ;
926:
927: Defer is-forward
928:
929: : (ghostheader) ( -- )
930: ghost-list linked <fwd> , 0 , ['] NoExec , ['] is-forward ,
931: 0 , 0 , 0 , 0 , 0 , 0 , 0 , 0 , ;
932:
933: : ghostheader ( -- ) (ghostheader) 0 , ;
934:
935: ' Ghosts >wordlist Constant ghosts-wordlist
936:
937: \ the current wordlist for ghost definitions in the host
938: ghosts-wordlist Value current-ghosts
939:
940: : Make-Ghost ( "name" -- ghost )
941: >space
942: \ save current and create in ghost vocabulary
943: get-current >r current-ghosts set-current
944: >in @ Create >in !
945: \ some forth systems like iForth need the immediate directly
946: \ after the word is created
947: \ restore current
948: r> set-current
949: here (ghostheader)
950: bl word count string, align
951: space>
952: \ set ghost-xt field by doing a search
953: dup >ghost-name count
954: current-ghosts search-wordlist
955: 0= ABORT" CROSS: Just created, must be there!"
956: over >ghost-xt !
957: DOES>
958: dup executed-ghost !
959: >exec @ execute-exec ;
960:
961: \ ghost words 14oct92py
962: \ changed: 10may93py/jaw
963:
964: Defer search-ghosts
965:
966: : (search-ghosts) ( adr len -- cfa true | 0 )
967: current-ghosts search-wordlist ;
968:
969: ' (search-ghosts) IS search-ghosts
970:
971: : gsearch ( addr len -- ghost true | 0 )
972: search-ghosts
973: dup IF swap >body swap THEN ;
974:
975: : gfind ( string -- ghost true / string false )
976: \ searches for string in word-list ghosts
977: \ dup count type space
978: dup >r count gsearch
979: dup IF rdrop ELSE r> swap THEN ;
980:
981: : gdiscover ( xt -- ghost true | xt false )
982: >r ghost-list
983: BEGIN @ dup
984: WHILE dup >magic @ <fwd> <>
985: IF dup >link @ r@ =
986: IF rdrop true EXIT THEN
987: THEN
988: REPEAT
989: drop r> false ;
990:
991: : xt>ghost ( xt -- ghost )
992: gdiscover 0= ABORT" CROSS: ghost not found for this xt" ;
993:
994: : Ghost ( "name" -- ghost )
995: >in @ bl word gfind IF nip EXIT THEN
996: drop >in ! Make-Ghost ;
997:
998: : >ghostname ( ghost -- adr len )
999: >ghost-name count ;
1000:
1001: : forward? ( ghost -- flag )
1002: >magic @ <fwd> = ;
1003:
1004: : undefined? ( ghost -- flag )
1005: >magic @ dup <fwd> = swap <skip> = or ;
1006:
1007: : immediate? ( ghost -- flag )
1008: >magic @ <imm> = ;
1009:
1010: Variable TWarnings
1011: TWarnings on
1012: Variable Exists-Warnings
1013: Exists-Warnings on
1014:
1015: : exists-warning ( ghost -- ghost )
1016: TWarnings @ Exists-Warnings @ and
1017: IF dup >ghostname warnhead type ." exists " THEN ;
1018:
1019: \ : HeaderGhost Ghost ;
1020:
1021: Variable reuse-ghosts reuse-ghosts off
1022:
1023: : HeaderGhost ( "name" -- ghost )
1024: >in @
1025: bl word count
1026: \ 2dup type space
1027: current-ghosts search-wordlist
1028: IF >body dup undefined? reuse-ghosts @ or
1029: IF nip EXIT
1030: ELSE exists-warning
1031: THEN
1032: drop >in !
1033: ELSE >in !
1034: THEN
1035: \ we keep the execution semantics of the prviously
1036: \ defined words, this is a workaround
1037: \ for the redefined \ until vocs work
1038: Make-Ghost ;
1039:
1040: : .ghost ( ghost -- ) >ghostname type ;
1041:
1042: \ ' >ghostname ALIAS @name
1043:
1044: : findghost ( "ghostname" -- ghost )
1045: bl word gfind 0= ABORT" CROSS: Ghost don't exists" ;
1046:
1047: : [G'] ( -- ghost : name )
1048: \G ticks a ghost and returns its address
1049: findghost
1050: state @ IF postpone literal THEN ; immediate
1051:
1052: : g>xt ( ghost -- xt )
1053: \G Returns the xt (cfa) of a ghost. Issues a warning if undefined.
1054: dup undefined? ABORT" CROSS: forward " >link @ ;
1055:
1056: : g>body ( ghost -- body )
1057: \G Returns the body-address (pfa) of a ghost.
1058: \G Issues a warning if undefined (a forward-reference).
1059: g>xt X >body ;
1060:
1061: 1 Constant <label>
1062:
1063: Struct
1064: \ bitmask of address type (not used for now)
1065: cell% field addr-type
1066: \ if this address is an xt, this field points to the ghost
1067: cell% field addr-xt-ghost
1068: \ a bit mask that tells as what part of the cell
1069: \ is refenced from an address pointer, used for assembler generation
1070: cell% field addr-refs
1071: End-Struct addr-struct
1072:
1073: : %allocerase ( align size -- addr )
1074: dup >r %alloc dup r> erase ;
1075:
1076: \ returns the addr struct, define it if 0 reference
1077: : define-addr-struct ( addr -- struct-addr )
1078: dup @ ?dup IF nip EXIT THEN
1079: addr-struct %allocerase tuck swap ! ;
1080:
1081: >cross
1082:
1083: \ Predefined ghosts 12dec92py
1084:
1085: Ghost - drop \ need a ghost otherwise "-" would be treated as a number
1086:
1087: Ghost 0= drop
1088: Ghost branch Ghost ?branch 2drop
1089: Ghost unloop Ghost ;S 2drop
1090: Ghost lit Ghost ! 2drop
1091: Ghost noop drop
1092: Ghost over Ghost = Ghost drop 2drop drop
1093: Ghost 2drop drop
1094: Ghost 2dup drop
1095: Ghost call drop
1096: Ghost @ drop
1097: Ghost useraddr drop
1098: Ghost execute drop
1099: Ghost + drop
1100: Ghost decimal drop
1101: Ghost hex drop
1102: Ghost lit@ drop
1103: Ghost lit-perform drop
1104: Ghost lit+ drop
1105: Ghost does-exec drop
1106:
1107: Ghost :docol Ghost :doesjump Ghost :dodoes 2drop drop
1108: Ghost :dovar drop
1109:
1110: \ \ Parameter for target systems 06oct92py
1111:
1112:
1113: \ we define it ans like...
1114: wordlist Constant target-environment
1115:
1116: \ save information of current dictionary to restore with environ>
1117: Variable env-current
1118:
1119: : >ENVIRON get-current env-current ! target-environment set-current ;
1120: : ENVIRON> env-current @ set-current ;
1121:
1122: >TARGET
1123:
1124: : environment? ( addr len -- [ x ] true | false )
1125: \G returns the content of environment variable and true or
1126: \G false if not present
1127: target-environment search-wordlist
1128: IF EXECUTE true ELSE false THEN ;
1129:
1130: : $has? ( addr len -- x | false )
1131: \G returns the content of environment variable
1132: \G or false if not present
1133: T environment? H dup IF drop THEN ;
1134:
1135: : e? ( "name" -- x )
1136: \G returns the content of environment variable.
1137: \G The variable is expected to exist. If not, issue an error.
1138: bl word count T environment? H
1139: 0= ABORT" environment variable not defined!" ;
1140:
1141: : has? ( "name" --- x | false )
1142: \G returns the content of environment variable
1143: \G or false if not present
1144: bl word count T $has? H ;
1145:
1146:
1147: >ENVIRON get-order get-current swap 1+ set-order
1148: true SetValue compiler
1149: true SetValue cross
1150: true SetValue standard-threading
1151: >TARGET previous
1152:
1153: 0
1154: [IFDEF] mach-file drop mach-file count 1 [THEN]
1155: [IFDEF] machine-file drop machine-file 1 [THEN]
1156: [IF] included hex
1157: [ELSE] cr ." No machine description!" ABORT
1158: [THEN]
1159:
1160: >ENVIRON
1161:
1162: T has? ec H
1163: [IF]
1164: false DefaultValue relocate
1165: false DefaultValue file
1166: false DefaultValue OS
1167: false DefaultValue prims
1168: false DefaultValue floating
1169: false DefaultValue glocals
1170: false DefaultValue dcomps
1171: false DefaultValue hash
1172: false DefaultValue xconds
1173: false DefaultValue header
1174: false DefaultValue backtrace
1175: false DefaultValue new-input
1176: false DefaultValue peephole
1177: false DefaultValue abranch
1178: true DefaultValue control-rack
1179: [THEN]
1180:
1181: true DefaultValue interpreter
1182: true DefaultValue ITC
1183: false DefaultValue rom
1184: true DefaultValue standardthreading
1185:
1186: >TARGET
1187: s" relocate" T environment? H
1188: \ JAW why set NIL to this?!
1189: [IF] drop \ SetValue NIL
1190: [ELSE] >ENVIRON X NIL SetValue relocate
1191: [THEN]
1192: >TARGET
1193:
1194: 0 Constant NIL
1195:
1196: >CROSS
1197:
1198: \ \ Create additional parameters 19jan95py
1199:
1200: \ currently cross only works for host machines with address-unit-bits
1201: \ eual to 8 because of s! and sc!
1202: \ but I start to query the environment just to modularize a little bit
1203:
1204: : check-address-unit-bits ( -- )
1205: \ s" ADDRESS-UNIT-BITS" environment?
1206: \ IF 8 <> ELSE true THEN
1207: \ ABORT" ADDRESS-UNIT-BITS unknown or not equal to 8!"
1208:
1209: \ shit, this doesn't work because environment? is only defined for
1210: \ gforth.fi and not kernl???.fi
1211: ;
1212:
1213: check-address-unit-bits
1214: 8 Constant bits/byte \ we define: byte is address-unit
1215:
1216: 1 bits/byte lshift Constant maxbyte
1217: \ this sets byte size for the target machine, (probably right guess) jaw
1218:
1219: T
1220: NIL Constant TNIL
1221: cell Constant tcell
1222: cell<< Constant tcell<<
1223: cell>bit Constant tcell>bit
1224: bits/char Constant tbits/char
1225: bits/char H bits/byte T /
1226: Constant tchar
1227: float Constant tfloat
1228: 1 bits/char lshift Constant tmaxchar
1229: [IFUNDEF] bits/byte
1230: 8 Constant tbits/byte
1231: [ELSE]
1232: bits/byte Constant tbits/byte
1233: [THEN]
1234: H
1235: tbits/char bits/byte / Constant tbyte
1236:
1237:
1238: \ Variables 06oct92py
1239:
1240: Variable image
1241: Variable (tlast)
1242: (tlast) Value tlast TNIL tlast ! \ Last name field
1243: Variable tlastcfa \ Last code field
1244: Variable bit$
1245:
1246: \ statistics 10jun97jaw
1247:
1248: Variable headers-named 0 headers-named !
1249: Variable user-vars 0 user-vars !
1250:
1251: : target>bitmask-size ( u1 -- u2 )
1252: 1- tcell>bit rshift 1+ ;
1253:
1254: : allocatetarget ( size -- adr )
1255: dup allocate ABORT" CROSS: No memory for target"
1256: swap over swap erase ;
1257:
1258: \ \ memregion.fs
1259:
1260:
1261: Variable last-defined-region \ pointer to last defined region
1262: Variable region-link \ linked list with all regions
1263: Variable mirrored-link \ linked list for mirrored regions
1264: 0 dup mirrored-link ! region-link !
1265:
1266: : >rname 8 cells + ;
1267: : >rbm 4 cells + ; \ bitfield per cell witch indicates relocation
1268: : >rmem 5 cells + ;
1269: : >rtype 6 cells + ; \ field per cell witch points to a type struct
1270: : >rrom 7 cells + ; \ a -1 indicates that this region is rom
1271: : >rlink 3 cells + ;
1272: : >rdp 2 cells + ;
1273: : >rlen cell+ ;
1274: : >rstart ;
1275:
1276: : (region) ( addr len region -- )
1277: \G change startaddress and length of an existing region
1278: >r r@ last-defined-region !
1279: r@ >rlen ! dup r@ >rstart ! r> >rdp ! ;
1280:
1281: : region ( addr len -- "name" )
1282: \G create a new region
1283: \ check whether predefined region exists
1284: save-input bl word find >r >r restore-input throw r> r> 0=
1285: IF \ make region
1286: drop
1287: save-input create restore-input throw
1288: here last-defined-region !
1289: over ( startaddr ) , ( length ) , ( dp ) ,
1290: region-link linked 0 , 0 , 0 , 0 , bl word count string,
1291: ELSE \ store new parameters in region
1292: bl word drop
1293: >body (region)
1294: THEN ;
1295:
1296: : borders ( region -- startaddr endaddr )
1297: \G returns lower and upper region border
1298: dup >rstart @ swap >rlen @ over + ;
1299:
1300: : extent ( region -- startaddr len )
1301: \G returns the really used area
1302: dup >rstart @ swap >rdp @ over - ;
1303:
1304: : area ( region -- startaddr totallen )
1305: \G returns the total area
1306: dup >rstart @ swap >rlen @ ;
1307:
1308: : mirrored ( -- )
1309: \G mark last defined region as mirrored
1310: mirrored-link
1311: align linked last-defined-region @ , ;
1312:
1313: : writeprotected
1314: \G mark a region as write protected
1315: -1 last-defined-region @ >rrom ! ;
1316:
1317: : .addr ( u -- )
1318: \G prints a 16 or 32 Bit nice hex value
1319: base @ >r hex
1320: tcell 2 u>
1321: IF s>d <# # # # # [char] . hold # # # # #> type
1322: ELSE s>d <# # # # # # #> type
1323: THEN r> base ! space ;
1324:
1325: : .regions \G display region statistic
1326:
1327: \ we want to list the regions in the right order
1328: \ so first collect all regions on stack
1329: 0 region-link @
1330: BEGIN dup WHILE dup @ REPEAT drop
1331: BEGIN dup
1332: WHILE cr
1333: 0 >rlink - >r
1334: r@ >rname count tuck type
1335: 12 swap - 0 max spaces space
1336: ." Start: " r@ >rstart @ dup .addr space
1337: ." End: " r@ >rlen @ + .addr space
1338: ." DP: " r> >rdp @ .addr
1339: REPEAT drop
1340: s" rom" T $has? H 0= ?EXIT
1341: cr ." Mirrored:"
1342: mirrored-link @
1343: BEGIN dup
1344: WHILE space dup cell+ @ >rname count type @
1345: REPEAT drop cr
1346: ;
1347:
1348: \ -------- predefined regions
1349:
1350: 0 0 region address-space
1351: \ total memory addressed and used by the target system
1352:
1353: 0 0 region dictionary
1354: \ rom area for the compiler
1355:
1356: T has? rom H
1357: [IF]
1358: 0 0 region ram-dictionary mirrored
1359: \ ram area for the compiler
1360: [ELSE]
1361: ' dictionary ALIAS ram-dictionary
1362: [THEN]
1363:
1364: 0 0 region return-stack
1365:
1366: 0 0 region data-stack
1367:
1368: 0 0 region tib-region
1369:
1370: ' dictionary ALIAS rom-dictionary
1371:
1372:
1373: : setup-target ( -- ) \G initialize target's memory space
1374: s" rom" T $has? H
1375: IF \ check for ram and rom...
1376: \ address-space area nip 0<>
1377: ram-dictionary area nip 0<>
1378: rom-dictionary area nip 0<>
1379: and 0=
1380: ABORT" CROSS: define address-space, rom- , ram-dictionary, with rom-support!"
1381: THEN
1382: address-space area nip
1383: IF
1384: address-space area
1385: ELSE
1386: dictionary area
1387: THEN
1388: nip 0=
1389: ABORT" CROSS: define at least address-space or dictionary!!"
1390:
1391: \ allocate target for each region
1392: region-link
1393: BEGIN @ dup
1394: WHILE dup
1395: 0 >rlink - >r
1396: r@ >rlen @
1397: IF \ allocate mem
1398: r@ >rlen @ allocatetarget dup image !
1399: r@ >rmem !
1400:
1401: r@ >rlen @
1402: target>bitmask-size allocatetarget
1403: dup bit$ !
1404: r@ >rbm !
1405:
1406: r@ >rlen @
1407: tcell / 1+ cells allocatetarget r@ >rtype !
1408:
1409: rdrop
1410: ELSE r> drop THEN
1411: REPEAT drop ;
1412:
1413: \ MakeKernel 22feb99jaw
1414:
1415: : makekernel ( start targetsize -- )
1416: \G convenience word to setup the memory of the target
1417: \G used by main.fs of the c-engine based systems
1418: dictionary (region) setup-target ;
1419:
1420: >MINIMAL
1421: : makekernel makekernel ;
1422: >CROSS
1423:
1424: \ \ switched tdp for rom support 03jun97jaw
1425:
1426: \ second value is here to store some maximal value for statistics
1427: \ tempdp is also embedded here but has nothing to do with rom support
1428: \ (needs switched dp)
1429:
1430: variable tempdp 0 , \ temporary dp for resolving
1431: variable tempdp-save
1432:
1433: 0 [IF]
1434: variable romdp 0 , \ Dictionary-Pointer for ramarea
1435: variable ramdp 0 , \ Dictionary-Pointer for romarea
1436:
1437: \
1438: variable sramdp \ start of ram-area for forth
1439: variable sromdp \ start of rom-area for forth
1440:
1441: [THEN]
1442:
1443: 0 Value current-region
1444: 0 Value tdp
1445: Variable fixed \ flag: true: no automatic switching
1446: \ false: switching is done automatically
1447:
1448: \ Switch-Policy:
1449: \
1450: \ a header is always compiled into rom
1451: \ after a created word (create and variable) compilation goes to ram
1452: \
1453: \ Be careful: If you want to make the data behind create into rom
1454: \ you have to put >rom before create!
1455:
1456: variable constflag constflag off
1457:
1458: : activate ( region -- )
1459: \G next code goes to this region
1460: dup to current-region >rdp to tdp ;
1461:
1462: : (switchram)
1463: fixed @ ?EXIT s" rom" T $has? H 0= ?EXIT
1464: ram-dictionary activate ;
1465:
1466: : switchram
1467: constflag @
1468: IF constflag off ELSE (switchram) THEN ;
1469:
1470: : switchrom
1471: fixed @ ?EXIT rom-dictionary activate ;
1472:
1473: : >tempdp ( addr -- )
1474: tdp tempdp-save ! tempdp to tdp tdp ! ;
1475: : tempdp> ( -- )
1476: tempdp-save @ to tdp ;
1477:
1478: : >ram fixed off (switchram) fixed on ;
1479: : >rom fixed off switchrom fixed on ;
1480: : >auto fixed off switchrom ;
1481:
1482:
1483:
1484: \ : romstart dup sromdp ! romdp ! ;
1485: \ : ramstart dup sramdp ! ramdp ! ;
1486:
1487: \ default compilation goes to rom
1488: \ when romable support is off, only the rom switch is used (!!)
1489: >auto
1490:
1491: : there tdp @ ;
1492:
1493: >TARGET
1494:
1495: \ \ Target Memory Handling
1496:
1497: \ Byte ordering and cell size 06oct92py
1498:
1499: : cell+ tcell + ;
1500: : cells tcell<< lshift ;
1501: : chars tchar * ;
1502: : char+ tchar + ;
1503: : floats tfloat * ;
1504:
1505: >CROSS
1506: : cell/ tcell<< rshift ;
1507: >TARGET
1508: 20 CONSTANT bl
1509: \ TNIL Constant NIL
1510:
1511: >CROSS
1512:
1513: bigendian
1514: [IF]
1515: : DS! ( d addr -- ) tcell bounds swap 1-
1516: DO maxbyte ud/mod rot I c! -1 +LOOP 2drop ;
1517: : DS@ ( addr -- d ) >r 0 0 r> tcell bounds
1518: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap LOOP ;
1519: : Sc! ( n addr -- ) >r s>d r> tchar bounds swap 1-
1520: DO maxbyte ud/mod rot I c! -1 +LOOP 2drop ;
1521: : Sc@ ( addr -- n ) >r 0 0 r> tchar bounds
1522: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap LOOP d>s ;
1523: [ELSE]
1524: : DS! ( d addr -- ) tcell bounds
1525: DO maxbyte ud/mod rot I c! LOOP 2drop ;
1526: : DS@ ( addr -- n ) >r 0 0 r> tcell bounds swap 1-
1527: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap -1 +LOOP ;
1528: : Sc! ( n addr -- ) >r s>d r> tchar bounds
1529: DO maxbyte ud/mod rot I c! LOOP 2drop ;
1530: : Sc@ ( addr -- n ) >r 0 0 r> tchar bounds swap 1-
1531: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap -1 +LOOP d>s ;
1532: [THEN]
1533:
1534: : S! ( n addr -- ) >r s>d r> DS! ;
1535: : S@ ( addr -- n ) DS@ d>s ;
1536:
1537: : taddr>region ( taddr -- region | 0 )
1538: \G finds for a target-address the correct region
1539: \G returns 0 if taddr is not in range of a target memory region
1540: region-link
1541: BEGIN @ dup
1542: WHILE dup >r
1543: 0 >rlink - >r
1544: r@ >rlen @
1545: IF dup r@ borders within
1546: IF r> r> drop nip EXIT THEN
1547: THEN
1548: r> drop
1549: r>
1550: REPEAT
1551: 2drop 0 ;
1552:
1553: : taddr>region-abort ( taddr -- region | 0 )
1554: \G Same as taddr>region but aborts if taddr is not
1555: \G a valid address in the target address space
1556: dup taddr>region dup 0=
1557: IF drop cr ." Wrong address: " .addr
1558: -1 ABORT" Address out of range!"
1559: THEN nip ;
1560:
1561: : (>regionimage) ( taddr -- 'taddr )
1562: dup
1563: \ find region we want to address
1564: taddr>region-abort
1565: >r
1566: \ calculate offset in region
1567: r@ >rstart @ -
1568: \ add regions real address in our memory
1569: r> >rmem @ + ;
1570:
1571: : (>regionramimage) ( taddr -- 'taddr )
1572: \G same as (>regionimage) but aborts if the region is rom
1573: dup
1574: \ find region we want to address
1575: taddr>region-abort
1576: >r
1577: r@ >rrom @ ABORT" CROSS: region is write-protected!"
1578: \ calculate offset in region
1579: r@ >rstart @ -
1580: \ add regions real address in our memory
1581: r> >rmem @ + ;
1582:
1583: : (>regionbm) ( taddr -- 'taddr bitmaskbaseaddr )
1584: dup
1585: \ find region we want to address
1586: taddr>region-abort
1587: >r
1588: \ calculate offset in region
1589: r@ >rstart @ -
1590: \ add regions real address in our memory
1591: r> >rbm @ ;
1592:
1593: : (>regiontype) ( taddr -- 'taddr )
1594: dup
1595: \ find region we want to address
1596: taddr>region-abort
1597: >r
1598: \ calculate offset in region
1599: r@ >rstart @ - tcell / cells
1600: \ add regions real address in our memory
1601: r> >rtype @ + ;
1602:
1603: \ Bit string manipulation 06oct92py
1604: \ 9may93jaw
1605: CREATE Bittable 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
1606: : bits ( n -- n ) chars Bittable + c@ ;
1607:
1608: : >bit ( addr n -- c-addr mask ) 8 /mod rot + swap bits ;
1609: : +bit ( addr n -- ) >bit over c@ or swap c! ;
1610: : -bit ( addr n -- ) >bit invert over c@ and swap c! ;
1611:
1612: : @relbit ( taddr -- f ) (>regionbm) swap cell/ >bit swap c@ and ;
1613:
1614: : (relon) ( taddr -- )
1615: [ [IFDEF] fd-relocation-table ]
1616: s" +" fd-relocation-table write-file throw
1617: dup s>d <# #s #> fd-relocation-table write-line throw
1618: [ [THEN] ]
1619: (>regionbm) swap cell/ +bit ;
1620:
1621: : (reloff) ( taddr -- )
1622: [ [IFDEF] fd-relocation-table ]
1623: s" -" fd-relocation-table write-file throw
1624: dup s>d <# #s #> fd-relocation-table write-line throw
1625: [ [THEN] ]
1626: (>regionbm) swap cell/ -bit ;
1627:
1628: : (>image) ( taddr -- absaddr ) image @ + ;
1629:
1630: DEFER >image
1631: DEFER >ramimage
1632: DEFER relon
1633: DEFER reloff
1634: DEFER correcter
1635:
1636: T has? relocate H
1637: [IF]
1638: ' (relon) IS relon
1639: ' (reloff) IS reloff
1640: ' (>regionimage) IS >image
1641: ' (>regionimage) IS >ramimage
1642: [ELSE]
1643: ' drop IS relon
1644: ' drop IS reloff
1645: ' (>regionimage) IS >image
1646: ' (>regionimage) IS >ramimage
1647: [THEN]
1648:
1649: : enforce-writeprotection ( -- )
1650: ['] (>regionramimage) IS >ramimage ;
1651:
1652: : relax-writeprotection ( -- )
1653: ['] (>regionimage) IS >ramimage ;
1654:
1655: : writeprotection-relaxed? ( -- )
1656: ['] >ramimage >body @ ['] (>regionimage) = ;
1657:
1658: \ Target memory access 06oct92py
1659:
1660: : align+ ( taddr -- rest )
1661: tcell tuck 1- and - [ tcell 1- ] Literal and ;
1662: : cfalign+ ( taddr -- rest )
1663: \ see kernel.fs:cfaligned
1664: /maxalign tuck 1- and - [ /maxalign 1- ] Literal and ;
1665:
1666: >TARGET
1667: : aligned ( taddr -- ta-addr ) dup align+ + ;
1668: \ assumes cell alignment granularity (as GNU C)
1669:
1670: : cfaligned ( taddr1 -- taddr2 )
1671: \ see kernel.fs
1672: dup cfalign+ + ;
1673:
1674: : @ ( taddr -- w ) >image S@ ;
1675: : ! ( w taddr -- ) >ramimage S! ;
1676: : c@ ( taddr -- char ) >image Sc@ ;
1677: : c! ( char taddr -- ) >ramimage Sc! ;
1678: : 2@ ( taddr -- x1 x2 ) T dup cell+ @ swap @ H ;
1679: : 2! ( x1 x2 taddr -- ) T tuck ! cell+ ! H ;
1680:
1681: \ Target compilation primitives 06oct92py
1682: \ included A! 16may93jaw
1683:
1684: : here ( -- there ) there ;
1685: : allot ( n -- ) tdp +! ;
1686: : , ( w -- ) T here H tcell T allot ! H ;
1687: : c, ( char -- ) T here H tchar T allot c! H ;
1688: : align ( -- ) T here H align+ 0 ?DO bl T c, H tchar +LOOP ;
1689: : cfalign ( -- )
1690: T here H cfalign+ 0 ?DO bl T c, H tchar +LOOP ;
1691:
1692: : >address dup 0>= IF tbyte / THEN ; \ ?? jaw
1693: : A! swap >address swap dup relon T ! H ;
1694: : A, ( w -- ) >address T here H relon T , H ;
1695:
1696: \ high-level ghosts
1697:
1698: >CROSS
1699:
1700: Ghost (do) Ghost (?do) 2drop
1701: Ghost (for) drop
1702: Ghost (loop) Ghost (+loop) 2drop
1703: Ghost (next) drop
1704: Ghost (does>) Ghost (compile) 2drop
1705: Ghost (.") Ghost (S") Ghost (ABORT") 2drop drop
1706: Ghost (C") Ghost c(abort") Ghost type 2drop drop
1707: Ghost ' drop
1708:
1709: \ user ghosts
1710:
1711: Ghost state drop
1712:
1713: \ \ -------------------- Host/Target copy etc. 29aug01jaw
1714:
1715:
1716: >CROSS
1717:
1718: : TD! >image DS! ;
1719: : TD@ >image DS@ ;
1720:
1721: : th-count ( taddr -- host-addr len )
1722: \G returns host address of target string
1723: assert1( tbyte 1 = )
1724: dup X c@ swap X char+ >image swap ;
1725:
1726: : ht-move ( haddr taddr len -- )
1727: \G moves data from host-addr to destination in target-addr
1728: \G character by character
1729: swap -rot bounds ?DO I c@ over X c! X char+ LOOP drop ;
1730:
1731: 2Variable last-string
1732:
1733: : ht-string, ( addr count -- )
1734: dup there swap last-string 2!
1735: dup T c, H bounds ?DO I c@ T c, H LOOP ;
1736: : ht-mem, ( addr count )
1737: bounds ?DO I c@ T c, H LOOP ;
1738:
1739: >TARGET
1740:
1741: : count dup X c@ swap X char+ swap ;
1742:
1743: : on -1 -1 rot TD! ;
1744: : off T 0 swap ! H ;
1745:
1746: : tcmove ( source dest len -- )
1747: \G cmove in target memory
1748: tchar * bounds
1749: ?DO dup T c@ H I T c! H 1+
1750: tchar +LOOP drop ;
1751:
1752: : td, ( d -- )
1753: \G Store a host value as one cell into the target
1754: there tcell X allot TD! ;
1755:
1756: \ \ Load Assembler
1757:
1758: >TARGET
1759: H also Forth definitions
1760:
1761: \ FIXME: should we include the assembler really in the forth
1762: \ dictionary?!?!?!? This conflicts with the existing assembler
1763: \ of the host forth system!!
1764: [IFDEF] asm-include asm-include [THEN] hex
1765:
1766: previous
1767:
1768:
1769: >CROSS
1770:
1771: : (cc) T a, H ; ' (cc) plugin-of colon,
1772: : (prim) T a, H ; ' (prim) plugin-of prim,
1773:
1774: : (cr) >tempdp colon, tempdp> ; ' (cr) plugin-of colon-resolve
1775: : (ar) T ! H ; ' (ar) plugin-of addr-resolve
1776: : (dr) ( ghost res-pnt target-addr addr )
1777: >tempdp drop over
1778: dup >magic @ <do:> =
1779: IF doer,
1780: ELSE dodoes,
1781: THEN
1782: tempdp> ; ' (dr) plugin-of doer-resolve
1783:
1784: : (cm) ( -- addr )
1785: there -1 colon, ; ' (cm) plugin-of colonmark,
1786:
1787: >TARGET
1788: : compile, ( xt -- )
1789: dup xt>ghost >comp @ EXECUTE ;
1790: >CROSS
1791:
1792: \ resolve structure
1793:
1794: : >next ; \ link to next field
1795: : >tag cell+ ; \ indecates type of reference: 0: call, 1: address, 2: doer
1796: : >taddr cell+ cell+ ;
1797: : >ghost 3 cells + ;
1798: : >file 4 cells + ;
1799: : >line 5 cells + ;
1800:
1801: : (refered) ( ghost addr tag -- )
1802: \G creates a reference to ghost at address taddr
1803: >space
1804: rot >link linked
1805: ( taddr tag ) ,
1806: ( taddr ) ,
1807: last-header-ghost @ ,
1808: loadfile ,
1809: sourceline# ,
1810: space>
1811: ;
1812:
1813: : refered ( ghost tag -- )
1814: \G creates a resolve structure
1815: T here aligned H swap (refered)
1816: ;
1817:
1818: : killref ( addr ghost -- )
1819: \G kills a forward reference to ghost at position addr
1820: \G this is used to eleminate a :dovar refence after making a DOES>
1821: dup >magic @ <fwd> <> IF 2drop EXIT THEN
1822: swap >r >link
1823: BEGIN dup @ dup ( addr last this )
1824: WHILE dup >taddr @ r@ =
1825: IF @ over !
1826: ELSE nip THEN
1827: REPEAT rdrop 2drop
1828: ;
1829:
1830: Defer resolve-warning
1831:
1832: : reswarn-test ( ghost res-struct -- ghost res-struct )
1833: over cr ." Resolving " .ghost dup ." in " >ghost @ .ghost ;
1834:
1835: : reswarn-forward ( ghost res-struct -- ghost res-struct )
1836: over warnhead .ghost dup ." is referenced in "
1837: >ghost @ .ghost ;
1838:
1839: \ ' reswarn-test IS resolve-warning
1840:
1841: \ resolve 14oct92py
1842:
1843: : resolve-loop ( ghost resolve-list tcfa -- )
1844: >r
1845: BEGIN dup WHILE
1846: \ dup >tag @ 2 = IF reswarn-forward THEN
1847: resolve-warning
1848: r@ over >taddr @
1849: 2 pick >tag @
1850: CASE 0 OF colon-resolve ENDOF
1851: 1 OF addr-resolve ENDOF
1852: 2 OF doer-resolve ENDOF
1853: ENDCASE
1854: @ \ next list element
1855: REPEAT 2drop rdrop
1856: ;
1857:
1858: \ : resolve-loop ( ghost tcfa -- ghost tcfa )
1859: \ >r dup >link @
1860: \ BEGIN dup WHILE dup T @ H r@ rot T ! H REPEAT drop r> ;
1861:
1862: \ exists 9may93jaw
1863:
1864: : exists ( ghost tcfa -- )
1865: \G print warning and set new target link in ghost
1866: swap exists-warning
1867: >link ! ;
1868:
1869: : colon-resolved ( ghost -- )
1870: \ compiles a call to a colon definition,
1871: \ compile action for >comp field
1872: >link @ colon, ;
1873:
1874: : prim-resolved ( ghost -- )
1875: \ compiles a call to a primitive
1876: >link @ prim, ;
1877:
1878: : (is-forward) ( ghost -- )
1879: colonmark, 0 (refered) ; \ compile space for call
1880: ' (is-forward) IS is-forward
1881:
1882: 0 Value resolved
1883:
1884: : resolve-forward-references ( ghost resolve-list -- )
1885: \ loop through forward referencies
1886: comp-state @ >r Resolving comp-state !
1887: over >link @ resolve-loop
1888: r> comp-state !
1889:
1890: ['] noop IS resolve-warning ;
1891:
1892:
1893: : (resolve) ( ghost tcfa -- ghost resolve-list )
1894: \ check for a valid address, it is a primitive reference
1895: \ otherwise
1896: dup taddr>region 0<> IF
1897: \ define this address in the region address type table
1898: 2dup (>regiontype) define-addr-struct addr-xt-ghost
1899: \ we define new address only if empty
1900: \ this is for not to take over the alias ghost
1901: \ (different ghost, but identical xt)
1902: \ but the very first that really defines it
1903: dup @ 0= IF ! ELSE 2drop THEN
1904: THEN
1905: swap >r
1906: r@ to resolved
1907:
1908: \ r@ >comp @ ['] is-forward =
1909: \ ABORT" >comp action not set on a resolved ghost"
1910:
1911: \ copmile action defaults to colon-resolved
1912: \ if this is not right something must be set before
1913: \ calling resolve
1914: r@ >comp @ ['] is-forward = IF
1915: ['] colon-resolved r@ >comp !
1916: THEN
1917: r@ >link @ swap \ ( list tcfa R: ghost )
1918: \ mark ghost as resolved
1919: r@ >link ! <res> r@ >magic !
1920: r> swap ;
1921:
1922: : resolve ( ghost tcfa -- )
1923: \G resolve referencies to ghost with tcfa
1924: \ is ghost resolved?, second resolve means another
1925: \ definition with the same name
1926: over undefined? 0= IF exists EXIT THEN
1927: (resolve)
1928: ( ghost resolve-list )
1929: resolve-forward-references ;
1930:
1931: : resolve-noforwards ( ghost tcfa -- )
1932: \G Same as resolve but complain if there are any
1933: \G forward references on this ghost
1934: \ is ghost resolved?, second resolve means another
1935: \ definition with the same name
1936: over undefined? 0= IF exists EXIT THEN
1937: (resolve)
1938: IF cr ." No forward references allowed on: " .ghost cr
1939: -1 ABORT" Illegal forward reference"
1940: THEN
1941: drop ;
1942:
1943: \ gexecute ghost, 01nov92py
1944:
1945: : (gexecute) ( ghost -- )
1946: dup >comp @ EXECUTE ;
1947:
1948: : gexecute ( ghost -- )
1949: dup >magic @ <imm> = ABORT" CROSS: gexecute on immediate word"
1950: (gexecute) ;
1951:
1952: : addr, ( ghost -- )
1953: dup forward? IF 1 refered 0 T a, H ELSE >link @ T a, H THEN ;
1954:
1955: \ .unresolved 11may93jaw
1956:
1957: variable ResolveFlag
1958:
1959: \ ?touched 11may93jaw
1960:
1961: : ?touched ( ghost -- flag ) dup forward? swap >link @
1962: 0 <> and ;
1963:
1964: : .forwarddefs ( ghost -- )
1965: ." appeared in:"
1966: >link
1967: BEGIN @ dup
1968: WHILE cr 5 spaces
1969: dup >ghost @ .ghost
1970: ." file " dup >file @ ?dup IF count type ELSE ." CON" THEN
1971: ." line " dup >line @ .dec
1972: REPEAT
1973: drop ;
1974:
1975: : ?resolved ( ghost -- )
1976: dup ?touched
1977: IF ResolveFlag on
1978: dup cr .ghost .forwarddefs
1979: ELSE drop
1980: THEN ;
1981:
1982: : .unresolved ( -- )
1983: ResolveFlag off cr ." Unresolved: "
1984: ghost-list
1985: BEGIN @ dup
1986: WHILE dup ?resolved
1987: REPEAT drop ResolveFlag @
1988: IF
1989: -1 abort" Unresolved words!"
1990: ELSE
1991: ." Nothing!"
1992: THEN
1993: cr ;
1994:
1995: : .stats
1996: base @ >r decimal
1997: cr ." named Headers: " headers-named @ .
1998: r> base ! ;
1999:
2000: >MINIMAL
2001:
2002: : .unresolved .unresolved ;
2003:
2004: >CROSS
2005: \ Header states 12dec92py
2006:
2007: \ : flag! ( 8b -- ) tlast @ dup >r T c@ xor r> c! H ;
2008: bigendian [IF] 0 [ELSE] tcell 1- [THEN] Constant flag+
2009: : flag! ( w -- ) tlast @ flag+ + dup >r T c@ xor r> c! H ;
2010:
2011: VARIABLE ^imm
2012:
2013: \ !! should be target wordsize specific
2014: $80 constant alias-mask
2015: $40 constant immediate-mask
2016: $20 constant restrict-mask
2017:
2018: >TARGET
2019: : immediate immediate-mask flag!
2020: ^imm @ @ dup <imm> = IF drop EXIT THEN
2021: <res> <> ABORT" CROSS: Cannot immediate a unresolved word"
2022: <imm> ^imm @ ! ;
2023: : restrict restrict-mask flag! ;
2024:
2025: : isdoer
2026: \G define a forth word as doer, this makes obviously only sence on
2027: \G forth processors such as the PSC1000
2028: <do:> last-header-ghost @ >magic ! ;
2029: >CROSS
2030:
2031: \ Target Header Creation 01nov92py
2032:
2033: : ht-lstring, ( addr count -- )
2034: dup T , H bounds ?DO I c@ T c, H LOOP ;
2035:
2036: >TARGET
2037: : name, ( "name" -- ) bl word count ht-lstring, X cfalign ;
2038: : view, ( -- ) ( dummy ) ;
2039: >CROSS
2040:
2041: \ Target Document Creation (goes to crossdoc.fd) 05jul95py
2042:
2043: s" ./doc/crossdoc.fd" r/w create-file throw value doc-file-id
2044: \ contains the file-id of the documentation file
2045:
2046: : T-\G ( -- )
2047: source >in @ /string doc-file-id write-line throw
2048: postpone \ ;
2049:
2050: Variable to-doc to-doc on
2051:
2052: : cross-doc-entry ( -- )
2053: to-doc @ tlast @ 0<> and \ not an anonymous (i.e. noname) header
2054: IF
2055: s" " doc-file-id write-line throw
2056: s" make-doc " doc-file-id write-file throw
2057:
2058: Last-Header-Ghost @ >ghostname doc-file-id write-file throw
2059: >in @
2060: [char] ( parse 2drop
2061: [char] ) parse doc-file-id write-file throw
2062: s" )" doc-file-id write-file throw
2063: [char] \ parse 2drop
2064: T-\G
2065: >in !
2066: THEN ;
2067:
2068: \ Target TAGS creation
2069:
2070: s" kernel.TAGS" r/w create-file throw value tag-file-id
2071: s" kernel.tags" r/w create-file throw value vi-tag-file-id
2072: \ contains the file-id of the tags file
2073:
2074: Create tag-beg 2 c, 7F c, bl c,
2075: Create tag-end 2 c, bl c, 01 c,
2076: Create tag-bof 1 c, 0C c,
2077: Create tag-tab 1 c, 09 c,
2078:
2079: 2variable last-loadfilename 0 0 last-loadfilename 2!
2080:
2081: : put-load-file-name ( -- )
2082: sourcefilename last-loadfilename 2@ d<>
2083: IF
2084: tag-bof count tag-file-id write-line throw
2085: sourcefilename 2dup
2086: tag-file-id write-file throw
2087: last-loadfilename 2!
2088: s" ,0" tag-file-id write-line throw
2089: THEN ;
2090:
2091: : cross-gnu-tag-entry ( -- )
2092: tlast @ 0<> \ not an anonymous (i.e. noname) header
2093: IF
2094: put-load-file-name
2095: source >in @ min tag-file-id write-file throw
2096: tag-beg count tag-file-id write-file throw
2097: Last-Header-Ghost @ >ghostname tag-file-id write-file throw
2098: tag-end count tag-file-id write-file throw
2099: base @ decimal sourceline# 0 <# #s #> tag-file-id write-file throw
2100: \ >in @ 0 <# #s [char] , hold #> tag-file-id write-line throw
2101: s" ,0" tag-file-id write-line throw
2102: base !
2103: THEN ;
2104:
2105: : cross-vi-tag-entry ( -- )
2106: tlast @ 0<> \ not an anonymous (i.e. noname) header
2107: IF
2108: sourcefilename vi-tag-file-id write-file throw
2109: tag-tab count vi-tag-file-id write-file throw
2110: Last-Header-Ghost @ >ghostname vi-tag-file-id write-file throw
2111: tag-tab count vi-tag-file-id write-file throw
2112: s" /^" vi-tag-file-id write-file throw
2113: source vi-tag-file-id write-file throw
2114: s" $/" vi-tag-file-id write-line throw
2115: THEN ;
2116:
2117: : cross-tag-entry ( -- )
2118: cross-gnu-tag-entry
2119: cross-vi-tag-entry ;
2120:
2121: \ Check for words
2122:
2123: Defer skip? ' false IS skip?
2124:
2125: : skipdef ( "name" -- )
2126: \G skip definition of an undefined word in undef-words and
2127: \G all-words mode
2128: Ghost dup forward?
2129: IF >magic <skip> swap !
2130: ELSE drop THEN ;
2131:
2132: : tdefined? ( "name" -- flag )
2133: Ghost undefined? 0= ;
2134:
2135: : defined2? ( "name" -- flag )
2136: \G return true for anything else than forward, even for <skip>
2137: \G that's what we want
2138: Ghost forward? 0= ;
2139:
2140: : forced? ( "name" -- flag )
2141: \G return ture if it is a foreced skip with defskip
2142: Ghost >magic @ <skip> = ;
2143:
2144: : needed? ( -- flag ) \ name
2145: \G returns a false flag when
2146: \G a word is not defined
2147: \G a forward reference exists
2148: \G so the definition is not skipped!
2149: bl word gfind
2150: IF dup undefined?
2151: nip
2152: 0=
2153: ELSE drop true THEN ;
2154:
2155: : doer? ( -- flag ) \ name
2156: Ghost >magic @ <do:> = ;
2157:
2158: : skip-defs ( -- )
2159: BEGIN refill WHILE source -trailing nip 0= UNTIL THEN ;
2160:
2161: \ Target header creation
2162:
2163: Variable NoHeaderFlag
2164: NoHeaderFlag off
2165:
2166: : 0.r ( n1 n2 -- )
2167: base @ >r hex
2168: 0 swap <# 0 ?DO # LOOP #> type
2169: r> base ! ;
2170:
2171: : .sym ( adr len -- )
2172: \G escapes / and \ to produce sed output
2173: bounds
2174: DO I c@ dup
2175: CASE [char] / OF drop ." \/" ENDOF
2176: [char] \ OF drop ." \\" ENDOF
2177: dup OF emit ENDOF
2178: ENDCASE
2179: LOOP ;
2180:
2181: Defer setup-execution-semantics
2182: 0 Value lastghost
2183:
2184: : (THeader ( "name" -- ghost )
2185: \ >in @ bl word count type 2 spaces >in !
2186: \ wordheaders will always be compiled to rom
2187: switchrom
2188: \ build header in target
2189: NoHeaderFlag @
2190: IF NoHeaderFlag off
2191: ELSE
2192: T align H view,
2193: tlast @ dup 0> IF tcell - THEN T A, H there tlast !
2194: 1 headers-named +! \ Statistic
2195: >in @ T name, H >in !
2196: THEN
2197: T cfalign here H tlastcfa !
2198: \ Old Symbol table sed-script
2199: \ >in @ cr ." sym:s/CFA=" there 4 0.r ." /" bl word count .sym ." /g" cr >in !
2200: HeaderGhost
2201: \ output symbol table to extra file
2202: dup >ghostname there symentry
2203: dup Last-Header-Ghost ! dup to lastghost
2204: dup >magic ^imm ! \ a pointer for immediate
2205: alias-mask flag!
2206: cross-doc-entry cross-tag-entry
2207: setup-execution-semantics
2208: ;
2209:
2210: \ this is the resolver information from ":"
2211: \ resolving is done by ";"
2212: Variable ;Resolve 1 cells allot
2213:
2214: : hereresolve ( ghost -- )
2215: there resolve 0 ;Resolve ! ;
2216:
2217: : Theader ( "name" -- ghost )
2218: (THeader dup hereresolve ;
2219:
2220: Variable aprim-nr -20 aprim-nr !
2221:
2222: : copy-execution-semantics ( ghost-from ghost-dest -- )
2223: >r
2224: dup >exec @ r@ >exec !
2225: dup >comp @ r@ >comp !
2226: dup >exec2 @ r@ >exec2 !
2227: dup >exec-compile @ r@ >exec-compile !
2228: dup >ghost-xt @ r@ >ghost-xt !
2229: dup >created @ r@ >created !
2230: rdrop drop ;
2231:
2232: >TARGET
2233:
2234: : Alias ( cfa -- ) \ name
2235: >in @ skip? IF 2drop EXIT THEN >in !
2236: (THeader ( S xt ghost )
2237: 2dup swap xt>ghost swap copy-execution-semantics
2238: over resolve T A, H alias-mask flag! ;
2239:
2240: Variable last-prim-ghost
2241: 0 last-prim-ghost !
2242:
2243: : asmprimname, ( ghost -- : name )
2244: dup last-prim-ghost !
2245: >r
2246: here bl word count string, r@ >asm-name !
2247: aprim-nr @ r> >asm-dummyaddr ! ;
2248:
2249: Defer setup-prim-semantics
2250:
2251: : mapprim ( "forthname" "asmlabel" -- )
2252: THeader -1 aprim-nr +! aprim-nr @ T A, H
2253: asmprimname,
2254: setup-prim-semantics ;
2255:
2256: : mapprim: ( "forthname" "asmlabel" -- )
2257: -1 aprim-nr +! aprim-nr @
2258: Ghost tuck swap resolve-noforwards <do:> swap tuck >magic !
2259: asmprimname, ;
2260:
2261: : Doer: ( cfa -- ) \ name
2262: >in @ skip? IF 2drop EXIT THEN >in !
2263: dup 0< s" prims" T $has? H 0= and
2264: IF
2265: .sourcepos ." needs doer: " >in @ bl word count type >in ! cr
2266: THEN
2267: Ghost
2268: tuck swap resolve-noforwards <do:> swap >magic ! ;
2269:
2270: Variable prim#
2271: : first-primitive ( n -- ) prim# ! ;
2272: : group 0 word drop prim# @ 1- -$200 and prim# ! ;
2273: : Primitive ( -- ) \ name
2274: >in @ skip? IF drop EXIT THEN >in !
2275: s" prims" T $has? H 0=
2276: IF
2277: .sourcepos ." needs prim: " >in @ bl word count type >in ! cr
2278: THEN
2279: prim# @ (THeader ( S xt ghost )
2280: ['] prim-resolved over >comp !
2281: dup >ghost-flags <primitive> set-flag
2282: over resolve-noforwards T A, H alias-mask flag!
2283: -1 prim# +! ;
2284: >CROSS
2285:
2286: \ Conditionals and Comments 11may93jaw
2287:
2288: \G saves the existing cond action, this is used for redefining in
2289: \G instant
2290: Variable cond-xt-old
2291:
2292: : cond-target ( -- )
2293: \G Compiles semantic of redefined cond into new one
2294: cond-xt-old @ compile, ; immediate restrict
2295:
2296: : ;Cond
2297: postpone ;
2298: swap ! ; immediate
2299:
2300: : Cond: ( "name" -- )
2301: \g defines a conditional or another word that must
2302: \g be executed directly while compiling
2303: \g these words have no interpretative semantics by default
2304: Ghost
2305: >exec-compile
2306: dup @ cond-xt-old !
2307: :NONAME ;
2308:
2309:
2310: : Comment ( -- )
2311: >in @ Ghost swap >in ! ' swap
2312: 2dup >exec-compile ! >exec ! ;
2313:
2314: Comment ( Comment \
2315:
2316: \ compile 10may93jaw
2317:
2318: : compile ( "name" -- ) \ name
2319: findghost
2320: dup >exec-compile @ ?dup
2321: IF nip compile,
2322: ELSE postpone literal postpone gexecute THEN ; immediate restrict
2323:
2324: >TARGET
2325:
2326: : ' ( -- xt )
2327: \G returns the target-cfa of a ghost
2328: bl word gfind 0= ABORT" CROSS: Ghost don't exists"
2329: g>xt ;
2330:
2331: \ FIXME: this works for the current use cases, but is not
2332: \ in all cases correct ;-)
2333: : comp' X ' 0 ;
2334:
2335: Cond: ['] T ' H alit, ;Cond
2336:
2337: >CROSS
2338:
2339: : [T']
2340: \ returns the target-cfa of a ghost, or compiles it as literal
2341: postpone [G']
2342: state @ IF postpone g>xt ELSE g>xt THEN ; immediate
2343:
2344: \ \ threading modell 13dec92py
2345: \ modularized 14jun97jaw
2346:
2347: T 2 cells H Value xt>body
2348:
2349: : (>body) ( cfa -- pfa )
2350: xt>body + ; ' (>body) plugin-of t>body
2351:
2352: : fillcfa ( usedcells -- )
2353: T cells H xt>body swap -
2354: assert1( dup 0 >= )
2355: 0 ?DO 0 X c, tchar +LOOP ;
2356:
2357: : (doer,) ( ghost -- )
2358: addr, 1 fillcfa ; ' (doer,) plugin-of doer,
2359:
2360: : (docol,) ( -- ) [G'] :docol (doer,) ; ' (docol,) plugin-of docol,
2361:
2362: ' NOOP plugin-of ca>native
2363:
2364: : (doprim,) ( -- )
2365: there xt>body + ca>native T a, H 1 fillcfa ; ' (doprim,) plugin-of doprim,
2366:
2367: : (doeshandler,) ( -- )
2368: T cfalign H [G'] :doesjump addr, T 0 , H ; ' (doeshandler,) plugin-of doeshandler,
2369:
2370: : (dodoes,) ( does-action-ghost -- )
2371: ]comp [G'] :dodoes addr, comp[
2372: addr,
2373: \ the relocator in the c engine, does not like the
2374: \ does-address to marked for relocation
2375: [ T e? ec H 0= [IF] ] T here H tcell - reloff [ [THEN] ]
2376: 2 fillcfa ; ' (dodoes,) plugin-of dodoes,
2377:
2378: : (dlit,) ( n -- ) compile lit td, ; ' (dlit,) plugin-of dlit,
2379:
2380: : (lit,) ( n -- ) s>d dlit, ; ' (lit,) plugin-of lit,
2381:
2382: \ if we dont produce relocatable code alit, defaults to lit, jaw
2383: \ this is just for convenience, so we don't have to define alit,
2384: \ seperately for embedded systems....
2385: T has? relocate H
2386: [IF]
2387: : (alit,) ( n -- ) compile lit T a, H ; ' (alit,) plugin-of alit,
2388: [ELSE]
2389: : (alit,) ( n -- ) lit, ; ' (alit,) plugin-of alit,
2390: [THEN]
2391:
2392: : (fini,) compile ;s ; ' (fini,) plugin-of fini,
2393:
2394: [IFUNDEF] (code)
2395: Defer (code)
2396: Defer (end-code)
2397: [THEN]
2398:
2399: >TARGET
2400: : Code
2401: defempty?
2402: (THeader ( ghost )
2403: ['] prim-resolved over >comp !
2404: there resolve-noforwards
2405:
2406: [ T e? prims H 0= [IF] T e? ITC H [ELSE] true [THEN] ] [IF]
2407: doprim,
2408: [THEN]
2409: depth (code) ;
2410:
2411: \ FIXME : no-compile -1 ABORT" this ghost is not for compilation" ;
2412:
2413: : Code:
2414: defempty?
2415: Ghost >r
2416: r@ >ghostname there symentry
2417: r@ there ca>native resolve-noforwards
2418: <do:> r@ >magic !
2419: r> drop
2420: depth (code) ;
2421:
2422: : end-code
2423: (end-code)
2424: depth ?dup IF 1- <> ABORT" CROSS: Stack changed"
2425: ELSE true ABORT" CROSS: Stack empty" THEN
2426: ;
2427:
2428: >CROSS
2429:
2430: \ tLiteral 12dec92py
2431:
2432: >TARGET
2433: Cond: \G T-\G ;Cond
2434:
2435: Cond: Literal ( n -- ) lit, ;Cond
2436: Cond: ALiteral ( n -- ) alit, ;Cond
2437:
2438: : Char ( "<char>" -- ) bl word char+ c@ ;
2439: Cond: [Char] ( "<char>" -- ) Char lit, ;Cond
2440:
2441: tchar 1 = [IF]
2442: Cond: chars ;Cond
2443: [THEN]
2444:
2445: \ some special literals 27jan97jaw
2446:
2447: Cond: MAXU
2448: -1 s>d dlit,
2449: ;Cond
2450:
2451: tcell 2 = tcell 4 = or tcell 8 = or 0=
2452: [IF]
2453: .( Warning: MINI and MAXI may not work with this host) cr
2454: [THEN]
2455:
2456: Cond: MINI
2457: tcell 2 = IF $8000 ELSE $80000000 THEN 0
2458: tcell 8 = IF swap THEN dlit,
2459: ;Cond
2460:
2461: Cond: MAXI
2462: tcell 2 = IF $7fff ELSE $7fffffff THEN 0
2463: tcell 8 = IF drop -1 swap THEN dlit,
2464: ;Cond
2465:
2466: >CROSS
2467:
2468: \ Target compiling loop 12dec92py
2469: \ ">tib trick thrown out 10may93jaw
2470: \ number? defined at the top 11may93jaw
2471: \ replaced >in by save-input
2472:
2473: : discard 0 ?DO drop LOOP ;
2474:
2475: \ compiled word might leave items on stack!
2476: : tcom ( x1 .. xn n name -- )
2477: \ dup count type space
2478: gfind
2479: IF >r ( discard saved input state ) discard r>
2480: dup >exec-compile @ ?dup
2481: IF nip execute-exec-compile ELSE gexecute THEN
2482: EXIT
2483: THEN
2484: number? dup
2485: IF 0> IF swap lit, THEN lit, discard
2486: ELSE 2drop restore-input throw Ghost gexecute THEN ;
2487:
2488: \ : ; DOES> 13dec92py
2489: \ ] 9may93py/jaw
2490:
2491: >CROSS
2492:
2493: : compiling-state ( -- )
2494: \G set states to compililng
2495: Compiling comp-state !
2496: \ if we have a state in target, change it with the compile state
2497: [G'] state dup undefined? 0=
2498: IF >ghost-xt @ execute X on ELSE drop THEN ;
2499:
2500: : interpreting-state ( -- )
2501: \G set states to interpreting
2502: \ if target has a state variable, change it according to our state
2503: [G'] state dup undefined? 0=
2504: IF >ghost-xt @ execute X off ELSE drop THEN
2505: Interpreting comp-state ! ;
2506:
2507: >TARGET
2508:
2509: : ]
2510: compiling-state
2511: BEGIN
2512: BEGIN save-input bl word
2513: dup c@ 0= WHILE drop discard refill 0=
2514: ABORT" CROSS: End of file while target compiling"
2515: REPEAT
2516: tcom
2517: compiling? 0=
2518: UNTIL ;
2519:
2520: \ by the way: defining a second interpreter (a compiler-)loop
2521: \ is not allowed if a system should be ans conform
2522:
2523: : (:) ( ghost -- )
2524: \ common factor of : and :noname. Prepare ;Resolve and start definition
2525: ;Resolve ! there ;Resolve cell+ !
2526: docol, ]comp colon-start depth T ] H ;
2527:
2528: : : ( -- colon-sys ) \ Name
2529: defempty?
2530: constflag off \ don't let this flag work over colon defs
2531: \ just to go sure nothing unwanted happens
2532: >in @ skip? IF drop skip-defs EXIT THEN >in !
2533: (THeader (:) ;
2534:
2535: : :noname ( -- colon-sys )
2536: X cfalign there
2537: \ define a nameless ghost
2538: here ghostheader dup last-header-ghost ! dup to lastghost
2539: (:) ;
2540:
2541: Cond: EXIT ( -- ) compile ;S ;Cond
2542:
2543: Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond
2544:
2545: >CROSS
2546: : LastXT ;Resolve @ 0= abort" CROSS: no definition for LastXT"
2547: ;Resolve cell+ @ ;
2548:
2549: >TARGET
2550:
2551: Cond: recurse ( -- ) Last-Header-Ghost @ gexecute ;Cond
2552:
2553: Cond: ; ( -- )
2554: depth ?dup
2555: IF 1- <> ABORT" CROSS: Stack changed"
2556: ELSE true ABORT" CROSS: Stack empty"
2557: THEN
2558: colon-end
2559: fini,
2560: comp[
2561: ;Resolve @
2562: IF ['] colon-resolved ;Resolve @ >comp !
2563: ;Resolve @ ;Resolve cell+ @ resolve
2564: THEN
2565: interpreting-state
2566: ;Cond
2567:
2568: Cond: [ ( -- ) interpreting-state ;Cond
2569:
2570: >CROSS
2571:
2572: 0 Value created
2573:
2574: : !does ( does-action -- )
2575: tlastcfa @ [G'] :dovar killref
2576: >space here >r ghostheader space>
2577: ['] colon-resolved r@ >comp !
2578: r@ created >do:ghost ! r@ swap resolve
2579: r> tlastcfa @ >tempdp dodoes, tempdp> ;
2580:
2581: Defer instant-interpret-does>-hook
2582:
2583: T has? peephole H [IF]
2584: : does-resolved ( ghost -- )
2585: compile does-exec g>xt T a, H ;
2586: [ELSE]
2587: : does-resolved ( ghost -- )
2588: g>xt T a, H ;
2589: [THEN]
2590:
2591: : resolve-does>-part ( -- )
2592: \ resolve words made by builders
2593: Last-Header-Ghost @ >do:ghost @ ?dup
2594: IF there resolve THEN ;
2595:
2596: >TARGET
2597: Cond: DOES>
2598: compile (does>) doeshandler,
2599: resolve-does>-part
2600: ;Cond
2601:
2602: : DOES>
2603: ['] does-resolved created >comp !
2604: switchrom doeshandler, T here H !does
2605: instant-interpret-does>-hook
2606: depth T ] H ;
2607:
2608: >CROSS
2609: \ Creation 01nov92py
2610:
2611: \ Builder 11may93jaw
2612:
2613: 0 Value built
2614:
2615: : Builder ( Create-xt do-ghost "name" -- )
2616: \ builds up a builder in current vocabulary
2617: \ create-xt is executed when word is interpreted
2618: \ do:-xt is executed when the created word from builder is executed
2619: \ for do:-xt an additional entry after the normal ghost-entrys is used
2620:
2621: ghost to built
2622: built >created @ 0= IF
2623: built >created on
2624: THEN ;
2625:
2626: : gdoes, ( ghost -- )
2627: \ makes the codefield for a word that is built
2628: >do:ghost @ dup undefined? 0=
2629: IF
2630: dup >magic @ <do:> =
2631: IF doer,
2632: ELSE dodoes,
2633: THEN
2634: EXIT
2635: THEN
2636: \ compile :dodoes gexecute
2637: \ T here H tcell - reloff
2638: 2 refered
2639: 0 fillcfa
2640: ;
2641:
2642: : takeover-x-semantics ( S constructor-ghost new-ghost -- )
2643: \g stores execution semantic and compilation semantic in the built word
2644: swap >do:ghost @ 2dup swap >do:ghost !
2645: \ we use the >exec2 field for the semantic of a created word,
2646: \ using exec or exec2 makes no difference for normal cross-compilation
2647: \ but is usefull for instant where the exec field is already
2648: \ defined (e.g. Vocabularies)
2649: 2dup >exec @ swap >exec2 !
2650: >comp @ swap >comp ! ;
2651:
2652: 0 Value createhere
2653:
2654: : create-resolve ( -- )
2655: created createhere resolve 0 ;Resolve ! ;
2656: : create-resolve-immediate ( -- )
2657: create-resolve T immediate H ;
2658:
2659: : TCreate ( <name> -- )
2660: create-forward-warn
2661: IF ['] reswarn-forward IS resolve-warning THEN
2662: executed-ghost @ (Theader
2663: dup >created on dup to created
2664: 2dup takeover-x-semantics
2665: there to createhere drop gdoes, ;
2666:
2667: : RTCreate ( <name> -- )
2668: \ creates a new word with code-field in ram
2669: create-forward-warn
2670: IF ['] reswarn-forward IS resolve-warning THEN
2671: \ make Alias
2672: executed-ghost @ (THeader
2673: dup >created on dup to created
2674: 2dup takeover-x-semantics
2675: there 0 T a, H alias-mask flag!
2676: \ store poiter to code-field
2677: switchram T cfalign H
2678: there swap T ! H
2679: there tlastcfa !
2680: there to createhere drop gdoes, ;
2681:
2682: : Build: ( -- [xt] [colon-sys] )
2683: :noname postpone TCreate ;
2684:
2685: : BuildSmart: ( -- [xt] [colon-sys] )
2686: :noname
2687: [ T has? rom H [IF] ]
2688: postpone RTCreate
2689: [ [ELSE] ]
2690: postpone TCreate
2691: [ [THEN] ] ;
2692:
2693: : ;Build
2694: postpone create-resolve postpone ; built >exec ! ; immediate
2695:
2696: : ;Build-immediate
2697: postpone create-resolve-immediate
2698: postpone ; built >exec ! ; immediate
2699:
2700: : gdoes> ( ghost -- addr flag )
2701: executed-ghost @ g>body ;
2702:
2703: \ DO: ;DO 11may93jaw
2704:
2705: : do:ghost! ( ghost -- ) built >do:ghost ! ;
2706: : doexec! ( xt -- ) built >do:ghost @ >exec ! ;
2707:
2708: : DO: ( -- [xt] [colon-sys] )
2709: here ghostheader do:ghost!
2710: :noname postpone gdoes> ;
2711:
2712: : by: ( -- [xt] [colon-sys] ) \ name
2713: Ghost do:ghost!
2714: :noname postpone gdoes> ;
2715:
2716: : ;DO ( [xt] [colon-sys] -- )
2717: postpone ; doexec! ; immediate
2718:
2719: : by ( -- ) \ Name
2720: Ghost >do:ghost @ do:ghost! ;
2721:
2722: : compile: ( --[xt] [colon-sys] )
2723: \G defines a compile time action for created words
2724: \G by this builder
2725: :noname ;
2726:
2727: : ;compile ( [xt] [colon-sys] -- )
2728: postpone ; built >do:ghost @ >comp ! ; immediate
2729:
2730: \ Variables and Constants 05dec92py
2731:
2732: Builder (Constant)
2733: Build: ( n -- ) ;Build
2734: by: :docon ( target-body-addr -- n ) T @ H ;DO
2735:
2736: Builder Constant
2737: Build: ( n -- ) T , H ;Build
2738: by (Constant)
2739:
2740: Builder AConstant
2741: Build: ( n -- ) T A, H ;Build
2742: by (Constant)
2743:
2744: Builder 2Constant
2745: Build: ( d -- ) T , , H ;Build
2746: DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO
2747:
2748: Builder Create
2749: BuildSmart: ;Build
2750: by: :dovar ( target-body-addr -- addr ) ;DO
2751:
2752: Builder Variable
2753: T has? rom H [IF]
2754: Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 , H ( switchrom ) ;Build
2755: by (Constant)
2756: [ELSE]
2757: Build: T 0 , H ;Build
2758: by Create
2759: [THEN]
2760:
2761: Builder 2Variable
2762: T has? rom H [IF]
2763: Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 , 0 , H ( switchrom ) ;Build
2764: by (Constant)
2765: [ELSE]
2766: Build: T 0 , 0 , H ;Build
2767: by Create
2768: [THEN]
2769:
2770: Builder AVariable
2771: T has? rom H [IF]
2772: Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 A, H ( switchrom ) ;Build
2773: by (Constant)
2774: [ELSE]
2775: Build: T 0 A, H ;Build
2776: by Create
2777: [THEN]
2778:
2779: \ User variables 04may94py
2780:
2781: Variable tup 0 tup !
2782: Variable tudp 0 tudp !
2783:
2784: : u, ( n -- udp )
2785: tup @ tudp @ + T ! H
2786: tudp @ dup T cell+ H tudp ! ;
2787:
2788: : au, ( n -- udp )
2789: tup @ tudp @ + T A! H
2790: tudp @ dup T cell+ H tudp ! ;
2791:
2792: Builder User
2793: Build: 0 u, X , ;Build
2794: by: :douser ( ghost -- up-addr ) X @ tup @ + ;DO
2795:
2796: Builder 2User
2797: Build: 0 u, X , 0 u, drop ;Build
2798: by User
2799:
2800: Builder AUser
2801: Build: 0 au, X , ;Build
2802: by User
2803:
2804: Builder (Value)
2805: Build: ( n -- ) ;Build
2806: by: :docon ( target-body-addr -- n ) T @ H ;DO
2807:
2808: Builder Value
2809: BuildSmart: T , H ;Build
2810: by (Value)
2811:
2812: Builder AValue
2813: BuildSmart: T A, H ;Build
2814: by (Value)
2815:
2816: Defer texecute
2817:
2818: Builder Defer
2819: BuildSmart: ( -- ) [T'] noop T A, H ;Build
2820: by: :dodefer ( ghost -- ) X @ texecute ;DO
2821:
2822: Builder interpret/compile:
2823: Build: ( inter comp -- ) swap T A, A, H ;Build-immediate
2824: DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
2825:
2826: \ Sturctures 23feb95py
2827:
2828: : nalign ( addr1 n -- addr2 )
2829: \ addr2 is the aligned version of addr1 wrt the alignment size n
2830: 1- tuck + swap invert and ;
2831:
2832:
2833: Builder (Field)
2834: Build: ;Build
2835: by: :dofield T @ H + ;DO
2836:
2837: Builder Field
2838: Build: ( align1 offset1 align size "name" -- align2 offset2 )
2839: rot dup T , H ( align1 align size offset1 )
2840: + >r nalign r> ;Build
2841: by (Field)
2842:
2843: >TARGET
2844: : struct T 1 chars 0 H ;
2845: : end-struct T 2Constant H ;
2846:
2847: : cell% ( n -- size align )
2848: T 1 cells H dup ;
2849: >CROSS
2850:
2851: \ Input-Methods 01py
2852:
2853: Builder input-method
2854: Build: ( m v -- m' v ) dup T , cell+ H ;Build
2855: DO: abort" Not in cross mode" ;DO
2856:
2857: Builder input-var
2858: Build: ( m v size -- m v' ) over T , H + ;Build
2859: DO: abort" Not in cross mode" ;DO
2860:
2861: \ Peephole optimization 05sep01jaw
2862:
2863: \ this section defines different compilation
2864: \ actions for created words
2865: \ this will help the peephole optimizer
2866: \ I (jaw) took this from bernds latest cross-compiler
2867: \ changes but seperated it from the original
2868: \ Builder words. The final plan is to put this
2869: \ into a seperate file, together with the peephole
2870: \ optimizer for cross
2871:
2872:
2873: T has? peephole H [IF]
2874:
2875: >CROSS
2876:
2877: : (callc) compile call T >body a, H ; ' (callc) plugin-of colon,
2878: : (callcm) T here 0 a, 0 a, H ; ' (callcm) plugin-of colonmark,
2879: : (call-res) >tempdp resolved gexecute tempdp> drop ;
2880: ' (call-res) plugin-of colon-resolve
2881: : (pprim) dup 0< IF $4000 - ELSE
2882: cr ." wrong usage of (prim) "
2883: dup gdiscover IF .ghost ELSE . THEN cr -1 throw THEN
2884: T a, H ; ' (pprim) plugin-of prim,
2885:
2886: \ if we want this, we have to spilt aconstant
2887: \ and constant!!
2888: \ Builder (Constant)
2889: \ compile: g>body X @ lit, ;compile
2890:
2891: Builder (Constant)
2892: compile: g>body compile lit@ T a, H ;compile
2893:
2894: Builder (Value)
2895: compile: g>body compile lit@ T a, H ;compile
2896:
2897: \ this changes also Variable, AVariable and 2Variable
2898: Builder Create
2899: compile: g>body alit, ;compile
2900:
2901: Builder User
2902: compile: g>body compile useraddr T @ , H ;compile
2903:
2904: Builder Defer
2905: compile: g>body compile lit-perform T A, H ;compile
2906:
2907: Builder (Field)
2908: compile: g>body T @ H compile lit+ T , H ;compile
2909:
2910: Builder interpret/compile:
2911: compile: does-resolved ;compile
2912:
2913: Builder input-method
2914: compile: does-resolved ;compile
2915:
2916: Builder input-var
2917: compile: does-resolved ;compile
2918:
2919: [THEN]
2920:
2921: \ structural conditionals 17dec92py
2922:
2923: >CROSS
2924: : (ncontrols?) ( n -- )
2925: \g We expect n open control structures
2926: depth over u<=
2927: ABORT" CROSS: unstructured, stack underflow"
2928: 0 ?DO I pick 0=
2929: ABORT" CROSS: unstructured"
2930: LOOP ; ' (ncontrols?) plugin-of ncontrols?
2931:
2932: \ : ?struc ( flag -- ) ABORT" CROSS: unstructured " ;
2933: \ : sys? ( sys -- sys ) dup 0= ?struc ;
2934:
2935: : >mark ( -- sys ) T here ( dup ." M" hex. ) 0 , H ;
2936:
2937: X has? abranch [IF]
2938: : branchoffset ( src dest -- ) drop ;
2939: : offset, ( n -- ) X A, ;
2940: [ELSE]
2941: : branchoffset ( src dest -- ) - tchar / ; \ ?? jaw
2942: : offset, ( n -- ) X , ;
2943: [THEN]
2944:
2945: :noname compile branch X here branchoffset offset, ;
2946: IS branch, ( target-addr -- )
2947: :noname compile ?branch X here branchoffset offset, ;
2948: IS ?branch, ( target-addr -- )
2949: :noname compile branch T here 0 H offset, ;
2950: IS branchmark, ( -- branchtoken )
2951: :noname compile ?branch T here 0 H offset, ;
2952: IS ?branchmark, ( -- branchtoken )
2953: :noname T here 0 H offset, ;
2954: IS ?domark, ( -- branchtoken )
2955: :noname dup X @ ?struc X here over branchoffset swap X ! ;
2956: IS branchtoresolve, ( branchtoken -- )
2957: :noname branchto, X here ;
2958: IS branchtomark, ( -- target-addr )
2959:
2960: >TARGET
2961:
2962: \ Structural Conditionals 12dec92py
2963:
2964: \ CLEANUP Cond: BUT sys? swap ;Cond
2965: \ CLEANUP Cond: YET sys? dup ;Cond
2966:
2967: >CROSS
2968:
2969: Variable tleavings 0 tleavings !
2970:
2971: : (done) ( do-addr -- )
2972: \G resolve branches of leave and ?leave and ?do
2973: \G do-addr is the address of the beginning of our
2974: \G loop so we can take care of nested loops
2975: tleavings @
2976: BEGIN dup
2977: WHILE
2978: >r dup r@ cell+ @ \ address of branch
2979: u> 0= \ lower than DO?
2980: WHILE
2981: r@ 2 cells + @ \ branch token
2982: branchtoresolve,
2983: r@ @ r> free throw
2984: REPEAT r> THEN
2985: tleavings ! drop ;
2986:
2987: >TARGET
2988:
2989: \ What for? ANS? JAW Cond: DONE ( addr -- ) (done) ;Cond
2990:
2991: >CROSS
2992: : (leave) ( branchtoken -- )
2993: 3 cells allocate throw >r
2994: T here H r@ cell+ !
2995: r@ 2 cells + !
2996: tleavings @ r@ !
2997: r> tleavings ! ;
2998: >TARGET
2999:
3000: : (leave,) ( -- )
3001: branchmark, (leave) ; ' (leave,) plugin-of leave,
3002:
3003: : (?leave,) ( -- )
3004: compile 0= ?branchmark, (leave) ; ' (?leave,) plugin-of ?leave,
3005:
3006: Cond: LEAVE leave, ;Cond
3007: Cond: ?LEAVE ?leave, ;Cond
3008:
3009: >CROSS
3010: \ !!JW ToDo : Move to general tools section
3011:
3012: : to1 ( x1 x2 xn n -- addr )
3013: \G packs n stack elements in am allocated memory region
3014: dup dup 1+ cells allocate throw dup >r swap 1+
3015: 0 DO tuck ! cell+ LOOP
3016: drop r> ;
3017:
3018: : 1to ( addr -- x1 x2 xn )
3019: \G unpacks the elements saved by to1
3020: dup @ swap over cells + swap
3021: 0 DO dup @ swap 1 cells - LOOP
3022: free throw ;
3023:
3024: : loop] ( target-addr -- )
3025: branchto,
3026: dup X here branchoffset offset,
3027: tcell - (done) ;
3028:
3029: : skiploop] ?dup IF branchto, branchtoresolve, THEN ;
3030:
3031: >TARGET
3032:
3033: \ Structural Conditionals 12dec92py
3034:
3035: : (cs-swap) ( x1 x2 -- x2 x1 )
3036: swap ; ' (cs-swap) plugin-of cs-swap
3037:
3038: : (ahead,) branchmark, ; ' (ahead,) plugin-of ahead,
3039:
3040: : (if,) ?branchmark, ; ' (if,) plugin-of if,
3041:
3042: : (then,) branchto, branchtoresolve, ; ' (then,) plugin-of then,
3043:
3044: : (else,) ( ahead ) branchmark,
3045: swap
3046: ( then ) branchto, branchtoresolve, ; ' (else,) plugin-of else,
3047:
3048: : (begin,) branchtomark, ; ' (begin,) plugin-of begin,
3049:
3050: : (while,) ( if ) ?branchmark,
3051: swap ; ' (while,) plugin-of while,
3052:
3053: : (again,) branch, ; ' (again,) plugin-of again,
3054:
3055: : (until,) ?branch, ; ' (until,) plugin-of until,
3056:
3057: : (repeat,) ( again ) branch,
3058: ( then ) branchto, branchtoresolve, ; ' (repeat,) plugin-of repeat,
3059:
3060: : (case,) ( -- n )
3061: 0 ; ' (case,) plugin-of case,
3062:
3063: : (of,) ( n -- x1 n )
3064: 1+ >r
3065: compile over compile =
3066: if, compile drop r> ; ' (of,) plugin-of of,
3067:
3068: : (endof,) ( x1 n -- x2 n )
3069: >r 1 ncontrols? else, r> ; ' (endof,) plugin-of endof,
3070:
3071: : (endcase,) ( x1 .. xn n -- )
3072: compile drop 0 ?DO 1 ncontrols? then, LOOP ; ' (endcase,) plugin-of endcase,
3073:
3074: >TARGET
3075: Cond: AHEAD ahead, ;Cond
3076: Cond: IF if, ;Cond
3077: Cond: THEN 1 ncontrols? then, ;Cond
3078: Cond: ENDIF 1 ncontrols? then, ;Cond
3079: Cond: ELSE 1 ncontrols? else, ;Cond
3080:
3081: Cond: BEGIN begin, ;Cond
3082: Cond: WHILE 1 ncontrols? while, ;Cond
3083: Cond: AGAIN 1 ncontrols? again, ;Cond
3084: Cond: UNTIL 1 ncontrols? until, ;Cond
3085: Cond: REPEAT 2 ncontrols? repeat, ;Cond
3086:
3087: Cond: CASE case, ;Cond
3088: Cond: OF of, ;Cond
3089: Cond: ENDOF endof, ;Cond
3090: Cond: ENDCASE endcase, ;Cond
3091:
3092: \ Structural Conditionals 12dec92py
3093:
3094: : (do,) ( -- target-addr )
3095: \ ?? i think 0 is too much! jaw
3096: 0 compile (do)
3097: branchtomark, 2 to1 ; ' (do,) plugin-of do,
3098:
3099: \ alternative for if no ?do
3100: \ : (do,)
3101: \ compile 2dup compile = compile IF
3102: \ compile 2drop compile ELSE
3103: \ compile (do) branchtomark, 2 to1 ;
3104:
3105: : (?do,) ( -- target-addr )
3106: 0 compile (?do) ?domark, (leave)
3107: branchtomark, 2 to1 ; ' (?do,) plugin-of ?do,
3108:
3109: : (for,) ( -- target-addr )
3110: compile (for) branchtomark, ; ' (for,) plugin-of for,
3111:
3112: : (loop,) ( target-addr -- )
3113: 1to compile (loop) loop]
3114: compile unloop skiploop] ; ' (loop,) plugin-of loop,
3115:
3116: : (+loop,) ( target-addr -- )
3117: 1to compile (+loop) loop]
3118: compile unloop skiploop] ; ' (+loop,) plugin-of +loop,
3119:
3120: : (next,)
3121: compile (next) loop] compile unloop ; ' (next,) plugin-of next,
3122:
3123: Cond: DO do, ;Cond
3124: Cond: ?DO ?do, ;Cond
3125: Cond: FOR for, ;Cond
3126:
3127: Cond: LOOP 1 ncontrols? loop, ;Cond
3128: Cond: +LOOP 1 ncontrols? +loop, ;Cond
3129: Cond: NEXT 1 ncontrols? next, ;Cond
3130:
3131: \ String words 23feb93py
3132:
3133: : ," [char] " parse ht-string, X align ;
3134:
3135: X has? control-rack [IF]
3136: Cond: ." compile (.") T ," H ;Cond
3137: Cond: S" compile (S") T ," H ;Cond
3138: Cond: C" compile (C") T ," H ;Cond
3139: Cond: ABORT" compile (ABORT") T ," H ;Cond
3140: [ELSE]
3141: Cond: ." '" parse tuck 2>r ahead, there 2r> ht-mem, X align
3142: >r then, r> compile ALiteral compile Literal compile type ;Cond
3143: Cond: S" '" parse tuck 2>r ahead, there 2r> ht-mem, X align
3144: >r then, r> compile ALiteral compile Literal ;Cond
3145: Cond: C" ahead, there [char] " parse ht-string, X align
3146: >r then, r> compile ALiteral ;Cond
3147: Cond: ABORT" if, ahead, there [char] " parse ht-string, X align
3148: >r then, r> compile ALiteral compile c(abort") then, ;Cond
3149: [THEN]
3150:
3151: Cond: IS T ' >body H compile ALiteral compile ! ;Cond
3152: : IS T >address ' >body ! H ;
3153: Cond: TO T ' >body H compile ALiteral compile ! ;Cond
3154: : TO T ' >body ! H ;
3155:
3156: Cond: defers T ' >body @ compile, H ;Cond
3157:
3158: \ LINKED ERR" ENV" 2ENV" 18may93jaw
3159:
3160: \ linked list primitive
3161: : linked X here over X @ X A, swap X ! ;
3162: : chained T linked A, H ;
3163:
3164: : err" s" ErrLink linked" evaluate T , H
3165: [char] " parse ht-string, X align ;
3166:
3167: : env" [char] " parse s" EnvLink linked" evaluate
3168: ht-string, X align X , ;
3169:
3170: : 2env" [char] " parse s" EnvLink linked" evaluate
3171: here >r ht-string, X align X , X ,
3172: r> dup T c@ H 80 and swap T c! H ;
3173:
3174: \ compile must be last 22feb93py
3175:
3176: Cond: [compile] ( -- ) \ name
3177: \g For immediate words, works even if forward reference
3178: bl word gfind 0= ABORT" CROSS: Can't compile"
3179: (gexecute) ;Cond
3180:
3181: Cond: postpone ( -- ) \ name
3182: bl word gfind 0= ABORT" CROSS: Can't compile"
3183: dup >magic @ <fwd> =
3184: ABORT" CROSS: Can't postpone on forward declaration"
3185: dup >magic @ <imm> =
3186: IF (gexecute)
3187: ELSE compile (compile) addr, THEN ;Cond
3188:
3189: \ save-cross 17mar93py
3190:
3191: hex
3192:
3193: >CROSS
3194: Create magic s" Gforth3x" here over allot swap move
3195:
3196: bigendian 1+ \ strangely, in magic big=0, little=1
3197: tcell 1 = 0 and or
3198: tcell 2 = 2 and or
3199: tcell 4 = 4 and or
3200: tcell 8 = 6 and or
3201: tchar 1 = 00 and or
3202: tchar 2 = 28 and or
3203: tchar 4 = 50 and or
3204: tchar 8 = 78 and or
3205: magic 7 + c!
3206:
3207: : save-cross ( "image-name" "binary-name" -- )
3208: bl parse ." Saving to " 2dup type cr
3209: w/o bin create-file throw >r
3210: s" header" X $has? IF
3211: s" #! " r@ write-file throw
3212: bl parse r@ write-file throw
3213: s" --image-file" r@ write-file throw
3214: #lf r@ emit-file throw
3215: r@ dup file-position throw drop 8 mod 8 swap ( file-id limit index )
3216: ?do
3217: bl over emit-file throw
3218: loop
3219: drop
3220: magic 8 r@ write-file throw \ write magic
3221: ELSE
3222: bl parse 2drop
3223: THEN
3224: image @ there
3225: r@ write-file throw \ write image
3226: s" relocate" X $has? IF
3227: bit$ @ there 1- tcell>bit rshift 1+
3228: r@ write-file throw \ write tags
3229: THEN
3230: r> close-file throw ;
3231:
3232: : save-region ( addr len -- )
3233: bl parse w/o bin create-file throw >r
3234: swap >image swap r@ write-file throw
3235: r> close-file throw ;
3236:
3237: \ save-asm-region 29aug01jaw
3238:
3239: Variable name-ptr
3240: Create name-buf 200 chars allot
3241: : init-name-buf name-buf name-ptr ! ;
3242: : nb, name-ptr @ c! 1 chars name-ptr +! ;
3243: : $nb, ( adr len -- ) bounds ?DO I c@ nb, LOOP ;
3244: : @nb name-ptr @ name-buf tuck - ;
3245:
3246: \ stores a usefull string representation of the character
3247: \ in the name buffer
3248: : name-char, ( c -- )
3249: dup 'a 'z 1+ within IF nb, EXIT THEN
3250: dup 'A 'Z 1+ within IF $20 + nb, EXIT THEN
3251: dup '0 '9 1+ within IF nb, EXIT THEN
3252: CASE '+ OF s" _PLUS" $nb, ENDOF
3253: '- OF s" _MINUS" $nb, ENDOF
3254: '* OF s" _STAR" $nb, ENDOF
3255: '/ OF s" _SLASH" $nb, ENDOF
3256: '' OF s" _TICK" $nb, ENDOF
3257: '( OF s" _OPAREN" $nb, ENDOF
3258: ') OF s" _CPAREN" $nb, ENDOF
3259: '[ OF s" _OBRACKET" $nb, ENDOF
3260: '] OF s" _CBRACKET" $nb, ENDOF
3261: '! OF s" _STORE" $nb, ENDOF
3262: '@ OF s" _FETCH" $nb, ENDOF
3263: '> OF s" _GREATER" $nb, ENDOF
3264: '< OF s" _LESS" $nb, ENDOF
3265: '= OF s" _EQUAL" $nb, ENDOF
3266: '# OF s" _HASH" $nb, ENDOF
3267: '? OF s" _QUEST" $nb, ENDOF
3268: ': OF s" _COL" $nb, ENDOF
3269: '; OF s" _SEMICOL" $nb, ENDOF
3270: ', OF s" _COMMA" $nb, ENDOF
3271: '. OF s" _DOT" $nb, ENDOF
3272: '" OF s" _DQUOT" $nb, ENDOF
3273: dup
3274: base @ >r hex s>d <# #s 'X hold '_ hold #> $nb, r> base !
3275: ENDCASE ;
3276:
3277: : label-from-ghostname ( ghost -- addr len )
3278: dup >ghostname init-name-buf 'L nb, bounds
3279: ?DO I c@ name-char, LOOP
3280: \ we add the address to a name to make in unique
3281: \ because one name may appear more then once
3282: \ there are names (e.g. boot) that may be reference from other
3283: \ assembler source files, so we declare them as unique
3284: \ and don't add the address suffix
3285: dup >ghost-flags @ <unique> and 0=
3286: IF s" __" $nb, >link @ base @ >r hex 0 <# #s 'L hold #> r> base ! $nb,
3287: ELSE drop
3288: THEN
3289: @nb ;
3290:
3291: \ FIXME why disabled?!
3292: : label-from-ghostnameXX ( ghost -- addr len )
3293: \ same as (label-from-ghostname) but caches generated names
3294: dup >asm-name @ ?dup IF nip count EXIT THEN
3295: \ dup >r (label-from-ghostname) 2dup
3296: align here >r string, align
3297: r> r> >asm-name ! ;
3298:
3299: : primghostdiscover ( xt -- ghost true | xt false )
3300: dup 0= IF false EXIT THEN
3301: >r last-prim-ghost
3302: BEGIN @ dup
3303: WHILE dup >asm-dummyaddr @ r@ =
3304: IF rdrop true EXIT THEN
3305: REPEAT
3306: drop r> false ;
3307:
3308: : gdiscover2 ( xt -- ghost true | xt false )
3309: dup taddr>region 0= IF false EXIT THEN
3310: dup (>regiontype) @ dup 0= IF drop false EXIT THEN
3311: addr-xt-ghost @ dup 0= IF drop false EXIT THEN
3312: nip true ;
3313: \ dup >ghost-name @ IF nip true ELSE drop false THEN ;
3314:
3315: \ generates a label name for the target address
3316: : generate-label-name ( taddr -- addr len )
3317: gdiscover2
3318: IF dup >magic @ <do:> =
3319: IF >asm-name @ count EXIT THEN
3320: label-from-ghostname
3321: ELSE
3322: primghostdiscover
3323: IF >asm-name @ count
3324: ELSE base @ >r hex 0 <# #s 'L hold #> r> base !
3325: THEN
3326: THEN ;
3327:
3328: Variable outfile-fd
3329:
3330: : $out ( adr len -- ) outfile-fd @ write-file throw ;
3331: : nlout newline $out ;
3332: : .ux ( n -- )
3333: base @ hex swap 0 <# #S #> $out base ! ;
3334:
3335: : save-asm-region-part-aligned ( taddr len -- 'taddr 'len )
3336: dup cell/ 0
3337: ?DO nlout s" .word " $out over @relbit
3338: IF over X @ generate-label-name $out
3339: ELSE over X @ s" 0x0" $out .ux
3340: THEN
3341: tcell /string
3342: LOOP ;
3343:
3344: : print-bytes ( taddr len n -- taddr' len' )
3345: over min dup 0>
3346: IF nlout s" .byte " $out 0
3347: ?DO I 0> IF s" , " $out THEN
3348: over X c@ s" 0x0" $out .ux 1 /string
3349: LOOP
3350: THEN ;
3351:
3352: : save-asm-region-part ( addr len -- )
3353: over dup X aligned swap - ?dup
3354: IF print-bytes THEN
3355: save-asm-region-part-aligned
3356: dup dup X aligned swap - ?dup
3357: IF 2 pick @relbit ABORT" relocated field splitted"
3358: print-bytes
3359: THEN
3360: 2drop ;
3361:
3362: : print-label ( taddr -- )
3363: nlout generate-label-name $out s" :" $out ;
3364:
3365: : snl-calc ( taddr taddr2 -- )
3366: tuck over - ;
3367:
3368: : skip-nolables ( taddr -- taddr2 taddr len )
3369: \G skips memory region where no lables are defined
3370: \G starting from taddr+1
3371: \G Labels will be introduced for each reference mark
3372: \G in addr-refs.
3373: \G This word deals with lables at byte addresses as well.
3374: \G The main idea is to have an intro part which
3375: \G skips until the next cell boundary, the middle part
3376: \G which skips whole cells very efficiently and the third
3377: \G part which skips the bytes to the label in a cell
3378: dup 1+ dup (>regiontype)
3379: ( S taddr taddr-realstart type-addr )
3380: dup @ dup IF addr-refs @ THEN
3381: swap >r
3382: over align+ tuck tcell swap - rshift swap 0
3383: ?DO dup 1 and
3384: IF drop rdrop snl-calc UNLOOP EXIT THEN
3385: 2/ swap 1+ swap
3386: LOOP
3387: drop r> cell+
3388: ( S .. taddr2 type-addr ) dup
3389: BEGIN dup @ dup IF addr-refs @ THEN 0= WHILE cell+ REPEAT
3390: dup >r swap - 1 cells / tcell * + r>
3391: ( S .. taddr2+skiplencells type-addr )
3392: @ addr-refs @ 1 tcell lshift or
3393: BEGIN dup 1 and 0= WHILE swap 1+ swap 2/ REPEAT drop
3394: ( S .. taddr2+skiplencells+skiplenbytes )
3395: snl-calc ;
3396:
3397: : insert-label ( taddr -- )
3398: dup 0= IF drop EXIT THEN
3399: \ ignore everything which points outside our memory regions
3400: \ maybe a primitive pointer or whatever
3401: dup taddr>region 0= IF drop EXIT THEN
3402: dup >r (>regiontype) define-addr-struct addr-refs dup @
3403: r> tcell 1- and 1 swap lshift or swap ! ;
3404:
3405: \ this generates a sorted list of addresses which must be labels
3406: \ it scans therefore a whole region
3407: : generate-label-list-region ( taddr len -- )
3408: BEGIN over @relbit IF over X @ insert-label THEN
3409: tcell /string dup 0<
3410: UNTIL 2drop ;
3411:
3412: : generate-label-list ( -- )
3413: region-link
3414: BEGIN @ dup WHILE
3415: dup 0 >rlink - extent
3416: ?dup IF generate-label-list-region ELSE drop THEN
3417: REPEAT drop ;
3418:
3419: : create-outfile ( addr len -- )
3420: w/o bin create-file throw outfile-fd ! ;
3421:
3422: : close-outfile ( -- )
3423: outfile-fd @ close-file throw ;
3424:
3425: : (save-asm-region) ( region -- )
3426: \ ." label list..."
3427: generate-label-list
3428: \ ." ok!" cr
3429: extent ( S taddr len )
3430: over insert-label
3431: 2dup + dup insert-label >r ( R end-label )
3432: ( S taddr len ) drop
3433: BEGIN
3434: dup print-label
3435: dup r@ <> WHILE
3436: skip-nolables save-asm-region-part
3437: REPEAT drop rdrop ;
3438:
3439: : lineout ( addr len -- )
3440: outfile-fd @ write-line throw ;
3441:
3442: : save-asm-region ( region adr len -- )
3443: create-outfile (save-asm-region) close-outfile ;
3444:
3445: \ \ minimal definitions
3446:
3447: >MINIMAL also minimal
3448:
3449: \ Usefull words 13feb93py
3450:
3451: : KB 400 * ;
3452:
3453: \ \ [IF] [ELSE] [THEN] ... 14sep97jaw
3454:
3455: \ it is useful to define our own structures and not to rely
3456: \ on the words in the host system
3457: \ The words in the host system might be defined with vocabularies
3458: \ this doesn't work with our self-made compile-loop
3459:
3460: Create parsed 20 chars allot \ store word we parsed
3461:
3462: : upcase
3463: parsed count bounds
3464: ?DO I c@ toupper I c! LOOP ;
3465:
3466: : [ELSE]
3467: 1 BEGIN
3468: BEGIN bl word count dup WHILE
3469: comment? 20 umin parsed place upcase parsed count
3470: 2dup s" [IF]" str= >r
3471: 2dup s" [IFUNDEF]" str= >r
3472: 2dup s" [IFDEF]" str= r> or r> or
3473: IF 2drop 1+
3474: ELSE 2dup s" [ELSE]" str=
3475: IF 2drop 1- dup
3476: IF 1+
3477: THEN
3478: ELSE
3479: 2dup s" [ENDIF]" str= >r
3480: s" [THEN]" str= r> or
3481: IF 1- THEN
3482: THEN
3483: THEN
3484: ?dup 0= ?EXIT
3485: REPEAT
3486: 2drop refill 0=
3487: UNTIL drop ; immediate
3488:
3489: : [THEN] ( -- ) ; immediate
3490:
3491: : [ENDIF] ( -- ) ; immediate
3492:
3493: : [IF] ( flag -- )
3494: 0= IF postpone [ELSE] THEN ; immediate
3495:
3496: Cond: [IF] postpone [IF] ;Cond
3497: Cond: [THEN] postpone [THEN] ;Cond
3498: Cond: [ELSE] postpone [ELSE] ;Cond
3499:
3500: \ define new [IFDEF] and [IFUNDEF] 20may93jaw
3501:
3502: : defined? tdefined? ;
3503: : needed? needed? ;
3504: : doer? doer? ;
3505:
3506: \ we want to use IFDEF on compiler directives (e.g. E?) in the source, too
3507:
3508: : directive?
3509: bl word count [ ' target >wordlist ] literal search-wordlist
3510: dup IF nip THEN ;
3511:
3512: : [IFDEF] >in @ directive? swap >in !
3513: 0= IF tdefined? ELSE name 2drop true THEN
3514: postpone [IF] ;
3515:
3516: : [IFUNDEF] tdefined? 0= postpone [IF] ;
3517:
3518: Cond: [IFDEF] postpone [IFDEF] ;Cond
3519:
3520: Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond
3521:
3522: \ C: \- \+ Conditional Compiling 09jun93jaw
3523:
3524: : C: >in @ tdefined? 0=
3525: IF >in ! X :
3526: ELSE drop
3527: BEGIN bl word dup c@
3528: IF count comment? s" ;" str= ?EXIT
3529: ELSE refill 0= ABORT" CROSS: Out of Input while C:"
3530: THEN
3531: AGAIN
3532: THEN ;
3533:
3534: : d? d? ;
3535:
3536: : \D ( -- "debugswitch" )
3537: \G doesn't skip line when debug switch is on
3538: D? 0= IF postpone \ THEN ;
3539:
3540: : \- ( -- "wordname" )
3541: \G interprets the line if word is not defined
3542: tdefined? IF postpone \ THEN ;
3543:
3544: : \+ ( -- "wordname" )
3545: \G interprets the line if word is defined
3546: tdefined? 0= IF postpone \ THEN ;
3547:
3548: : \? ( -- "envorinstring" )
3549: \G Skip line if environmental variable evaluates to false
3550: X has? 0= IF postpone \ THEN ;
3551:
3552: Cond: \- \- ;Cond
3553: Cond: \+ \+ ;Cond
3554: Cond: \D \D ;Cond
3555: Cond: \? \? ;Cond
3556:
3557: : ?? bl word find IF execute ELSE drop 0 THEN ;
3558:
3559: : needed:
3560: \G defines ghost for words that we want to be compiled
3561: BEGIN >in @ bl word c@ WHILE >in ! Ghost drop REPEAT drop ;
3562:
3563: \ words that should be in minimal
3564:
3565: create s-buffer 50 chars allot
3566:
3567: bigendian Constant bigendian
3568:
3569: : here there ;
3570: : equ constant ;
3571: : mark there constant ;
3572:
3573: \ compiler directives
3574: : >ram >ram ;
3575: : >rom >rom ;
3576: : >auto >auto ;
3577: : >tempdp >tempdp ;
3578: : tempdp> tempdp> ;
3579: : const constflag on ;
3580:
3581: : Redefinitions-start
3582: \G Starts a redefinition section. Warnings are disabled and
3583: \G existing ghosts are reused. This is used in the kernel
3584: \G where ( and \ and the like are redefined
3585: twarnings off warnings off reuse-ghosts on ;
3586:
3587: : Redefinitions-end
3588: \G Ends a redefinition section. Warnings are enabled again.
3589: twarnings on warnings on reuse-ghosts off ;
3590:
3591: : warnings name 3 =
3592: IF twarnings off warnings off ELSE twarnings on warnings on THEN drop ;
3593:
3594: : | ;
3595: \ : | NoHeaderFlag on ; \ This is broken (damages the last word)
3596:
3597: : save-cross save-cross ;
3598: : save-region save-region ;
3599: : tdump swap >image swap dump ;
3600:
3601: also forth
3602: [IFDEF] Label : Label defempty? Label ; [THEN]
3603: [IFDEF] start-macros : start-macros defempty? start-macros ; [THEN]
3604: \ [IFDEF] builttag : builttag builttag ; [THEN]
3605: previous
3606:
3607: : s" [char] " parse s-buffer place s-buffer count ; \ for environment?
3608: : + + ;
3609: : 1+ 1 + ;
3610: : 2+ 2 + ;
3611: : 1- 1- ;
3612: : - - ;
3613: : and and ;
3614: : or or ;
3615: : 2* 2* ;
3616: : * * ;
3617: : / / ;
3618: : dup dup ;
3619: : over over ;
3620: : swap swap ;
3621: : rot rot ;
3622: : drop drop ;
3623: : = = ;
3624: : <> <> ;
3625: : 0= 0= ;
3626: : lshift lshift ;
3627: : 2/ 2/ ;
3628: \ : . . ;
3629:
3630: : all-words ['] forced? IS skip? ;
3631: : needed-words ['] needed? IS skip? ;
3632: : undef-words ['] defined2? IS skip? ;
3633: : skipdef skipdef ;
3634:
3635: : \ postpone \ ; immediate
3636: : \G T-\G ; immediate
3637: : ( postpone ( ; immediate
3638: : include bl word count included ;
3639: : included swap >image swap included ;
3640: : require require ;
3641: : needs require ;
3642: : .( [char] ) parse type ;
3643: : ." [char] " parse type ;
3644: : cr cr ;
3645:
3646: : times 0 ?DO dup X c, LOOP drop ; \ used for space table creation
3647:
3648: \ only forth also cross also minimal definitions order
3649:
3650: \ cross-compiler words
3651:
3652: : decimal decimal [g'] decimal >exec2 @ ?dup IF EXECUTE THEN ;
3653: : hex hex [g'] hex >exec2 @ ?dup IF EXECUTE THEN ;
3654:
3655: \ : tudp X tudp ;
3656: \ : tup X tup ;
3657:
3658: : doc-off false to-doc ! ;
3659: : doc-on true to-doc ! ;
3660:
3661: : declareunique ( "name" -- )
3662: \ Sets the unique flag for a ghost. The assembler output
3663: \ generates labels with the ghostname concatenated with the address
3664: \ while cross-compiling. The address is concatenated
3665: \ because we have double occurences of the same name.
3666: \ If we want to reference the labels from the assembler or C
3667: \ code we declare them unique, so the address is skipped.
3668: Ghost >ghost-flags dup @ <unique> or swap ! ;
3669:
3670: \ [IFDEF] dbg : dbg dbg ; [THEN]
3671:
3672: \ for debugging...
3673: \ : dbg dbg ;
3674: : horder order ;
3675: : hwords words ;
3676: \ : words also ghosts
3677: \ words previous ;
3678: : .s .s ;
3679: : depth depth ;
3680: : bye bye ;
3681:
3682: \ dummy
3683:
3684: \ turnkey direction
3685: : H forth ; immediate
3686: : T minimal ; immediate
3687: : G ghosts ; immediate
3688:
3689:
3690: \ these ones are pefered:
3691:
3692: : unlock previous forth also cross ;
3693:
3694: \ also minimal
3695: >cross
3696:
3697: : turnkey
3698: ghosts-wordlist 1 set-order
3699: also target definitions
3700: also Minimal also ;
3701:
3702: >minimal
3703:
3704: : [[+++
3705: turnkey unlock ;
3706:
3707: unlock definitions also minimal
3708:
3709: : lock turnkey ;
3710:
3711: Defer +++]]-hook
3712: : +++]] +++]]-hook lock ;
3713:
3714: LOCK
3715: \ load cross compiler extension defined in mach file
3716:
3717: UNLOCK >CROSS
3718:
3719: [IFDEF] extend-cross extend-cross [THEN]
3720:
3721: LOCK
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>