1: \ miscelleneous words
2:
3: \ Copyright (C) 1996,1997,1998,2000,2003,2004,2005,2006,2007,2008 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 3
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, see http://www.gnu.org/licenses/.
19:
20: require glocals.fs
21:
22: ' require alias needs ( ... "name" -- ... ) \ gforth
23: \G An alias for @code{require}; exists on other systems (e.g., Win32Forth).
24: \ needs is an F-PC name. we will probably switch to 'needs' in the future
25:
26: \ a little more compiler security
27:
28: \ currently not used by Gforth, but maybe by add-ons e.g., the 486asm
29: AUser CSP
30:
31: : !CSP ( -- )
32: sp@ csp ! ;
33:
34: : ?CSP ( -- )
35: sp@ csp @ <> -22 and throw ;
36:
37: \ DMIN and DMAX
38:
39: : dmin ( d1 d2 -- d ) \ double d-min
40: 2over 2over d> IF 2swap THEN 2drop ;
41:
42:
43: : dmax ( d1 d2 -- d ) \ double d-max
44: 2over 2over d< IF 2swap THEN 2drop ;
45:
46: \ shell commands
47:
48: 0 Value $? ( -- n ) \ gforth dollar-question
49: \G @code{Value} -- the exit status returned by the most recently executed
50: \G @code{system} command.
51:
52: : system ( c-addr u -- ) \ gforth
53: \G Pass the string specified by @var{c-addr u} to the host operating
54: \G system for execution in a sub-shell. The value of the environment
55: \G variable @code{GFORTHSYSTEMPREFIX} (or its default value) is
56: \G prepended to the string (mainly to support using @code{command.com}
57: \G as shell in Windows instead of whatever shell Cygwin uses by
58: \G default; @pxref{Environment variables}).
59: (system) throw TO $? ;
60:
61: : sh ( "..." -- ) \ gforth
62: \G Parse a string and use @code{system} to pass it to the host
63: \G operating system for execution in a sub-shell.
64: '# parse cr system ;
65:
66: \ stuff
67:
68: : ]L ( compilation: n -- ; run-time: -- n ) \ gforth
69: \G equivalent to @code{] literal}
70: ] postpone literal ;
71:
72: [ifundef] in-dictionary?
73: : in-dictionary? ( x -- f )
74: forthstart dictionary-end within ;
75: [endif]
76:
77: : in-return-stack? ( addr -- f )
78: rp0 @ swap - [ forthstart 6 cells + ]L @ u< ;
79:
80: \ const-does>
81:
82: : compile-literals ( w*u u -- ; run-time: -- w*u ) recursive
83: \ compile u literals, starting with the bottommost one
84: ?dup-if
85: swap >r 1- compile-literals
86: r> POSTPONE literal
87: endif ;
88:
89: : compile-fliterals ( r*u u -- ; run-time: -- w*u ) recursive
90: \ compile u fliterals, starting with the bottommost one
91: ?dup-if
92: { F: r } 1- compile-fliterals
93: r POSTPONE fliteral
94: endif ;
95:
96: : (const-does>) ( w*uw r*ur uw ur target "name" -- )
97: \ define a colon definition "name" containing w*uw r*ur as
98: \ literals and a call to target.
99: { uw ur target }
100: header docol: cfa, \ start colon def without stack junk
101: ur compile-fliterals uw compile-literals
102: target compile, POSTPONE exit reveal ;
103:
104: : const-does> ( run-time: w*uw r*ur uw ur "name" -- ) \ gforth
105: \G Defines @var{name} and returns.
106: \G
107: \G @var{name} execution: pushes @var{w*uw r*ur}, then performs the
108: \G code following the @code{const-does>}.
109: here >r 0 POSTPONE literal
110: POSTPONE (const-does>)
111: POSTPONE ;
112: noname : POSTPONE rdrop
113: latestxt r> cell+ ! \ patch the literal
114: ; immediate
115:
116: \ !! rewrite slurp-file using slurp-fid
117: : slurp-file ( c-addr1 u1 -- c-addr2 u2 ) \ gforth
118: \G @var{c-addr1 u1} is the filename, @var{c-addr2 u2} is the file's contents
119: r/o bin open-file throw >r
120: r@ file-size throw abort" file too large"
121: dup allocate throw swap
122: 2dup r@ read-file throw over <> abort" could not read whole file"
123: r> close-file throw ;
124:
125: : slurp-fid ( fid -- addr u ) \ gforth
126: \G @var{addr u} is the content of the file @var{fid}
127: { fid }
128: 0 0 begin ( awhole uwhole )
129: dup 1024 + dup >r extend-mem ( anew awhole uwhole R: unew )
130: rot r@ fid read-file throw ( awhole uwhole uread R: unew )
131: r> 2dup =
132: while ( awhole uwhole uread unew )
133: 2drop
134: repeat
135: - + dup >r resize throw r> ;
136:
137: \ ]] ... [[
138:
139: : compile-literal ( n -- )
140: postpone literal ;
141:
142: : compile-compile-literal ( n -- )
143: compile-literal postpone compile-literal ;
144:
145: : compile-2literal ( n1 n2 -- )
146: postpone 2literal ;
147:
148: : compile-compile-2literal ( n1 n2 -- )
149: compile-2literal postpone compile-2literal ;
150:
151: : [[ ( -- )
152: \G switch from postpone state to compile state
153: \ this is only a marker; it is never really interpreted
154: compile-only-error ; immediate
155:
156: [ifdef] compiler1
157: : postponer1 ( c-addr u -- ... xt )
158: 2dup find-name
159: [ifdef] run-prelude run-prelude [then]
160: dup if ( c-addr u nt )
161: nip nip name>comp
162: 2dup [comp'] [[ d= if
163: 2drop ['] compiler1 is parser1 ['] noop
164: else
165: ['] postpone,
166: endif
167: else
168: drop
169: 2dup 2>r snumber? dup if
170: 0> IF
171: ['] compile-compile-2literal
172: ELSE
173: ['] compile-compile-literal
174: THEN
175: 2rdrop
176: ELSE
177: drop 2r> no.extensions
178: THEN
179: then ;
180:
181: : ]] ( -- )
182: \ switch into postpone state
183: ['] postponer1 is parser1 state on ; immediate restrict
184:
185: [then]
186:
187: \ f.rdp
188:
189: : push-right ( c-addr u1 u2 cfill -- )
190: \ move string at c-addr u1 right by u2 chars (without exceeding
191: \ the original bound); fill the gap with cfill
192: >r over min dup >r rot dup >r ( u1 u2 c-addr R: cfill u2 c-addr )
193: dup 2swap /string cmove>
194: r> r> r> fill ;
195:
196: : f>buf-rdp-try { f: rf c-addr ur nd up um1 -- um2 }
197: \ um1 is the mantissa length to try, um2 is the actual mantissa length
198: c-addr ur um1 /string '0 fill
199: rf c-addr um1 represent if { nexp fsign }
200: nd nexp + up >=
201: ur nd - 1- dup { beforep } fsign + nexp 0 max >= and if
202: \ fixed-point notation
203: c-addr ur beforep nexp - dup { befored } '0 push-right
204: befored 1+ ur >= if \ <=1 digit left, will be pushed out by '.'
205: rf fabs f2* 0.1e nd s>d d>f f** f> if \ round last digit
206: '1 c-addr befored + 1- c!
207: endif
208: endif
209: c-addr beforep 1- befored min dup { beforez } 0 max bl fill
210: fsign if
211: '- c-addr beforez 1- 0 max + c!
212: endif
213: c-addr ur beforep /string 1 '. push-right
214: nexp nd +
215: else \ exponential notation
216: c-addr ur 1 /string 1 '. push-right
217: fsign if
218: c-addr ur 1 '- push-right
219: endif
220: nexp 1- s>d tuck dabs <<# #s rot sign 'E hold #> { explen }
221: ur explen - 1- fsign + { mantlen }
222: mantlen 0< if \ exponent too large
223: drop c-addr ur '* fill
224: else
225: c-addr ur + 0 explen negate /string move
226: endif
227: #>> mantlen
228: endif
229: else \ inf or nan
230: if \ negative
231: c-addr ur 1 '- push-right
232: endif
233: drop ur
234: \ !! align in some way?
235: endif
236: 1 max ur min ;
237:
238: : f>buf-rdp ( rf c-addr +nr +nd +np -- ) \ gforth
239: \G Convert @i{rf} into a string at @i{c-addr nr}. The conversion
240: \G rules and the meanings of @i{nr nd np} are the same as for
241: \G @code{f.rdp}.
242: \ first, get the mantissa length, then convert for real. The
243: \ mantissa length is wrong in a few cases because of different
244: \ rounding; In most cases this does not matter, because the
245: \ mantissa is shorter than expected and the final digits are 0;
246: \ but in a few cases the mantissa gets longer. Then it is
247: \ conceivable that you will see a result that is rounded too much.
248: \ However, I have not been able to construct an example where this
249: \ leads to an unexpected result.
250: swap 0 max swap 0 max
251: fdup 2over 2over 2 pick f>buf-rdp-try f>buf-rdp-try drop ;
252:
253: : f>str-rdp ( rf +nr +nd +np -- c-addr nr ) \ gforth
254: \G Convert @i{rf} into a string at @i{c-addr nr}. The conversion
255: \G rules and the meanings of @i{nr +nd np} are the same as for
256: \G @code{f.rdp}. The result in in the pictured numeric output buffer
257: \G and will be destroyed by anything destroying that buffer.
258: rot holdptr @ 1- 0 rot negate /string ( rf +nd np c-addr nr )
259: over holdbuf u< -&17 and throw
260: 2tuck 2>r f>buf-rdp 2r> ;
261:
262: : f.rdp ( rf +nr +nd +np -- ) \ gforth
263: \G Print float @i{rf} formatted. The total width of the output is
264: \G @i{nr}. For fixed-point notation, the number of digits after the
265: \G decimal point is @i{+nd} and the minimum number of significant
266: \G digits is @i{np}. @code{Set-precision} has no effect on
267: \G @code{f.rdp}. Fixed-point notation is used if the number of
268: \G siginicant digits would be at least @i{np} and if the number of
269: \G digits before the decimal point would fit. If fixed-point notation
270: \G is not used, exponential notation is used, and if that does not
271: \G fit, asterisks are printed. We recommend using @i{nr}>=7 to avoid
272: \G the risk of numbers not fitting at all. We recommend
273: \G @i{nr}>=@i{np}+5 to avoid cases where @code{f.rdp} switches to
274: \G exponential notation because fixed-point notation would have too
275: \G few significant digits, yet exponential notation offers fewer
276: \G significant digits. We recommend @i{nr}>=@i{nd}+2, if you want to
277: \G have fixed-point notation for some numbers. We recommend
278: \G @i{np}>@i{nr}, if you want to have exponential notation for all
279: \G numbers.
280: f>str-rdp type ;
281:
282: 0 [if]
283: : testx ( rf ur nd up -- )
284: '| emit f.rdp ;
285:
286: : test ( -- )
287: -0.123456789123456789e-20
288: 40 0 ?do
289: cr
290: fdup 7 3 1 testx
291: fdup 7 3 4 testx
292: fdup 7 3 0 testx
293: fdup 7 7 1 testx
294: fdup 7 5 1 testx
295: fdup 7 0 2 testx
296: fdup 5 2 1 testx
297: fdup 4 2 1 testx
298: fdup 18 8 5 testx
299: '| emit
300: 10e f*
301: loop ;
302: [then]
303:
304: : f.s ( -- ) \ gforth f-dot-s
305: \G Display the number of items on the floating-point stack, followed
306: \G by a list of the items (but not more than specified by
307: \G @code{maxdepth-.s}; TOS is the right-most item.
308: ." <" fdepth 0 .r ." > " fdepth 0 max maxdepth-.s @ min dup 0
309: ?DO dup i - 1- floats fp@ + f@ 16 5 11 f.rdp space LOOP drop ;
310:
311: \ defer stuff
312:
313: [ifundef] defer@ : defer@ >body @ ; [then]
314:
315: :noname ' defer@ ;
316: :noname postpone ['] postpone defer@ ;
317: interpret/compile: action-of ( interpretation "name" -- xt; compilation "name" -- ; run-time -- xt ) \ gforth
318: \G @i{Xt} is the XT that is currently assigned to @i{name}.
319:
320: ' action-of
321: comp' action-of drop
322: interpret/compile: what's ( interpretation "name" -- xt; compilation "name" -- ; run-time -- xt ) \ gforth-obsolete
323: \G Old name of @code{action-of}
324:
325:
326: : typewhite ( addr n -- ) \ gforth
327: \G Like type, but white space is printed instead of the characters.
328: \ bounds u+do
329: 0 max bounds ?do
330: i c@ #tab = if \ check for tab
331: #tab
332: else
333: bl
334: then
335: emit
336: loop ;
337:
338: \ w and l stuff
339:
340: environment-wordlist >order
341:
342: 16 address-unit-bits / 1 max constant /w ( -- u ) \ gforth slash-w
343: \G address units for a 16-bit value
344:
345: 32 address-unit-bits / 1 max constant /l ( -- u ) \ gforth slash-l
346: \G address units for a 32-bit value
347:
348: previous
349:
350: [ifdef] uw@
351: \ Open firmware names
352: ' uw@ alias w@ ( addr -- u )
353: ' ul@ alias l@ ( addr -- u )
354: \ ' sw@ alias <w@ ( addr -- n )
355: [then]
356:
357: \ safe output redirection
358:
359: : outfile-execute ( ... xt file-id -- ... ) \ gforth
360: \G execute @i{xt} with the output of @code{type} etc. redirected to
361: \G @i{file-id}.
362: outfile-id { oldfid } try
363: to outfile-id execute 0
364: restore
365: oldfid to outfile-id
366: endtry
367: throw ;
368:
369: : infile-execute ( ... xt file-id -- ... ) \ gforth
370: \G execute @i{xt} with the input of @code{key} etc. redirected to
371: \G @i{file-id}.
372: infile-id { oldfid } try
373: to infile-id execute 0
374: restore
375: oldfid to infile-id
376: endtry
377: throw ;
378:
379: \ safe BASE wrapper
380:
381: : base-execute ( i*x xt u -- j*x ) \ gforth
382: \G execute @i{xt} with the content of @code{BASE} being @i{u}, and
383: \G restoring the original @code{BASE} afterwards.
384: base @ { oldbase } \ use local, because TRY blocks the return stack
385: try
386: base ! execute 0
387: restore
388: oldbase base !
389: endtry
390: throw ;
391:
392: \ th
393:
394: : th ( addr1 u -- addr2 )
395: cells + ;
396:
397: \ \\\ - skip to end of file
398:
399: : \\\ ( -- ) \ gforth
400: \G skip remaining source file
401: source-id dup 0> IF
402: >r r@ file-size throw r> reposition-file throw
403: BEGIN refill 0= UNTIL postpone \ THEN ; immediate
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>