File:
[gforth] /
gforth /
cross.fs
Revision
1.4:
download - view:
text,
annotated -
select for diffs
Wed May 18 17:29:50 1994 UTC (29 years, 4 months ago) by
pazsan
Branches:
MAIN
CVS tags:
HEAD
Fixed problem with ?dup
Deleted noop output like sp+=0 from prims2x.fs
Made wordinfo.fs work with DTC on i386
Added a faster (???) relocater
1: \ CROSS.FS The Cross-Compiler 06oct92py
2: \ $Id: cross.fs,v 1.4 1994/05/18 17:29:50 pazsan Exp $
3: \ Idea and implementation: Bernd Paysan (py)
4: \ Copyright 1992 by the ANSI figForth Development Group
5:
6: \ Log:
7: \ changed in ; [ to state off 12may93jaw
8: \ included place +place 12may93jaw
9: \ for a created word (variable, constant...)
10: \ is now an alias in the target voabulary.
11: \ this means it is no longer necessary to
12: \ switch between vocabularies for variable
13: \ initialization 12may93jaw
14: \ discovered error in DOES>
15: \ replaced !does with (;code) 16may93jaw
16: \ made complete redesign and
17: \ introduced two vocs method
18: \ to be asure that the right words
19: \ are found 08jun93jaw
20: \ btw: ! works not with 16 bit
21: \ targets 09jun93jaw
22: \ added: 2user and value 11jun93jaw
23:
24: include other.fs \ ansforth extentions for cross
25:
26: decimal
27:
28: \ number? 11may93jaw
29:
30: \ checks for +, -, $, & ...
31: : leading? ( c-addr u -- c-addr u doubleflag negflag base )
32: 2dup 1- chars + c@ [char] . = \ process double
33: IF dup 1 chars = IF over 1 swap c! false ELSE 1 chars - true THEN
34: \ only if more than only . ( may be number output! )
35: \ if only . => store garbage
36: ELSE false THEN >r \ numbers
37: false -rot base @ -rot
38: BEGIN over c@
39: dup [char] - =
40: IF drop >r >r >r
41: drop true r> r> r> 0 THEN
42: dup [char] + =
43: IF drop 0 THEN
44: dup [char] $ =
45: IF drop >r >r drop 16 r> r> 0 THEN
46: dup [char] & =
47: IF drop >r >r drop 10 r> r> 0 THEN
48: 0= IF 1 chars - swap char+ swap false ELSE true THEN
49: over 0= or
50: UNTIL
51: rot >r rot r> r> -rot ;
52:
53: : number? ( c-addr -- n/d flag )
54: \ return -1 if cell 1 if double 0 if garbage
55: 0 swap 0 swap \ create double number
56: count leading?
57: base @ >r base !
58: >r >r
59: >number IF 2drop false r> r> 2drop
60: r> base ! EXIT THEN
61: drop r> r>
62: IF IF dnegate 1
63: ELSE drop negate -1 THEN
64: ELSE IF 1 ELSE drop -1 THEN
65: THEN r> base ! ;
66:
67:
68:
69: \ Begin CROSS COMPILER:
70:
71: \ GhostNames 9may93jaw
72: \ second name source to search trough list
73:
74: VARIABLE GhostNames
75: 0 GhostNames !
76: : GhostName ( -- addr )
77: here GhostNames @ , GhostNames ! here 0 ,
78: name count
79: \ 2dup type space
80: dup c, here over chars allot swap move align ;
81:
82: hex
83:
84:
85: Vocabulary Cross
86: Vocabulary Target
87: Vocabulary Ghosts
88: VOCABULARY Minimal
89: only Forth also Target also also
90: definitions Forth
91:
92: : T previous Cross also Target ; immediate
93: : G Ghosts ; immediate
94: : H previous Forth also Cross ; immediate
95:
96: forth definitions
97:
98: : T previous Cross also Target ; immediate
99: : G Ghosts ; immediate
100:
101: : >cross also Cross definitions previous ;
102: : >target also Target definitions previous ;
103: : >minimal also Minimal definitions previous ;
104:
105: H
106:
107: >CROSS
108:
109: \ Variables 06oct92py
110:
111: -1 Constant NIL
112: Variable image
113: Variable tlast NIL tlast ! \ Last name field
114: Variable tlastcfa \ Last code field
115: Variable tdoes \ Resolve does> calls
116: Variable bit$
117: Variable tdp
118: : there tdp @ ;
119:
120: \ Parameter for target systems 06oct92py
121:
122: include machine.fs
123:
124: >TARGET
125:
126: \ Byte ordering and cell size 06oct92py
127:
128: : cell+ cell + ;
129: : cells cell<< lshift ;
130: : chars ;
131:
132: >CROSS
133: : cell/ cell<< rshift ;
134: >TARGET
135: 20 CONSTANT bl
136: -1 Constant NIL
137: -2 Constant :docol
138: -3 Constant :docon
139: -4 Constant :dovar
140: -5 Constant :douser
141: -6 Constant :dodoes
142: -7 Constant :doesjump
143:
144: >CROSS
145:
146: endian 0 pad ! -1 pad c! pad @ 0<
147: = [IF] : bswap ; immediate
148: [ELSE] : bswap ( big / little -- little / big ) 0
149: cell 1- FOR bits/byte lshift over
150: [ 1 bits/byte lshift 1- ] Literal and or
151: swap bits/byte rshift swap NEXT nip ;
152: [THEN]
153:
154: \ Memory initialisation 05dec92py
155: \ Fixed bug in else part 11may93jaw
156:
157: [IFDEF] Memory \ Memory is a bigFORTH feature
158: Memory
159: : initmem ( var len -- )
160: 2dup swap handle! >r @ r> erase ;
161: Target
162: [ELSE]
163: : initmem ( var len -- )
164: tuck allocate abort" CROSS: No memory for target"
165: ( len var adr ) dup rot !
166: ( len adr ) swap erase ;
167: [THEN]
168:
169: \ MakeKernal 12dec92py
170:
171: >MINIMAL
172: : makekernal ( targetsize -- targetsize )
173: bit$ over 1- cell>bit rshift 1+ initmem
174: image over initmem tdp off ;
175:
176: >CROSS
177: \ Bit string manipulation 06oct92py
178: \ 9may93jaw
179: CREATE Bittable 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
180: : bits ( n -- n ) chars Bittable + c@ ;
181:
182: : >bit ( addr n -- c-addr mask ) 8 /mod rot + swap bits ;
183: : +bit ( addr n -- ) >bit over c@ or swap c! ;
184: : -bit ( addr n -- ) >bit invert over c@ and swap c! ;
185: : relon ( taddr -- ) bit$ @ swap cell/ +bit ;
186: : reloff ( taddr -- ) bit$ @ swap cell/ -bit ;
187:
188: \ Target memory access 06oct92py
189:
190: : align+ ( taddr -- rest )
191: cell tuck 1- and - [ cell 1- ] Literal and ;
192:
193: >TARGET
194: : aligned ( taddr -- ta-addr ) dup align+ + ;
195: \ assumes cell alignment granularity (as GNU C)
196:
197: >CROSS
198: : >image ( taddr -- absaddr ) image @ + ;
199: >TARGET
200: : @ ( taddr -- w ) >image @ bswap ;
201: : ! ( w taddr -- ) >r bswap r> >image ! ;
202: : c@ ( taddr -- char ) >image c@ ;
203: : c! ( char taddr -- ) >image c! ;
204:
205: \ Target compilation primitives 06oct92py
206: \ included A! 16may93jaw
207:
208: : here ( -- there ) there ;
209: : allot ( n -- ) tdp +! ;
210: : , ( w -- ) T here H cell T allot ! H ;
211: : c, ( char -- ) T here 1 allot c! H ;
212: : align ( -- ) T here H align+ 0 ?DO bl T c, H LOOP ;
213:
214: : A! dup relon T ! H ;
215: : A, ( w -- ) T here H relon T , H ;
216:
217: >CROSS
218:
219: \ threading modell 13dec92py
220:
221: \ generic threading modell
222: : docol, ( -- ) :docol T A, 0 , H ;
223:
224: >TARGET
225: : >body ( cfa -- pfa ) T cell+ cell+ H ;
226: >CROSS
227:
228: : dodoes, ( -- ) T :doesjump A, 0 , H ;
229:
230: \ Ghost Builder 06oct92py
231:
232: \ <T T> new version with temp variable 10may93jaw
233:
234: VARIABLE VocTemp
235:
236: : <T get-current VocTemp ! also Ghosts definitions ;
237: : T> previous VocTemp @ set-current ;
238:
239: 4711 Constant <fwd> 4712 Constant <res>
240: 4713 Constant <imm>
241:
242: \ iForth makes only immediate directly after create
243: \ make atonce trick! ?
244:
245: Variable atonce atonce off
246:
247: : NoExec true ABORT" CROSS: Don't execute ghost" ;
248:
249: : GhostHeader <fwd> , 0 , ['] NoExec , ;
250:
251: : >magic ; : >link cell+ ; : >exec cell+ cell+ ;
252: : >end 3 cells + ;
253:
254: : Make-Ghost ( "name" -- ghost )
255: >in @ GhostName swap >in !
256: <T Create atonce @ IF immediate atonce off THEN
257: here tuck swap ! ghostheader T>
258: DOES> >exec @ execute ;
259:
260: \ ghost words 14oct92py
261: \ changed: 10may93py/jaw
262:
263: : gfind ( string -- ghost true/1 / string false )
264: \ searches for string in word-list ghosts
265: \ !! wouldn't it be simpler to just use search-wordlist ? ae
266: >r get-order 0 set-order also ghosts r> find >r >r
267: set-order r> r@ IF >body THEN r> ;
268:
269: VARIABLE Already
270:
271: : ghost ( "name" -- ghost )
272: Already off
273: >in @ name gfind IF Already on nip EXIT THEN
274: drop >in ! Make-Ghost ;
275:
276: \ resolve 14oct92py
277:
278: : resolve-loop ( ghost tcfa -- ghost tcfa )
279: >r dup >link @
280: BEGIN dup WHILE dup T @ H r@ rot T ! H REPEAT drop r> ;
281:
282: \ exists 9may93jaw
283:
284: : exists ( ghost tcfa -- )
285: over GhostNames
286: BEGIN @ dup
287: WHILE 2dup cell+ @ =
288: UNTIL
289: nip 2 cells + count cr ." CROSS: Exists: " type 4 spaces
290: swap cell+ !
291: ELSE true ABORT" CROSS: Ghostnames inconsistent"
292: THEN ;
293:
294: : resolve ( ghost tcfa -- )
295: over >magic @ <fwd> <> IF exists EXIT THEN
296: resolve-loop over >link ! <res> swap >magic ! ;
297:
298: \ gexecute ghost, 01nov92py
299:
300: : do-forward ( ghost -- )
301: >link dup @ there rot ! T A, H ;
302: : do-resolve ( ghost -- )
303: >link @ T A, H ;
304:
305: : gexecute ( ghost -- ) dup @
306: <fwd> = IF do-forward ELSE do-resolve THEN ;
307: : ghost, ghost gexecute ;
308:
309: \ .unresolved 11may93jaw
310:
311: variable ResolveFlag
312:
313: \ ?touched 11may93jaw
314:
315: : ?touched ( ghost -- flag ) dup >magic @ <fwd> = swap >link @
316: 0 <> and ;
317:
318: : ?resolved ( ghostname -- )
319: dup cell+ @ ?touched
320: IF cell+ cell+ count cr type ResolveFlag on ELSE drop THEN ;
321:
322: >MINIMAL
323: : .unresolved ( -- )
324: ResolveFlag off cr ." Unresolved: "
325: Ghostnames
326: BEGIN @ dup
327: WHILE dup ?resolved
328: REPEAT drop ResolveFlag @ 0= IF ." Nothing!" THEN cr ;
329:
330: >CROSS
331: \ Header states 12dec92py
332:
333: : flag! ( 8b -- ) tlast @ dup >r T c@ xor r> c! H ;
334:
335: VARIABLE ^imm
336:
337: >TARGET
338: : immediate 20 flag!
339: ^imm @ @ dup <imm> = ?EXIT
340: <res> <> ABORT" CROSS: Cannot immediate a unresolved word"
341: <imm> ^imm @ ! ;
342: : restrict ;
343: >CROSS
344:
345: \ ALIAS2 ansforth conform alias 9may93jaw
346:
347: : ALIAS2 create here 0 , DOES> @ execute ;
348: \ usage:
349: \ ' alias2 bla !
350:
351: \ Target Header Creation 01nov92py
352:
353: : string, ( addr count -- )
354: dup T c, H bounds DO I c@ T c, H LOOP ;
355: : name, ( "name" -- ) name count string, T align H ;
356: : view, ( -- ) ( dummy ) ;
357:
358: VARIABLE CreateFlag CreateFlag off
359:
360: : (Theader ( "name" -- ghost ) T align H view,
361: tlast @ dup 0> IF T 1 cells - THEN A, H there tlast !
362: >in @ name, >in ! T here H tlastcfa !
363: CreateFlag @ IF
364: >in @ alias2 swap >in ! \ create alias in target
365: >in @ ghost swap >in !
366: swap also ghosts ' previous swap ! \ tick ghost and store in alias
367: CreateFlag off
368: ELSE ghost THEN
369: dup >magic ^imm ! \ a pointer for immediate
370: Already @ IF dup >end tdoes !
371: ELSE 0 tdoes ! THEN
372: 80 flag! ;
373:
374: VARIABLE ;Resolve 1 cells allot
375:
376: : Theader ( "name" -- ) (THeader there resolve 0 ;Resolve ! ;
377:
378: >TARGET
379: : Alias ( cfa -- ) \ name
380: (THeader over resolve T A, H 80 flag! ;
381: >CROSS
382:
383: \ Conditionals and Comments 11may93jaw
384:
385: : ;Cond
386: postpone ;
387: swap ! ; immediate
388:
389: : Cond: ( -- ) \ name {code } ;
390: atonce on
391: ghost
392: >exec
393: :NONAME ;
394:
395: : restrict? ( -- )
396: \ aborts on interprete state - ae
397: state @ 0= ABORT" CROSS: Restricted" ;
398:
399: : Comment ( -- )
400: >in @ atonce on ghost swap >in ! ' swap >exec ! ;
401:
402: Comment ( Comment \
403:
404: \ Predefined ghosts 12dec92py
405:
406: ghost 0= drop
407: ghost branch ghost ?branch 2drop
408: ghost (do) ghost (?do) 2drop
409: ghost (for) drop
410: ghost (loop) ghost (+loop) 2drop
411: ghost (next) drop
412: ghost unloop ghost ;S 2drop
413: ghost lit ghost (compile) ghost ! 2drop drop
414: ghost (;code) ghost noop 2drop
415: ghost (.") ghost (S") ghost (ABORT") 2drop drop
416:
417: \ compile 10may93jaw
418:
419: : compile ( -- ) \ name
420: restrict?
421: name gfind dup 0= ABORT" CROSS: Can't compile "
422: 0> ( immediate? )
423: IF >exec @ compile,
424: ELSE postpone literal postpone gexecute THEN ;
425: immediate
426:
427: >TARGET
428: : ' ( -- cfa ) name gfind 0= ABORT" CROSS: undefined "
429: dup >magic @ <fwd> = ABORT" CROSS: forward " >link @ ;
430:
431: Cond: ['] compile lit ghost gexecute ;Cond
432:
433: >CROSS
434: \ tLiteral 12dec92py
435:
436: : lit, ( n -- ) compile lit T , H ;
437: : alit, ( n -- ) compile lit T A, H ;
438:
439: >TARGET
440: Cond: Literal ( n -- ) restrict? lit, ;Cond
441: Cond: ALiteral ( n -- ) restrict? alit, ;Cond
442:
443: : Char ( "<char>" -- ) bl word char+ c@ ;
444: Cond: [Char] ( "<char>" -- ) restrict? Char lit, ;Cond
445:
446: >CROSS
447: \ Target compiling loop 12dec92py
448: \ ">tib trick thrown out 10may93jaw
449: \ number? defined at the top 11may93jaw
450:
451: \ compiled word might leave items on stack!
452: : tcom ( in name -- )
453: gfind ?dup IF 0> IF nip >exec @ execute
454: ELSE nip gexecute THEN EXIT THEN
455: number? dup IF 0> IF swap lit, THEN lit, drop
456: ELSE 2drop >in !
457: ghost gexecute THEN ;
458:
459: >TARGET
460: \ : ; DOES> 13dec92py
461: \ ] 9may93py/jaw
462:
463: : ] state on
464: BEGIN
465: BEGIN >in @ name
466: dup c@ 0= WHILE 2drop refill 0=
467: ABORT" CROSS: End of file while target compiling"
468: REPEAT
469: tcom
470: state @
471: 0=
472: UNTIL ;
473:
474: \ by the way: defining a second interpreter (a compiler-)loop
475: \ is not allowed if a system should be ans conform
476:
477: : : ( -- colon-sys ) \ Name
478: (THeader ;Resolve ! there ;Resolve cell+ !
479: docol, depth T ] H ;
480:
481: Cond: EXIT ( -- ) restrict? compile ;S ;Cond
482:
483: Cond: ; ( -- ) restrict?
484: depth ?dup IF 1- <> ABORT" CROSS: Stack changed"
485: ELSE true ABORT" CROSS: Stack empty" THEN
486: compile ;S state off
487: ;Resolve @
488: IF ;Resolve @ ;Resolve cell+ @ resolve THEN
489: ;Cond
490: Cond: [ restrict? state off ;Cond
491:
492: >CROSS
493: : !does :dodoes tlastcfa @ tuck T ! cell+ ! H ;
494:
495: >TARGET
496: Cond: DOES> restrict?
497: compile (;code) dodoes, tdoes @ ?dup IF @ T here H resolve THEN
498: ;Cond
499: : DOES> dodoes, T here H !does depth T ] H ;
500:
501: >CROSS
502: \ Creation 01nov92py
503:
504: \ Builder 11may93jaw
505:
506: : Builder ( Create do: "name" -- )
507: >in @ alias2 swap dup >in ! >r >r
508: Make-Ghost rot swap >exec ! ,
509: r> r> >in !
510: also ghosts ' previous swap !
511: DOES> dup >exec @ execute ;
512:
513: : gdoes, ( ghost -- ) >end @ dup >magic @ <fwd> <>
514: IF dup >link @ dup 0< IF T A, 0 , H drop EXIT THEN drop THEN
515: :dodoes T A, H gexecute T here H cell - reloff ;
516:
517: : TCreate ( ghost -- )
518: CreateFlag on
519: Theader dup gdoes,
520: >end @ >exec @ execute ;
521:
522: : Build: ( -- [xt] [colon-sys] )
523: :noname postpone TCreate ;
524:
525: : gdoes> ( ghost -- addr flag )
526: state @ IF gexecute true EXIT THEN
527: cell+ @ T >body H false ;
528:
529: \ DO: ;DO 11may93jaw
530: \ changed to ?EXIT 10may93jaw
531:
532: : (does>) postpone does> ; immediate \ second level does>
533:
534: : DO: ( -- addr [xt] [colon-sys] )
535: here ghostheader
536: :noname
537: postpone (does>) postpone gdoes> postpone ?EXIT ;
538:
539: : ;DO ( addr [xt] [colon-sys] -- )
540: postpone ; ( S addr xt )
541: over >exec ! ; immediate
542:
543: : by ( -- addr ) \ Name
544: ghost >end @ ;
545:
546: >TARGET
547: \ Variables and Constants 05dec92py
548:
549: Build: ;
550: DO: ( ghost -- addr ) ;DO
551: Builder Create
552: by Create :dovar resolve
553:
554: Build: T 0 , H ;
555: by Create
556: Builder Variable
557:
558: Build: T 0 A, H ;
559: by Create
560: Builder AVariable
561:
562: \ User variables 04may94py
563:
564: >CROSS
565: Variable tup 0 tup !
566: Variable tudp 0 tudp !
567: : u, ( n -- udp )
568: tup @ tudp @ + T ! H
569: tudp @ dup cell+ tudp ! ;
570: : au, ( n -- udp )
571: tup @ tudp @ + T A! H
572: tudp @ dup cell+ tudp ! ;
573: >TARGET
574:
575: Build: T 0 u, , H ;
576: DO: ( ghost -- up-addr ) T @ H tup @ + ;DO
577: Builder User
578: by User :douser resolve
579:
580: Build: T 0 u, , 0 u, drop H ;
581: by User
582: Builder 2User
583:
584: Build: T 0 au, , H ;
585: by User
586: Builder AUser
587:
588: Build: ( n -- ) T , H ;
589: DO: ( ghost -- n ) T @ H ;DO
590: Builder Constant
591: by Constant :docon resolve
592:
593: Build: ( n -- ) T A, H ;
594: by Constant
595: Builder AConstant
596:
597: Build: T 0 , H ;
598: by Constant
599: Builder Value
600:
601: Build: ( -- ) compile noop ;
602: DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
603: Builder Defer
604:
605: \ structural conditionals 17dec92py
606:
607: >CROSS
608: : ?struc ( flag -- ) ABORT" CROSS: unstructured " ;
609: : sys? ( sys -- sys ) dup 0= ?struc ;
610: : >mark ( -- sys ) T here 0 , H ;
611: : >resolve ( sys -- ) T here over - swap ! H ;
612: : <resolve ( sys -- ) T here - , H ;
613: >TARGET
614:
615: \ Structural Conditionals 12dec92py
616:
617: Cond: BUT restrict? sys? swap ;Cond
618: Cond: YET restrict? sys? dup ;Cond
619:
620: >CROSS
621: Variable tleavings
622: >TARGET
623:
624: Cond: DONE ( addr -- ) restrict? tleavings @
625: BEGIN 2dup u> 0= WHILE dup T @ H swap >resolve REPEAT
626: tleavings ! drop ;Cond
627:
628: >CROSS
629: : (leave T here H tleavings @ T , H tleavings ! ;
630: >TARGET
631:
632: Cond: LEAVE restrict? compile branch (leave ;Cond
633: Cond: ?LEAVE restrict? compile 0= compile ?branch (leave ;Cond
634:
635: \ Structural Conditionals 12dec92py
636:
637: Cond: AHEAD restrict? compile branch >mark ;Cond
638: Cond: IF restrict? compile ?branch >mark ;Cond
639: Cond: THEN restrict? sys? dup T @ H ?struc >resolve ;Cond
640: Cond: ELSE restrict? sys? compile AHEAD swap compile THEN ;Cond
641:
642: Cond: BEGIN restrict? T here H ;Cond
643: Cond: WHILE restrict? sys? compile IF swap ;Cond
644: Cond: AGAIN restrict? sys? compile branch <resolve ;Cond
645: Cond: UNTIL restrict? sys? compile ?branch <resolve ;Cond
646: Cond: REPEAT restrict? over 0= ?struc compile AGAIN compile THEN ;Cond
647:
648: \ Structural Conditionals 12dec92py
649:
650: Cond: DO restrict? compile (do) T here H ;Cond
651: Cond: ?DO restrict? compile (?do) (leave T here H ;Cond
652: Cond: FOR restrict? compile (for) T here H ;Cond
653:
654: >CROSS
655: : loop] dup <resolve cell - compile DONE compile unloop ;
656: >TARGET
657:
658: Cond: LOOP restrict? sys? compile (loop) loop] ;Cond
659: Cond: +LOOP restrict? sys? compile (+loop) loop] ;Cond
660: Cond: NEXT restrict? sys? compile (next) loop] ;Cond
661:
662: \ String words 23feb93py
663:
664: : ," [char] " parse string, T align H ;
665:
666: Cond: ." restrict? compile (.") T ," H ;Cond
667: Cond: S" restrict? compile (S") T ," H ;Cond
668: Cond: ABORT" restrict? compile (ABORT") T ," H ;Cond
669:
670: Cond: IS T ' >body H compile ALiteral compile ! ;Cond
671: : IS T ' >body ! H ;
672:
673: \ LINKED ERR" ENV" 2ENV" 18may93jaw
674:
675: \ linked list primitive
676: : linked T here over @ A, swap ! H ;
677:
678: : err" s" ErrLink linked" evaluate T , H
679: [char] " parse string, T align H ;
680:
681: : env" [char] " parse s" EnvLink linked" evaluate
682: string, T align , H ;
683:
684: : 2env" [char] " parse s" EnvLink linked" evaluate
685: here >r string, T align , , H
686: r> dup T c@ H 80 and swap T c! H ;
687:
688: \ compile must be last 22feb93py
689:
690: Cond: compile ( -- ) restrict? \ name
691: name gfind dup 0= ABORT" CROSS: Can't compile"
692: 0> IF gexecute
693: ELSE dup >magic @ <imm> =
694: IF gexecute
695: ELSE compile (compile) gexecute THEN THEN ;Cond
696:
697: Cond: postpone ( -- ) restrict? \ name
698: name gfind dup 0= ABORT" CROSS: Can't compile"
699: 0> IF gexecute
700: ELSE dup >magic @ <imm> =
701: IF gexecute
702: ELSE compile (compile) gexecute THEN THEN ;Cond
703:
704: >MINIMAL
705: also minimal
706: \ Usefull words 13feb93py
707:
708: : KB 400 * ;
709:
710: \ define new [IFDEF] and [IFUNDEF] 20may93jaw
711:
712: : there? name gfind IF >magic @ <fwd> <> ELSE drop false THEN ;
713:
714: : [IFDEF] there? postpone [IF] ;
715: : [IFUNDEF] there? 0= postpone [IF] ;
716:
717: \ C: \- \+ Conditional Compiling 09jun93jaw
718:
719: : C: >in @ there? 0=
720: IF >in ! T : H
721: ELSE drop
722: BEGIN bl word dup c@
723: IF count comment? s" ;" compare 0= ?EXIT
724: ELSE refill 0= ABORT" CROSS: Out of Input while C:"
725: THEN
726: AGAIN
727: THEN ;
728:
729: also minimal
730:
731: : \- there? IF postpone \ THEN ;
732: : \+ there? 0= IF postpone \ THEN ;
733:
734: : [IF] postpone [IF] ;
735: : [THEN] postpone [THEN] ;
736: : [ELSE] postpone [ELSE] ;
737:
738: Cond: [IF] [IF] ;Cond
739: Cond: [IFDEF] [IFDEF] ;Cond
740: Cond: [IFUNDEF] [IFUNDEF] ;Cond
741: Cond: [THEN] [THEN] ;Cond
742: Cond: [ELSE] [ELSE] ;Cond
743:
744: \ save-cross 17mar93py
745:
746: \ i'm not interested in bigforth features this time 10may93jaw
747: \ [IFDEF] file
748: \ also file
749: \ [THEN]
750: \ included throw after create-file 11may93jaw
751:
752: endian Constant endian
753:
754: : save-cross ( "name" -- )
755: bl parse ." Saving to " 2dup type
756: w/o bin create-file throw >r
757: image @ there r@ write-file throw
758: bit$ @ there 1- cell>bit rshift 1+ r@ write-file throw
759: r> close-file throw ;
760:
761: \ words that should be in minimal
762:
763: : + + ; : 1- 1- ;
764: : - - ; : 2* 2* ;
765: : dup dup ; : over over ;
766: : swap swap ; : rot rot ;
767:
768: \ include bug5.fs
769: \ only forth also minimal definitions
770:
771: : \ postpone \ ;
772: : ( postpone ( ;
773: : include bl word count included ;
774: : .( [char] ) parse type ;
775: : cr cr ;
776:
777: : times 0 ?DO dup T c, H LOOP drop ; \ used for space table creation
778: only forth also minimal definitions
779:
780: \ cross-compiler words
781:
782: : decimal decimal ;
783: : hex hex ;
784:
785: : tudp T tudp H ;
786: : tup T tup H ; minimal
787:
788: \ for debugging...
789: : order order ;
790: : words words ;
791: : .s .s ;
792:
793: : bye bye ;
794:
795: \ turnkey direction
796: : H forth ; immediate
797: : T minimal ; immediate
798: : G ghosts ; immediate
799:
800: : turnkey 0 set-order also Target definitions
801: also Minimal also ;
802:
803: \ these ones are pefered:
804:
805: : lock turnkey ;
806: : unlock forth also cross ;
807:
808: unlock definitions also minimal
809: : lock lock ;
810: lock
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>