1: \ CROSS.FS The Cross-Compiler 06oct92py
2: \ Idea and implementation: Bernd Paysan (py)
3:
4: \ Copyright (C) 1995,1996,1997,1998,1999 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., 675 Mass Ave, Cambridge, MA 02139, 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:
35: hex \ the defualt base for the cross-compiler is hex !!
36: Warnings off
37:
38: \ words that are generaly useful
39:
40: : KB 400 * ;
41: : >wordlist ( vocabulary-xt -- wordlist-struct )
42: also execute get-order swap >r 1- set-order r> ;
43:
44: : umax 2dup u< IF swap THEN drop ;
45: : umin 2dup u> IF swap THEN drop ;
46:
47: : string, ( c-addr u -- )
48: \ puts down string as cstring
49: dup c, here swap chars dup allot move ;
50:
51: : SetValue ( n -- <name> )
52: \G Same behaviour as "Value" if the <name> is not defined
53: \G Same behaviour as "to" if <name> is defined
54: \G SetValue searches in the current vocabulary
55: save-input bl word >r restore-input throw r> count
56: get-current search-wordlist
57: IF drop >r
58: \ we have to set current to be topmost context wordlist
59: get-order get-order get-current swap 1+ set-order
60: r> ['] to execute
61: set-order order
62: ELSE Value THEN ;
63:
64: : DefaultValue ( n -- <name> )
65: \G Same behaviour as "Value" if the <name> is not defined
66: \G DefaultValue searches in the current vocabulary
67: save-input bl word >r restore-input throw r> count
68: get-current search-wordlist
69: IF bl word drop 2drop ELSE Value THEN ;
70:
71: hex
72:
73: Vocabulary Cross
74: Vocabulary Target
75: Vocabulary Ghosts
76: VOCABULARY Minimal
77: only Forth also Target also also
78: definitions Forth
79:
80: : T previous Cross also Target ; immediate
81: : G Ghosts ; immediate
82: : H previous Forth also Cross ; immediate
83:
84: forth definitions
85:
86: : T previous Cross also Target ; immediate
87: : G Ghosts ; immediate
88:
89: : >cross also Cross definitions previous ;
90: : >target also Target definitions previous ;
91: : >minimal also Minimal definitions previous ;
92:
93: H
94:
95: >CROSS
96:
97: \ 1 Constant Cross-Flag \ to check whether assembler compiler plug-ins are
98: \ for cross-compiling
99: \ No! we use "[IFUNDEF]" there to find out whether we are target compiling!!!
100:
101: : comment? ( c-addr u -- c-addr u )
102: 2dup s" (" compare 0=
103: IF postpone (
104: ELSE 2dup s" \" compare 0= IF postpone \ THEN
105: THEN ;
106:
107: \ Begin CROSS COMPILER:
108:
109:
110:
111: \ \ -------------------- Error Handling 05aug97jaw
112:
113: \ Flags
114:
115: also forth definitions \ these values may be predefined before
116: \ the cross-compiler is loaded
117:
118: false DefaultValue stack-warn \ check on empty stack at any definition
119: false DefaultValue create-forward-warn \ warn on forward declaration of created words
120:
121: [IFUNDEF] DebugMaskSrouce Variable DebugMaskSource 0 DebugMaskSource ! [THEN]
122: [IFUNDEF] DebugMaskCross Variable DebugMaskCross 0 DebugMaskCross ! [THEN]
123:
124: previous >CROSS
125:
126: : .dec
127: base @ decimal swap . base ! ;
128:
129: : .sourcepos
130: cr sourcefilename type ." :"
131: sourceline# .dec ;
132:
133: : warnhead
134: \G display error-message head
135: \G perhaps with linenumber and filename
136: .sourcepos ." Warning: " ;
137:
138: : empty? depth IF .sourcepos ." Stack not empty!" THEN ;
139:
140: stack-warn [IF]
141: : defempty? empty? ;
142: [ELSE]
143: : defempty? ; immediate
144: [THEN]
145:
146:
147:
148: \ \ GhostNames Ghosts 9may93jaw
149:
150: \ second name source to search trough list
151:
152: VARIABLE GhostNames
153: 0 GhostNames !
154:
155: : GhostName ( -- addr )
156: here GhostNames @ , GhostNames ! here 0 ,
157: bl word count
158: \ 2dup type space
159: string, \ !! cfalign ?
160: align ;
161:
162: \ Ghost Builder 06oct92py
163:
164: \ <T T> new version with temp variable 10may93jaw
165:
166: VARIABLE VocTemp
167:
168: : <T get-current VocTemp ! also Ghosts definitions ;
169: : T> previous VocTemp @ set-current ;
170:
171: hex
172: 4711 Constant <fwd> 4712 Constant <res>
173: 4713 Constant <imm> 4714 Constant <do:>
174:
175: \ iForth makes only immediate directly after create
176: \ make atonce trick! ?
177:
178: Variable atonce atonce off
179:
180: : NoExec true ABORT" CROSS: Don't execute ghost" ;
181:
182: : GhostHeader <fwd> , 0 , ['] NoExec , ;
183:
184: : >magic ; \ type of ghost
185: : >link cell+ ; \ pointer where ghost is in target, or if unresolved
186: \ points to the where we have to resolve (linked-list)
187: : >exec cell+ cell+ ; \ execution symantics (while target compiling) of ghost
188: : >end 3 cells + ; \ room for additional tags
189: \ for builder (create, variable...) words the
190: \ execution symantics of words built are placed here
191:
192: Variable executed-ghost \ last executed ghost, needed in tcreate and gdoes>
193: Variable last-ghost \ last ghost that is created
194: Variable last-header-ghost \ last ghost definitions with header
195:
196: : Make-Ghost ( "name" -- ghost )
197: >in @ GhostName swap >in !
198: <T Create atonce @ IF immediate atonce off THEN
199: here tuck swap ! ghostheader T>
200: dup last-ghost !
201: DOES> dup executed-ghost ! >exec @ execute ;
202:
203: \ ghost words 14oct92py
204: \ changed: 10may93py/jaw
205:
206: : gfind ( string -- ghost true/1 / string false )
207: \ searches for string in word-list ghosts
208: dup count [ ' ghosts >wordlist ] ALiteral search-wordlist
209: dup IF >r >body nip r> THEN ;
210:
211: : gdiscover ( xt -- ghost true | xt false )
212: GhostNames
213: BEGIN @ dup
214: WHILE 2dup
215: cell+ @ dup >magic @ <fwd> <>
216: >r >link @ = r> and
217: IF cell+ @ nip true EXIT THEN
218: REPEAT
219: drop false ;
220:
221: VARIABLE Already
222:
223: : ghost ( "name" -- ghost )
224: Already off
225: >in @ bl word gfind IF Already on nip EXIT THEN
226: drop >in ! Make-Ghost ;
227:
228: : >ghostname ( ghost -- adr len )
229: GhostNames
230: BEGIN @ dup
231: WHILE 2dup cell+ @ =
232: UNTIL nip 2 cells + count
233: ELSE 2drop
234: \ true abort" CROSS: Ghostnames inconsistent"
235: s" ?!?!?!"
236: THEN ;
237:
238: ' >ghostname ALIAS @name
239:
240: : forward? ( ghost -- flag )
241: >magic @ <fwd> = ;
242:
243: \ Predefined ghosts 12dec92py
244:
245: ghost 0= drop
246: ghost branch ghost ?branch 2drop
247: ghost (do) ghost (?do) 2drop
248: ghost (for) drop
249: ghost (loop) ghost (+loop) 2drop
250: ghost (next) drop
251: ghost unloop ghost ;S 2drop
252: ghost lit ghost (compile) ghost ! 2drop drop
253: ghost (does>) ghost noop 2drop
254: ghost (.") ghost (S") ghost (ABORT") 2drop drop
255: ghost ' drop
256: ghost :docol ghost :doesjump ghost :dodoes 2drop drop
257: ghost :dovar drop
258: ghost over ghost = ghost drop 2drop drop
259: ghost - drop
260: ghost 2drop drop
261: ghost 2dup drop
262:
263: \ \ Parameter for target systems 06oct92py
264:
265: \ we define it ans like...
266: wordlist Constant target-environment
267:
268: VARIABLE env-current \ save information of current dictionary to restore with environ>
269:
270: : >ENVIRON get-current env-current ! target-environment set-current ;
271: : ENVIRON> env-current @ set-current ;
272:
273: >TARGET
274:
275: : environment? ( adr len -- [ x ] true | false )
276: target-environment search-wordlist
277: IF execute true ELSE false THEN ;
278:
279: : e? bl word count T environment? H 0= ABORT" environment variable not defined!" ;
280:
281: : has? bl word count T environment? H
282: IF \ environment variable is present, return its value
283: ELSE \ environment variable is not present, return false
284: \ !! JAW abort is just for testing
285: false true ABORT" arg"
286: THEN ;
287:
288: : $has? T environment? H IF ELSE false THEN ;
289:
290: >ENVIRON get-order get-current swap 1+ set-order
291: true SetValue compiler
292: true SetValue cross
293: true SetValue standard-threading
294: >TARGET previous
295:
296:
297: mach-file count included hex
298:
299: >ENVIRON
300:
301: T has? ec H
302: [IF]
303: false DefaultValue relocate
304: false DefaultValue file
305: false DefaultValue OS
306: false DefaultValue prims
307: false DefaultValue floating
308: false DefaultValue glocals
309: false DefaultValue dcomps
310: false DefaultValue hash
311: false DefaultValue xconds
312: false DefaultValue header
313: [THEN]
314:
315: true DefaultValue interpreter
316: true DefaultValue ITC
317: false DefaultValue rom
318:
319: >TARGET
320: s" relocate" T environment? H
321: [IF] SetValue NIL
322: [ELSE] >ENVIRON T NIL H SetValue relocate
323: [THEN]
324:
325: >CROSS
326:
327: \ \ Create additional parameters 19jan95py
328:
329: \ currently cross only works for host machines with address-unit-bits
330: \ eual to 8 because of s! and sc!
331: \ but I start to query the environment just to modularize a little bit
332:
333: : check-address-unit-bits ( -- )
334: \ s" ADDRESS-UNIT-BITS" environment?
335: \ IF 8 <> ELSE true THEN
336: \ ABORT" ADDRESS-UNIT-BITS unknown or not equal to 8!"
337:
338: \ shit, this doesn't work because environment? is only defined for
339: \ gforth.fi and not kernl???.fi
340: ;
341:
342: check-address-unit-bits
343: 8 Constant bits/byte \ we define: byte is address-unit
344:
345: 1 bits/byte lshift Constant maxbyte
346: \ this sets byte size for the target machine, an (probably right guess) jaw
347:
348: T
349: NIL Constant TNIL
350: cell Constant tcell
351: cell<< Constant tcell<<
352: cell>bit Constant tcell>bit
353: bits/char Constant tbits/char
354: bits/char H bits/byte T /
355: Constant tchar
356: float Constant tfloat
357: 1 bits/char lshift Constant tmaxchar
358: [IFUNDEF] bits/byte
359: 8 Constant tbits/byte
360: [ELSE]
361: bits/byte Constant tbits/byte
362: [THEN]
363: H
364: tbits/byte bits/byte / Constant tbyte
365:
366:
367: \ Variables 06oct92py
368:
369: Variable image
370: Variable tlast TNIL tlast ! \ Last name field
371: Variable tlastcfa \ Last code field
372: Variable tdoes \ Resolve does> calls
373: Variable bit$
374:
375: \ statistics 10jun97jaw
376:
377: Variable headers-named 0 headers-named !
378: Variable user-vars 0 user-vars !
379:
380: : target>bitmask-size ( u1 -- u2 )
381: 1- tcell>bit rshift 1+ ;
382:
383: : allocatetarget ( size --- adr )
384: dup allocate ABORT" CROSS: No memory for target"
385: swap over swap erase ;
386:
387: \ \ memregion.fs
388:
389:
390: Variable last-defined-region \ pointer to last defined region
391: Variable region-link \ linked list with all regions
392: Variable mirrored-link \ linked list for mirrored regions
393: 0 dup mirrored-link ! region-link !
394:
395:
396: : >rname 6 cells + ;
397: : >rbm 5 cells + ;
398: : >rmem 4 cells + ;
399: : >rlink 3 cells + ;
400: : >rdp 2 cells + ;
401: : >rlen cell+ ;
402: : >rstart ;
403:
404:
405: : region ( addr len -- ) \G create a new region
406: \ check whether predefined region exists
407: save-input bl word find >r >r restore-input throw r> r> 0=
408: IF \ make region
409: drop
410: save-input create restore-input throw
411: here last-defined-region !
412: over ( startaddr ) , ( length ) , ( dp ) ,
413: region-link linked 0 , 0 , bl word count string,
414: ELSE \ store new parameters in region
415: bl word drop
416: >body >r r@ last-defined-region !
417: r@ >rlen ! dup r@ >rstart ! r> >rdp !
418: THEN ;
419:
420: : borders ( region -- startaddr endaddr ) \G returns lower and upper region border
421: dup >rstart @ swap >rlen @ over + ;
422:
423: : extent ( region -- startaddr len ) \G returns the really used area
424: dup >rstart @ swap >rdp @ over - ;
425:
426: : area ( region -- startaddr totallen ) \G returns the total area
427: dup >rstart swap >rlen @ ;
428:
429: : mirrored \G mark a region as mirrored
430: mirrored-link
431: align linked last-defined-region @ , ;
432:
433: : .addr ( u -- )
434: \G prints a 16 or 32 Bit nice hex value
435: base @ >r hex
436: tcell 2 u>
437: IF s>d <# # # # # '. hold # # # # #> type
438: ELSE s>d <# # # # # # #> type
439: THEN r> base ! ;
440:
441: : .regions \G display region statistic
442:
443: \ we want to list the regions in the right order
444: \ so first collect all regions on stack
445: 0 region-link @
446: BEGIN dup WHILE dup @ REPEAT drop
447: BEGIN dup
448: WHILE cr
449: 0 >rlink - >r
450: r@ >rname count tuck type
451: 12 swap - 0 max spaces space
452: ." Start: " r@ >rstart @ dup .addr space
453: ." End: " r@ >rlen @ + .addr space
454: ." DP: " r> >rdp @ .addr
455: REPEAT drop
456: s" rom" T $has? H 0= ?EXIT
457: cr ." Mirrored:"
458: mirrored-link @
459: BEGIN dup
460: WHILE space dup cell+ @ >rname count type @
461: REPEAT drop cr
462: ;
463:
464: \ -------- predefined regions
465:
466: 0 0 region address-space
467: \ total memory addressed and used by the target system
468:
469: 0 0 region dictionary
470: \ rom area for the compiler
471:
472: T has? rom H
473: [IF]
474: 0 0 region ram-dictionary mirrored
475: \ ram area for the compiler
476: [ELSE]
477: ' dictionary ALIAS ram-dictionary
478: [THEN]
479:
480: 0 0 region return-stack
481:
482: 0 0 region data-stack
483:
484: 0 0 region tib-region
485:
486: ' dictionary ALIAS rom-dictionary
487:
488:
489: : setup-target ( -- ) \G initialize targets memory space
490: s" rom" T $has? H
491: IF \ check for ram and rom...
492: \ address-space area nip 0<>
493: ram-dictionary area nip 0<>
494: rom-dictionary area nip 0<>
495: and 0=
496: ABORT" CROSS: define address-space, rom- , ram-dictionary, with rom-support!"
497: THEN
498: address-space area nip
499: IF
500: address-space area
501: ELSE
502: dictionary area
503: THEN
504: nip 0=
505: ABORT" CROSS: define at least address-space or dictionary!!"
506:
507: \ allocate target for each region
508: region-link
509: BEGIN @ dup
510: WHILE dup
511: 0 >rlink - >r
512: r@ >rlen @
513: IF \ allocate mem
514: r@ >rlen @ dup
515:
516: allocatetarget dup image !
517: r@ >rmem !
518:
519: target>bitmask-size allocatetarget
520: dup bit$ !
521: r> >rbm !
522:
523: ELSE r> drop THEN
524: REPEAT drop ;
525:
526: \ MakeKernal 22feb99jaw
527:
528: : makekernel ( targetsize -- targetsize )
529: dup dictionary >rlen ! setup-target ;
530:
531: >MINIMAL
532: : makekernel makekernel ;
533: >CROSS
534:
535: \ \ switched tdp for rom support 03jun97jaw
536:
537: \ second value is here to store some maximal value for statistics
538: \ tempdp is also embedded here but has nothing to do with rom support
539: \ (needs switched dp)
540:
541: variable tempdp 0 , \ temporary dp for resolving
542: variable tempdp-save
543:
544: 0 [IF]
545: variable romdp 0 , \ Dictionary-Pointer for ramarea
546: variable ramdp 0 , \ Dictionary-Pointer for romarea
547:
548: \
549: variable sramdp \ start of ram-area for forth
550: variable sromdp \ start of rom-area for forth
551:
552: [THEN]
553:
554:
555: 0 value tdp
556: variable fixed \ flag: true: no automatic switching
557: \ false: switching is done automatically
558:
559: \ Switch-Policy:
560: \
561: \ a header is always compiled into rom
562: \ after a created word (create and variable) compilation goes to ram
563: \
564: \ Be careful: If you want to make the data behind create into rom
565: \ you have to put >rom before create!
566:
567: variable constflag constflag off
568:
569: : activate ( region -- )
570: \G next code goes to this region
571: >rdp to tdp ;
572:
573: : (switchram)
574: fixed @ ?EXIT s" rom" T $has? H 0= ?EXIT
575: ram-dictionary activate ;
576:
577: : switchram
578: constflag @
579: IF constflag off ELSE (switchram) THEN ;
580:
581: : switchrom
582: fixed @ ?EXIT rom-dictionary activate ;
583:
584: : >tempdp ( addr -- )
585: tdp tempdp-save ! tempdp to tdp tdp ! ;
586: : tempdp> ( -- )
587: tempdp-save @ to tdp ;
588:
589: : >ram fixed off (switchram) fixed on ;
590: : >rom fixed off switchrom fixed on ;
591: : >auto fixed off switchrom ;
592:
593:
594:
595: \ : romstart dup sromdp ! romdp ! ;
596: \ : ramstart dup sramdp ! ramdp ! ;
597:
598: \ default compilation goes to rom
599: \ when romable support is off, only the rom switch is used (!!)
600: >auto
601:
602: : there tdp @ ;
603:
604: >TARGET
605:
606: \ \ Target Memory Handling
607:
608: \ Byte ordering and cell size 06oct92py
609:
610: : cell+ tcell + ;
611: : cells tcell<< lshift ;
612: : chars tchar * ;
613: : char+ tchar + ;
614: : floats tfloat * ;
615:
616: >CROSS
617: : cell/ tcell<< rshift ;
618: >TARGET
619: 20 CONSTANT bl
620: \ TNIL Constant NIL
621:
622: >CROSS
623:
624: bigendian
625: [IF]
626: : S! ( n addr -- ) >r s>d r> tcell bounds swap 1-
627: DO maxbyte ud/mod rot I c! -1 +LOOP 2drop ;
628: : S@ ( addr -- n ) >r 0 0 r> tcell bounds
629: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap LOOP d>s ;
630: : Sc! ( n addr -- ) >r s>d r> tchar bounds swap 1-
631: DO maxbyte ud/mod rot I c! -1 +LOOP 2drop ;
632: : Sc@ ( addr -- n ) >r 0 0 r> tchar bounds
633: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap LOOP d>s ;
634: [ELSE]
635: : S! ( n addr -- ) >r s>d r> tcell bounds
636: DO maxbyte ud/mod rot I c! LOOP 2drop ;
637: : S@ ( addr -- n ) >r 0 0 r> tcell bounds swap 1-
638: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap -1 +LOOP d>s ;
639: : Sc! ( n addr -- ) >r s>d r> tchar bounds
640: DO maxbyte ud/mod rot I c! LOOP 2drop ;
641: : Sc@ ( addr -- n ) >r 0 0 r> tchar bounds swap 1-
642: DO maxbyte * swap maxbyte um* rot + swap I c@ + swap -1 +LOOP d>s ;
643: [THEN]
644:
645: : taddr>region ( taddr -- region | 0 )
646: \G finds for a target-address the correct region
647: \G returns 0 if taddr is not in range of a target memory region
648: region-link
649: BEGIN @ dup
650: WHILE dup >r
651: 0 >rlink - >r
652: r@ >rlen @
653: IF dup r@ borders within
654: IF r> r> drop nip EXIT THEN
655: THEN
656: r> drop
657: r>
658: REPEAT
659: 2drop 0 ;
660:
661: : (>regionimage) ( taddr -- 'taddr )
662: dup
663: \ find region we want to address
664: taddr>region dup 0= ABORT" Address out of range!"
665: >r
666: \ calculate offset in region
667: r@ >rstart @ -
668: \ add regions real address in our memory
669: r> >rmem @ + ;
670:
671: \ Bit string manipulation 06oct92py
672: \ 9may93jaw
673: CREATE Bittable 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
674: : bits ( n -- n ) chars Bittable + c@ ;
675:
676: : >bit ( addr n -- c-addr mask ) 8 /mod rot + swap bits ;
677: : +bit ( addr n -- ) >bit over c@ or swap c! ;
678: : -bit ( addr n -- ) >bit invert over c@ and swap c! ;
679:
680: : (relon) ( taddr -- ) bit$ @ swap cell/ +bit ;
681: : (reloff) ( taddr -- ) bit$ @ swap cell/ -bit ;
682:
683: : (>image) ( taddr -- absaddr ) image @ + ;
684:
685: DEFER >image
686: DEFER relon
687: DEFER reloff
688: DEFER correcter
689:
690: T has? relocate H
691: [IF]
692: ' (relon) IS relon
693: ' (reloff) IS reloff
694: ' (>image) IS >image
695: [ELSE]
696: ' drop IS relon
697: ' drop IS reloff
698: ' (>regionimage) IS >image
699: [THEN]
700:
701: \ Target memory access 06oct92py
702:
703: : align+ ( taddr -- rest )
704: tcell tuck 1- and - [ tcell 1- ] Literal and ;
705: : cfalign+ ( taddr -- rest )
706: \ see kernel.fs:cfaligned
707: /maxalign tuck 1- and - [ /maxalign 1- ] Literal and ;
708:
709: >TARGET
710: : aligned ( taddr -- ta-addr ) dup align+ + ;
711: \ assumes cell alignment granularity (as GNU C)
712:
713: : cfaligned ( taddr1 -- taddr2 )
714: \ see kernel.fs
715: dup cfalign+ + ;
716:
717: : @ ( taddr -- w ) >image S@ ;
718: : ! ( w taddr -- ) >image S! ;
719: : c@ ( taddr -- char ) >image Sc@ ;
720: : c! ( char taddr -- ) >image Sc! ;
721: : 2@ ( taddr -- x1 x2 ) T dup cell+ @ swap @ H ;
722: : 2! ( x1 x2 taddr -- ) T swap over ! cell+ ! H ;
723:
724: \ Target compilation primitives 06oct92py
725: \ included A! 16may93jaw
726:
727: : here ( -- there ) there ;
728: : allot ( n -- ) tdp +! ;
729: : , ( w -- ) T here H tcell T allot ! H T here drop H ;
730: : c, ( char -- ) T here tchar allot c! H ;
731: : align ( -- ) T here H align+ 0 ?DO bl T c, tchar H +LOOP ;
732: : cfalign ( -- )
733: T here H cfalign+ 0 ?DO bl T c, tchar H +LOOP ;
734:
735: : >address dup 0>= IF tbyte / THEN ; \ ?? jaw
736: : A! swap >address swap dup relon T ! H ;
737: : A, ( w -- ) >address T here H relon T , H ;
738:
739: >CROSS
740:
741: : tcmove ( source dest len -- )
742: \G cmove in target memory
743: tchar * bounds
744: ?DO dup T c@ H I T c! H 1+
745: tchar +LOOP drop ;
746:
747: \ \ Load Assembler
748:
749: >TARGET
750: H also Forth definitions \ ." asm: " order
751:
752: : X also target bl word find
753: IF state @ IF compile,
754: ELSE execute THEN
755: ELSE previous ABORT" Cross: access method not supported!"
756: THEN
757: previous ; immediate
758:
759: [IFDEF] asm-include asm-include [THEN] hex
760:
761: previous
762: >CROSS H
763:
764: \ \ -------------------- Compiler Plug Ins 01aug97jaw
765:
766: \ Compiler States
767:
768: Variable comp-state
769: 0 Constant interpreting
770: 1 Constant compiling
771: 2 Constant resolving
772: 3 Constant assembling
773:
774: Defer lit, ( n -- )
775: Defer alit, ( n -- )
776:
777: Defer branch, ( target-addr -- ) \ compiles a branch
778: Defer ?branch, ( target-addr -- ) \ compiles a ?branch
779: Defer branchmark, ( -- branch-addr ) \ reserves room for a branch
780: Defer ?branchmark, ( -- branch-addr ) \ reserves room for a ?branch
781: Defer ?domark, ( -- branch-addr ) \ reserves room for a ?do branch
782: Defer branchto, ( -- ) \ actual program position is target of a branch (do e.g. alignment)
783: Defer branchtoresolve, ( branch-addr -- ) \ resolves a forward reference from branchmark
784: Defer branchfrom, ( -- ) \ ?!
785: Defer branchtomark, ( -- target-addr ) \ marks a branch destination
786:
787: Defer colon, ( tcfa -- ) \ compiles call to tcfa at current position
788: Defer colonmark, ( -- addr ) \ marks a colon call
789: Defer colon-resolve ( tcfa addr -- )
790:
791: Defer addr-resolve ( target-addr addr -- )
792: Defer doer-resolve ( ghost res-pnt target-addr addr -- ghost res-pnt )
793:
794: Defer do, ( -- do-token )
795: Defer ?do, ( -- ?do-token )
796: Defer for, ( -- for-token )
797: Defer loop, ( do-token / ?do-token -- )
798: Defer +loop, ( do-token / ?do-token -- )
799: Defer next, ( for-token )
800:
801: [IFUNDEF] ca>native
802: defer ca>native
803: [THEN]
804:
805: >TARGET
806: DEFER >body \ we need the system >body
807: \ and the target >body
808: >CROSS
809: T 2 cells H VALUE xt>body
810: DEFER doprim, \ compiles start of a primitive
811: DEFER docol, \ compiles start of a colon definition
812: DEFER doer,
813: DEFER fini, \ compiles end of definition ;s
814: DEFER doeshandler,
815: DEFER dodoes,
816:
817: DEFER ]comp \ starts compilation
818: DEFER comp[ \ ends compilation
819:
820: : (cc) T a, H ; ' (cc) IS colon,
821:
822: : (cr) >tempdp ]comp colon, comp[ tempdp> ; ' (cr) IS colon-resolve
823: : (ar) T ! H ; ' (ar) IS addr-resolve
824: : (dr) ( ghost res-pnt target-addr addr )
825: >tempdp drop over
826: dup >magic @ <do:> =
827: IF doer,
828: ELSE dodoes,
829: THEN
830: tempdp> ; ' (dr) IS doer-resolve
831:
832: : (cm) ( -- addr )
833: T here align H
834: -1 colon, ; ' (cm) IS colonmark,
835:
836: >TARGET
837: : compile, colon, ;
838: >CROSS
839:
840: \ file loading
841:
842: : >fl-id 1 cells + ;
843: : >fl-name 2 cells + ;
844:
845: Variable filelist 0 filelist !
846: Create NoFile ," #load-file#"
847: 0 Value filemem
848: : loadfile FileMem ?dup IF >fl-name ELSE NoFile THEN ;
849:
850: 1 [IF] \ !! JAW WIP
851:
852: : add-included-file ( adr len -- )
853: dup char+ >fl-name allocate throw >r
854: r@ >fl-name place
855: filelist @ r@ !
856: r> dup filelist ! to FileMem
857: ;
858:
859: : included? ( c-addr u -- f )
860: filelist
861: BEGIN @ dup
862: WHILE >r r@ 1 cells + count compare 0=
863: IF rdrop 2drop true EXIT THEN
864: r>
865: REPEAT
866: 2drop drop false ;
867:
868: : included
869: \ cr ." Including: " 2dup type ." ..."
870: FileMem >r
871: 2dup add-included-file included
872: r> to FileMem ;
873:
874: : include bl word count included ;
875:
876: : require bl word count included ;
877:
878: [THEN]
879:
880: \ resolve structure
881:
882: : >next ; \ link to next field
883: : >tag cell+ ; \ indecates type of reference: 0: call, 1: address, 2: doer
884: : >taddr cell+ cell+ ;
885: : >ghost 3 cells + ;
886: : >file 4 cells + ;
887: : >line 5 cells + ;
888:
889: : (refered) ( ghost addr tag -- )
890: \G creates a reference to ghost at address taddr
891: rot >r here r@ >link @ , r> >link !
892: ( taddr tag ) ,
893: ( taddr ) ,
894: last-header-ghost @ ,
895: loadfile ,
896: sourceline# ,
897: ;
898:
899: : refered ( ghost tag -- )
900: \G creates a resolve structure
901: T here aligned H swap (refered)
902: ;
903:
904: : killref ( addr ghost -- )
905: \G kills a forward reference to ghost at position addr
906: \G this is used to eleminate a :dovar refence after making a DOES>
907: dup >magic @ <fwd> <> IF 2drop EXIT THEN
908: swap >r >link
909: BEGIN dup @ dup ( addr last this )
910: WHILE dup >taddr @ r@ =
911: IF @ over !
912: ELSE nip THEN
913: REPEAT rdrop 2drop
914: ;
915:
916: Defer resolve-warning
917:
918: : reswarn-test ( ghost res-struct -- ghost res-struct )
919: over cr ." Resolving " >ghostname type dup ." in " >ghost @ >ghostname type ;
920:
921: : reswarn-forward ( ghost res-struct -- ghost res-struct )
922: over warnhead >ghostname type dup ." is referenced in "
923: >ghost @ >ghostname type ;
924:
925: \ ' reswarn-test IS resolve-warning
926:
927: \ resolve 14oct92py
928:
929: : resolve-loop ( ghost resolve-list tcfa -- )
930: >r
931: BEGIN dup WHILE
932: \ dup >tag @ 2 = IF reswarn-forward THEN
933: resolve-warning
934: r@ over >taddr @
935: 2 pick >tag @
936: CASE 0 OF colon-resolve ENDOF
937: 1 OF addr-resolve ENDOF
938: 2 OF doer-resolve ENDOF
939: ENDCASE
940: @ \ next list element
941: REPEAT 2drop rdrop
942: ;
943:
944: \ : resolve-loop ( ghost tcfa -- ghost tcfa )
945: \ >r dup >link @
946: \ BEGIN dup WHILE dup T @ H r@ rot T ! H REPEAT drop r> ;
947:
948: \ exists 9may93jaw
949:
950: Variable TWarnings
951: TWarnings on
952: Variable Exists-Warnings
953: Exists-Warnings on
954:
955: : exists ( ghost tcfa -- )
956: over GhostNames
957: BEGIN @ dup
958: WHILE 2dup cell+ @ =
959: UNTIL
960: 2 cells + count
961: TWarnings @ Exists-Warnings @ and
962: IF warnhead type ." exists"
963: ELSE 2drop THEN
964: drop swap >link !
965: ELSE true abort" CROSS: Ghostnames inconsistent "
966: THEN ;
967:
968: : resolve ( ghost tcfa -- )
969: \G resolve referencies to ghost with tcfa
970: \ is ghost resolved?, second resolve means another definition with the
971: \ same name
972: over forward? 0= IF exists EXIT THEN
973: \ get linked-list
974: swap >r r@ >link @ swap \ ( list tcfa R: ghost )
975: \ mark ghost as resolved
976: dup r@ >link ! <res> r@ >magic !
977: \ loop through forward referencies
978: r> -rot
979: comp-state @ >r Resolving comp-state !
980: resolve-loop
981: r> comp-state !
982:
983: ['] noop IS resolve-warning
984: ;
985:
986: \ gexecute ghost, 01nov92py
987:
988: : is-forward ( ghost -- )
989: colonmark, 0 (refered) ; \ compile space for call
990:
991: : is-resolved ( ghost -- )
992: >link @ colon, ; \ compile-call
993:
994: : gexecute ( ghost -- )
995: dup @ <fwd> = IF is-forward ELSE is-resolved THEN ;
996:
997: : addr, ( ghost -- )
998: dup @ <fwd> = IF 1 refered 0 T a, H ELSE >link @ T a, H THEN ;
999:
1000: \ !! : ghost, ghost gexecute ;
1001:
1002: \ .unresolved 11may93jaw
1003:
1004: variable ResolveFlag
1005:
1006: \ ?touched 11may93jaw
1007:
1008: : ?touched ( ghost -- flag ) dup forward? swap >link @
1009: 0 <> and ;
1010:
1011: : .forwarddefs ( ghost -- )
1012: ." appeared in:"
1013: >link
1014: BEGIN @ dup
1015: WHILE cr 5 spaces
1016: dup >ghost @ >ghostname type
1017: ." file " dup >file @ ?dup IF count type ELSE ." CON" THEN
1018: ." line " dup >line @ .dec
1019: REPEAT
1020: drop ;
1021:
1022: : ?resolved ( ghostname -- )
1023: dup cell+ @ ?touched
1024: IF dup
1025: cell+ cell+ count cr type ResolveFlag on
1026: cell+ @ .forwarddefs
1027: ELSE drop
1028: THEN ;
1029:
1030: >MINIMAL
1031: : .unresolved ( -- )
1032: ResolveFlag off cr ." Unresolved: "
1033: Ghostnames
1034: BEGIN @ dup
1035: WHILE dup ?resolved
1036: REPEAT drop ResolveFlag @
1037: IF
1038: -1 abort" Unresolved words!"
1039: ELSE
1040: ." Nothing!"
1041: THEN
1042: cr ;
1043:
1044: : .stats
1045: base @ >r decimal
1046: cr ." named Headers: " headers-named @ .
1047: r> base ! ;
1048:
1049: >CROSS
1050: \ Header states 12dec92py
1051:
1052: : flag! ( 8b -- ) tlast @ dup >r T c@ xor r> c! H ;
1053:
1054: VARIABLE ^imm
1055:
1056: >TARGET
1057: : immediate 40 flag!
1058: ^imm @ @ dup <imm> = IF drop EXIT THEN
1059: <res> <> ABORT" CROSS: Cannot immediate a unresolved word"
1060: <imm> ^imm @ ! ;
1061: : restrict 20 flag! ;
1062:
1063: : isdoer
1064: \G define a forth word as doer, this makes obviously only sence on
1065: \G forth processors such as the PSC1000
1066: <do:> last-header-ghost @ >magic ! ;
1067: >CROSS
1068:
1069: \ ALIAS2 ansforth conform alias 9may93jaw
1070:
1071: : ALIAS2 create here 0 , DOES> @ execute ;
1072: \ usage:
1073: \ ' <name> alias2 bla !
1074:
1075: \ Target Header Creation 01nov92py
1076:
1077: >TARGET
1078: : string, ( addr count -- )
1079: dup T c, H bounds ?DO I c@ T c, H LOOP ;
1080: : name, ( "name" -- ) bl word count T string, cfalign H ;
1081: : view, ( -- ) ( dummy ) ;
1082: >CROSS
1083:
1084: \ Target Document Creation (goes to crossdoc.fd) 05jul95py
1085:
1086: s" ./doc/crossdoc.fd" r/w create-file throw value doc-file-id
1087: \ contains the file-id of the documentation file
1088:
1089: : T-\G ( -- )
1090: source >in @ /string doc-file-id write-line throw
1091: postpone \ ;
1092:
1093: Variable to-doc to-doc on
1094:
1095: : cross-doc-entry ( -- )
1096: to-doc @ tlast @ 0<> and \ not an anonymous (i.e. noname) header
1097: IF
1098: s" " doc-file-id write-line throw
1099: s" make-doc " doc-file-id write-file throw
1100: tlast @ >image count $1F and doc-file-id write-file throw
1101: >in @
1102: [char] ( parse 2drop
1103: [char] ) parse doc-file-id write-file throw
1104: s" )" doc-file-id write-file throw
1105: [char] \ parse 2drop
1106: T-\G
1107: >in !
1108: THEN ;
1109:
1110: \ Target TAGS creation
1111:
1112: s" kernel.TAGS" r/w create-file throw value tag-file-id
1113: \ contains the file-id of the tags file
1114:
1115: Create tag-beg 2 c, 7F c, bl c,
1116: Create tag-end 2 c, bl c, 01 c,
1117: Create tag-bof 1 c, 0C c,
1118:
1119: 2variable last-loadfilename 0 0 last-loadfilename 2!
1120:
1121: : put-load-file-name ( -- )
1122: loadfilename 2@ last-loadfilename 2@ d<>
1123: IF
1124: tag-bof count tag-file-id write-line throw
1125: sourcefilename 2dup
1126: tag-file-id write-file throw
1127: last-loadfilename 2!
1128: s" ,0" tag-file-id write-line throw
1129: THEN ;
1130:
1131: : cross-tag-entry ( -- )
1132: tlast @ 0<> \ not an anonymous (i.e. noname) header
1133: IF
1134: put-load-file-name
1135: source >in @ min tag-file-id write-file throw
1136: tag-beg count tag-file-id write-file throw
1137: tlast @ >image count $1F and tag-file-id write-file throw
1138: tag-end count tag-file-id write-file throw
1139: base @ decimal sourceline# 0 <# #s #> tag-file-id write-file throw
1140: \ >in @ 0 <# #s [char] , hold #> tag-file-id write-line throw
1141: s" ,0" tag-file-id write-line throw
1142: base !
1143: THEN ;
1144:
1145: \ Check for words
1146:
1147: Defer skip? ' false IS skip?
1148:
1149: : defined? ( -- flag ) \ name
1150: ghost forward? 0= ;
1151:
1152: : needed? ( -- flag ) \ name
1153: \G returns a false flag when
1154: \G a word is not defined
1155: \G a forward reference exists
1156: \G so the definition is not skipped!
1157: bl word gfind
1158: IF dup forward?
1159: nip
1160: 0=
1161: ELSE drop true THEN ;
1162:
1163: : doer? ( -- flag ) \ name
1164: ghost >magic @ <do:> = ;
1165:
1166: : skip-defs ( -- )
1167: BEGIN refill WHILE source -trailing nip 0= UNTIL THEN ;
1168:
1169: \ Target header creation
1170:
1171: Variable CreateFlag
1172: CreateFlag off
1173:
1174: Variable NoHeaderFlag
1175: NoHeaderFlag off
1176:
1177: : 0.r ( n1 n2 -- )
1178: base @ >r hex
1179: 0 swap <# 0 ?DO # LOOP #> type
1180: r> base ! ;
1181: : .sym
1182: bounds
1183: DO I c@ dup
1184: CASE '/ OF drop ." \/" ENDOF
1185: '\ OF drop ." \\" ENDOF
1186: dup OF emit ENDOF
1187: ENDCASE
1188: LOOP ;
1189:
1190: : (Theader ( "name" -- ghost )
1191: \ >in @ bl word count type 2 spaces >in !
1192: \ wordheaders will always be compiled to rom
1193: switchrom
1194: \ build header in target
1195: NoHeaderFlag @
1196: IF NoHeaderFlag off
1197: ELSE
1198: T align H view,
1199: tlast @ dup 0> IF T 1 cells - H THEN T A, H there tlast !
1200: 1 headers-named +! \ Statistic
1201: >in @ T name, H >in !
1202: THEN
1203: T cfalign here H tlastcfa !
1204: \ Symbol table
1205: \ >in @ cr ." sym:s/CFA=" there 4 0.r ." /" bl word count .sym ." /g" cr >in !
1206: CreateFlag @
1207: IF
1208: >in @ alias2 swap >in ! \ create alias in target
1209: >in @ ghost swap >in !
1210: swap also ghosts ' previous swap ! \ tick ghost and store in alias
1211: CreateFlag off
1212: ELSE ghost
1213: THEN
1214: dup Last-Header-Ghost !
1215: dup >magic ^imm ! \ a pointer for immediate
1216: Already @
1217: IF dup >end tdoes !
1218: ELSE 0 tdoes !
1219: THEN
1220: 80 flag!
1221: cross-doc-entry cross-tag-entry ;
1222:
1223: VARIABLE ;Resolve 1 cells allot
1224: \ this is the resolver information from ":"
1225: \ resolving is done by ";"
1226:
1227: : Theader ( "name" -- ghost )
1228: (THeader dup there resolve 0 ;Resolve ! ;
1229:
1230: >TARGET
1231: : Alias ( cfa -- ) \ name
1232: >in @ skip? IF 2drop EXIT THEN >in !
1233: dup 0< s" prims" T $has? H 0= and
1234: IF
1235: .sourcepos ." needs prim: " >in @ bl word count type >in ! cr
1236: THEN
1237: (THeader over resolve T A, H 80 flag! ;
1238: : Alias: ( cfa -- ) \ name
1239: >in @ skip? IF 2drop EXIT THEN >in !
1240: dup 0< s" prims" T $has? H 0= and
1241: IF
1242: .sourcepos ." needs doer: " >in @ bl word count type >in ! cr
1243: THEN
1244: ghost tuck swap resolve <do:> swap >magic ! ;
1245:
1246: Variable prim#
1247: : first-primitive ( n -- ) prim# ! ;
1248: : Primitive ( -- ) \ name
1249: prim# @ T Alias H -1 prim# +! ;
1250: >CROSS
1251:
1252: \ Conditionals and Comments 11may93jaw
1253:
1254: : ;Cond
1255: postpone ;
1256: swap ! ; immediate
1257:
1258: : Cond: ( -- ) \ name {code } ;
1259: atonce on
1260: ghost
1261: >exec
1262: :NONAME ;
1263:
1264: : restrict? ( -- )
1265: \ aborts on interprete state - ae
1266: state @ 0= ABORT" CROSS: Restricted" ;
1267:
1268: : Comment ( -- )
1269: >in @ atonce on ghost swap >in ! ' swap >exec ! ;
1270:
1271: Comment ( Comment \
1272:
1273: \ compile 10may93jaw
1274:
1275: : compile ( -- ) \ name
1276: restrict?
1277: bl word gfind dup 0= ABORT" CROSS: Can't compile "
1278: 0> ( immediate? )
1279: IF >exec @ compile,
1280: ELSE postpone literal postpone gexecute THEN ;
1281: immediate
1282:
1283: : [G']
1284: \G ticks a ghost and returns its address
1285: bl word gfind 0= ABORT" CROSS: Ghost don't exists"
1286: state @
1287: IF postpone literal
1288: THEN ; immediate
1289:
1290: : ghost>cfa
1291: dup forward? ABORT" CROSS: forward " >link @ ;
1292:
1293: >TARGET
1294:
1295: : ' ( -- cfa )
1296: \ returns the target-cfa of a ghost
1297: bl word gfind 0= ABORT" CROSS: Ghost don't exists"
1298: ghost>cfa ;
1299:
1300: Cond: ['] T ' H alit, ;Cond
1301:
1302: >CROSS
1303:
1304: : [T']
1305: \ returns the target-cfa of a ghost, or compiles it as literal
1306: postpone [G'] state @ IF postpone ghost>cfa ELSE ghost>cfa THEN ; immediate
1307:
1308: \ \ threading modell 13dec92py
1309: \ modularized 14jun97jaw
1310:
1311: : fillcfa ( usedcells -- )
1312: T cells H xt>body swap - 0 ?DO 0 T c, tchar H +LOOP ;
1313:
1314: : (>body) ( cfa -- pfa ) xt>body + ; ' (>body) T IS >body H
1315:
1316: : (doer,) ( ghost -- ) ]comp gexecute comp[ 1 fillcfa ; ' (doer,) IS doer,
1317:
1318: : (docol,) ( -- ) [G'] :docol doer, ; ' (docol,) IS docol,
1319:
1320: : (doprim,) ( -- )
1321: there xt>body + ca>native T a, H 1 fillcfa ; ' (doprim,) IS doprim,
1322:
1323: : (doeshandler,) ( -- )
1324: T cfalign H compile :doesjump T 0 , H ; ' (doeshandler,) IS doeshandler,
1325:
1326: : (dodoes,) ( does-action-ghost -- )
1327: ]comp [G'] :dodoes gexecute comp[
1328: addr,
1329: T here H tcell - reloff 2 fillcfa ; ' (dodoes,) IS dodoes,
1330:
1331: : (lit,) ( n -- ) compile lit T , H ; ' (lit,) IS lit,
1332:
1333: \ if we dont produce relocatable code alit, defaults to lit, jaw
1334: has? relocate
1335: [IF]
1336: : (alit,) ( n -- ) compile lit T a, H ; ' (alit,) IS alit,
1337: [ELSE]
1338: : (alit,) ( n -- ) lit, ; ' (alit,) IS alit,
1339: [THEN]
1340:
1341: : (fini,) compile ;s ; ' (fini,) IS fini,
1342:
1343: [IFUNDEF] (code)
1344: Defer (code)
1345: Defer (end-code)
1346: [THEN]
1347:
1348: >TARGET
1349: : Code
1350: defempty?
1351: (THeader there resolve
1352: [ T e? prims H 0= [IF] T e? ITC H [ELSE] true [THEN] ] [IF]
1353: doprim,
1354: [THEN]
1355: depth (code) ;
1356:
1357: : Code:
1358: defempty?
1359: ghost dup there ca>native resolve <do:> swap >magic !
1360: depth (code) ;
1361:
1362: : end-code
1363: (end-code)
1364: depth ?dup IF 1- <> ABORT" CROSS: Stack changed"
1365: ELSE true ABORT" CROSS: Stack empty" THEN
1366: ;
1367:
1368: ( Cond ) : chars tchar * ; ( Cond )
1369:
1370: >CROSS
1371:
1372: \ tLiteral 12dec92py
1373:
1374: >TARGET
1375: Cond: \G T-\G ;Cond
1376:
1377: Cond: Literal ( n -- ) restrict? lit, ;Cond
1378: Cond: ALiteral ( n -- ) restrict? alit, ;Cond
1379:
1380: : Char ( "<char>" -- ) bl word char+ c@ ;
1381: Cond: [Char] ( "<char>" -- ) restrict? Char lit, ;Cond
1382:
1383: \ some special literals 27jan97jaw
1384:
1385: \ !! Known Bug: Special Literals and plug-ins work only correct
1386: \ on 16 and 32 Bit Targets and 32 Bit Hosts!
1387:
1388: Cond: MAXU
1389: restrict?
1390: tcell 1 cells u>
1391: IF compile lit tcell 0 ?DO FF T c, H LOOP
1392: ELSE $ffffffff lit, THEN
1393: ;Cond
1394:
1395: Cond: MINI
1396: restrict?
1397: tcell 1 cells u>
1398: IF compile lit bigendian
1399: IF 80 T c, H tcell 1 ?DO 0 T c, H LOOP
1400: ELSE tcell 1 ?DO 0 T c, H LOOP 80 T c, H
1401: THEN
1402: ELSE tcell 2 = IF $8000 ELSE $80000000 THEN lit, THEN
1403: ;Cond
1404:
1405: Cond: MAXI
1406: restrict?
1407: tcell 1 cells u>
1408: IF compile lit bigendian
1409: IF 7F T c, H tcell 1 ?DO FF T c, H LOOP
1410: ELSE tcell 1 ?DO FF T c, H LOOP 7F T c, H
1411: THEN
1412: ELSE tcell 2 = IF $7fff ELSE $7fffffff THEN lit, THEN
1413: ;Cond
1414:
1415: >CROSS
1416: \ Target compiling loop 12dec92py
1417: \ ">tib trick thrown out 10may93jaw
1418: \ number? defined at the top 11may93jaw
1419:
1420: \ compiled word might leave items on stack!
1421: : tcom ( in name -- )
1422: gfind ?dup IF 0> IF nip >exec @ execute
1423: ELSE nip gexecute THEN EXIT THEN
1424: number? dup IF 0> IF swap lit, THEN lit, drop
1425: ELSE 2drop >in !
1426: ghost gexecute THEN ;
1427:
1428: >TARGET
1429: \ : ; DOES> 13dec92py
1430: \ ] 9may93py/jaw
1431:
1432: : ] state on
1433: Compiling comp-state !
1434: BEGIN
1435: BEGIN >in @ bl word
1436: dup c@ 0= WHILE 2drop refill 0=
1437: ABORT" CROSS: End of file while target compiling"
1438: REPEAT
1439: tcom
1440: state @
1441: 0=
1442: UNTIL ;
1443:
1444: \ by the way: defining a second interpreter (a compiler-)loop
1445: \ is not allowed if a system should be ans conform
1446:
1447: : : ( -- colon-sys ) \ Name
1448: defempty?
1449: constflag off \ don't let this flag work over colon defs
1450: \ just to go sure nothing unwanted happens
1451: >in @ skip? IF drop skip-defs EXIT THEN >in !
1452: (THeader ;Resolve ! there ;Resolve cell+ !
1453: docol, ]comp depth T ] H ;
1454:
1455: : :noname ( -- colon-sys )
1456: T cfalign H there docol, 0 ;Resolve ! depth T ] H ;
1457:
1458: Cond: EXIT ( -- ) restrict? compile ;S ;Cond
1459:
1460: Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond
1461:
1462: >CROSS
1463: : LastXT ;Resolve @ 0= abort" CROSS: no definition for LastXT"
1464: ;Resolve cell+ @ ;
1465:
1466: >TARGET
1467:
1468: Cond: recurse ( -- ) Last-Ghost @ gexecute ;Cond
1469:
1470: Cond: ; ( -- ) restrict?
1471: depth ?dup IF 1- <> ABORT" CROSS: Stack changed"
1472: ELSE true ABORT" CROSS: Stack empty" THEN
1473: fini,
1474: comp[
1475: state off
1476: ;Resolve @
1477: IF ;Resolve @ ;Resolve cell+ @ resolve THEN
1478: Interpreting comp-state !
1479: ;Cond
1480: Cond: [ restrict? state off Interpreting comp-state ! ;Cond
1481:
1482: >CROSS
1483:
1484: Create GhostDummy ghostheader
1485: <res> GhostDummy >magic !
1486:
1487: : !does ( does-action -- )
1488: \ !! zusammenziehen und dodoes, machen!
1489: tlastcfa @ [G'] :dovar killref
1490: \ tlastcfa @ dup there >r tdp ! compile :dodoes r> tdp ! T cell+ ! H ;
1491: \ !! geht so nicht, da dodoes, ghost will!
1492: GhostDummy >link ! GhostDummy
1493: tlastcfa @ >tempdp dodoes, tempdp> ;
1494:
1495: >TARGET
1496: Cond: DOES> restrict?
1497: compile (does>) doeshandler,
1498: \ resolve words made by builders
1499: tdoes @ ?dup IF @ T here H resolve THEN
1500: ;Cond
1501: : DOES> switchrom doeshandler, T here H !does depth T ] H ;
1502:
1503: >CROSS
1504: \ Creation 01nov92py
1505:
1506: \ Builder 11may93jaw
1507:
1508: : Builder ( Create-xt do:-xt "name" -- )
1509: \ builds up a builder in current vocabulary
1510: \ create-xt is executed when word is interpreted
1511: \ do:-xt is executet when the created word from builder is executed
1512: \ for do:-xt an additional entry after the normal ghost-enrys is used
1513:
1514: >in @ alias2 swap dup >in ! >r >r
1515: Make-Ghost
1516: rot swap >exec dup @ ['] NoExec <>
1517: IF 2drop ELSE ! THEN
1518: ,
1519: r> r> >in !
1520: also ghosts ' previous swap ! ;
1521: \ DOES> dup >exec @ execute ;
1522:
1523: : gdoes, ( ghost -- )
1524: \ makes the codefield for a word that is built
1525: >end @ dup forward? 0=
1526: IF
1527: dup >magic @ <do:> =
1528: IF doer,
1529: ELSE dodoes,
1530: THEN
1531: EXIT
1532: THEN
1533: \ compile :dodoes gexecute
1534: \ T here H tcell - reloff
1535: 2 refered
1536: 0 fillcfa
1537: ;
1538:
1539: : TCreate ( <name> -- )
1540: executed-ghost @
1541: CreateFlag on
1542: create-forward-warn
1543: IF ['] reswarn-forward IS resolve-warning THEN
1544: Theader >r dup gdoes,
1545: \ stores execution symantic in the built word
1546: >end @ >exec @ r> >exec ! ;
1547:
1548: : RTCreate ( <name> -- )
1549: \ creates a new word with code-field in ram
1550: executed-ghost @
1551: CreateFlag on
1552: create-forward-warn
1553: IF ['] reswarn-forward IS resolve-warning THEN
1554: \ make Alias
1555: (THeader there 0 T a, H 80 flag! ( S executed-ghost new-ghost )
1556: \ store poiter to code-field
1557: switchram T cfalign H
1558: there swap T ! H
1559: there tlastcfa !
1560: dup there resolve 0 ;Resolve !
1561: >r dup gdoes,
1562: >end @ >exec @ r> >exec ! ;
1563:
1564: : Build: ( -- [xt] [colon-sys] )
1565: :noname postpone TCreate ;
1566:
1567: : BuildSmart: ( -- [xt] [colon-sys] )
1568: :noname
1569: [ T has? rom H [IF] ]
1570: postpone RTCreate
1571: [ [ELSE] ]
1572: postpone TCreate
1573: [ [THEN] ] ;
1574:
1575: : gdoes> ( ghost -- addr flag )
1576: executed-ghost @
1577: state @ IF gexecute true EXIT THEN
1578: >link @ T >body H false ;
1579:
1580: \ DO: ;DO 11may93jaw
1581: \ changed to ?EXIT 10may93jaw
1582:
1583: : DO: ( -- addr [xt] [colon-sys] )
1584: here ghostheader
1585: :noname postpone gdoes> postpone ?EXIT ;
1586:
1587: : by: ( -- addr [xt] [colon-sys] ) \ name
1588: ghost
1589: :noname postpone gdoes> postpone ?EXIT ;
1590:
1591: : ;DO ( addr [xt] [colon-sys] -- addr )
1592: postpone ; ( S addr xt )
1593: over >exec ! ; immediate
1594:
1595: : by ( -- addr ) \ Name
1596: ghost >end @ ;
1597:
1598: >TARGET
1599: \ Variables and Constants 05dec92py
1600:
1601: Build: ( n -- ) ;
1602: by: :docon ( ghost -- n ) T @ H ;DO
1603: Builder (Constant)
1604:
1605: Build: ( n -- ) T , H ;
1606: by (Constant)
1607: Builder Constant
1608:
1609: Build: ( n -- ) T A, H ;
1610: by (Constant)
1611: Builder AConstant
1612:
1613: Build: ( d -- ) T , , H ;
1614: DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO
1615: Builder 2Constant
1616:
1617: BuildSmart: ;
1618: by: :dovar ( ghost -- addr ) ;DO
1619: Builder Create
1620:
1621: T has? rom H [IF]
1622: Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , H ( switchrom ) ;
1623: by (Constant)
1624: Builder Variable
1625: [ELSE]
1626: Build: T 0 , H ;
1627: by Create
1628: Builder Variable
1629: [THEN]
1630:
1631: T has? rom H [IF]
1632: Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , 0 , H ( switchrom ) ;
1633: by (Constant)
1634: Builder 2Variable
1635: [ELSE]
1636: Build: T 0 , 0 , H ;
1637: by Create
1638: Builder 2Variable
1639: [THEN]
1640:
1641: T has? rom H [IF]
1642: Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , H ( switchrom ) ;
1643: by (Constant)
1644: Builder AVariable
1645: [ELSE]
1646: Build: T 0 A, H ;
1647: by Create
1648: Builder AVariable
1649: [THEN]
1650:
1651: \ User variables 04may94py
1652:
1653: >CROSS
1654: Variable tup 0 tup !
1655: Variable tudp 0 tudp !
1656: : u, ( n -- udp )
1657: tup @ tudp @ + T ! H
1658: tudp @ dup T cell+ H tudp ! ;
1659: : au, ( n -- udp )
1660: tup @ tudp @ + T A! H
1661: tudp @ dup T cell+ H tudp ! ;
1662: >TARGET
1663:
1664: Build: T 0 u, , H ;
1665: by: :douser ( ghost -- up-addr ) T @ H tup @ + ;DO
1666: Builder User
1667:
1668: Build: T 0 u, , 0 u, drop H ;
1669: by User
1670: Builder 2User
1671:
1672: Build: T 0 au, , H ;
1673: by User
1674: Builder AUser
1675:
1676: BuildSmart: T , H ;
1677: by (Constant)
1678: Builder Value
1679:
1680: BuildSmart: T A, H ;
1681: by (Constant)
1682: Builder AValue
1683:
1684: BuildSmart: ( -- ) [T'] noop T A, H ;
1685: by: :dodefer ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
1686: Builder Defer
1687:
1688: BuildSmart: ( inter comp -- ) swap T immediate A, A, H ;
1689: DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
1690: Builder interpret/compile:
1691:
1692: \ Sturctures 23feb95py
1693:
1694: >CROSS
1695: : nalign ( addr1 n -- addr2 )
1696: \ addr2 is the aligned version of addr1 wrt the alignment size n
1697: 1- tuck + swap invert and ;
1698: >TARGET
1699:
1700: Build: ;
1701: by: :dofield T @ H + ;DO
1702: Builder (Field)
1703:
1704: Build: ( align1 offset1 align size "name" -- align2 offset2 )
1705: rot dup T , H ( align1 align size offset1 )
1706: + >r nalign r> ;
1707: by (Field)
1708: Builder Field
1709:
1710: : struct T 1 chars 0 H ;
1711: : end-struct T 2Constant H ;
1712:
1713: : cell% ( n -- size align )
1714: T 1 cells H dup ;
1715:
1716: \ ' 2Constant Alias2 end-struct
1717: \ 0 1 T Chars H 2Constant struct
1718:
1719: \ structural conditionals 17dec92py
1720:
1721: >CROSS
1722: : ?struc ( flag -- ) ABORT" CROSS: unstructured " ;
1723: : sys? ( sys -- sys ) dup 0= ?struc ;
1724: : >mark ( -- sys ) T here ( dup ." M" hex. ) 0 , H ;
1725:
1726: : branchoffset ( src dest -- ) - tchar / ; \ ?? jaw
1727:
1728: : >resolve ( sys -- ) T here ( dup ." >" hex. ) over branchoffset swap ! H ;
1729:
1730: : <resolve ( sys -- ) T here ( dup ." <" hex. ) branchoffset , H ;
1731:
1732: :noname compile branch T here branchoffset , H ;
1733: IS branch, ( target-addr -- )
1734: :noname compile ?branch T here branchoffset , H ;
1735: IS ?branch, ( target-addr -- )
1736: :noname compile branch T here 0 , H ;
1737: IS branchmark, ( -- branchtoken )
1738: :noname compile ?branch T here 0 , H ;
1739: IS ?branchmark, ( -- branchtoken )
1740: :noname T here 0 , H ;
1741: IS ?domark, ( -- branchtoken )
1742: :noname dup T @ H ?struc T here over branchoffset swap ! H ;
1743: IS branchtoresolve, ( branchtoken -- )
1744: :noname branchto, T here H ;
1745: IS branchtomark, ( -- target-addr )
1746:
1747: >TARGET
1748:
1749: \ Structural Conditionals 12dec92py
1750:
1751: Cond: BUT restrict? sys? swap ;Cond
1752: Cond: YET restrict? sys? dup ;Cond
1753:
1754: 0 [IF]
1755: >CROSS
1756: Variable tleavings
1757: >TARGET
1758:
1759: Cond: DONE ( addr -- ) restrict? tleavings @
1760: BEGIN 2dup u> 0= WHILE dup T @ H swap >resolve REPEAT
1761: tleavings ! drop ;Cond
1762:
1763: >CROSS
1764: : (leave) T here H tleavings @ T , H tleavings ! ;
1765: >TARGET
1766:
1767: Cond: LEAVE restrict? compile branch (leave) ;Cond
1768: Cond: ?LEAVE restrict? compile 0= compile ?branch (leave) ;Cond
1769:
1770: [ELSE]
1771: \ !! This is WIP
1772: \ The problem is (?DO)!
1773: \ perhaps we need a plug-in for (?DO)
1774:
1775: >CROSS
1776: Variable tleavings 0 tleavings !
1777: : (done) ( addr -- )
1778: tleavings @
1779: BEGIN dup
1780: WHILE
1781: >r dup r@ cell+ @ \ address of branch
1782: u> 0= \ lower than DO?
1783: WHILE
1784: r@ 2 cells + @ \ branch token
1785: branchtoresolve,
1786: r@ @ r> free throw
1787: REPEAT r> THEN
1788: tleavings ! drop ;
1789:
1790: >TARGET
1791:
1792: Cond: DONE ( addr -- ) restrict? (done) ;Cond
1793:
1794: >CROSS
1795: : (leave) ( branchtoken -- )
1796: 3 cells allocate throw >r
1797: T here H r@ cell+ !
1798: r@ 2 cells + !
1799: tleavings @ r@ !
1800: r> tleavings ! ;
1801: >TARGET
1802:
1803: Cond: LEAVE restrict? branchmark, (leave) ;Cond
1804: Cond: ?LEAVE restrict? compile 0= ?branchmark, (leave) ;Cond
1805:
1806: [THEN]
1807:
1808: >CROSS
1809: \ !!JW ToDo : Move to general tools section
1810:
1811: : to1 ( x1 x2 xn n -- addr )
1812: \G packs n stack elements in a allocated memory region
1813: dup dup 1+ cells allocate throw dup >r swap 1+
1814: 0 DO tuck ! cell+ LOOP
1815: drop r> ;
1816: : 1to ( addr -- x1 x2 xn )
1817: \G unpacks the elements saved by to1
1818: dup @ swap over cells + swap
1819: 0 DO dup @ swap 1 cells - LOOP
1820: free throw ;
1821:
1822: : loop] branchto, dup <resolve tcell - (done) ;
1823:
1824: : skiploop] ?dup IF branchto, branchtoresolve, THEN ;
1825:
1826: >TARGET
1827:
1828: \ Structural Conditionals 12dec92py
1829:
1830: >TARGET
1831: Cond: AHEAD restrict? branchmark, ;Cond
1832: Cond: IF restrict? ?branchmark, ;Cond
1833: Cond: THEN restrict? sys? branchto, branchtoresolve, ;Cond
1834: Cond: ELSE restrict? sys? compile AHEAD swap compile THEN ;Cond
1835:
1836: Cond: BEGIN restrict? branchtomark, ;Cond
1837: Cond: WHILE restrict? sys? compile IF swap ;Cond
1838: Cond: AGAIN restrict? sys? branch, ;Cond
1839: Cond: UNTIL restrict? sys? ?branch, ;Cond
1840: Cond: REPEAT restrict? over 0= ?struc compile AGAIN compile THEN ;Cond
1841:
1842: Cond: CASE restrict? 0 ;Cond
1843: Cond: OF restrict? 1+ >r compile over compile =
1844: compile IF compile drop r> ;Cond
1845: Cond: ENDOF restrict? >r compile ELSE r> ;Cond
1846: Cond: ENDCASE restrict? compile drop 0 ?DO compile THEN LOOP ;Cond
1847:
1848: \ Structural Conditionals 12dec92py
1849:
1850: :noname \ ?? i think 0 is too much! jaw
1851: 0 compile (do)
1852: branchtomark, 2 to1 ;
1853: IS do, ( -- target-addr )
1854:
1855: \ :noname
1856: \ compile 2dup compile = compile IF
1857: \ compile 2drop compile ELSE
1858: \ compile (do) branchtomark, 2 to1 ;
1859: \ IS ?do,
1860:
1861: :noname
1862: 0 compile (?do) ?domark, (leave)
1863: branchtomark, 2 to1 ;
1864: IS ?do, ( -- target-addr )
1865: :noname compile (for) branchtomark, ;
1866: IS for, ( -- target-addr )
1867: :noname 1to compile (loop) loop] compile unloop skiploop] ;
1868: IS loop, ( target-addr -- )
1869: :noname 1to compile (+loop) loop] compile unloop skiploop] ;
1870: IS +loop, ( target-addr -- )
1871: :noname compile (next) loop] compile unloop ;
1872: IS next, ( target-addr -- )
1873:
1874: Cond: DO restrict? do, ;Cond
1875: Cond: ?DO restrict? ?do, ;Cond
1876: Cond: FOR restrict? for, ;Cond
1877:
1878: Cond: LOOP restrict? sys? loop, ;Cond
1879: Cond: +LOOP restrict? sys? +loop, ;Cond
1880: Cond: NEXT restrict? sys? next, ;Cond
1881:
1882: \ String words 23feb93py
1883:
1884: : ," [char] " parse T string, align H ;
1885:
1886: Cond: ." restrict? compile (.") T ," H ;Cond
1887: Cond: S" restrict? compile (S") T ," H ;Cond
1888: Cond: ABORT" restrict? compile (ABORT") T ," H ;Cond
1889:
1890: Cond: IS T ' >body H compile ALiteral compile ! ;Cond
1891: : IS T >address ' >body ! H ;
1892: Cond: TO T ' >body H compile ALiteral compile ! ;Cond
1893: : TO T ' >body ! H ;
1894:
1895: Cond: defers T ' >body @ compile, H ;Cond
1896: : on T -1 swap ! H ;
1897: : off T 0 swap ! H ;
1898:
1899: \ LINKED ERR" ENV" 2ENV" 18may93jaw
1900:
1901: \ linked list primitive
1902: : linked T here over @ A, swap ! H ;
1903: : chained T linked A, H ;
1904:
1905: : err" s" ErrLink linked" evaluate T , H
1906: [char] " parse T string, align H ;
1907:
1908: : env" [char] " parse s" EnvLink linked" evaluate
1909: T string, align , H ;
1910:
1911: : 2env" [char] " parse s" EnvLink linked" evaluate
1912: here >r T string, align , , H
1913: r> dup T c@ H 80 and swap T c! H ;
1914:
1915: \ compile must be last 22feb93py
1916:
1917: Cond: compile ( -- ) restrict? \ name
1918: bl word gfind dup 0= ABORT" CROSS: Can't compile"
1919: 0> IF gexecute
1920: ELSE dup >magic @ <imm> =
1921: IF gexecute
1922: ELSE compile (compile) addr, THEN THEN ;Cond
1923:
1924: Cond: postpone ( -- ) restrict? \ name
1925: bl word gfind dup 0= ABORT" CROSS: Can't compile"
1926: 0> IF gexecute
1927: ELSE dup >magic @ <imm> =
1928: IF gexecute
1929: ELSE compile (compile) addr, THEN THEN ;Cond
1930:
1931: \ \ minimal definitions
1932:
1933: >MINIMAL
1934: also minimal
1935: \ Usefull words 13feb93py
1936:
1937: : KB 400 * ;
1938:
1939: \ \ [IF] [ELSE] [THEN] ... 14sep97jaw
1940:
1941: \ it is useful to define our own structures and not to rely
1942: \ on the words in the compiler
1943: \ The words in the compiler might be defined with vocabularies
1944: \ this doesn't work with our self-made compile-loop
1945:
1946: Create parsed 20 chars allot \ store word we parsed
1947:
1948: : upcase
1949: parsed count bounds
1950: ?DO I c@ toupper I c! LOOP ;
1951:
1952: : [ELSE]
1953: 1 BEGIN
1954: BEGIN bl word count dup WHILE
1955: comment? parsed place upcase parsed count
1956: 2dup s" [IF]" compare 0= >r
1957: 2dup s" [IFUNDEF]" compare 0= >r
1958: 2dup s" [IFDEF]" compare 0= r> or r> or
1959: IF 2drop 1+
1960: ELSE 2dup s" [ELSE]" compare 0=
1961: IF 2drop 1- dup
1962: IF 1+
1963: THEN
1964: ELSE
1965: 2dup s" [ENDIF]" compare 0= >r
1966: s" [THEN]" compare 0= r> or
1967: IF 1- THEN
1968: THEN
1969: THEN
1970: ?dup 0= ?EXIT
1971: REPEAT
1972: 2drop refill 0=
1973: UNTIL drop ; immediate
1974:
1975: : [THEN] ( -- ) ; immediate
1976:
1977: : [ENDIF] ( -- ) ; immediate
1978:
1979: : [IF] ( flag -- )
1980: 0= IF postpone [ELSE] THEN ; immediate
1981:
1982: Cond: [IF] postpone [IF] ;Cond
1983: Cond: [THEN] postpone [THEN] ;Cond
1984: Cond: [ELSE] postpone [ELSE] ;Cond
1985:
1986: \ define new [IFDEF] and [IFUNDEF] 20may93jaw
1987:
1988: : defined? defined? ;
1989: : needed? needed? ;
1990: : doer? doer? ;
1991:
1992: \ we want to use IFDEF on compiler directives (e.g. E?) in the source, too
1993:
1994: : directive?
1995: bl word count [ ' target >wordlist ] aliteral search-wordlist
1996: dup IF nip THEN ;
1997:
1998: : [IFDEF] >in @ directive? swap >in !
1999: 0= IF defined? ELSE name 2drop true THEN
2000: postpone [IF] ;
2001:
2002: : [IFUNDEF] defined? 0= postpone [IF] ;
2003:
2004: Cond: [IFDEF] postpone [IFDEF] ;Cond
2005:
2006: Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond
2007:
2008: \ C: \- \+ Conditional Compiling 09jun93jaw
2009:
2010: : C: >in @ defined? 0=
2011: IF >in ! T : H
2012: ELSE drop
2013: BEGIN bl word dup c@
2014: IF count comment? s" ;" compare 0= ?EXIT
2015: ELSE refill 0= ABORT" CROSS: Out of Input while C:"
2016: THEN
2017: AGAIN
2018: THEN ;
2019:
2020: also minimal
2021:
2022: \G doesn't skip line when bit is set in debugmask
2023: : \D name evaluate debugmasksource @ and 0= IF postpone \ THEN ;
2024:
2025: \G interprets the line if word is not defined
2026: : \- defined? IF postpone \ THEN ;
2027:
2028: \G interprets the line if word is defined
2029: : \+ defined? 0= IF postpone \ THEN ;
2030:
2031: Cond: \- \- ;Cond
2032: Cond: \+ \+ ;Cond
2033: Cond: \D \D ;Cond
2034:
2035: : ?? bl word find IF execute ELSE drop 0 THEN ;
2036:
2037: : needed:
2038: \G defines ghost for words that we want to be compiled
2039: BEGIN >in @ bl word c@ WHILE >in ! ghost drop REPEAT drop ;
2040:
2041: previous
2042:
2043: \ save-cross 17mar93py
2044:
2045: >CROSS
2046: Create magic s" Gforth2x" here over allot swap move
2047:
2048: bigendian 1+ \ strangely, in magic big=0, little=1
2049: tcell 1 = 0 and or
2050: tcell 2 = 2 and or
2051: tcell 4 = 4 and or
2052: tcell 8 = 6 and or
2053: tchar 1 = $00 and or
2054: tchar 2 = $28 and or
2055: tchar 4 = $50 and or
2056: tchar 8 = $78 and or
2057: magic 7 + c!
2058:
2059: : save-cross ( "image-name" "binary-name" -- )
2060: bl parse ." Saving to " 2dup type cr
2061: w/o bin create-file throw >r
2062: TNIL IF
2063: s" #! " r@ write-file throw
2064: bl parse r@ write-file throw
2065: s" -i" r@ write-file throw
2066: #lf r@ emit-file throw
2067: r@ dup file-position throw drop 8 mod 8 swap ( file-id limit index )
2068: ?do
2069: bl over emit-file throw
2070: loop
2071: drop
2072: magic 8 r@ write-file throw \ write magic
2073: ELSE
2074: bl parse 2drop
2075: THEN
2076: image @ there
2077: r@ write-file throw \ write image
2078: TNIL IF
2079: bit$ @ there 1- tcell>bit rshift 1+
2080: r@ write-file throw \ write tags
2081: THEN
2082: r> close-file throw ;
2083:
2084: : save-region ( addr len -- )
2085: bl parse w/o bin create-file throw >r
2086: swap >image swap r@ write-file throw
2087: r> close-file throw ;
2088:
2089: \ words that should be in minimal
2090:
2091: create s-buffer 50 chars allot
2092:
2093: >MINIMAL
2094: also minimal
2095:
2096: bigendian Constant bigendian
2097: : here there ;
2098: : equ constant ;
2099: : mark there constant ;
2100:
2101: \ compiler directives
2102: : >ram >ram ;
2103: : >rom >rom ;
2104: : >auto >auto ;
2105: : >tempdp >tempdp ;
2106: : tempdp> tempdp> ;
2107: : const constflag on ;
2108: : warnings name 3 = 0= twarnings ! drop ;
2109: : | ;
2110: \ : | NoHeaderFlag on ; \ This is broken (damages the last word)
2111:
2112: : save-cross save-cross ;
2113: : save-region save-region ;
2114: : tdump swap >image swap dump ;
2115:
2116: also forth
2117: [IFDEF] Label : Label defempty? Label ; [THEN]
2118: [IFDEF] start-macros : start-macros defempty? start-macros ; [THEN]
2119: [IFDEF] builttag : builttag builttag ; [THEN]
2120: previous
2121:
2122: : s" [char] " parse s-buffer place s-buffer count ; \ for environment?
2123: : + + ;
2124: : 1+ 1 + ;
2125: : 2+ 2 + ;
2126: : or or ;
2127: : 1- 1- ;
2128: : - - ;
2129: : and and ;
2130: : or or ;
2131: : 2* 2* ;
2132: : * * ;
2133: : / / ;
2134: : dup dup ;
2135: : over over ;
2136: : swap swap ;
2137: : rot rot ;
2138: : drop drop ;
2139: : = = ;
2140: : 0= 0= ;
2141: : lshift lshift ;
2142: : 2/ 2/ ;
2143: : . . ;
2144:
2145: : all-words ['] false IS skip? ;
2146: : needed-words ['] needed? IS skip? ;
2147: : undef-words ['] defined? IS skip? ;
2148:
2149: : \ postpone \ ; immediate
2150: : \G T-\G ; immediate
2151: : ( postpone ( ; immediate
2152: : include bl word count included ;
2153: : require require ;
2154: : .( [char] ) parse type ;
2155: : ." [char] " parse type ;
2156: : cr cr ;
2157:
2158: : times 0 ?DO dup T c, H LOOP drop ; \ used for space table creation
2159: only forth also minimal definitions
2160:
2161: \ cross-compiler words
2162:
2163: : decimal decimal ;
2164: : hex hex ;
2165:
2166: : tudp T tudp H ;
2167: : tup T tup H ;
2168:
2169: : doc-off false T to-doc H ! ;
2170: : doc-on true T to-doc H ! ;
2171: [IFDEF] dbg : dbg dbg ; [THEN]
2172:
2173: minimal
2174:
2175: \ for debugging...
2176: : order order ;
2177: : hwords words ;
2178: : words also ghosts words previous ;
2179: : .s .s ;
2180: : bye bye ;
2181:
2182: \ turnkey direction
2183: : H forth ; immediate
2184: : T minimal ; immediate
2185: : G ghosts ; immediate
2186:
2187: : turnkey 0 set-order also Target definitions
2188: also Minimal also ;
2189:
2190: \ these ones are pefered:
2191:
2192: : lock turnkey ;
2193: : unlock forth also cross ;
2194:
2195: : [[ also unlock ;
2196: : ]] previous previous ;
2197:
2198: unlock definitions also minimal
2199: : lock lock ;
2200: lock
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>