File:
[gforth] /
gforth /
prim
Revision
1.125:
download - view:
text,
annotated -
select for diffs
Sun Jan 26 20:56:37 2003 UTC (20 years, 8 months ago) by
anton
Branches:
MAIN
CVS tags:
HEAD
use AC_SYS_LARGEFILE instead of declaring this stuff unconditionally
moved memcasecmp() into support.c
eliminated -TEXT (all uses replaced, except within prim)
converted CAPSCOMP and -TRAILING into high-level words
folded C code for more complex primitives into support.c
Fliterals are now decompiled ok
f.rdp etc. documentation changes
added test cases for SEARCH
1: \ Gforth primitives
2:
3: \ Copyright (C) 1995,1996,1997,1998,2000 Free Software Foundation, Inc.
4:
5: \ This file is part of Gforth.
6:
7: \ Gforth is free software; you can redistribute it and/or
8: \ modify it under the terms of the GNU General Public License
9: \ as published by the Free Software Foundation; either version 2
10: \ of the License, or (at your option) any later version.
11:
12: \ This program is distributed in the hope that it will be useful,
13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15: \ GNU General Public License for more details.
16:
17: \ You should have received a copy of the GNU General Public License
18: \ along with this program; if not, write to the Free Software
19: \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
20:
21:
22: \ WARNING: This file is processed by m4. Make sure your identifiers
23: \ don't collide with m4's (e.g. by undefining them).
24: \
25: \
26: \
27: \ This file contains primitive specifications in the following format:
28: \
29: \ forth name ( stack effect ) category [pronunciation]
30: \ [""glossary entry""]
31: \ C code
32: \ [:
33: \ Forth code]
34: \
35: \ Note: Fields in brackets are optional. Word specifications have to
36: \ be separated by at least one empty line
37: \
38: \ Both pronounciation and stack items (in the stack effect) must
39: \ conform to the C identifier syntax or the C compiler will complain.
40: \ If you don't have a pronounciation field, the Forth name is used,
41: \ and has to conform to the C identifier syntax.
42: \
43: \ These specifications are automatically translated into C-code for the
44: \ interpreter and into some other files. I hope that your C compiler has
45: \ decent optimization, otherwise the automatically generated code will
46: \ be somewhat slow. The Forth version of the code is included for manual
47: \ compilers, so they will need to compile only the important words.
48: \
49: \ Note that stack pointer adjustment is performed according to stack
50: \ effect by automatically generated code and NEXT is automatically
51: \ appended to the C code. Also, you can use the names in the stack
52: \ effect in the C code. Stack access is automatic. One exception: if
53: \ your code does not fall through, the results are not stored into the
54: \ stack. Use different names on both sides of the '--', if you change a
55: \ value (some stores to the stack are optimized away).
56: \
57: \ For superinstructions the syntax is:
58: \
59: \ forth-name [/ c-name] = forth-name forth-name ...
60: \
61: \
62: \ The stack variables have the following types:
63: \
64: \ name matches type
65: \ f.* Bool
66: \ c.* Char
67: \ [nw].* Cell
68: \ u.* UCell
69: \ d.* DCell
70: \ ud.* UDCell
71: \ r.* Float
72: \ a_.* Cell *
73: \ c_.* Char *
74: \ f_.* Float *
75: \ df_.* DFloat *
76: \ sf_.* SFloat *
77: \ xt.* XT
78: \ f83name.* F83Name *
79:
80: \E stack data-stack sp Cell
81: \E stack fp-stack fp Float
82: \E stack return-stack rp Cell
83: \E
84: \E get-current prefixes set-current
85: \E
86: \E s" Bool" single data-stack type-prefix f
87: \E s" Char" single data-stack type-prefix c
88: \E s" Cell" single data-stack type-prefix n
89: \E s" Cell" single data-stack type-prefix w
90: \E s" UCell" single data-stack type-prefix u
91: \E s" DCell" double data-stack type-prefix d
92: \E s" UDCell" double data-stack type-prefix ud
93: \E s" Float" single fp-stack type-prefix r
94: \E s" Cell *" single data-stack type-prefix a_
95: \E s" Char *" single data-stack type-prefix c_
96: \E s" Float *" single data-stack type-prefix f_
97: \E s" DFloat *" single data-stack type-prefix df_
98: \E s" SFloat *" single data-stack type-prefix sf_
99: \E s" Xt" single data-stack type-prefix xt
100: \E s" struct F83Name *" single data-stack type-prefix f83name
101: \E s" struct Longname *" single data-stack type-prefix longname
102: \E
103: \E return-stack stack-prefix R:
104: \E inst-stream stack-prefix #
105: \E
106: \E set-current
107: \E store-optimization on
108: \E ' noop tail-nextp2 ! \ now INST_TAIL just stores, but does not jump
109:
110: \
111: \
112: \
113: \ In addition the following names can be used:
114: \ ip the instruction pointer
115: \ sp the data stack pointer
116: \ rp the parameter stack pointer
117: \ lp the locals stack pointer
118: \ NEXT executes NEXT
119: \ cfa
120: \ NEXT1 executes NEXT1
121: \ FLAG(x) makes a Forth flag from a C flag
122: \
123: \
124: \
125: \ Percentages in comments are from Koopmans book: average/maximum use
126: \ (taken from four, not very representative benchmarks)
127: \
128: \
129: \
130: \ To do:
131: \
132: \ throw execute, cfa and NEXT1 out?
133: \ macroize *ip, ip++, *ip++ (pipelining)?
134:
135: \ these m4 macros would collide with identifiers
136: undefine(`index')
137: undefine(`shift')
138: undefine(`symbols')
139:
140: \g control
141:
142: noop ( -- ) gforth
143: :
144: ;
145:
146: call ( #a_callee -- R:a_retaddr ) new
147: ""Call callee (a variant of docol with inline argument).""
148: #ifdef NO_IP
149: INST_TAIL;
150: JUMP(a_callee);
151: #else
152: #ifdef DEBUG
153: {
154: CFA_TO_NAME((((Cell *)a_callee)-2));
155: fprintf(stderr,"%08lx: call %08lx %.*s\n",(Cell)ip,(Cell)a_callee,
156: len,name);
157: }
158: #endif
159: a_retaddr = (Cell *)IP;
160: SET_IP((Xt *)a_callee);
161: #endif
162:
163: execute ( xt -- ) core
164: ""Perform the semantics represented by the execution token, @i{xt}.""
165: #ifndef NO_IP
166: ip=IP;
167: #endif
168: IF_spTOS(spTOS = sp[0]);
169: SUPER_END;
170: EXEC(xt);
171:
172: perform ( a_addr -- ) gforth
173: ""@code{@@ execute}.""
174: /* and pfe */
175: #ifndef NO_IP
176: ip=IP;
177: #endif
178: IF_spTOS(spTOS = sp[0]);
179: SUPER_END;
180: EXEC(*(Xt *)a_addr);
181: :
182: @ execute ;
183:
184: ;s ( R:w -- ) gforth semis
185: ""The primitive compiled by @code{EXIT}.""
186: #ifdef NO_IP
187: INST_TAIL;
188: goto *(void *)w;
189: #else
190: SET_IP((Xt *)w);
191: #endif
192:
193: unloop ( R:w1 R:w2 -- ) core
194: /* !! alias for 2rdrop */
195: :
196: r> rdrop rdrop >r ;
197:
198: lit-perform ( #a_addr -- ) new lit_perform
199: #ifndef NO_IP
200: ip=IP;
201: #endif
202: SUPER_END;
203: EXEC(*(Xt *)a_addr);
204:
205: does-exec ( #a_cfa -- R:nest a_pfa ) new does_exec
206: #ifdef NO_IP
207: /* compiled to LIT CALL by compile_prim */
208: assert(0);
209: #else
210: a_pfa = PFA(a_cfa);
211: nest = (Cell)IP;
212: IF_spTOS(spTOS = sp[0]);
213: #ifdef DEBUG
214: {
215: CFA_TO_NAME(a_cfa);
216: fprintf(stderr,"%08lx: does %08lx %.*s\n",
217: (Cell)ip,(Cell)a_cfa,len,name);
218: }
219: #endif
220: SET_IP(DOES_CODE1(a_cfa));
221: #endif
222:
223: \+glocals
224:
225: branch-lp+!# ( #a_target #nlocals -- ) gforth branch_lp_plus_store_number
226: /* this will probably not be used */
227: lp += nlocals;
228: #ifdef NO_IP
229: INST_TAIL;
230: JUMP(a_target);
231: #else
232: SET_IP((Xt *)a_target);
233: #endif
234:
235: \+
236:
237: branch ( #a_target -- ) gforth
238: #ifdef NO_IP
239: INST_TAIL;
240: JUMP(a_target);
241: #else
242: SET_IP((Xt *)a_target);
243: #endif
244: :
245: r> @ >r ;
246:
247: \ condbranch(forthname,stackeffect,restline,code1,code2,forthcode)
248: \ this is non-syntactical: code must open a brace that is closed by the macro
249: define(condbranch,
250: $1 ( `#'a_target $2 ) $3
251: $4 #ifdef NO_IP
252: INST_TAIL;
253: #endif
254: $5 #ifdef NO_IP
255: JUMP(a_target);
256: #else
257: SET_IP((Xt *)a_target);
258: INST_TAIL; NEXT_P2;
259: #endif
260: }
261: SUPER_CONTINUE;
262: $6
263:
264: \+glocals
265:
266: $1-lp+!`#' ( `#'a_target `#'nlocals $2 ) $3_lp_plus_store_number
267: $4 #ifdef NO_IP
268: INST_TAIL;
269: #endif
270: $5 lp += nlocals;
271: #ifdef NO_IP
272: JUMP(a_target);
273: #else
274: SET_IP((Xt *)a_target);
275: INST_TAIL; NEXT_P2;
276: #endif
277: }
278: SUPER_CONTINUE;
279:
280: \+
281: )
282:
283: condbranch(?branch,f --,f83 question_branch,
284: ,if (f==0) {
285: ,:
286: 0= dup 0= \ !f f
287: r> tuck cell+ \ !f branchoffset f IP+
288: and -rot @ and or \ f&IP+|!f&branch
289: >r ;)
290:
291: \ we don't need an lp_plus_store version of the ?dup-stuff, because it
292: \ is only used in if's (yet)
293:
294: \+xconds
295:
296: ?dup-?branch ( #a_target f -- f ) new question_dupe_question_branch
297: ""The run-time procedure compiled by @code{?DUP-IF}.""
298: if (f==0) {
299: sp++;
300: IF_spTOS(spTOS = sp[0]);
301: #ifdef NO_IP
302: INST_TAIL;
303: JUMP(a_target);
304: #else
305: SET_IP((Xt *)a_target);
306: INST_TAIL; NEXT_P2;
307: #endif
308: }
309: SUPER_CONTINUE;
310:
311: ?dup-0=-?branch ( #a_target f -- ) new question_dupe_zero_equals_question_branch
312: ""The run-time procedure compiled by @code{?DUP-0=-IF}.""
313: /* the approach taken here of declaring the word as having the stack
314: effect ( f -- ) and correcting for it in the branch-taken case costs a
315: few cycles in that case, but is easy to convert to a CONDBRANCH
316: invocation */
317: if (f!=0) {
318: sp--;
319: #ifdef NO_IP
320: JUMP(a_target);
321: #else
322: SET_IP((Xt *)a_target);
323: NEXT;
324: #endif
325: }
326: SUPER_CONTINUE;
327:
328: \+
329: \fhas? skiploopprims 0= [IF]
330:
331: condbranch((next),R:n1 -- R:n2,cmFORTH paren_next,
332: n2=n1-1;
333: ,if (n1) {
334: ,:
335: r> r> dup 1- >r
336: IF @ >r ELSE cell+ >r THEN ;)
337:
338: condbranch((loop),R:nlimit R:n1 -- R:nlimit R:n2,gforth paren_loop,
339: n2=n1+1;
340: ,if (n2 != nlimit) {
341: ,:
342: r> r> 1+ r> 2dup =
343: IF >r 1- >r cell+ >r
344: ELSE >r >r @ >r THEN ;)
345:
346: condbranch((+loop),n R:nlimit R:n1 -- R:nlimit R:n2,gforth paren_plus_loop,
347: /* !! check this thoroughly */
348: /* sign bit manipulation and test: (x^y)<0 is equivalent to (x<0) != (y<0) */
349: /* dependent upon two's complement arithmetic */
350: Cell olddiff = n1-nlimit;
351: n2=n1+n;
352: ,if ((olddiff^(olddiff+n))>=0 /* the limit is not crossed */
353: || (olddiff^n)>=0 /* it is a wrap-around effect */) {
354: ,:
355: r> swap
356: r> r> 2dup - >r
357: 2 pick r@ + r@ xor 0< 0=
358: 3 pick r> xor 0< 0= or
359: IF >r + >r @ >r
360: ELSE >r >r drop cell+ >r THEN ;)
361:
362: \+xconds
363:
364: condbranch((-loop),u R:nlimit R:n1 -- R:nlimit R:n2,gforth paren_minus_loop,
365: UCell olddiff = n1-nlimit;
366: n2=n1-u;
367: ,if (olddiff>u) {
368: ,)
369:
370: condbranch((s+loop),n R:nlimit R:n1 -- R:nlimit R:n2,gforth paren_symmetric_plus_loop,
371: ""The run-time procedure compiled by S+LOOP. It loops until the index
372: crosses the boundary between limit and limit-sign(n). I.e. a symmetric
373: version of (+LOOP).""
374: /* !! check this thoroughly */
375: Cell diff = n1-nlimit;
376: Cell newdiff = diff+n;
377: if (n<0) {
378: diff = -diff;
379: newdiff = -newdiff;
380: }
381: n2=n1+n;
382: ,if (diff>=0 || newdiff<0) {
383: ,)
384:
385: \+
386:
387: (for) ( ncount -- R:nlimit R:ncount ) cmFORTH paren_for
388: /* or (for) = >r -- collides with unloop! */
389: nlimit=0;
390: :
391: r> swap 0 >r >r >r ;
392:
393: (do) ( nlimit nstart -- R:nlimit R:nstart ) gforth paren_do
394: :
395: r> swap rot >r >r >r ;
396:
397: (?do) ( #a_target nlimit nstart -- R:nlimit R:nstart ) gforth paren_question_do
398: #ifdef NO_IP
399: INST_TAIL;
400: #endif
401: if (nstart == nlimit) {
402: #ifdef NO_IP
403: JUMP(a_target);
404: #else
405: SET_IP((Xt *)a_target);
406: INST_TAIL; NEXT_P2;
407: #endif
408: }
409: SUPER_CONTINUE;
410: :
411: 2dup =
412: IF r> swap rot >r >r
413: @ >r
414: ELSE r> swap rot >r >r
415: cell+ >r
416: THEN ; \ --> CORE-EXT
417:
418: \+xconds
419:
420: (+do) ( #a_target nlimit nstart -- R:nlimit R:nstart ) gforth paren_plus_do
421: #ifdef NO_IP
422: INST_TAIL;
423: #endif
424: if (nstart >= nlimit) {
425: #ifdef NO_IP
426: JUMP(a_target);
427: #else
428: SET_IP((Xt *)a_target);
429: INST_TAIL; NEXT_P2;
430: #endif
431: }
432: SUPER_CONTINUE;
433: :
434: swap 2dup
435: r> swap >r swap >r
436: >=
437: IF
438: @
439: ELSE
440: cell+
441: THEN >r ;
442:
443: (u+do) ( #a_target ulimit ustart -- R:ulimit R:ustart ) gforth paren_u_plus_do
444: #ifdef NO_IP
445: INST_TAIL;
446: #endif
447: if (ustart >= ulimit) {
448: #ifdef NO_IP
449: JUMP(a_target);
450: #else
451: SET_IP((Xt *)a_target);
452: INST_TAIL; NEXT_P2;
453: #endif
454: }
455: SUPER_CONTINUE;
456: :
457: swap 2dup
458: r> swap >r swap >r
459: u>=
460: IF
461: @
462: ELSE
463: cell+
464: THEN >r ;
465:
466: (-do) ( #a_target nlimit nstart -- R:nlimit R:nstart ) gforth paren_minus_do
467: #ifdef NO_IP
468: INST_TAIL;
469: #endif
470: if (nstart <= nlimit) {
471: #ifdef NO_IP
472: JUMP(a_target);
473: #else
474: SET_IP((Xt *)a_target);
475: INST_TAIL; NEXT_P2;
476: #endif
477: }
478: SUPER_CONTINUE;
479: :
480: swap 2dup
481: r> swap >r swap >r
482: <=
483: IF
484: @
485: ELSE
486: cell+
487: THEN >r ;
488:
489: (u-do) ( #a_target ulimit ustart -- R:ulimit R:ustart ) gforth paren_u_minus_do
490: #ifdef NO_IP
491: INST_TAIL;
492: #endif
493: if (ustart <= ulimit) {
494: #ifdef NO_IP
495: JUMP(a_target);
496: #else
497: SET_IP((Xt *)a_target);
498: INST_TAIL; NEXT_P2;
499: #endif
500: }
501: SUPER_CONTINUE;
502: :
503: swap 2dup
504: r> swap >r swap >r
505: u<=
506: IF
507: @
508: ELSE
509: cell+
510: THEN >r ;
511:
512: \+
513:
514: \ don't make any assumptions where the return stack is!!
515: \ implement this in machine code if it should run quickly!
516:
517: i ( R:n -- R:n n ) core
518: :
519: \ rp@ cell+ @ ;
520: r> r> tuck >r >r ;
521:
522: i' ( R:w R:w2 -- R:w R:w2 w ) gforth i_tick
523: :
524: \ rp@ cell+ cell+ @ ;
525: r> r> r> dup itmp ! >r >r >r itmp @ ;
526: variable itmp
527:
528: j ( R:n R:d1 -- n R:n R:d1 ) core
529: :
530: \ rp@ cell+ cell+ cell+ @ ;
531: r> r> r> r> dup itmp ! >r >r >r >r itmp @ ;
532: [IFUNDEF] itmp variable itmp [THEN]
533:
534: k ( R:n R:d1 R:d2 -- n R:n R:d1 R:d2 ) gforth
535: :
536: \ rp@ [ 5 cells ] Literal + @ ;
537: r> r> r> r> r> r> dup itmp ! >r >r >r >r >r >r itmp @ ;
538: [IFUNDEF] itmp variable itmp [THEN]
539:
540: \f[THEN]
541:
542: \ digit is high-level: 0/0%
543:
544: \g strings
545:
546: move ( c_from c_to ucount -- ) core
547: ""Copy the contents of @i{ucount} aus at @i{c-from} to
548: @i{c-to}. @code{move} works correctly even if the two areas overlap.""
549: /* !! note that the standard specifies addr, not c-addr */
550: memmove(c_to,c_from,ucount);
551: /* make an Ifdef for bsd and others? */
552: :
553: >r 2dup u< IF r> cmove> ELSE r> cmove THEN ;
554:
555: cmove ( c_from c_to u -- ) string c_move
556: ""Copy the contents of @i{ucount} characters from data space at
557: @i{c-from} to @i{c-to}. The copy proceeds @code{char}-by-@code{char}
558: from low address to high address; i.e., for overlapping areas it is
559: safe if @i{c-to}=<@i{c-from}.""
560: cmove(c_from,c_to,u);
561: :
562: bounds ?DO dup c@ I c! 1+ LOOP drop ;
563:
564: cmove> ( c_from c_to u -- ) string c_move_up
565: ""Copy the contents of @i{ucount} characters from data space at
566: @i{c-from} to @i{c-to}. The copy proceeds @code{char}-by-@code{char}
567: from high address to low address; i.e., for overlapping areas it is
568: safe if @i{c-to}>=@i{c-from}.""
569: cmove_up(c_from,c_to,u);
570: :
571: dup 0= IF drop 2drop exit THEN
572: rot over + -rot bounds swap 1-
573: DO 1- dup c@ I c! -1 +LOOP drop ;
574:
575: fill ( c_addr u c -- ) core
576: ""Store @i{c} in @i{u} chars starting at @i{c-addr}.""
577: memset(c_addr,c,u);
578: :
579: -rot bounds
580: ?DO dup I c! LOOP drop ;
581:
582: compare ( c_addr1 u1 c_addr2 u2 -- n ) string
583: ""Compare two strings lexicographically. If they are equal, @i{n} is 0; if
584: the first string is smaller, @i{n} is -1; if the first string is larger, @i{n}
585: is 1. Currently this is based on the machine's character
586: comparison. In the future, this may change to consider the current
587: locale and its collation order.""
588: /* close ' to keep fontify happy */
589: n = compare(c_addr1, u1, c_addr2, u2);
590: :
591: rot 2dup swap - >r min swap -text dup
592: IF rdrop ELSE drop r> sgn THEN ;
593: : sgn ( n -- -1/0/1 )
594: dup 0= IF EXIT THEN 0< 2* 1+ ;
595:
596: \ -text is only used by replaced primitives now; move it elsewhere
597: \ -text ( c_addr1 u c_addr2 -- n ) new dash_text
598: \ n = memcmp(c_addr1, c_addr2, u);
599: \ if (n<0)
600: \ n = -1;
601: \ else if (n>0)
602: \ n = 1;
603: \ :
604: \ swap bounds
605: \ ?DO dup c@ I c@ = WHILE 1+ LOOP drop 0
606: \ ELSE c@ I c@ - unloop THEN sgn ;
607: \ : sgn ( n -- -1/0/1 )
608: \ dup 0= IF EXIT THEN 0< 2* 1+ ;
609:
610: toupper ( c1 -- c2 ) gforth
611: ""If @i{c1} is a lower-case character (in the current locale), @i{c2}
612: is the equivalent upper-case character. All other characters are unchanged.""
613: c2 = toupper(c1);
614: :
615: dup [char] a - [ char z char a - 1 + ] Literal u< bl and - ;
616:
617: /string ( c_addr1 u1 n -- c_addr2 u2 ) string slash_string
618: ""Adjust the string specified by @i{c-addr1, u1} to remove @i{n}
619: characters from the start of the string.""
620: c_addr2 = c_addr1+n;
621: u2 = u1-n;
622: :
623: tuck - >r + r> dup 0< IF - 0 THEN ;
624:
625: \g arith
626:
627: lit ( #w -- w ) gforth
628: :
629: r> dup @ swap cell+ >r ;
630:
631: + ( n1 n2 -- n ) core plus
632: n = n1+n2;
633:
634: \ lit+ / lit_plus = lit +
635:
636: lit+ ( n1 #n2 -- n ) new lit_plus
637: n=n1+n2;
638:
639: \ PFE-0.9.14 has it differently, but the next release will have it as follows
640: under+ ( n1 n2 n3 -- n n2 ) gforth under_plus
641: ""add @i{n3} to @i{n1} (giving @i{n})""
642: n = n1+n3;
643: :
644: rot + swap ;
645:
646: - ( n1 n2 -- n ) core minus
647: n = n1-n2;
648: :
649: negate + ;
650:
651: negate ( n1 -- n2 ) core
652: /* use minus as alias */
653: n2 = -n1;
654: :
655: invert 1+ ;
656:
657: 1+ ( n1 -- n2 ) core one_plus
658: n2 = n1+1;
659: :
660: 1 + ;
661:
662: 1- ( n1 -- n2 ) core one_minus
663: n2 = n1-1;
664: :
665: 1 - ;
666:
667: max ( n1 n2 -- n ) core
668: if (n1<n2)
669: n = n2;
670: else
671: n = n1;
672: :
673: 2dup < IF swap THEN drop ;
674:
675: min ( n1 n2 -- n ) core
676: if (n1<n2)
677: n = n1;
678: else
679: n = n2;
680: :
681: 2dup > IF swap THEN drop ;
682:
683: abs ( n -- u ) core
684: if (n<0)
685: u = -n;
686: else
687: u = n;
688: :
689: dup 0< IF negate THEN ;
690:
691: * ( n1 n2 -- n ) core star
692: n = n1*n2;
693: :
694: um* drop ;
695:
696: / ( n1 n2 -- n ) core slash
697: n = n1/n2;
698: :
699: /mod nip ;
700:
701: mod ( n1 n2 -- n ) core
702: n = n1%n2;
703: :
704: /mod drop ;
705:
706: /mod ( n1 n2 -- n3 n4 ) core slash_mod
707: n4 = n1/n2;
708: n3 = n1%n2; /* !! is this correct? look into C standard! */
709: :
710: >r s>d r> fm/mod ;
711:
712: 2* ( n1 -- n2 ) core two_star
713: ""Shift left by 1; also works on unsigned numbers""
714: n2 = 2*n1;
715: :
716: dup + ;
717:
718: 2/ ( n1 -- n2 ) core two_slash
719: ""Arithmetic shift right by 1. For signed numbers this is a floored
720: division by 2 (note that @code{/} not necessarily floors).""
721: n2 = n1>>1;
722: :
723: dup MINI and IF 1 ELSE 0 THEN
724: [ bits/byte cell * 1- ] literal
725: 0 DO 2* swap dup 2* >r MINI and
726: IF 1 ELSE 0 THEN or r> swap
727: LOOP nip ;
728:
729: fm/mod ( d1 n1 -- n2 n3 ) core f_m_slash_mod
730: ""Floored division: @i{d1} = @i{n3}*@i{n1}+@i{n2}, @i{n1}>@i{n2}>=0 or 0>=@i{n2}>@i{n1}.""
731: #ifdef BUGGY_LONG_LONG
732: DCell r = fmdiv(d1,n1);
733: n2=r.hi;
734: n3=r.lo;
735: #else
736: /* assumes that the processor uses either floored or symmetric division */
737: n3 = d1/n1;
738: n2 = d1%n1;
739: /* note that this 1%-3>0 is optimized by the compiler */
740: if (1%-3>0 && (d1<0) != (n1<0) && n2!=0) {
741: n3--;
742: n2+=n1;
743: }
744: #endif
745: :
746: dup >r dup 0< IF negate >r dnegate r> THEN
747: over 0< IF tuck + swap THEN
748: um/mod
749: r> 0< IF swap negate swap THEN ;
750:
751: sm/rem ( d1 n1 -- n2 n3 ) core s_m_slash_rem
752: ""Symmetric division: @i{d1} = @i{n3}*@i{n1}+@i{n2}, sign(@i{n2})=sign(@i{d1}) or 0.""
753: #ifdef BUGGY_LONG_LONG
754: DCell r = smdiv(d1,n1);
755: n2=r.hi;
756: n3=r.lo;
757: #else
758: /* assumes that the processor uses either floored or symmetric division */
759: n3 = d1/n1;
760: n2 = d1%n1;
761: /* note that this 1%-3<0 is optimized by the compiler */
762: if (1%-3<0 && (d1<0) != (n1<0) && n2!=0) {
763: n3++;
764: n2-=n1;
765: }
766: #endif
767: :
768: over >r dup >r abs -rot
769: dabs rot um/mod
770: r> r@ xor 0< IF negate THEN
771: r> 0< IF swap negate swap THEN ;
772:
773: m* ( n1 n2 -- d ) core m_star
774: #ifdef BUGGY_LONG_LONG
775: d = mmul(n1,n2);
776: #else
777: d = (DCell)n1 * (DCell)n2;
778: #endif
779: :
780: 2dup 0< and >r
781: 2dup swap 0< and >r
782: um* r> - r> - ;
783:
784: um* ( u1 u2 -- ud ) core u_m_star
785: /* use u* as alias */
786: #ifdef BUGGY_LONG_LONG
787: ud = ummul(u1,u2);
788: #else
789: ud = (UDCell)u1 * (UDCell)u2;
790: #endif
791: :
792: >r >r 0 0 r> r> [ 8 cells ] literal 0
793: DO
794: over >r dup >r 0< and d2*+ drop
795: r> 2* r> swap
796: LOOP 2drop ;
797: : d2*+ ( ud n -- ud+n c )
798: over MINI
799: and >r >r 2dup d+ swap r> + swap r> ;
800:
801: um/mod ( ud u1 -- u2 u3 ) core u_m_slash_mod
802: ""ud=u3*u1+u2, u1>u2>=0""
803: #ifdef BUGGY_LONG_LONG
804: UDCell r = umdiv(ud,u1);
805: u2=r.hi;
806: u3=r.lo;
807: #else
808: u3 = ud/u1;
809: u2 = ud%u1;
810: #endif
811: :
812: 0 swap [ 8 cells 1 + ] literal 0
813: ?DO /modstep
814: LOOP drop swap 1 rshift or swap ;
815: : /modstep ( ud c R: u -- ud-?u c R: u )
816: >r over r@ u< 0= or IF r@ - 1 ELSE 0 THEN d2*+ r> ;
817: : d2*+ ( ud n -- ud+n c )
818: over MINI
819: and >r >r 2dup d+ swap r> + swap r> ;
820:
821: m+ ( d1 n -- d2 ) double m_plus
822: #ifdef BUGGY_LONG_LONG
823: d2.lo = d1.lo+n;
824: d2.hi = d1.hi - (n<0) + (d2.lo<d1.lo);
825: #else
826: d2 = d1+n;
827: #endif
828: :
829: s>d d+ ;
830:
831: d+ ( d1 d2 -- d ) double d_plus
832: #ifdef BUGGY_LONG_LONG
833: d.lo = d1.lo+d2.lo;
834: d.hi = d1.hi + d2.hi + (d.lo<d1.lo);
835: #else
836: d = d1+d2;
837: #endif
838: :
839: rot + >r tuck + swap over u> r> swap - ;
840:
841: d- ( d1 d2 -- d ) double d_minus
842: #ifdef BUGGY_LONG_LONG
843: d.lo = d1.lo - d2.lo;
844: d.hi = d1.hi-d2.hi-(d1.lo<d2.lo);
845: #else
846: d = d1-d2;
847: #endif
848: :
849: dnegate d+ ;
850:
851: dnegate ( d1 -- d2 ) double d_negate
852: /* use dminus as alias */
853: #ifdef BUGGY_LONG_LONG
854: d2 = dnegate(d1);
855: #else
856: d2 = -d1;
857: #endif
858: :
859: invert swap negate tuck 0= - ;
860:
861: d2* ( d1 -- d2 ) double d_two_star
862: ""Shift left by 1; also works on unsigned numbers""
863: #ifdef BUGGY_LONG_LONG
864: d2.lo = d1.lo<<1;
865: d2.hi = (d1.hi<<1) | (d1.lo>>(CELL_BITS-1));
866: #else
867: d2 = 2*d1;
868: #endif
869: :
870: 2dup d+ ;
871:
872: d2/ ( d1 -- d2 ) double d_two_slash
873: ""Arithmetic shift right by 1. For signed numbers this is a floored
874: division by 2.""
875: #ifdef BUGGY_LONG_LONG
876: d2.hi = d1.hi>>1;
877: d2.lo= (d1.lo>>1) | (d1.hi<<(CELL_BITS-1));
878: #else
879: d2 = d1>>1;
880: #endif
881: :
882: dup 1 and >r 2/ swap 2/ [ 1 8 cells 1- lshift 1- ] Literal and
883: r> IF [ 1 8 cells 1- lshift ] Literal + THEN swap ;
884:
885: and ( w1 w2 -- w ) core
886: w = w1&w2;
887:
888: or ( w1 w2 -- w ) core
889: w = w1|w2;
890: :
891: invert swap invert and invert ;
892:
893: xor ( w1 w2 -- w ) core x_or
894: w = w1^w2;
895:
896: invert ( w1 -- w2 ) core
897: w2 = ~w1;
898: :
899: MAXU xor ;
900:
901: rshift ( u1 n -- u2 ) core r_shift
902: ""Logical shift right by @i{n} bits.""
903: u2 = u1>>n;
904: :
905: 0 ?DO 2/ MAXI and LOOP ;
906:
907: lshift ( u1 n -- u2 ) core l_shift
908: u2 = u1<<n;
909: :
910: 0 ?DO 2* LOOP ;
911:
912: \g compare
913:
914: \ comparisons(prefix, args, prefix, arg1, arg2, wordsets...)
915: define(comparisons,
916: $1= ( $2 -- f ) $6 $3equals
917: f = FLAG($4==$5);
918: :
919: [ char $1x char 0 = [IF]
920: ] IF false ELSE true THEN [
921: [ELSE]
922: ] xor 0= [
923: [THEN] ] ;
924:
925: $1<> ( $2 -- f ) $7 $3not_equals
926: f = FLAG($4!=$5);
927: :
928: [ char $1x char 0 = [IF]
929: ] IF true ELSE false THEN [
930: [ELSE]
931: ] xor 0<> [
932: [THEN] ] ;
933:
934: $1< ( $2 -- f ) $8 $3less_than
935: f = FLAG($4<$5);
936: :
937: [ char $1x char 0 = [IF]
938: ] MINI and 0<> [
939: [ELSE] char $1x char u = [IF]
940: ] 2dup xor 0< IF nip ELSE - THEN 0< [
941: [ELSE]
942: ] MINI xor >r MINI xor r> u< [
943: [THEN]
944: [THEN] ] ;
945:
946: $1> ( $2 -- f ) $9 $3greater_than
947: f = FLAG($4>$5);
948: :
949: [ char $1x char 0 = [IF] ] negate [ [ELSE] ] swap [ [THEN] ]
950: $1< ;
951:
952: $1<= ( $2 -- f ) gforth $3less_or_equal
953: f = FLAG($4<=$5);
954: :
955: $1> 0= ;
956:
957: $1>= ( $2 -- f ) gforth $3greater_or_equal
958: f = FLAG($4>=$5);
959: :
960: [ char $1x char 0 = [IF] ] negate [ [ELSE] ] swap [ [THEN] ]
961: $1<= ;
962:
963: )
964:
965: comparisons(0, n, zero_, n, 0, core, core-ext, core, core-ext)
966: comparisons(, n1 n2, , n1, n2, core, core-ext, core, core)
967: comparisons(u, u1 u2, u_, u1, u2, gforth, gforth, core, core-ext)
968:
969: \ dcomparisons(prefix, args, prefix, arg1, arg2, wordsets...)
970: define(dcomparisons,
971: $1= ( $2 -- f ) $6 $3equals
972: #ifdef BUGGY_LONG_LONG
973: f = FLAG($4.lo==$5.lo && $4.hi==$5.hi);
974: #else
975: f = FLAG($4==$5);
976: #endif
977:
978: $1<> ( $2 -- f ) $7 $3not_equals
979: #ifdef BUGGY_LONG_LONG
980: f = FLAG($4.lo!=$5.lo || $4.hi!=$5.hi);
981: #else
982: f = FLAG($4!=$5);
983: #endif
984:
985: $1< ( $2 -- f ) $8 $3less_than
986: #ifdef BUGGY_LONG_LONG
987: f = FLAG($4.hi==$5.hi ? $4.lo<$5.lo : $4.hi<$5.hi);
988: #else
989: f = FLAG($4<$5);
990: #endif
991:
992: $1> ( $2 -- f ) $9 $3greater_than
993: #ifdef BUGGY_LONG_LONG
994: f = FLAG($4.hi==$5.hi ? $4.lo>$5.lo : $4.hi>$5.hi);
995: #else
996: f = FLAG($4>$5);
997: #endif
998:
999: $1<= ( $2 -- f ) gforth $3less_or_equal
1000: #ifdef BUGGY_LONG_LONG
1001: f = FLAG($4.hi==$5.hi ? $4.lo<=$5.lo : $4.hi<=$5.hi);
1002: #else
1003: f = FLAG($4<=$5);
1004: #endif
1005:
1006: $1>= ( $2 -- f ) gforth $3greater_or_equal
1007: #ifdef BUGGY_LONG_LONG
1008: f = FLAG($4.hi==$5.hi ? $4.lo>=$5.lo : $4.hi>=$5.hi);
1009: #else
1010: f = FLAG($4>=$5);
1011: #endif
1012:
1013: )
1014:
1015: \+dcomps
1016:
1017: dcomparisons(d, d1 d2, d_, d1, d2, double, gforth, double, gforth)
1018: dcomparisons(d0, d, d_zero_, d, DZERO, double, gforth, double, gforth)
1019: dcomparisons(du, ud1 ud2, d_u_, ud1, ud2, gforth, gforth, double-ext, gforth)
1020:
1021: \+
1022:
1023: within ( u1 u2 u3 -- f ) core-ext
1024: ""u2=<u1<u3 or: u3=<u2 and u1 is not in [u3,u2). This works for
1025: unsigned and signed numbers (but not a mixture). Another way to think
1026: about this word is to consider the numbers as a circle (wrapping
1027: around from @code{max-u} to 0 for unsigned, and from @code{max-n} to
1028: min-n for signed numbers); now consider the range from u2 towards
1029: increasing numbers up to and excluding u3 (giving an empty range if
1030: u2=u3); if u1 is in this range, @code{within} returns true.""
1031: f = FLAG(u1-u2 < u3-u2);
1032: :
1033: over - >r - r> u< ;
1034:
1035: \g stack
1036:
1037: useraddr ( #u -- a_addr ) new
1038: a_addr = (Cell *)(up+u);
1039:
1040: up! ( a_addr -- ) gforth up_store
1041: UP=up=(char *)a_addr;
1042: :
1043: up ! ;
1044: Variable UP
1045:
1046: sp@ ( -- a_addr ) gforth sp_fetch
1047: a_addr = sp+1;
1048:
1049: sp! ( a_addr -- ) gforth sp_store
1050: sp = a_addr;
1051: /* works with and without spTOS caching */
1052:
1053: rp@ ( -- a_addr ) gforth rp_fetch
1054: a_addr = rp;
1055:
1056: rp! ( a_addr -- ) gforth rp_store
1057: rp = a_addr;
1058:
1059: \+floating
1060:
1061: fp@ ( -- f_addr ) gforth fp_fetch
1062: f_addr = fp;
1063:
1064: fp! ( f_addr -- ) gforth fp_store
1065: fp = f_addr;
1066:
1067: \+
1068:
1069: >r ( w -- R:w ) core to_r
1070: :
1071: (>r) ;
1072: : (>r) rp@ cell+ @ rp@ ! rp@ cell+ ! ;
1073:
1074: r> ( R:w -- w ) core r_from
1075: :
1076: rp@ cell+ @ rp@ @ rp@ cell+ ! (rdrop) rp@ ! ;
1077: Create (rdrop) ' ;s A,
1078:
1079: rdrop ( R:w -- ) gforth
1080: :
1081: r> r> drop >r ;
1082:
1083: 2>r ( w1 w2 -- R:w1 R:w2 ) core-ext two_to_r
1084: :
1085: swap r> swap >r swap >r >r ;
1086:
1087: 2r> ( R:w1 R:w2 -- w1 w2 ) core-ext two_r_from
1088: :
1089: r> r> swap r> swap >r swap ;
1090:
1091: 2r@ ( R:w1 R:w2 -- R:w1 R:w2 w1 w2 ) core-ext two_r_fetch
1092: :
1093: i' j ;
1094:
1095: 2rdrop ( R:w1 R:w2 -- ) gforth two_r_drop
1096: :
1097: r> r> drop r> drop >r ;
1098:
1099: over ( w1 w2 -- w1 w2 w1 ) core
1100: :
1101: sp@ cell+ @ ;
1102:
1103: drop ( w -- ) core
1104: :
1105: IF THEN ;
1106:
1107: swap ( w1 w2 -- w2 w1 ) core
1108: :
1109: >r (swap) ! r> (swap) @ ;
1110: Variable (swap)
1111:
1112: dup ( w -- w w ) core dupe
1113: :
1114: sp@ @ ;
1115:
1116: rot ( w1 w2 w3 -- w2 w3 w1 ) core rote
1117: :
1118: [ defined? (swap) [IF] ]
1119: (swap) ! (rot) ! >r (rot) @ (swap) @ r> ;
1120: Variable (rot)
1121: [ELSE] ]
1122: >r swap r> swap ;
1123: [THEN]
1124:
1125: -rot ( w1 w2 w3 -- w3 w1 w2 ) gforth not_rote
1126: :
1127: rot rot ;
1128:
1129: nip ( w1 w2 -- w2 ) core-ext
1130: :
1131: swap drop ;
1132:
1133: tuck ( w1 w2 -- w2 w1 w2 ) core-ext
1134: :
1135: swap over ;
1136:
1137: ?dup ( w -- w ) core question_dupe
1138: ""Actually the stack effect is: @code{( w -- 0 | w w )}. It performs a
1139: @code{dup} if w is nonzero.""
1140: if (w!=0) {
1141: IF_spTOS(*sp-- = w;)
1142: #ifndef USE_TOS
1143: *--sp = w;
1144: #endif
1145: }
1146: :
1147: dup IF dup THEN ;
1148:
1149: pick ( u -- w ) core-ext
1150: ""Actually the stack effect is @code{ x0 ... xu u -- x0 ... xu x0 }.""
1151: w = sp[u+1];
1152: :
1153: 1+ cells sp@ + @ ;
1154:
1155: 2drop ( w1 w2 -- ) core two_drop
1156: :
1157: drop drop ;
1158:
1159: 2dup ( w1 w2 -- w1 w2 w1 w2 ) core two_dupe
1160: :
1161: over over ;
1162:
1163: 2over ( w1 w2 w3 w4 -- w1 w2 w3 w4 w1 w2 ) core two_over
1164: :
1165: 3 pick 3 pick ;
1166:
1167: 2swap ( w1 w2 w3 w4 -- w3 w4 w1 w2 ) core two_swap
1168: :
1169: rot >r rot r> ;
1170:
1171: 2rot ( w1 w2 w3 w4 w5 w6 -- w3 w4 w5 w6 w1 w2 ) double-ext two_rote
1172: :
1173: >r >r 2swap r> r> 2swap ;
1174:
1175: 2nip ( w1 w2 w3 w4 -- w3 w4 ) gforth two_nip
1176: :
1177: 2swap 2drop ;
1178:
1179: 2tuck ( w1 w2 w3 w4 -- w3 w4 w1 w2 w3 w4 ) gforth two_tuck
1180: :
1181: 2swap 2over ;
1182:
1183: \ toggle is high-level: 0.11/0.42%
1184:
1185: \g memory
1186:
1187: @ ( a_addr -- w ) core fetch
1188: ""@i{w} is the cell stored at @i{a_addr}.""
1189: w = *a_addr;
1190:
1191: \ lit@ / lit_fetch = lit @
1192:
1193: lit@ ( #a_addr -- w ) new lit_fetch
1194: w = *a_addr;
1195:
1196: ! ( w a_addr -- ) core store
1197: ""Store @i{w} into the cell at @i{a-addr}.""
1198: *a_addr = w;
1199:
1200: +! ( n a_addr -- ) core plus_store
1201: ""Add @i{n} to the cell at @i{a-addr}.""
1202: *a_addr += n;
1203: :
1204: tuck @ + swap ! ;
1205:
1206: c@ ( c_addr -- c ) core c_fetch
1207: ""@i{c} is the char stored at @i{c_addr}.""
1208: c = *c_addr;
1209: :
1210: [ bigendian [IF] ]
1211: [ cell>bit 4 = [IF] ]
1212: dup [ 0 cell - ] Literal and @ swap 1 and
1213: IF $FF and ELSE 8>> THEN ;
1214: [ [ELSE] ]
1215: dup [ cell 1- ] literal and
1216: tuck - @ swap [ cell 1- ] literal xor
1217: 0 ?DO 8>> LOOP $FF and
1218: [ [THEN] ]
1219: [ [ELSE] ]
1220: [ cell>bit 4 = [IF] ]
1221: dup [ 0 cell - ] Literal and @ swap 1 and
1222: IF 8>> ELSE $FF and THEN
1223: [ [ELSE] ]
1224: dup [ cell 1- ] literal and
1225: tuck - @ swap
1226: 0 ?DO 8>> LOOP 255 and
1227: [ [THEN] ]
1228: [ [THEN] ]
1229: ;
1230: : 8>> 2/ 2/ 2/ 2/ 2/ 2/ 2/ 2/ ;
1231:
1232: c! ( c c_addr -- ) core c_store
1233: ""Store @i{c} into the char at @i{c-addr}.""
1234: *c_addr = c;
1235: :
1236: [ bigendian [IF] ]
1237: [ cell>bit 4 = [IF] ]
1238: tuck 1 and IF $FF and ELSE 8<< THEN >r
1239: dup -2 and @ over 1 and cells masks + @ and
1240: r> or swap -2 and ! ;
1241: Create masks $00FF , $FF00 ,
1242: [ELSE] ]
1243: dup [ cell 1- ] literal and dup
1244: [ cell 1- ] literal xor >r
1245: - dup @ $FF r@ 0 ?DO 8<< LOOP invert and
1246: rot $FF and r> 0 ?DO 8<< LOOP or swap ! ;
1247: [THEN]
1248: [ELSE] ]
1249: [ cell>bit 4 = [IF] ]
1250: tuck 1 and IF 8<< ELSE $FF and THEN >r
1251: dup -2 and @ over 1 and cells masks + @ and
1252: r> or swap -2 and ! ;
1253: Create masks $FF00 , $00FF ,
1254: [ELSE] ]
1255: dup [ cell 1- ] literal and dup >r
1256: - dup @ $FF r@ 0 ?DO 8<< LOOP invert and
1257: rot $FF and r> 0 ?DO 8<< LOOP or swap ! ;
1258: [THEN]
1259: [THEN]
1260: : 8<< 2* 2* 2* 2* 2* 2* 2* 2* ;
1261:
1262: 2! ( w1 w2 a_addr -- ) core two_store
1263: ""Store @i{w2} into the cell at @i{c-addr} and @i{w1} into the next cell.""
1264: a_addr[0] = w2;
1265: a_addr[1] = w1;
1266: :
1267: tuck ! cell+ ! ;
1268:
1269: 2@ ( a_addr -- w1 w2 ) core two_fetch
1270: ""@i{w2} is the content of the cell stored at @i{a-addr}, @i{w1} is
1271: the content of the next cell.""
1272: w2 = a_addr[0];
1273: w1 = a_addr[1];
1274: :
1275: dup cell+ @ swap @ ;
1276:
1277: cell+ ( a_addr1 -- a_addr2 ) core cell_plus
1278: ""@code{1 cells +}""
1279: a_addr2 = a_addr1+1;
1280: :
1281: cell + ;
1282:
1283: cells ( n1 -- n2 ) core
1284: "" @i{n2} is the number of address units of @i{n1} cells.""
1285: n2 = n1 * sizeof(Cell);
1286: :
1287: [ cell
1288: 2/ dup [IF] ] 2* [ [THEN]
1289: 2/ dup [IF] ] 2* [ [THEN]
1290: 2/ dup [IF] ] 2* [ [THEN]
1291: 2/ dup [IF] ] 2* [ [THEN]
1292: drop ] ;
1293:
1294: char+ ( c_addr1 -- c_addr2 ) core char_plus
1295: ""@code{1 chars +}.""
1296: c_addr2 = c_addr1 + 1;
1297: :
1298: 1+ ;
1299:
1300: (chars) ( n1 -- n2 ) gforth paren_chars
1301: n2 = n1 * sizeof(Char);
1302: :
1303: ;
1304:
1305: count ( c_addr1 -- c_addr2 u ) core
1306: ""@i{c-addr2} is the first character and @i{u} the length of the
1307: counted string at @i{c-addr1}.""
1308: u = *c_addr1;
1309: c_addr2 = c_addr1+1;
1310: :
1311: dup 1+ swap c@ ;
1312:
1313: \g compiler
1314:
1315: (listlfind) ( c_addr u longname1 -- longname2 ) new paren_listlfind
1316: longname2=listlfind(c_addr, u, longname1);
1317: :
1318: BEGIN dup WHILE (findl-samelen) dup WHILE
1319: >r 2dup r@ cell+ cell+ capscomp 0=
1320: IF 2drop r> EXIT THEN
1321: r> @
1322: REPEAT THEN nip nip ;
1323: : (findl-samelen) ( u longname1 -- u longname2/0 )
1324: BEGIN 2dup cell+ @ lcount-mask and <> WHILE @ dup 0= UNTIL THEN ;
1325:
1326: \+hash
1327:
1328: (hashlfind) ( c_addr u a_addr -- longname2 ) new paren_hashlfind
1329: longname2 = hashlfind(c_addr, u, a_addr);
1330: :
1331: BEGIN dup WHILE
1332: 2@ >r >r dup r@ cell+ @ lcount-mask and =
1333: IF 2dup r@ cell+ cell+ capscomp 0=
1334: IF 2drop r> rdrop EXIT THEN THEN
1335: rdrop r>
1336: REPEAT nip nip ;
1337:
1338: (tablelfind) ( c_addr u a_addr -- longname2 ) new paren_tablelfind
1339: ""A case-sensitive variant of @code{(hashfind)}""
1340: longname2 = tablelfind(c_addr, u, a_addr);
1341: :
1342: BEGIN dup WHILE
1343: 2@ >r >r dup r@ cell+ @ lcount-mask and =
1344: IF 2dup r@ cell+ cell+ -text 0=
1345: IF 2drop r> rdrop EXIT THEN THEN
1346: rdrop r>
1347: REPEAT nip nip ;
1348:
1349: (hashkey1) ( c_addr u ubits -- ukey ) gforth paren_hashkey1
1350: ""ukey is the hash key for the string c_addr u fitting in ubits bits""
1351: ukey = hashkey1(c_addr, u, ubits);
1352: :
1353: dup rot-values + c@ over 1 swap lshift 1- >r
1354: tuck - 2swap r> 0 2swap bounds
1355: ?DO dup 4 pick lshift swap 3 pick rshift or
1356: I c@ toupper xor
1357: over and LOOP
1358: nip nip nip ;
1359: Create rot-values
1360: 5 c, 0 c, 1 c, 2 c, 3 c, 4 c, 5 c, 5 c, 5 c, 5 c,
1361: 3 c, 5 c, 5 c, 5 c, 5 c, 7 c, 5 c, 5 c, 5 c, 5 c,
1362: 7 c, 5 c, 5 c, 5 c, 5 c, 6 c, 5 c, 5 c, 5 c, 5 c,
1363: 7 c, 5 c, 5 c,
1364:
1365: \+
1366:
1367: (parse-white) ( c_addr1 u1 -- c_addr2 u2 ) gforth paren_parse_white
1368: struct Cellpair r=parse_white(c_addr1, u1);
1369: c_addr2 = (Char *)(r.n1);
1370: u2 = r.n2;
1371: :
1372: BEGIN dup WHILE over c@ bl <= WHILE 1 /string
1373: REPEAT THEN 2dup
1374: BEGIN dup WHILE over c@ bl > WHILE 1 /string
1375: REPEAT THEN nip - ;
1376:
1377: aligned ( c_addr -- a_addr ) core
1378: "" @i{a-addr} is the first aligned address greater than or equal to @i{c-addr}.""
1379: a_addr = (Cell *)((((Cell)c_addr)+(sizeof(Cell)-1))&(-sizeof(Cell)));
1380: :
1381: [ cell 1- ] Literal + [ -1 cells ] Literal and ;
1382:
1383: faligned ( c_addr -- f_addr ) float f_aligned
1384: "" @i{f-addr} is the first float-aligned address greater than or equal to @i{c-addr}.""
1385: f_addr = (Float *)((((Cell)c_addr)+(sizeof(Float)-1))&(-sizeof(Float)));
1386: :
1387: [ 1 floats 1- ] Literal + [ -1 floats ] Literal and ;
1388:
1389: \ threading stuff is currently only interesting if we have a compiler
1390: \fhas? standardthreading has? compiler and [IF]
1391: threading-method ( -- n ) gforth threading_method
1392: ""0 if the engine is direct threaded. Note that this may change during
1393: the lifetime of an image.""
1394: #if defined(DOUBLY_INDIRECT)
1395: n=2;
1396: #else
1397: # if defined(DIRECT_THREADED)
1398: n=0;
1399: # else
1400: n=1;
1401: # endif
1402: #endif
1403: :
1404: 1 ;
1405:
1406: \f[THEN]
1407:
1408: \g hostos
1409:
1410: key-file ( wfileid -- n ) gforth paren_key_file
1411: #ifdef HAS_FILE
1412: fflush(stdout);
1413: n = key((FILE*)wfileid);
1414: #else
1415: n = key(stdin);
1416: #endif
1417:
1418: key?-file ( wfileid -- n ) facility key_q_file
1419: #ifdef HAS_FILE
1420: fflush(stdout);
1421: n = key_query((FILE*)wfileid);
1422: #else
1423: n = key_query(stdin);
1424: #endif
1425:
1426: \+os
1427:
1428: stdin ( -- wfileid ) gforth
1429: wfileid = (Cell)stdin;
1430:
1431: stdout ( -- wfileid ) gforth
1432: wfileid = (Cell)stdout;
1433:
1434: stderr ( -- wfileid ) gforth
1435: wfileid = (Cell)stderr;
1436:
1437: form ( -- urows ucols ) gforth
1438: ""The number of lines and columns in the terminal. These numbers may change
1439: with the window size.""
1440: /* we could block SIGWINCH here to get a consistent size, but I don't
1441: think this is necessary or always beneficial */
1442: urows=rows;
1443: ucols=cols;
1444:
1445: flush-icache ( c_addr u -- ) gforth flush_icache
1446: ""Make sure that the instruction cache of the processor (if there is
1447: one) does not contain stale data at @i{c-addr} and @i{u} bytes
1448: afterwards. @code{END-CODE} performs a @code{flush-icache}
1449: automatically. Caveat: @code{flush-icache} might not work on your
1450: installation; this is usually the case if direct threading is not
1451: supported on your machine (take a look at your @file{machine.h}) and
1452: your machine has a separate instruction cache. In such cases,
1453: @code{flush-icache} does nothing instead of flushing the instruction
1454: cache.""
1455: FLUSH_ICACHE(c_addr,u);
1456:
1457: (bye) ( n -- ) gforth paren_bye
1458: SUPER_END;
1459: return (Label *)n;
1460:
1461: (system) ( c_addr u -- wretval wior ) gforth paren_system
1462: #ifndef MSDOS
1463: int old_tp=terminal_prepped;
1464: deprep_terminal();
1465: #endif
1466: wretval=system(cstr(c_addr,u,1)); /* ~ expansion on first part of string? */
1467: wior = IOR(wretval==-1 || (wretval==127 && errno != 0));
1468: #ifndef MSDOS
1469: if (old_tp)
1470: prep_terminal();
1471: #endif
1472:
1473: getenv ( c_addr1 u1 -- c_addr2 u2 ) gforth
1474: ""The string @i{c-addr1 u1} specifies an environment variable. The string @i{c-addr2 u2}
1475: is the host operating system's expansion of that environment variable. If the
1476: environment variable does not exist, @i{c-addr2 u2} specifies a string 0 characters
1477: in length.""
1478: /* close ' to keep fontify happy */
1479: c_addr2 = getenv(cstr(c_addr1,u1,1));
1480: u2 = (c_addr2 == NULL ? 0 : strlen(c_addr2));
1481:
1482: open-pipe ( c_addr u wfam -- wfileid wior ) gforth open_pipe
1483: wfileid=(Cell)popen(cstr(c_addr,u,1),pfileattr[wfam]); /* ~ expansion of 1st arg? */
1484: wior = IOR(wfileid==0); /* !! the man page says that errno is not set reliably */
1485:
1486: close-pipe ( wfileid -- wretval wior ) gforth close_pipe
1487: wretval = pclose((FILE *)wfileid);
1488: wior = IOR(wretval==-1);
1489:
1490: time&date ( -- nsec nmin nhour nday nmonth nyear ) facility-ext time_and_date
1491: ""Report the current time of day. Seconds, minutes and hours are numbered from 0.
1492: Months are numbered from 1.""
1493: struct timeval time1;
1494: struct timezone zone1;
1495: struct tm *ltime;
1496: gettimeofday(&time1,&zone1);
1497: /* !! Single Unix specification:
1498: If tzp is not a null pointer, the behaviour is unspecified. */
1499: ltime=localtime((time_t *)&time1.tv_sec);
1500: nyear =ltime->tm_year+1900;
1501: nmonth=ltime->tm_mon+1;
1502: nday =ltime->tm_mday;
1503: nhour =ltime->tm_hour;
1504: nmin =ltime->tm_min;
1505: nsec =ltime->tm_sec;
1506:
1507: ms ( n -- ) facility-ext
1508: ""Wait at least @i{n} milli-second.""
1509: struct timeval timeout;
1510: timeout.tv_sec=n/1000;
1511: timeout.tv_usec=1000*(n%1000);
1512: (void)select(0,0,0,0,&timeout);
1513:
1514: allocate ( u -- a_addr wior ) memory
1515: ""Allocate @i{u} address units of contiguous data space. The initial
1516: contents of the data space is undefined. If the allocation is successful,
1517: @i{a-addr} is the start address of the allocated region and @i{wior}
1518: is 0. If the allocation fails, @i{a-addr} is undefined and @i{wior}
1519: is a non-zero I/O result code.""
1520: a_addr = (Cell *)malloc(u?u:1);
1521: wior = IOR(a_addr==NULL);
1522:
1523: free ( a_addr -- wior ) memory
1524: ""Return the region of data space starting at @i{a-addr} to the system.
1525: The region must originally have been obtained using @code{allocate} or
1526: @code{resize}. If the operational is successful, @i{wior} is 0.
1527: If the operation fails, @i{wior} is a non-zero I/O result code.""
1528: free(a_addr);
1529: wior = 0;
1530:
1531: resize ( a_addr1 u -- a_addr2 wior ) memory
1532: ""Change the size of the allocated area at @i{a-addr1} to @i{u}
1533: address units, possibly moving the contents to a different
1534: area. @i{a-addr2} is the address of the resulting area.
1535: If the operation is successful, @i{wior} is 0.
1536: If the operation fails, @i{wior} is a non-zero
1537: I/O result code. If @i{a-addr1} is 0, Gforth's (but not the Standard)
1538: @code{resize} @code{allocate}s @i{u} address units.""
1539: /* the following check is not necessary on most OSs, but it is needed
1540: on SunOS 4.1.2. */
1541: /* close ' to keep fontify happy */
1542: if (a_addr1==NULL)
1543: a_addr2 = (Cell *)malloc(u);
1544: else
1545: a_addr2 = (Cell *)realloc(a_addr1, u);
1546: wior = IOR(a_addr2==NULL); /* !! Define a return code */
1547:
1548: strerror ( n -- c_addr u ) gforth
1549: c_addr = strerror(n);
1550: u = strlen(c_addr);
1551:
1552: strsignal ( n -- c_addr u ) gforth
1553: c_addr = strsignal(n);
1554: u = strlen(c_addr);
1555:
1556: call-c ( w -- ) gforth call_c
1557: ""Call the C function pointed to by @i{w}. The C function has to
1558: access the stack itself. The stack pointers are exported in the global
1559: variables @code{SP} and @code{FP}.""
1560: /* This is a first attempt at support for calls to C. This may change in
1561: the future */
1562: IF_fpTOS(fp[0]=fpTOS);
1563: FP=fp;
1564: SP=sp;
1565: ((void (*)())w)();
1566: sp=SP;
1567: fp=FP;
1568: IF_spTOS(spTOS=sp[0]);
1569: IF_fpTOS(fpTOS=fp[0]);
1570:
1571: \+
1572: \+file
1573:
1574: close-file ( wfileid -- wior ) file close_file
1575: wior = IOR(fclose((FILE *)wfileid)==EOF);
1576:
1577: open-file ( c_addr u wfam -- wfileid wior ) file open_file
1578: wfileid = (Cell)fopen(tilde_cstr(c_addr, u, 1), fileattr[wfam]);
1579: wior = IOR(wfileid == 0);
1580:
1581: create-file ( c_addr u wfam -- wfileid wior ) file create_file
1582: Cell fd;
1583: fd = open(tilde_cstr(c_addr, u, 1), O_CREAT|O_TRUNC|ufileattr[wfam], 0666);
1584: if (fd != -1) {
1585: wfileid = (Cell)fdopen(fd, fileattr[wfam]);
1586: wior = IOR(wfileid == 0);
1587: } else {
1588: wfileid = 0;
1589: wior = IOR(1);
1590: }
1591:
1592: delete-file ( c_addr u -- wior ) file delete_file
1593: wior = IOR(unlink(tilde_cstr(c_addr, u, 1))==-1);
1594:
1595: rename-file ( c_addr1 u1 c_addr2 u2 -- wior ) file-ext rename_file
1596: ""Rename file @i{c_addr1 u1} to new name @i{c_addr2 u2}""
1597: wior = rename_file(c_addr1, u1, c_addr2, u2);
1598:
1599: file-position ( wfileid -- ud wior ) file file_position
1600: /* !! use tell and lseek? */
1601: ud = OFF2UD(ftello((FILE *)wfileid));
1602: wior = IOR(UD2OFF(ud)==-1);
1603:
1604: reposition-file ( ud wfileid -- wior ) file reposition_file
1605: wior = IOR(fseeko((FILE *)wfileid, UD2OFF(ud), SEEK_SET)==-1);
1606:
1607: file-size ( wfileid -- ud wior ) file file_size
1608: struct stat buf;
1609: wior = IOR(fstat(fileno((FILE *)wfileid), &buf)==-1);
1610: ud = OFF2UD(buf.st_size);
1611:
1612: resize-file ( ud wfileid -- wior ) file resize_file
1613: wior = IOR(ftruncate(fileno((FILE *)wfileid), UD2OFF(ud))==-1);
1614:
1615: read-file ( c_addr u1 wfileid -- u2 wior ) file read_file
1616: /* !! fread does not guarantee enough */
1617: u2 = fread(c_addr, sizeof(Char), u1, (FILE *)wfileid);
1618: wior = FILEIO(u2<u1 && ferror((FILE *)wfileid));
1619: /* !! is the value of ferror errno-compatible? */
1620: if (wior)
1621: clearerr((FILE *)wfileid);
1622:
1623: (read-line) ( c_addr u1 wfileid -- u2 flag u3 wior ) file paren_read_line
1624: struct Cellquad r = read_line(c_addr, u1, wfileid);
1625: u2 = r.n1;
1626: flag = r.n2;
1627: u3 = r.n3;
1628: wior = r.n4;
1629:
1630: \+
1631:
1632: write-file ( c_addr u1 wfileid -- wior ) file write_file
1633: /* !! fwrite does not guarantee enough */
1634: #ifdef HAS_FILE
1635: {
1636: UCell u2 = fwrite(c_addr, sizeof(Char), u1, (FILE *)wfileid);
1637: wior = FILEIO(u2<u1 && ferror((FILE *)wfileid));
1638: if (wior)
1639: clearerr((FILE *)wfileid);
1640: }
1641: #else
1642: TYPE(c_addr, u1);
1643: #endif
1644:
1645: emit-file ( c wfileid -- wior ) gforth emit_file
1646: #ifdef HAS_FILE
1647: wior = FILEIO(putc(c, (FILE *)wfileid)==EOF);
1648: if (wior)
1649: clearerr((FILE *)wfileid);
1650: #else
1651: PUTC(c);
1652: #endif
1653:
1654: \+file
1655:
1656: flush-file ( wfileid -- wior ) file-ext flush_file
1657: wior = IOR(fflush((FILE *) wfileid)==EOF);
1658:
1659: file-status ( c_addr u -- wfam wior ) file-ext file_status
1660: struct Cellpair r = file_status(c_addr, u);
1661: wfam = r.n1;
1662: wior = r.n2;
1663:
1664: file-eof? ( wfileid -- flag ) gforth file_eof_query
1665: flag = FLAG(feof((FILE *) wfileid));
1666:
1667: open-dir ( c_addr u -- wdirid wior ) gforth open_dir
1668: ""Open the directory specified by @i{c-addr, u}
1669: and return @i{dir-id} for futher access to it.""
1670: wdirid = (Cell)opendir(tilde_cstr(c_addr, u, 1));
1671: wior = IOR(wdirid == 0);
1672:
1673: read-dir ( c_addr u1 wdirid -- u2 flag wior ) gforth read_dir
1674: ""Attempt to read the next entry from the directory specified
1675: by @i{dir-id} to the buffer of length @i{u1} at address @i{c-addr}.
1676: If the attempt fails because there is no more entries,
1677: @i{ior}=0, @i{flag}=0, @i{u2}=0, and the buffer is unmodified.
1678: If the attempt to read the next entry fails because of any other reason,
1679: return @i{ior}<>0.
1680: If the attempt succeeds, store file name to the buffer at @i{c-addr}
1681: and return @i{ior}=0, @i{flag}=true and @i{u2} equal to the size of the file name.
1682: If the length of the file name is greater than @i{u1},
1683: store first @i{u1} characters from file name into the buffer and
1684: indicate "name too long" with @i{ior}, @i{flag}=true, and @i{u2}=@i{u1}.""
1685: struct dirent * dent;
1686: dent = readdir((DIR *)wdirid);
1687: wior = 0;
1688: flag = -1;
1689: if(dent == NULL) {
1690: u2 = 0;
1691: flag = 0;
1692: } else {
1693: u2 = strlen(dent->d_name);
1694: if(u2 > u1) {
1695: u2 = u1;
1696: wior = -512-ENAMETOOLONG;
1697: }
1698: memmove(c_addr, dent->d_name, u2);
1699: }
1700:
1701: close-dir ( wdirid -- wior ) gforth close_dir
1702: ""Close the directory specified by @i{dir-id}.""
1703: wior = IOR(closedir((DIR *)wdirid));
1704:
1705: filename-match ( c_addr1 u1 c_addr2 u2 -- flag ) gforth match_file
1706: char * string = cstr(c_addr1, u1, 1);
1707: char * pattern = cstr(c_addr2, u2, 0);
1708: flag = FLAG(!fnmatch(pattern, string, 0));
1709:
1710: \+
1711:
1712: newline ( -- c_addr u ) gforth
1713: ""String containing the newline sequence of the host OS""
1714: char newline[] = {
1715: #if DIRSEP=='/'
1716: /* Unix */
1717: '\n'
1718: #else
1719: /* DOS, Win, OS/2 */
1720: '\r','\n'
1721: #endif
1722: };
1723: c_addr=newline;
1724: u=sizeof(newline);
1725: :
1726: "newline count ;
1727: Create "newline e? crlf [IF] 2 c, $0D c, [ELSE] 1 c, [THEN] $0A c,
1728:
1729: \+os
1730:
1731: utime ( -- dtime ) gforth
1732: ""Report the current time in microseconds since some epoch.""
1733: struct timeval time1;
1734: gettimeofday(&time1,NULL);
1735: dtime = timeval2us(&time1);
1736:
1737: cputime ( -- duser dsystem ) gforth
1738: ""duser and dsystem are the respective user- and system-level CPU
1739: times used since the start of the Forth system (excluding child
1740: processes), in microseconds (the granularity may be much larger,
1741: however). On platforms without the getrusage call, it reports elapsed
1742: time (since some epoch) for duser and 0 for dsystem.""
1743: #ifdef HAVE_GETRUSAGE
1744: struct rusage usage;
1745: getrusage(RUSAGE_SELF, &usage);
1746: duser = timeval2us(&usage.ru_utime);
1747: dsystem = timeval2us(&usage.ru_stime);
1748: #else
1749: struct timeval time1;
1750: gettimeofday(&time1,NULL);
1751: duser = timeval2us(&time1);
1752: #ifndef BUGGY_LONG_LONG
1753: dsystem = (DCell)0;
1754: #else
1755: dsystem=(DCell){0,0};
1756: #endif
1757: #endif
1758:
1759: \+
1760:
1761: \+floating
1762:
1763: \g floating
1764:
1765: comparisons(f, r1 r2, f_, r1, r2, gforth, gforth, float, gforth)
1766: comparisons(f0, r, f_zero_, r, 0., float, gforth, float, gforth)
1767:
1768: d>f ( d -- r ) float d_to_f
1769: #ifdef BUGGY_LONG_LONG
1770: extern double ldexp(double x, int exp);
1771: if (d.hi<0) {
1772: DCell d2=dnegate(d);
1773: r = -(ldexp((Float)d2.hi,CELL_BITS) + (Float)d2.lo);
1774: } else
1775: r = ldexp((Float)d.hi,CELL_BITS) + (Float)d.lo;
1776: #else
1777: r = d;
1778: #endif
1779:
1780: f>d ( r -- d ) float f_to_d
1781: extern DCell double2ll(Float r);
1782: d = double2ll(r);
1783:
1784: f! ( r f_addr -- ) float f_store
1785: ""Store @i{r} into the float at address @i{f-addr}.""
1786: *f_addr = r;
1787:
1788: f@ ( f_addr -- r ) float f_fetch
1789: ""@i{r} is the float at address @i{f-addr}.""
1790: r = *f_addr;
1791:
1792: df@ ( df_addr -- r ) float-ext d_f_fetch
1793: ""Fetch the double-precision IEEE floating-point value @i{r} from the address @i{df-addr}.""
1794: #ifdef IEEE_FP
1795: r = *df_addr;
1796: #else
1797: !! df@
1798: #endif
1799:
1800: df! ( r df_addr -- ) float-ext d_f_store
1801: ""Store @i{r} as double-precision IEEE floating-point value to the
1802: address @i{df-addr}.""
1803: #ifdef IEEE_FP
1804: *df_addr = r;
1805: #else
1806: !! df!
1807: #endif
1808:
1809: sf@ ( sf_addr -- r ) float-ext s_f_fetch
1810: ""Fetch the single-precision IEEE floating-point value @i{r} from the address @i{sf-addr}.""
1811: #ifdef IEEE_FP
1812: r = *sf_addr;
1813: #else
1814: !! sf@
1815: #endif
1816:
1817: sf! ( r sf_addr -- ) float-ext s_f_store
1818: ""Store @i{r} as single-precision IEEE floating-point value to the
1819: address @i{sf-addr}.""
1820: #ifdef IEEE_FP
1821: *sf_addr = r;
1822: #else
1823: !! sf!
1824: #endif
1825:
1826: f+ ( r1 r2 -- r3 ) float f_plus
1827: r3 = r1+r2;
1828:
1829: f- ( r1 r2 -- r3 ) float f_minus
1830: r3 = r1-r2;
1831:
1832: f* ( r1 r2 -- r3 ) float f_star
1833: r3 = r1*r2;
1834:
1835: f/ ( r1 r2 -- r3 ) float f_slash
1836: r3 = r1/r2;
1837:
1838: f** ( r1 r2 -- r3 ) float-ext f_star_star
1839: ""@i{r3} is @i{r1} raised to the @i{r2}th power.""
1840: r3 = pow(r1,r2);
1841:
1842: fnegate ( r1 -- r2 ) float f_negate
1843: r2 = - r1;
1844:
1845: fdrop ( r -- ) float f_drop
1846:
1847: fdup ( r -- r r ) float f_dupe
1848:
1849: fswap ( r1 r2 -- r2 r1 ) float f_swap
1850:
1851: fover ( r1 r2 -- r1 r2 r1 ) float f_over
1852:
1853: frot ( r1 r2 r3 -- r2 r3 r1 ) float f_rote
1854:
1855: fnip ( r1 r2 -- r2 ) gforth f_nip
1856:
1857: ftuck ( r1 r2 -- r2 r1 r2 ) gforth f_tuck
1858:
1859: float+ ( f_addr1 -- f_addr2 ) float float_plus
1860: ""@code{1 floats +}.""
1861: f_addr2 = f_addr1+1;
1862:
1863: floats ( n1 -- n2 ) float
1864: ""@i{n2} is the number of address units of @i{n1} floats.""
1865: n2 = n1*sizeof(Float);
1866:
1867: floor ( r1 -- r2 ) float
1868: ""Round towards the next smaller integral value, i.e., round toward negative infinity.""
1869: /* !! unclear wording */
1870: r2 = floor(r1);
1871:
1872: fround ( r1 -- r2 ) gforth f_round
1873: ""Round to the nearest integral value.""
1874: r2 = rint(r1);
1875:
1876: fmax ( r1 r2 -- r3 ) float f_max
1877: if (r1<r2)
1878: r3 = r2;
1879: else
1880: r3 = r1;
1881:
1882: fmin ( r1 r2 -- r3 ) float f_min
1883: if (r1<r2)
1884: r3 = r1;
1885: else
1886: r3 = r2;
1887:
1888: represent ( r c_addr u -- n f1 f2 ) float
1889: char *sig;
1890: size_t siglen;
1891: int flag;
1892: int decpt;
1893: sig=ecvt(r, u, &decpt, &flag);
1894: n=(r==0. ? 1 : decpt);
1895: f1=FLAG(flag!=0);
1896: f2=FLAG(isdigit((unsigned)(sig[0]))!=0);
1897: siglen=strlen(sig);
1898: if (siglen>u) /* happens in glibc-2.1.3 if 999.. is rounded up */
1899: siglen=u;
1900: memcpy(c_addr,sig,siglen);
1901: memset(c_addr+siglen,f2?'0':' ',u-siglen);
1902:
1903: >float ( c_addr u -- flag ) float to_float
1904: ""Actual stack effect: ( c_addr u -- r t | f ). Attempt to convert the
1905: character string @i{c-addr u} to internal floating-point
1906: representation. If the string represents a valid floating-point number
1907: @i{r} is placed on the floating-point stack and @i{flag} is
1908: true. Otherwise, @i{flag} is false. A string of blanks is a special
1909: case and represents the floating-point number 0.""
1910: Float r;
1911: flag = to_float(c_addr, u, &r);
1912: if (flag) {
1913: IF_fpTOS(fp[0] = fpTOS);
1914: fp += -1;
1915: fpTOS = r;
1916: }
1917:
1918: fabs ( r1 -- r2 ) float-ext f_abs
1919: r2 = fabs(r1);
1920:
1921: facos ( r1 -- r2 ) float-ext f_a_cos
1922: r2 = acos(r1);
1923:
1924: fasin ( r1 -- r2 ) float-ext f_a_sine
1925: r2 = asin(r1);
1926:
1927: fatan ( r1 -- r2 ) float-ext f_a_tan
1928: r2 = atan(r1);
1929:
1930: fatan2 ( r1 r2 -- r3 ) float-ext f_a_tan_two
1931: ""@i{r1/r2}=tan(@i{r3}). ANS Forth does not require, but probably
1932: intends this to be the inverse of @code{fsincos}. In gforth it is.""
1933: r3 = atan2(r1,r2);
1934:
1935: fcos ( r1 -- r2 ) float-ext f_cos
1936: r2 = cos(r1);
1937:
1938: fexp ( r1 -- r2 ) float-ext f_e_x_p
1939: r2 = exp(r1);
1940:
1941: fexpm1 ( r1 -- r2 ) float-ext f_e_x_p_m_one
1942: ""@i{r2}=@i{e}**@i{r1}@minus{}1""
1943: #ifdef HAVE_EXPM1
1944: extern double
1945: #ifdef NeXT
1946: const
1947: #endif
1948: expm1(double);
1949: r2 = expm1(r1);
1950: #else
1951: r2 = exp(r1)-1.;
1952: #endif
1953:
1954: fln ( r1 -- r2 ) float-ext f_l_n
1955: r2 = log(r1);
1956:
1957: flnp1 ( r1 -- r2 ) float-ext f_l_n_p_one
1958: ""@i{r2}=ln(@i{r1}+1)""
1959: #ifdef HAVE_LOG1P
1960: extern double
1961: #ifdef NeXT
1962: const
1963: #endif
1964: log1p(double);
1965: r2 = log1p(r1);
1966: #else
1967: r2 = log(r1+1.);
1968: #endif
1969:
1970: flog ( r1 -- r2 ) float-ext f_log
1971: ""The decimal logarithm.""
1972: r2 = log10(r1);
1973:
1974: falog ( r1 -- r2 ) float-ext f_a_log
1975: ""@i{r2}=10**@i{r1}""
1976: extern double pow10(double);
1977: r2 = pow10(r1);
1978:
1979: fsin ( r1 -- r2 ) float-ext f_sine
1980: r2 = sin(r1);
1981:
1982: fsincos ( r1 -- r2 r3 ) float-ext f_sine_cos
1983: ""@i{r2}=sin(@i{r1}), @i{r3}=cos(@i{r1})""
1984: r2 = sin(r1);
1985: r3 = cos(r1);
1986:
1987: fsqrt ( r1 -- r2 ) float-ext f_square_root
1988: r2 = sqrt(r1);
1989:
1990: ftan ( r1 -- r2 ) float-ext f_tan
1991: r2 = tan(r1);
1992: :
1993: fsincos f/ ;
1994:
1995: fsinh ( r1 -- r2 ) float-ext f_cinch
1996: r2 = sinh(r1);
1997: :
1998: fexpm1 fdup fdup 1. d>f f+ f/ f+ f2/ ;
1999:
2000: fcosh ( r1 -- r2 ) float-ext f_cosh
2001: r2 = cosh(r1);
2002: :
2003: fexp fdup 1/f f+ f2/ ;
2004:
2005: ftanh ( r1 -- r2 ) float-ext f_tan_h
2006: r2 = tanh(r1);
2007: :
2008: f2* fexpm1 fdup 2. d>f f+ f/ ;
2009:
2010: fasinh ( r1 -- r2 ) float-ext f_a_cinch
2011: r2 = asinh(r1);
2012: :
2013: fdup fdup f* 1. d>f f+ fsqrt f/ fatanh ;
2014:
2015: facosh ( r1 -- r2 ) float-ext f_a_cosh
2016: r2 = acosh(r1);
2017: :
2018: fdup fdup f* 1. d>f f- fsqrt f+ fln ;
2019:
2020: fatanh ( r1 -- r2 ) float-ext f_a_tan_h
2021: r2 = atanh(r1);
2022: :
2023: fdup f0< >r fabs 1. d>f fover f- f/ f2* flnp1 f2/
2024: r> IF fnegate THEN ;
2025:
2026: sfloats ( n1 -- n2 ) float-ext s_floats
2027: ""@i{n2} is the number of address units of @i{n1}
2028: single-precision IEEE floating-point numbers.""
2029: n2 = n1*sizeof(SFloat);
2030:
2031: dfloats ( n1 -- n2 ) float-ext d_floats
2032: ""@i{n2} is the number of address units of @i{n1}
2033: double-precision IEEE floating-point numbers.""
2034: n2 = n1*sizeof(DFloat);
2035:
2036: sfaligned ( c_addr -- sf_addr ) float-ext s_f_aligned
2037: ""@i{sf-addr} is the first single-float-aligned address greater
2038: than or equal to @i{c-addr}.""
2039: sf_addr = (SFloat *)((((Cell)c_addr)+(sizeof(SFloat)-1))&(-sizeof(SFloat)));
2040: :
2041: [ 1 sfloats 1- ] Literal + [ -1 sfloats ] Literal and ;
2042:
2043: dfaligned ( c_addr -- df_addr ) float-ext d_f_aligned
2044: ""@i{df-addr} is the first double-float-aligned address greater
2045: than or equal to @i{c-addr}.""
2046: df_addr = (DFloat *)((((Cell)c_addr)+(sizeof(DFloat)-1))&(-sizeof(DFloat)));
2047: :
2048: [ 1 dfloats 1- ] Literal + [ -1 dfloats ] Literal and ;
2049:
2050: v* ( f_addr1 nstride1 f_addr2 nstride2 ucount -- r ) gforth v_star
2051: ""dot-product: r=v1*v2. The first element of v1 is at f_addr1, the
2052: next at f_addr1+nstride1 and so on (similar for v2). Both vectors have
2053: ucount elements.""
2054: r = v_star(f_addr1, nstride1, f_addr2, nstride2, ucount);
2055: :
2056: >r swap 2swap swap 0e r> 0 ?DO
2057: dup f@ over + 2swap dup f@ f* f+ over + 2swap
2058: LOOP 2drop 2drop ;
2059:
2060: faxpy ( ra f_x nstridex f_y nstridey ucount -- ) gforth
2061: ""vy=ra*vx+vy""
2062: faxpy(ra, f_x, nstridex, f_y, nstridey, ucount);
2063: :
2064: >r swap 2swap swap r> 0 ?DO
2065: fdup dup f@ f* over + 2swap dup f@ f+ dup f! over + 2swap
2066: LOOP 2drop 2drop fdrop ;
2067:
2068: \+
2069:
2070: \ The following words access machine/OS/installation-dependent
2071: \ Gforth internals
2072: \ !! how about environmental queries DIRECT-THREADED,
2073: \ INDIRECT-THREADED, TOS-CACHED, FTOS-CACHED, CODEFIELD-DOES */
2074:
2075: \ local variable implementation primitives
2076:
2077: \+glocals
2078:
2079: \g locals
2080:
2081: @local# ( #noffset -- w ) gforth fetch_local_number
2082: w = *(Cell *)(lp+noffset);
2083:
2084: @local0 ( -- w ) new fetch_local_zero
2085: w = ((Cell *)lp)[0];
2086:
2087: @local1 ( -- w ) new fetch_local_four
2088: w = ((Cell *)lp)[1];
2089:
2090: @local2 ( -- w ) new fetch_local_eight
2091: w = ((Cell *)lp)[2];
2092:
2093: @local3 ( -- w ) new fetch_local_twelve
2094: w = ((Cell *)lp)[3];
2095:
2096: \+floating
2097:
2098: f@local# ( #noffset -- r ) gforth f_fetch_local_number
2099: r = *(Float *)(lp+noffset);
2100:
2101: f@local0 ( -- r ) new f_fetch_local_zero
2102: r = ((Float *)lp)[0];
2103:
2104: f@local1 ( -- r ) new f_fetch_local_eight
2105: r = ((Float *)lp)[1];
2106:
2107: \+
2108:
2109: laddr# ( #noffset -- c_addr ) gforth laddr_number
2110: /* this can also be used to implement lp@ */
2111: c_addr = (Char *)(lp+noffset);
2112:
2113: lp+!# ( #noffset -- ) gforth lp_plus_store_number
2114: ""used with negative immediate values it allocates memory on the
2115: local stack, a positive immediate argument drops memory from the local
2116: stack""
2117: lp += noffset;
2118:
2119: lp- ( -- ) new minus_four_lp_plus_store
2120: lp += -sizeof(Cell);
2121:
2122: lp+ ( -- ) new eight_lp_plus_store
2123: lp += sizeof(Float);
2124:
2125: lp+2 ( -- ) new sixteen_lp_plus_store
2126: lp += 2*sizeof(Float);
2127:
2128: lp! ( c_addr -- ) gforth lp_store
2129: lp = (Address)c_addr;
2130:
2131: >l ( w -- ) gforth to_l
2132: lp -= sizeof(Cell);
2133: *(Cell *)lp = w;
2134:
2135: \+floating
2136:
2137: f>l ( r -- ) gforth f_to_l
2138: lp -= sizeof(Float);
2139: *(Float *)lp = r;
2140:
2141: fpick ( u -- r ) gforth
2142: ""Actually the stack effect is @code{ r0 ... ru u -- r0 ... ru r0 }.""
2143: r = fp[u+1]; /* +1, because update of fp happens before this fragment */
2144: :
2145: floats fp@ + f@ ;
2146:
2147: \+
2148: \+
2149:
2150: \+OS
2151:
2152: \g syslib
2153:
2154: define(`uploop',
2155: `pushdef(`$1', `$2')_uploop(`$1', `$2', `$3', `$4', `$5')`'popdef(`$1')')
2156: define(`_uploop',
2157: `ifelse($1, `$3', `$5',
2158: `$4`'define(`$1', incr($1))_uploop(`$1', `$2', `$3', `$4', `$5')')')
2159: \ argflist(argnum): Forth argument list
2160: define(argflist,
2161: `ifelse($1, 0, `',
2162: `uploop(`_i', 1, $1, `format(`u%d ', _i)', `format(`u%d ', _i)')')')
2163: \ argdlist(argnum): declare C's arguments
2164: define(argdlist,
2165: `ifelse($1, 0, `',
2166: `uploop(`_i', 1, $1, `Cell, ', `Cell')')')
2167: \ argclist(argnum): pass C's arguments
2168: define(argclist,
2169: `ifelse($1, 0, `',
2170: `uploop(`_i', 1, $1, `format(`u%d, ', _i)', `format(`u%d', _i)')')')
2171: \ icall(argnum)
2172: define(icall,
2173: `icall$1 ( argflist($1)u -- uret ) gforth
2174: uret = (SYSCALL(Cell(*)(argdlist($1)))u)(argclist($1));
2175:
2176: ')
2177: define(fcall,
2178: `fcall$1 ( argflist($1)u -- rret ) gforth
2179: rret = (SYSCALL(Float(*)(argdlist($1)))u)(argclist($1));
2180:
2181: ')
2182:
2183: \ close ' to keep fontify happy
2184:
2185: open-lib ( c_addr1 u1 -- u2 ) gforth open_lib
2186: #if defined(HAVE_LIBDL) || defined(HAVE_DLOPEN)
2187: #ifndef RTLD_GLOBAL
2188: #define RTLD_GLOBAL 0
2189: #endif
2190: u2=(UCell) dlopen(cstr(c_addr1, u1, 1), RTLD_GLOBAL | RTLD_LAZY);
2191: #else
2192: # ifdef _WIN32
2193: u2 = (Cell) GetModuleHandle(cstr(c_addr1, u1, 1));
2194: # else
2195: #warning Define open-lib!
2196: u2 = 0;
2197: # endif
2198: #endif
2199:
2200: lib-sym ( c_addr1 u1 u2 -- u3 ) gforth lib_sym
2201: #if defined(HAVE_LIBDL) || defined(HAVE_DLOPEN)
2202: u3 = (UCell) dlsym((void*)u2,cstr(c_addr1, u1, 1));
2203: #else
2204: # ifdef _WIN32
2205: u3 = (Cell) GetProcAddress((HMODULE)u2, cstr(c_addr1, u1, 1));
2206: # else
2207: #warning Define lib-sym!
2208: u3 = 0;
2209: # endif
2210: #endif
2211:
2212: uploop(i, 0, 7, `icall(i)')
2213: icall(20)
2214: uploop(i, 0, 7, `fcall(i)')
2215: fcall(20)
2216:
2217: \+
2218:
2219: wcall ( u -- ) gforth
2220: IF_fpTOS(fp[0]=fpTOS);
2221: FP=fp;
2222: sp=(Cell*)(SYSCALL(Cell*(*)(Cell *, void *))u)(sp, &FP);
2223: fp=FP;
2224: IF_spTOS(spTOS=sp[0];)
2225: IF_fpTOS(fpTOS=fp[0]);
2226:
2227: \+peephole
2228:
2229: \g peephole
2230:
2231: compile-prim1 ( a_prim -- ) gforth compile_prim1
2232: ""compile prim (incl. immargs) at @var{a_prim}""
2233: compile_prim1(a_prim);
2234:
2235: finish-code ( -- ) gforth finish_code
2236: ""Perform delayed steps in code generation (branch resolution, I-cache
2237: flushing).""
2238: finish_code();
2239:
2240: forget-dyncode ( c_code -- f ) gforth-internal forget_dyncode
2241: f = forget_dyncode(c_code);
2242:
2243: decompile-prim ( a_code -- a_prim ) gforth-internal decompile_prim
2244: ""a_prim is the code address of the primitive that has been
2245: compile_prim1ed to a_code""
2246: a_prim = (Cell *)decompile_code((Label)a_code);
2247:
2248: \ set-next-code and call2 do not appear in images and can be
2249: \ renumbered arbitrarily
2250:
2251: set-next-code ( #w -- ) gforth set_next_code
2252: #ifdef NO_IP
2253: next_code = (Label)w;
2254: #endif
2255:
2256: call2 ( #a_callee #a_ret_addr -- R:a_ret_addr ) gforth
2257: /* call with explicit return address */
2258: #ifdef NO_IP
2259: INST_TAIL;
2260: JUMP(a_callee);
2261: #else
2262: assert(0);
2263: #endif
2264:
2265: \+
2266:
2267: include(peeprules.vmg)
2268:
2269: \g end
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>