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