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