Annotation of gforth/extend.fs, revision 1.50
1.1 anton 1: \ EXTEND.FS CORE-EXT Word not fully tested! 12may93jaw
2:
1.44 anton 3: \ Copyright (C) 1995,1998,2000 Free Software Foundation, Inc.
1.12 anton 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
1.45 anton 19: \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
1.12 anton 20:
21:
1.1 anton 22: \ May be cross-compiled
23:
24: decimal
25:
26: \ .( 12may93jaw
27:
1.50 ! anton 28: : .( ( compilation&interpretation "ccc<paren>" -- ) \ core-ext dot-paren
1.41 anton 29: \G Compilation and interpretation semantics: Parse a string @i{ccc}
30: \G delimited by a @code{)} (right parenthesis). Display the
31: \G string. This is often used to display progress information during
32: \G compilation; see examples below.
1.32 crook 33: [char] ) parse type ; immediate
1.1 anton 34:
35: \ VALUE 2>R 2R> 2R@ 17may93jaw
36:
1.3 anton 37: \ !! 2value
1.1 anton 38:
1.11 anton 39: : 2Literal ( compilation w1 w2 -- ; run-time -- w1 w2 ) \ double two-literal
1.36 crook 40: \G Compile appropriate code such that, at run-time, cell pair @i{w1, w2} are
1.32 crook 41: \G placed on the stack. Interpretation semantics are undefined.
1.11 anton 42: swap postpone Literal postpone Literal ; immediate restrict
1.2 pazsan 43:
1.16 anton 44: ' drop alias d>s ( d -- n ) \ double d_to_s
45:
1.39 anton 46: : m*/ ( d1 n2 u3 -- dquot ) \ double m-star-slash
1.40 anton 47: \G dquot=(d1*n2)/u3, with the intermediate result being triple-precision.
48: \G In ANS Forth u3 can only be a positive signed number.
1.11 anton 49: >r s>d >r abs -rot
50: s>d r> xor r> swap >r >r dabs rot tuck um* 2swap um*
51: swap >r 0 d+ r> -rot r@ um/mod -rot r> um/mod nip swap
52: r> IF dnegate THEN ;
1.4 pazsan 53:
1.1 anton 54: \ CASE OF ENDOF ENDCASE 17may93jaw
55:
56: \ just as described in dpANS5
57:
1.11 anton 58: 0 CONSTANT case ( compilation -- case-sys ; run-time -- ) \ core-ext
59: immediate
1.1 anton 60:
1.11 anton 61: : of ( compilation -- of-sys ; run-time x1 x2 -- |x1 ) \ core-ext
62: \ !! the implementation does not match the stack effect
63: 1+ >r
64: postpone over postpone = postpone if postpone drop
65: r> ; immediate
66:
67: : endof ( compilation case-sys1 of-sys -- case-sys2 ; run-time -- ) \ core-ext end-of
68: >r postpone else r> ; immediate
69:
70: : endcase ( compilation case-sys -- ; run-time x -- ) \ core-ext end-case
71: postpone drop
72: 0 ?do postpone then loop ; immediate
1.1 anton 73:
74: \ C" 17may93jaw
75:
1.32 crook 76: : C" ( compilation "ccc<quote>" -- ; run-time -- c-addr ) \ core-ext c-quote
1.36 crook 77: \G Compilation: parse a string @i{ccc} delimited by a @code{"}
78: \G (double quote). At run-time, return @i{c-addr} which
79: \G specifies the counted string @i{ccc}. Interpretation
1.33 crook 80: \G semantics are undefined.
1.11 anton 81: [char] " parse postpone CLiteral ; immediate restrict
1.1 anton 82:
83: \ [COMPILE] 17may93jaw
84:
1.11 anton 85: : [compile] ( compilation "name" -- ; run-time ? -- ? ) \ core-ext bracket-compile
1.37 anton 86: comp' drop
87: dup [ comp' exit drop ] literal = if
88: execute \ EXIT has default compilation semantics, perform them
89: else
90: compile,
91: then ; immediate
1.1 anton 92:
93: \ CONVERT 17may93jaw
94:
1.11 anton 95: : convert ( ud1 c-addr1 -- ud2 c-addr2 ) \ core-ext
1.34 crook 96: \G OBSOLESCENT: superseded by @code{>number}.
1.26 anton 97: char+ true >number drop ;
1.1 anton 98:
99: \ ERASE 17may93jaw
100:
1.40 anton 101: : erase ( addr u -- ) \ core-ext
102: \G Clear all bits in @i{u} aus starting at @i{addr}.
1.11 anton 103: \ !! dependence on "1 chars 1 ="
104: ( 0 1 chars um/mod nip ) 0 fill ;
1.34 crook 105: : blank ( c-addr u -- ) \ string
1.40 anton 106: \G Store the space character into @i{u} chars starting at @i{c-addr}.
1.11 anton 107: bl fill ;
1.1 anton 108:
1.7 pazsan 109: \ SEARCH 02sep94py
110:
1.28 anton 111: : search ( c-addr1 u1 c-addr2 u2 -- c-addr3 u3 flag ) \ string
1.36 crook 112: \G Search the string specified by @i{c-addr1, u1} for the string
113: \G specified by @i{c-addr2, u2}. If @i{flag} is true: match was found
114: \G at @i{c-addr3} with @i{u3} characters remaining. If @i{flag} is false:
115: \G no match was found; @i{c-addr3, u3} are equal to @i{c-addr1, u1}.
1.28 anton 116: \ not very efficient; but if we want efficiency, we'll do it as primitive
117: 2>r 2dup
118: begin
119: dup r@ >=
120: while
121: over 2r@ swap -text 0= if
122: 2swap 2drop 2r> 2drop true exit
123: endif
124: 1 /string
125: repeat
126: 2drop 2r> 2drop false ;
1.7 pazsan 127:
1.1 anton 128: \ SOURCE-ID SAVE-INPUT RESTORE-INPUT 11jun93jaw
129:
1.46 pazsan 130: [IFUNDEF] source-id
1.22 anton 131: : source-id ( -- 0 | -1 | fileid ) \ core-ext,file source-i-d
1.34 crook 132: \G Return 0 (the input source is the user input device), -1 (the
133: \G input source is a string being processed by @code{evaluate}) or
1.36 crook 134: \G a @i{fileid} (the input source is the file specified by
135: \G @i{fileid}).
1.34 crook 136: loadfile @ dup 0= IF drop sourceline# 0 min THEN ;
137:
138: : save-input ( -- xn .. x1 n ) \ core-ext
1.36 crook 139: \G The @i{n} entries @i{xn - x1} describe the current state of the
1.34 crook 140: \G input source specification, in some platform-dependent way that can
141: \G be used by @code{restore-input}.
1.14 anton 142: >in @
143: loadfile @
144: if
1.43 pazsan 145: loadfile @ file-position throw
146: [IFDEF] #fill-bytes #fill-bytes @ [ELSE] #tib @ 1+ [THEN] 0 d-
1.14 anton 147: else
148: blk @
149: linestart @
150: then
151: sourceline#
152: >tib @
153: source-id
154: 6 ;
1.1 anton 155:
1.34 crook 156: : restore-input ( xn .. x1 n -- flag ) \ core-ext
157: \G Attempt to restore the input source specification to the state
1.36 crook 158: \G described by the @i{n} entries @i{xn - x1}. @i{flag} is
1.35 anton 159: \G true if the restore fails. In Gforth it fails pretty often
160: \G (and sometimes with a @code{throw}).
1.14 anton 161: 6 <> -12 and throw
162: source-id <> -12 and throw
163: >tib !
164: >r ( line# )
165: loadfile @ 0<>
166: if
167: loadfile @ reposition-file throw
1.38 anton 168: refill 0= -36 and throw \ should never throw
1.14 anton 169: else
170: linestart !
171: blk !
172: sourceline# r@ <> blk @ 0= and loadfile @ 0= and
173: if
174: drop rdrop true EXIT
175: then
176: then
177: r> loadline !
178: >in !
179: false ;
1.46 pazsan 180: [THEN]
1.1 anton 181: \ This things we don't need, but for being complete... jaw
182:
183: \ EXPECT SPAN 17may93jaw
184:
1.34 crook 185: variable span ( -- c-addr ) \ core-ext
1.36 crook 186: \G @code{Variable} -- @i{c-addr} is the address of a cell that stores the
187: \G length of the last string received by @code{expect}. OBSOLESCENT.
1.34 crook 188:
189: : expect ( c-addr +n -- ) \ core-ext
1.36 crook 190: \G Receive a string of at most @i{+n} characters, and store it
191: \G in memory starting at @i{c-addr}. The string is
1.34 crook 192: \G displayed. Input terminates when the <return> key is pressed or
1.36 crook 193: \G @i{+n} characters have been received. The normal Gforth line
1.34 crook 194: \G editing capabilites are available. The length of the string is
195: \G stored in @code{span}; it does not include the <return>
196: \G character. OBSOLESCENT: superceeded by @code{accept}.
1.9 anton 197: 0 rot over
198: BEGIN ( maxlen span c-addr pos1 )
199: key decode ( maxlen span c-addr pos2 flag )
200: >r 2over = r> or
201: UNTIL
1.17 pazsan 202: 2 pick swap /string type
203: nip span ! ;
1.27 jwilke 204:
205: \ marker 18dec94py
206:
207: \ Marker creates a mark that is removed (including everything
208: \ defined afterwards) when executing the mark.
209:
1.31 anton 210: : included-files-mark ( -- u )
211: included-files 2@ nip
212: blk @ 0=
213: if \ not input from blocks
214: source-id 1 -1 within
215: if \ input from file
216: 1- \ do not include the last file (hopefully this is the
217: \ currently included file)
218: then
219: then ;
220:
221: \ hmm, most of the saving appears to be pretty unnecessary: we could
222: \ derive the wordlists and the words that have to be kept from the
223: \ saved value of dp value. - anton
224:
225: : marker, ( -- mark )
226: here
227: included-files-mark ,
228: dup A, \ here
229: voclink @ A, \ vocabulary list start
230: \ for all wordlists, remember wordlist-id (the linked list)
231: voclink
232: BEGIN
233: @ dup
234: WHILE
235: dup 0 wordlist-link - wordlist-id @ A,
236: REPEAT
237: drop
238: \ remember udp
1.48 anton 239: udp @ ,
240: \ remember dyncode-ptr
241: here ['] noop , compile-prim1 finish-code ;
1.27 jwilke 242:
243: : marker! ( mark -- )
1.31 anton 244: \ reset included files count; resize will happen on next add-included-file
245: included-files 2@ drop over @ included-files 2! cell+
246: \ rest of marker!
247: dup @ swap cell+ ( here rest-of-marker )
1.27 jwilke 248: dup @ voclink ! cell+
1.31 anton 249: \ restore wordlists to former words
1.27 jwilke 250: voclink
251: BEGIN
252: @ dup
253: WHILE
1.31 anton 254: over @ over 0 wordlist-link - wordlist-id !
1.27 jwilke 255: swap cell+ swap
256: REPEAT
1.31 anton 257: drop
258: \ rehash wordlists to remove forgotten words
259: \ why don't we do this in a single step? - anton
260: voclink
1.27 jwilke 261: BEGIN
262: @ dup
263: WHILE
264: dup 0 wordlist-link - rehash
265: REPEAT
266: drop
1.31 anton 267: \ restore udp and dp
1.49 pazsan 268: [IFDEF] forget-dyncode
1.48 anton 269: dup cell+ @ forget-dyncode 0= abort" gforth bug"
1.49 pazsan 270: [THEN]
1.29 pazsan 271: @ udp ! dp !
272: \ clean up vocabulary stack
273: 0 vp @ 0
274: ?DO
275: vp cell+ I cells + @ dup here >
276: IF drop ELSE swap 1+ THEN
277: LOOP
278: dup 0= or set-order \ -1 set-order if order is empty
279: get-current here > IF
280: forth-wordlist set-current
281: THEN ;
1.27 jwilke 282:
1.32 crook 283: : marker ( "<spaces> name" -- ) \ core-ext
1.36 crook 284: \G Create a definition, @i{name} (called a @i{mark}) whose
1.32 crook 285: \G execution semantics are to remove itself and everything
286: \G defined after it.
1.27 jwilke 287: marker, Create A,
288: DOES> ( -- )
289: @ marker! ;
1.1 anton 290:
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>