Added J.
[forth.jl.git] / src / lib.4th
1 : / /MOD SWAP DROP ;
2 : MOD /MOD DROP ;
3 : */ -ROT * SWAP / ;
4
5 : NEGATE 0 SWAP - ;
6
7 : TRUE -1 ;
8 : FALSE 0 ;
9 : NOT 0= ;
10
11 : CELLS ; \ Allow for slightly more portable code
12
13 : DEPTH PSP@ PSP0 @ - ;
14
15 : '\n' 10 ;
16 : BL 32 ;
17
18 : LITERAL IMMEDIATE ' LIT , , ;
19
20 : ':' [ CHAR : ] LITERAL ;
21 : ';' [ CHAR ; ] LITERAL ;
22 : '(' [ CHAR ( ] LITERAL ;
23 : ')' [ CHAR ) ] LITERAL ;
24 : '<' [ CHAR < ] LITERAL ;
25 : '>' [ CHAR > ] LITERAL ;
26 : '"' [ CHAR " ] LITERAL ;
27 : 'A' [ CHAR A ] LITERAL ;
28 : '0' [ CHAR 0 ] LITERAL ;
29 : '-' [ CHAR - ] LITERAL ;
30 : '.' [ CHAR . ] LITERAL ;
31
32 : CR '\n' emit ;
33 : SPACE BL emit ;
34
35 : [COMPILE] IMMEDIATE
36         WORD            \ get the next word
37         FIND            \ find it in the dictionary
38         >CFA            \ get its codeword
39         ,               \ and compile that
40 ;
41
42 : RECURSE IMMEDIATE
43         LATEST @        \ LATEST points to the word being compiled at the moment
44         >CFA            \ get the codeword
45         ,               \ compile it
46 ;
47
48 : DEBUGON TRUE DEBUG ! ;
49 : DEBUGOFF FALSE DEBUG ! ;
50
51 \ CONTROL STRUCTURES ----------------------------------------------------------------------
52
53 : IF IMMEDIATE
54         ' 0BRANCH ,     \ compile 0BRANCH
55         HERE @          \ save location of the offset on the stack
56         0 ,             \ compile a dummy offset
57 ;
58
59 : THEN IMMEDIATE
60         DUP
61         HERE @ SWAP -   \ calculate the offset from the address saved on the stack
62         SWAP !          \ store the offset in the back-filled location
63 ;
64
65 : ELSE IMMEDIATE
66         ' BRANCH ,      \ definite branch to just over the false-part
67         HERE @          \ save location of the offset on the stack
68         0 ,             \ compile a dummy offset
69         SWAP            \ now back-fill the original (IF) offset
70         DUP             \ same as for THEN word above
71         HERE @ SWAP -
72         SWAP !
73 ;
74
75 : BEGIN IMMEDIATE
76         HERE @          \ save location on the stack
77 ;
78
79 : UNTIL IMMEDIATE
80         ' 0BRANCH ,     \ compile 0BRANCH
81         HERE @ -        \ calculate the offset from the address saved on the stack
82         ,               \ compile the offset here
83 ;
84
85 : AGAIN IMMEDIATE
86         ' BRANCH ,      \ compile BRANCH
87         HERE @ -        \ calculate the offset back
88         ,               \ compile the offset here
89 ;
90
91 : WHILE IMMEDIATE
92         ' 0BRANCH ,     \ compile 0BRANCH
93         HERE @          \ save location of the offset2 on the stack
94         0 ,             \ compile a dummy offset2
95 ;
96
97 : REPEAT IMMEDIATE
98         ' BRANCH ,      \ compile BRANCH
99         SWAP            \ get the original offset (from BEGIN)
100         HERE @ - ,      \ and compile it after BRANCH
101         DUP
102         HERE @ SWAP -   \ calculate the offset2
103         SWAP !          \ and back-fill it in the original location
104 ;
105
106 : UNLESS IMMEDIATE
107         ' NOT ,         \ compile NOT (to reverse the test)
108         [COMPILE] IF    \ continue by calling the normal IF
109 ;
110
111 : DO IMMEDIATE
112         ' >R , ' >R ,
113         ' LIT , HERE @ 0 , ' >R ,
114         HERE @
115 ;
116
117 : I RSP@ 3 - @ ;
118
119 : J RSP@ 6 - @ ;
120
121 : ?LEAVE IMMEDIATE
122         ' 0BRANCH , 13 ,
123         ' R> , ' RDROP , ' RDROP ,
124         ' LIT ,  HERE @ 7 + , ' DUP , ' -ROT , ' - , ' SWAP , ' ! ,
125         ' BRANCH ,
126         0 ,
127 ;
128
129 : LEAVE IMMEDIATE
130         ' LIT , -1 ,
131         [COMPILE] ?LEAVE
132 ;
133
134 : +LOOP IMMEDIATE
135         ' R> , ' SWAP , ' R> , ' SWAP , ' R> , ' SWAP , ' + , ' 2DUP , ' - ,
136         ' SWAP , ' >R , ' SWAP , ' >R , ' SWAP , ' >R ,
137         ' 0<= , ' 0BRANCH ,
138         HERE @ - ,
139         ' RDROP , ' RDROP , ' RDROP ,
140         HERE @ SWAP !
141 ;
142
143 : LOOP IMMEDIATE
144         ' LIT , 1 ,
145         [COMPILE] +LOOP
146 ;
147
148 \ COMMENTS ----------------------------------------------------------------------
149
150 : ( IMMEDIATE
151         1               \ allowed nested parens by keeping track of depth
152         BEGIN
153                 KEY             \ read next character
154                 DUP '(' = IF    \ open paren?
155                         DROP            \ drop the open paren
156                         1+              \ depth increases
157                 ELSE
158                         ')' = IF        \ close paren?
159                                 1-              \ depth decreases
160                         THEN
161                 THEN
162         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
163         DROP            \ drop the depth counter
164 ;
165
166 ( Some more complicated stack examples, showing the stack notation. )
167 : NIP ( x y -- y ) SWAP DROP ;
168 : TUCK ( x y -- y x y ) DUP -ROT ;
169 : PICK ( x_u ... x_1 x_0 u -- x_u ... x_1 x_0 x_u )
170         1+              ( add one because of 'u' on the stack )
171         PSP@ SWAP -     ( add to the stack pointer )
172         @               ( and fetch )
173 ;
174
175 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
176 : SPACES        ( n -- )
177         0 DO
178             SPACE
179         LOOP
180 ;
181
182 ( Standard words for manipulating BASE. )
183 : DECIMAL ( -- ) 10 BASE ! ;
184 : HEX ( -- ) 16 BASE ! ;
185
186 ( Compute absolute value. )
187 : ABS           ( n -- |n| )
188         dup 0< if
189                 negate
190         then
191 ;
192
193 : MAX           ( n m -- max )
194         2dup - 0< if
195                 swap drop
196         else
197                 drop
198         then
199 ;
200
201 : MIN           ( n m -- max )
202         2dup - 0> if
203                 swap drop
204         else
205                 drop
206         then
207 ;
208
209 ( PRINTING NUMBERS ---------------------------------------------------------------------- )
210
211 ( This is the underlying recursive definition of U. )
212 : U.            ( u -- )
213         BASE @ /MOD     ( width rem quot )
214         ?DUP IF                 ( if quotient <> 0 then )
215                 RECURSE         ( print the quotient )
216         THEN
217
218         ( print the remainder )
219         DUP 10 < IF
220                 '0'             ( decimal digits 0..9 )
221         ELSE
222                 10 -            ( hex and beyond digits A..Z )
223                 'A'
224         THEN
225         +
226         EMIT
227 ;
228
229 ( This word returns the width (in characters) of an unsigned number in the current base )
230 : UWIDTH        ( u -- width )
231         BASE @ /        ( rem quot )
232         ?DUP IF         ( if quotient <> 0 then )
233                 RECURSE 1+      ( return 1+recursive call )
234         ELSE
235                 1               ( return 1 )
236         THEN
237 ;
238
239 : U.R           ( u width -- )
240         SWAP            ( width u )
241         DUP             ( width u u )
242         UWIDTH          ( width u uwidth )
243         ROT            ( u uwidth width )
244         SWAP -          ( u width-uwidth )
245         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
246           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
247           a negative number of spaces anyway, so it's now safe to call SPACES ... )
248         SPACES
249         ( ... and then call the underlying implementation of U. )
250         U.
251 ;
252
253 : .R            ( n width -- )
254         SWAP            ( width n )
255         DUP 0< IF
256                 NEGATE          ( width u )
257                 1               ( save a flag to remember that it was negative | width n 1 )
258                 -ROT             ( 1 width u )
259                 SWAP            ( 1 u width )
260                 1-              ( 1 u width-1 )
261         ELSE
262                 0               ( width u 0 )
263                 -ROT             ( 0 width u )
264                 SWAP            ( 0 u width )
265         THEN
266         SWAP            ( flag width u )
267         DUP             ( flag width u u )
268         UWIDTH          ( flag width u uwidth )
269         ROT            ( flag u uwidth width )
270         SWAP -          ( flag u width-uwidth )
271
272         SPACES          ( flag u )
273         SWAP            ( u flag )
274
275         IF                      ( was it negative? print the - character )
276                 '-' EMIT
277         THEN
278
279         U.
280 ;
281
282 : . 0 .R SPACE ;
283
284 : .S            ( -- )
285         '<' EMIT DEPTH U. '>' EMIT SPACE
286         PSP0 @ 1+
287         BEGIN
288                 DUP PSP@ 2 - <=
289         WHILE
290                 DUP @ .
291                 1+
292         REPEAT
293         DROP
294 ;
295
296 : U. U. SPACE ;
297
298 ( ? fetches the integer at an address and prints it. )
299 : ? ( addr -- ) @ . ;
300
301 ( c a b WITHIN returns true if a <= c and c < b )
302 : WITHIN
303         -ROT             ( b c a )
304         OVER            ( b c a c )
305         <= IF
306                 > IF            ( b c -- )
307                         TRUE
308                 ELSE
309                         FALSE
310                 THEN
311         ELSE
312                 2DROP           ( b c -- )
313                 FALSE
314         THEN
315 ;
316
317 : ROLL ( x_u x_u-1... x_0 u -- x_u-1 ... x_0 x_u )
318         1+ DUP PICK SWAP    ( x_u x_u-1 ... x_0 x_u u+1 )
319         PSP@ 1- SWAP - PSP@ 2- SWAP
320         DO
321             i 1+ @ i !
322         LOOP
323         SWAP DROP
324 ;
325
326