diff view
color-dirk4d.f color-ed4.f
end of diff view
1. 0 [IF]
2.    Forth to HTML converter
3. 
4.    Main contributors: Brad Eckert, Ed Beroset & Dirk Busch
5.    Revision 4d. See bottom for revision history.
6. 
7.    This ANS Forth program is public domain. It translates ANS Forth to colorized
8.    HTML. Hyperlinks to the ANS Forth draft standard are inserted for all ANS
9.    standard words. Hyperlinks to user definitions are included.
10. 
11.    Usage: HTML FileName    Generates HTML file from Forth source.
12.                            Output file is Filename with .HTM extension.
13.           Q [forth code]   Outputs HTML for 1 line to screen
14. 
15.    Q is used for debugging. You can use "linenum ?" to show the line number if an
16.    ABORT occurs. The HTML is about 10 times as big as the Forth source because of
17.    all the links, color changes and whitespace.
18. 
19.    INCLUDEd files produce corresponding HTML pages. Most browsers get severely
20.    bogged down with large files. If you're converting a large Forth program to
21.    HTML, try to keep the source files under 500 lines each by splitting long
22.    source into multiple INCLUDE files.
23. 
24.    When you INCLUDE this file some redefinition complaints may occur. That's
25.    okay since you won't be loading an application on top of this.
26. 
27.    Users of specific Forths can extend the hyperlink table to point to words
28.    in a glossary for that particular Forth.
29. [THEN]
30. 
31. ONLY FORTH ALSO DEFINITIONS
32. 
33. \ ------------------------------------------------------------------------------
34. \ Configuration - You can change the options:
35. 0 VALUE bold                                      \ T if bold text
36. 1 VALUE italic                                    \ T if italic comments
37. 1 VALUE nestable                                  \ T if INCLUDE nested files
38. 1 VALUE linksource                                \ T link to the org. file /4a/
39. create  dpanspath ," .\win32forth-defs\"          \ path to the ANS-Files   /4a/
40. create  footer    ," "                            \ text to output at       /4a/
41.                                                   \ the bottom of the HTML-file
42. \ ------------------------------------------------------------------------------
43. 
44. : undefined ( <name> -- f ) BL WORD FIND NIP 0= ;
45. undefined C+!    [IF] : C+! SWAP OVER C@ + SWAP C! ;                      [THEN]
46. undefined BOUNDS [IF] : BOUNDS OVER + SWAP ;                              [THEN]
47. undefined SCAN   [IF] : SCAN
48.    >R
49.    BEGIN DUP WHILE OVER C@ R@ <> WHILE 1 /STRING REPEAT THEN
50.    R> DROP ;                                                              [THEN]
51. undefined SKIP   [IF] : SKIP
52.    >R
53.    BEGIN DUP WHILE OVER C@ R@ = WHILE 1 /STRING REPEAT THEN
54.    R> DROP ;                                                              [THEN]
55. undefined NOOP   [IF] : NOOP ;                                            [THEN]
56. undefined +PLACE [IF] : +PLACE 2DUP 2>R COUNT CHARS + SWAP MOVE 2R> C+! ; [THEN]
57. undefined PLACE  [IF] : PLACE  0 OVER C! +PLACE ;                         [THEN]
58. undefined FDROP  [IF] : FDROP ;                                           [THEN]
59. undefined >FLOAT [IF] : >FLOAT DROP C@ [CHAR] 0 [CHAR] 9 1+ WITHIN ;      [THEN]
60. 
61. 0 VALUE outf                                    \ output to file
62. 1 VALUE screen-only                             \ screen is for testing
63. : werr     ( n -- )      ABORT" Error writing file" ;
64. : out      ( a len -- )  screen-only IF TYPE    ELSE outf WRITE-FILE werr THEN ;
65. : outln    ( a len -- )  screen-only IF TYPE CR ELSE outf WRITE-LINE werr THEN ;
66. : ,$       ( a len -- )  DUP C, BOUNDS ?DO I C@ C, LOOP ; \ text to dictionary
67. : text     ( <text> -- ) -1 WORD COUNT -TRAILING ,$ ;
68. : boiler   ( addr -- )   BEGIN COUNT DUP WHILE 2DUP + >R outln R> REPEAT 2DROP ;
69. : html-num ( n -- )      BASE @ >R 0 HEX <# # # # # # # #> out R> BASE ! ;
70. 
71. \ create a named text string terminated by char
72. \ when executed, emits the named text using out
73. : namedtext ( char <name> <text> -- )
74.    CREATE WORD COUNT BL SKIP -TRAILING ,$ \ /4c/
75.    DOES> COUNT out ;
76. 
77. \ new and improved strings are now named
78.    CHAR ! namedtext _<a_href="   <a href="!
79.    CHAR ! namedtext _<a_href="#x <a href="#x!
80.    CHAR ! namedtext _<a_name="x  <a name="x!
81. 
82.    CHAR ! namedtext <span_style="color:# <span style="color:#!
83.    CHAR ! namedtext </span>      </span>!
84.    CHAR ! namedtext <hr>         <hr />!
85.    CHAR ! namedtext </hr>        </hr>!
86.    CHAR ! namedtext <h1>         <h1>!
87.    CHAR ! namedtext </h1>        </h1>!
88.    CHAR ! namedtext <h4>         <h4 style="color:black">!
89.    CHAR ! namedtext </h4>        </h4>!
90.    CHAR ! namedtext <html>       <html>!
91.    CHAR ! namedtext </html>      </html>!
92.    CHAR ! namedtext <head>       <head>!
93.    CHAR ! namedtext </head>      </head>!
94.    CHAR ! namedtext <title>      <title>!
95.    CHAR ! namedtext </title>     </title>!
96.    CHAR ! namedtext <body>       <body>!
97.    CHAR ! namedtext </body>      </body>!
98.    CHAR ! namedtext <p>          <p>!
99.    CHAR ! namedtext </p>         </p>!
100.    CHAR ! namedtext <br>         <br />
101.    CHAR ! namedtext ">           ">!
102. 
103. VARIABLE attrib
104. : <a_href="   ( -- )  _<a_href="   1 attrib ! ;
105. : <a_href="#x ( -- )  _<a_href="#x 1 attrib ! ;
106. : <a_name="x  ( -- )  _<a_name="x  1 attrib ! ;
107. : </a>        ( -- )  attrib @ IF s" </a>" out 0 attrib ! THEN ;
108. : <i>         ( -- )  italic IF s" <i>" out THEN ;
109. : </i>        ( -- )  italic IF s" </i>" out THEN ;
110. : <b>         ( -- )  bold IF s" <b>" out THEN ;
111. : </b>        ( -- )  bold IF s" </b>" out THEN ;
112. 
113. VARIABLE infont                                 \ within <font> tag
114. : fontcolor ( color -- )                        \ change font color
115.    1 infont !
116.    <span_style="color:#   html-num   "> ;
117. 
118. : closefont ( -- )                              \ colse <font> tag
119.    infont @ IF </span> 0 infont ! THEN ;
120. 
121. VARIABLE color                                  \ current color
122. : fcol ( color <name> -- )                      \ define a font color
123.    CREATE , DOES> @ color ! ;
124. 
125. HEX
126. 808080 fcol unknown
127. 008000 fcol commentary
128. CC0000 fcol numeric
129. 990080 fcol values
130. 000000 fcol userwords
131. 009999 fcol userdefiner
132. CC00CC fcol variables
133. 0000FF fcol core_ws
134. 0000FF fcol core_ext_ws
135. 0000FF fcol block_ws
136. 0000FF fcol double_ws
137. 0000FF fcol exception_ws
138. 0000FF fcol facilities_ws
139. 0000FF fcol file_ws
140. 0000FF fcol fp_ws
141. 0000FF fcol local_ws
142. 0000FF fcol malloc_ws
143. 0000FF fcol progtools_ws
144. 0000FF fcol searchord_ws
145. 0000FF fcol string_ws
146. DECIMAL
147. 
148. HEX
149. : setcolor ( -- )                               \ select next color
150.    attrib @ 1 = color @ 0000FF = AND 0=         \ blue link: don't color
151.    DROP TRUE                                    \ /4/ vlinks are still purple
152.    IF color @ fontcolor THEN ;
153. DECIMAL
154. 
155. VARIABLE bltally
156. : outh    ( a n -- )                            \ HTMLized text output
157.    999 bltally !
158.    BOUNDS ?DO I C@ CASE
159.       [CHAR] & OF S" &amp;"     out ENDOF
160.       [CHAR] < OF S" &lt;"      out ENDOF
161.       [CHAR] > OF S" &gt;"      out ENDOF
162.       [CHAR] " OF S" &quot;"    out ENDOF
163.       [CHAR] © OF S" &copy;"    out ENDOF       \ /4a/
164.       BL       OF bltally @ 0= IF S"  " ELSE S" &nbsp;" THEN out
165.                 1 bltally +!     ENDOF
166.       I 1 out   0 bltally !
167.    ENDCASE LOOP ;
168. 
169. : outhattr  ( a n -- )                          \ HTMLized text output
170.    BOUNDS ?DO I C@ CASE
171.       [CHAR] & OF S" amp"       out ENDOF
172.       [CHAR] < OF S" lt"        out ENDOF
173.       [CHAR] > OF S" gt"        out ENDOF
174.       [CHAR] " OF S" quot"      out ENDOF
175.       [CHAR] + OF S" plus"      out ENDOF
176.       [CHAR] ! OF S" bang"      out ENDOF
177.       [CHAR] / OF S" slash"     out ENDOF
178.       [CHAR] \ OF S" backslash" out ENDOF
179.       [CHAR] ' OF S" apos"      out ENDOF
180.       [CHAR] = OF S" equal"     out ENDOF
181.       [CHAR] - OF S" dash"      out ENDOF
182.       [CHAR] @ OF S" at"        out ENDOF
183.       [CHAR] ; OF S" semi"      out ENDOF
184.       [CHAR] * OF S" star"      out ENDOF
185.       [CHAR] ? OF S" question"  out ENDOF
186.       [CHAR] ~ OF S" tilde"     out ENDOF
187.       [CHAR] # OF S" pound"     out ENDOF
188.       [CHAR] , OF S" comma"     out ENDOF
189.       [CHAR] $ OF S" dollar"    out ENDOF
190.       [CHAR] | OF S" bar"       out ENDOF
191.       [CHAR] [ OF S" leftbracket"  out ENDOF
192.       [CHAR] ( OF S" leftparen"    out ENDOF
193.       [CHAR] { OF S" leftbrace"    out ENDOF
194.       [CHAR] ] OF S" rightbracket" out ENDOF
195.       [CHAR] ) OF S" rightparen"   out ENDOF
196.       [CHAR] } OF S" rightbrace"   out ENDOF
197.       BL       OF S" _"            out ENDOF
198.       I 1 out   
199.    ENDCASE LOOP ;
200. 
201. CREATE begin_header                             \ begin of HTML file part 1
202.    text <?xml version="1.0"?>
203.    text <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Strict//EN"
204.    text     "http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd">
205.    text <html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
206.    text <head>
207.    text <meta http-equiv="Content-Type" content="text/xml; charset=iso-8859-1" />
208.    text <meta name="GENERATOR" content="Forth2HTML 0.4" />
209.    text <style type="text/css">
210.    text body {background: #FFFFEE;}
211.    text h1 {color: #000000;}
212.    text p {font-family: monospace;}
213.    text a {text-decoration:none;}
214.    text </style>
215.    text <title>
216.    0 C,
217. 
218. : mid_header ( -- )                             \ begin of HTML file part 2
219.    </title>
220.    </head>
221.    <body>
222. ;
223. 
224. : end_header ( -- )                             \ end of HTML file /4a/
225.    footer COUNT ?DUP IF <hr> <h4> outh </h4> ELSE drop THEN
226.    </body> </html> ;
227. 
228. : label ( addr len -- ) </a>                    \ associate a label with a word
229.    <a_name="x outhattr "> ;
230. 
231. \ Assuming this is running on a PC, we allocate enough storage that crashes from
232. \ string overflows can't happen.                /4/
233. 
234. CREATE inbuf 260 CHARS ALLOT                    \ current line from file
235. CREATE token 260 CHARS ALLOT                    \ the last blank delimited string
236. CREATE XPAD  260 CHARS ALLOT                    \ temporary pad for word storage
237. CREATE EPAD  260 CHARS ALLOT                    \ temporary pad for evaluation
238. CREATE fn    260 CHARS ALLOT                    \ file name
239. CREATE fn1   260 CHARS ALLOT                    \ file name backup
240. CREATE "str" 260 CHARS ALLOT                    \ parsed string storage
241. CREATE uname 260 CHARS ALLOT                    \ : definition name
242. 0 VALUE inf
243. VARIABLE nufile                                 \ T if nesting a file
244. VARIABLE utype                                  \ type of defined word
245. VARIABLE hstate
246. VARIABLE linenum
247. VARIABLE special                                \ special action, 0=none
248. WORDLIST CONSTANT hyperlinks
249. 
250. : std    ( word 2nd_fn color filename label -- )
251.    CREATE ' , ' , BL WORD COUNT ,$ BL WORD COUNT ,$
252.    DOES> </a> DUP >R  2 CELLS +
253.    <a_href="                                    \ begin hyperlink
254.    dpanspath COUNT out                          \ output path to ANS files /4a/
255.    COUNT 2DUP + >R  out S" #" out               \ output file name      /4/
256.    R> COUNT out ">                              \ and anchor name
257.    R> 2@ SWAP EXECUTE EXECUTE ;                 \ extra attributes
258. 
259. : genHTML ( -- )                                \ generate pending HTML
260.    token COUNT DUP IF setcolor THEN outh closefont </a>  0 token ! ;
261. 
262. : isnumber? ( addr len -- f )                   \ string converts to number?
263.    0 0 2SWAP >NUMBER NIP NIP NIP 0= ;
264. 
265. : hparse ( a len char -- a' len' )
266.    >R 2DUP R@ SKIP R> SCAN BL SCAN
267.    2SWAP 2 PICK - token +PLACE ;
268. 
269. : >XPAD ( -- ) token COUNT BL SKIP XPAD PLACE ; \ move to temporary pad
270. 
271. : hint  ( addr len -- )                         \ interpret one line...
272.    BEGIN
273.       0 token !  BL hparse token C@
274.    WHILE unknown                                \ default color
275.       >XPAD XPAD COUNT hyperlinks SEARCH-WORDLIST \ got a hyperlink for this?
276.       IF DEPTH >R EXECUTE
277.          R> DEPTH <> ABORT" stack depth change in HTML generator"
278.       ELSE
279.          XPAD COUNT BASE @ 10 = IF
280.             >FLOAT IF FDROP numeric THEN        \ valid float or integer
281.          ELSE
282.             isnumber? IF numeric THEN
283.          THEN
284.       THEN genHTML
285.    REPEAT 2DROP
286.    <br> ;                                        \ new line
287. 
288. : ofn   ( -- addr len )                         \ output file name
289.    fn COUNT 2DUP [CHAR] . SCAN NIP - EPAD PLACE
290.    S" .htm" EPAD +PLACE   EPAD COUNT ;
291. 
292. : hcreate ( addr len -- )
293.    DUP 0= IF 2DROP S" fakename" THEN            \ in case the name is missing
294.    S" CREATE " EPAD PLACE  EPAD +PLACE
295.    GET-CURRENT >R hyperlinks SET-CURRENT
296.    EPAD COUNT EVALUATE    R> SET-CURRENT ;      \ create a hyperlink generator
297. 
298. \ The user defined words use the following data structure:
299. \ CELL   xt of coloring word
300. \ STRING name of reference word
301. \ STRING name of file
302. 
303. : deflink ( addr -- )                           \ make hyperlink from data structure
304.    DUP @ EXECUTE CELL+                          \ set color
305.    DUP COUNT + COUNT ofn COMPARE                \ in an external file?
306.    IF   <a_href=" DUP COUNT + COUNT out         \ yes, put file name
307.         S" #" out COUNT outh ">
308.    ELSE <a_href="#x COUNT outhattr ">           \ no, just use the name
309.    THEN ;
310. 
311. : defx  ( a len xt -- a' len' )
312.    >R genHTML BL hparse >XPAD                   \ output defining word
313.    XPAD COUNT 2DUP hcreate R> , ,$ ofn ,$
314.    DOES> deflink ;
315. 
316. : labelnow   genHTML XPAD COUNT label ;         \ /4/
317. : defdat ['] numeric   defx numeric   labelnow ;
318. : defvar ['] variables defx variables labelnow ;
319. : defusr ['] userwords defx userwords labelnow ;
320. : defval ['] values    defx values    labelnow ;
321. : defdef ['] userdefiner defx userdefiner labelnow ;
322. 
323. : hstate=0 ( -- )             0 hstate ! ;
324. : hstate=1 ( -- )             1 hstate ! ;
325. : spec=zero ( -- )            1 special ! ;
326. : skip)  ( a len -- a' len' ) [CHAR] ) hparse ;
327. : skip}  ( a len -- a' len' ) [CHAR] } hparse ; \ /4a/
328. : skipw  ( a len -- a' len' ) BL hparse ;
329. : skipc  ( a len -- a len )   hstate @ 0= IF numeric skipw THEN ;
330. : skip"  ( a len -- a' len' )                   \ copy string to "str"
331.    genHTML [CHAR] " hparse token COUNT 1- "str" PLACE ;
332. 
333. \ ------------------------------------------------------------------------------
334. \ ":" definitions might be defining words, so they can't be assumed to be defusr
335. \ types. ":" makes a label and saves the name for later use by ";" which makes
336. \ a hyperlink or a hyperlink defining word.
337. 
338. :NONAME                                         \ normal : definition
339.    uname COUNT ['] userwords defx 2DROP  0 token !
340. ; CONSTANT normal_def
341. 
342. :NONAME
343.    uname COUNT 2DUP hcreate ['] userwords , ,$ ofn ,$
344.    DOES> deflink defdef
345. ; CONSTANT defining_def
346. 
347. : defunk ( a len -- a' len' )                   \ starting unknown definition
348.    hstate=1  normal_def utype !                 \ save name of : definition
349.    genHTML skipw userwords token COUNT BL SKIP 2DUP uname PLACE label ;
350. 
351. : resunk ( -- )                                 \ resolve unknown defined word
352.    genHTML utype @ EXECUTE hstate=0 ;
353. 
354. : created ( -- ) hstate @
355.    IF   defining_def utype !                    \ make ; create a defining word
356.    ELSE defdat                                  \ not compiling
357.    THEN ;
358. 
359. \ ------------------------------------------------------------------------------
360. 
361. : header  ( addr len -- )                       \ output big header text /4b/
362.    <hr> <h1>
363.    linksource
364.    IF   2dup <a_href=" out "> outln </a>
365.    ELSE outln
366.    THEN </h1> <hr> <p> ;
367. 
368. : _incfil ( addr -- )                           \ trigger file nesting      /4/
369.    nestable 0= IF DROP EXIT THEN                \ don't nest files if disabled
370.    COUNT BL SKIP  2DUP R/O OPEN-FILE            \ can the file be opened?
371.    IF   DROP 2DROP                              \ no
372.    ELSE CLOSE-FILE DROP                         \ yes
373.         fn COUNT fn1 PLACE  fn PLACE 1 nufile !
374.    THEN ;
375. 
376. : incfile ( a len -- a' len' )                  \ include a file
377.    genHTML skipw token _incfil ;
378. 
379. : "incfil ( a len -- a' len' )                  \ include file from S" filename"
380.    skipw "str" _incfil ;
381. 
382. : hfill  ( -- len ior )                         \ read next line of file
383.    inbuf 256 BL FILL
384.    XPAD 256 inf READ-LINE ABORT" Error reading file"
385.    >R >R 0 XPAD R> BOUNDS                       ( idx . . )
386.    ?DO  I C@ 9 = IF 3 RSHIFT 1+ 3 LSHIFT        \ tab
387.         ELSE I C@ OVER 255 AND CHARS inbuf + C!
388.            1+ DUP 256 = IF CR ." Input line too long" THEN
389.         THEN
390.    LOOP R>
391.    1 linenum +! ;
392. 
393. : open  ( -- ) CR ." Reading " fn COUNT TYPE ."  at line " linenum @ .
394.    0 linenum !
395.    fn COUNT R/O OPEN-FILE ABORT" Error opening source file" TO inf ;
396. 
397. : close  ( -- ) CR ." closing " fn COUNT TYPE
398.    inf CLOSE-FILE ABORT" Error closing file" ;
399. 
400. : .title ( addr len -- )                        \ output as title string
401.    BOUNDS ?DO I C@ BL = IF S" %20" out ELSE I 1 out THEN LOOP ;
402. 
403. : oopen  ( -- )
404.    ofn W/O CREATE-FILE ABORT" Error creating file" TO outf
405.    begin_header boiler                          \ begin boilerplate
406.    fn COUNT .title  mid_header                  \ title and end boilerplate
407.    <b>
408.    fn COUNT header ;
409. 
410. : HTML  ( <infile> -- )
411.    S" /basic-links/" hyperlinks SEARCH-WORDLIST
412.    IF   EXECUTE  THEN                           \ remove user hyperlinks
413.    GET-CURRENT >R hyperlinks SET-CURRENT        \ replace the fence
414.    S" MARKER /basic-links/" EVALUATE
415.    R> SET-CURRENT
416.    0 TO screen-only  0 nufile !  1 linenum !    \ force usage of file
417.    0 infont ! 0 attrib !                        \ /4b/ /4d/
418.    BL WORD COUNT fn PLACE open oopen            \ open input and output files
419.    -1 DUP >R outf >R                            \ file nest uses stacks
420.    hstate=0
421.    BEGIN
422.       BEGIN 0 special !                         \ process line
423.          nufile @                               \ nest a file?
424.          IF   inf outf
425.               open oopen  outf >R               \ open new files
426.               0 nufile !
427.          THEN hfill
428.       WHILE inbuf SWAP hint
429.       REPEAT DROP
430.       close fn1 COUNT fn PLACE                  \ restore file name
431.       DUP -1 <>
432.       IF   TO outf TO inf FALSE                 \ unnest files
433.       ELSE TRUE
434.       THEN
435.    UNTIL DROP
436.    BEGIN R> DUP -1 <>                            \ close all output files
437.    WHILE </p> </b>                               \ /4b/
438.       end_header                                 \ finish up HTML
439.       CLOSE-FILE ABORT" Error closing file"
440.    REPEAT DROP ;
441. 
442. : q  ( -- ) 1 TO screen-only                    \ single line test
443.    -1 WORD COUNT inbuf PLACE inbuf COUNT hint ;
444. 
445. \ 0 [IF] is often used as a comment. If it is used as a comment, scan the file
446. \ for a [THEN]. [THEN] must be on the next line or beyond.
447. 
448. : upp ( an--) BOUNDS ?DO I C@ [CHAR] a > IF I C@ 32 - I C! THEN LOOP \ uppercase
449. ;
450. 
451. CREATE terminator 16 CHARS ALLOT                \ multiline comment terminator
452. 
453. : multicomment ( a len searchstring -- a' len' )
454.    terminator PLACE
455.    genHTML <i> commentary setcolor outh       \ finish up this line /4b/
456.    BEGIN hfill      <br>
457.    WHILE >R inbuf EPAD R@ MOVE
458.       EPAD R@ upp                               \ uppercase for search
459.       EPAD R@ terminator COUNT SEARCH
460.       IF   DROP EPAD - inbuf OVER token PLACE   \ before [THEN] is comment
461.            genHTML
462.            inbuf R> ROT /STRING
463.            </i> closefont EXIT
464.       ELSE 2DROP inbuf R> outh                  \ whole line is comment
465.       THEN
466.    REPEAT inbuf SWAP </i> closefont ;          \ EOF found
467. 
468. : bigif  ( a len -- a len )  special @ 1 =
469.    IF S" [THEN]" multicomment THEN ;
470. 
471. \ =============================================================================
472. 
473. : _DEFINITIONS DEFINITIONS ;
474. : _order order ;  : _words words ; : _see see ;
475. 
476. hyperlinks SET-CURRENT
477. \ The following words are not in the ANS standard but are very common.
478. : VOCABULARY    defusr ;
479. : DEFER         defusr ;
480. : INCLUDE       hstate @ 0= IF incfile THEN ;
481. : FLOAD         hstate @ 0= IF incfile THEN ;
482. : BINARY        2 BASE ! ;
483. : OCTAL         8 BASE ! ;
484. : 0             numeric spec=zero ;
485. : 1             numeric  ;
486. : -1            numeric  ;
487. : COMMENT:      S" COMMENT;" multicomment ;
488. : ((            S" ))"       multicomment ;
489. 
490. \ The following words are not in the ANS standard but are used in Win32Forth
491. : ANEW          skipw ;                    \ /4a/
492. : {             commentary genHTML skip} ; \ /4a/
493. : CallBack:     defunk ;                   \ /4a/
494. : :M            defunk ;                   \ /4a/
495. : ;M            resunk ;                   \ /4a/
496. 
497. \ The rest is ANS Forth standard
498. 
499. : \             commentary <i> genHTML token PLACE genHTML </i> token 0 ;
500. 
501. (   NAME                ACTION  COLOR           FILENAME        REFERENCE )
502. (   ------------------  ------  --------------  -----------     --------- )
503. std !                   NOOP    core_ws         dpans6.htm      6.1.0010
504. std #                   NOOP    core_ws         dpans6.htm      6.1.0030
505. std #>                  NOOP    core_ws         dpans6.htm      6.1.0040
506. std #S                  NOOP    core_ws         dpans6.htm      6.1.0050
507. std '                   NOOP    core_ws         dpans6.htm      6.1.0070
508. std (                   skip)   commentary      dpans6.htm      6.1.0080
509. std *                   NOOP    core_ws         dpans6.htm      6.1.0090
510. std */                  NOOP    core_ws         dpans6.htm      6.1.0100
511. std */MOD               NOOP    core_ws         dpans6.htm      6.1.0110
512. std +                   NOOP    core_ws         dpans6.htm      6.1.0120
513. std +!                  NOOP    core_ws         dpans6.htm      6.1.0130
514. std +LOOP               NOOP    core_ws         dpans6.htm      6.1.0140
515. std ,                   NOOP    core_ws         dpans6.htm      6.1.0150
516. std -                   NOOP    core_ws         dpans6.htm      6.1.0160
517. std .                   NOOP    core_ws         dpans6.htm      6.1.0180
518. std ."                  skip"   numeric         dpans6.htm      6.1.0190
519. std /                   NOOP    core_ws         dpans6.htm      6.1.0230
520. std /MOD                NOOP    core_ws         dpans6.htm      6.1.0240
521. std 0<                  NOOP    core_ws         dpans6.htm      6.1.0250
522. std 0=                  NOOP    core_ws         dpans6.htm      6.1.0270
523. std 1+                  NOOP    core_ws         dpans6.htm      6.1.0290
524. std 1-                  NOOP    core_ws         dpans6.htm      6.1.0300
525. std 2!                  NOOP    core_ws         dpans6.htm      6.1.0310
526. std 2*                  NOOP    core_ws         dpans6.htm      6.1.0320
527. std 2/                  NOOP    core_ws         dpans6.htm      6.1.0330
528. std 2@                  NOOP    core_ws         dpans6.htm      6.1.0350
529. std 2DROP               NOOP    core_ws         dpans6.htm      6.1.0370
530. std 2DUP                NOOP    core_ws         dpans6.htm      6.1.0380
531. std 2OVER               NOOP    core_ws         dpans6.htm      6.1.0400
532. std 2SWAP               NOOP    core_ws         dpans6.htm      6.1.0430
533. std :                   defunk  core_ws         dpans6.htm      6.1.0450
534. std ;                   resunk  core_ws         dpans6.htm      6.1.0460
535. std <                   NOOP    core_ws         dpans6.htm      6.1.0480
536. std <#                  NOOP    core_ws         dpans6.htm      6.1.0490
537. std =                   NOOP    core_ws         dpans6.htm      6.1.0530
538. std >                   NOOP    core_ws         dpans6.htm      6.1.0540
539. std >BODY               NOOP    core_ws         dpans6.htm      6.1.0550
540. std >IN                 NOOP    core_ws         dpans6.htm      6.1.0560
541. std >NUMBER             NOOP    core_ws         dpans6.htm      6.1.0570
542. std >R                  NOOP    core_ws         dpans6.htm      6.1.0580
543. std ?DUP                NOOP    core_ws         dpans6.htm      6.1.0630
544. std @                   NOOP    core_ws         dpans6.htm      6.1.0650
545. std ABORT               NOOP    core_ws         dpans6.htm      6.1.0670
546. std ABORT"              skip"   numeric         dpans6.htm      6.1.0680
547. std ABS                 NOOP    core_ws         dpans6.htm      6.1.0690
548. std ACCEPT              NOOP    core_ws         dpans6.htm      6.1.0695
549. std ALIGN               NOOP    core_ws         dpans6.htm      6.1.0705
550. std ALIGNED             NOOP    core_ws         dpans6.htm      6.1.0706
551. std ALLOT               NOOP    core_ws         dpans6.htm      6.1.0710
552. std AND                 NOOP    core_ws         dpans6.htm      6.1.0720
553. std BASE                NOOP    core_ws         dpans6.htm      6.1.0750
554. std BEGIN               NOOP    core_ws         dpans6.htm      6.1.0760
555. std BL                  NOOP    numeric         dpans6.htm      6.1.0770
556. std C!                  NOOP    core_ws         dpans6.htm      6.1.0850
557. std C,                  NOOP    core_ws         dpans6.htm      6.1.0860
558. std C@                  NOOP    core_ws         dpans6.htm      6.1.0870
559. std CELL+               NOOP    core_ws         dpans6.htm      6.1.0880
560. std CELLS               NOOP    core_ws         dpans6.htm      6.1.0890
561. std CHAR                skipc   core_ws         dpans6.htm      6.1.0895
562. std CHAR+               NOOP    core_ws         dpans6.htm      6.1.0897
563. std CHARS               NOOP    core_ws         dpans6.htm      6.1.0898
564. std CONSTANT            defdat  core_ws         dpans6.htm      6.1.0950
565. std COUNT               NOOP    core_ws         dpans6.htm      6.1.0980
566. std CR                  NOOP    core_ws         dpans6.htm      6.1.0990
567. std CREATE              created core_ws         dpans6.htm      6.1.1000
568. std DECIMAL             DECIMAL core_ws         dpans6.htm      6.1.1170
569. std DEPTH               NOOP    core_ws         dpans6.htm      6.1.1200
570. std DO                  NOOP    core_ws         dpans6.htm      6.1.1240
571. std DOES>               NOOP    core_ws         dpans6.htm      6.1.1250
572. std DROP                NOOP    core_ws         dpans6.htm      6.1.1260
573. std DUP                 NOOP    core_ws         dpans6.htm      6.1.1290
574. std ELSE                NOOP    core_ws         dpans6.htm      6.1.1310
575. std EMIT                NOOP    core_ws         dpans6.htm      6.1.1320
576. std ENVIRONMENT?        NOOP    core_ws         dpans6.htm      6.1.1345
577. std EVALUATE            NOOP    core_ws         dpans6.htm      6.1.1360
578. std EXECUTE             NOOP    core_ws         dpans6.htm      6.1.1370
579. std EXIT                NOOP    core_ws         dpans6.htm      6.1.1380
580. std FILL                NOOP    core_ws         dpans6.htm      6.1.1540
581. std FIND                NOOP    core_ws         dpans6.htm      6.1.1550
582. std FM/MOD              NOOP    core_ws         dpans6.htm      6.1.1561
583. std HERE                NOOP    core_ws         dpans6.htm      6.1.1650
584. std HOLD                NOOP    core_ws         dpans6.htm      6.1.1670
585. std I                   NOOP    core_ws         dpans6.htm      6.1.1680
586. std IF                  NOOP    core_ws         dpans6.htm      6.1.1700
587. std IMMEDIATE           NOOP    core_ws         dpans6.htm      6.1.1710
588. std INVERT              NOOP    core_ws         dpans6.htm      6.1.1720
589. std J                   NOOP    core_ws         dpans6.htm      6.1.1730
590. std KEY                 NOOP    core_ws         dpans6.htm      6.1.1750
591. std LEAVE               NOOP    core_ws         dpans6.htm      6.1.1760
592. std LITERAL             NOOP    core_ws         dpans6.htm      6.1.1780
593. std LOOP                NOOP    core_ws         dpans6.htm      6.1.1800
594. std LSHIFT              NOOP    core_ws         dpans6.htm      6.1.1805
595. std M*                  NOOP    core_ws         dpans6.htm      6.1.1810
596. std MAX                 NOOP    core_ws         dpans6.htm      6.1.1870
597. std MIN                 NOOP    core_ws         dpans6.htm      6.1.1880
598. std MOD                 NOOP    core_ws         dpans6.htm      6.1.1890
599. std MOVE                NOOP    core_ws         dpans6.htm      6.1.1900
600. std NEGATE              NOOP    core_ws         dpans6.htm      6.1.1910
601. std OR                  NOOP    core_ws         dpans6.htm      6.1.1980
602. std OVER                NOOP    core_ws         dpans6.htm      6.1.1990
603. std POSTPONE            NOOP    core_ws         dpans6.htm      6.1.2033
604. std QUIT                NOOP    core_ws         dpans6.htm      6.1.2050
605. std R>                  NOOP    core_ws         dpans6.htm      6.1.2060
606. std R@                  NOOP    core_ws         dpans6.htm      6.1.2070
607. std RECURSE             NOOP    core_ws         dpans6.htm      6.1.2120
608. std REPEAT              NOOP    core_ws         dpans6.htm      6.1.2140
609. std ROT                 NOOP    core_ws         dpans6.htm      6.1.2160
610. std RSHIFT              NOOP    core_ws         dpans6.htm      6.1.2162
611. std S"                  skip"   numeric         dpans6.htm      6.1.2165
612. std S>D                 NOOP    core_ws         dpans6.htm      6.1.2170
613. std SIGN                NOOP    core_ws         dpans6.htm      6.1.2210
614. std SM/REM              NOOP    core_ws         dpans6.htm      6.1.2214
615. std SOURCE              NOOP    core_ws         dpans6.htm      6.1.2216
616. std SPACE               NOOP    core_ws         dpans6.htm      6.1.2220
617. std SPACES              NOOP    core_ws         dpans6.htm      6.1.2230
618. std STATE               NOOP    core_ws         dpans6.htm      6.1.2250
619. std SWAP                NOOP    core_ws         dpans6.htm      6.1.2260
620. std THEN                NOOP    core_ws         dpans6.htm      6.1.2270
621. std TYPE                NOOP    core_ws         dpans6.htm      6.1.2310
622. std U.                  NOOP    core_ws         dpans6.htm      6.1.2320
623. std U<                  NOOP    core_ws         dpans6.htm      6.1.2340
624. std UM*                 NOOP    core_ws         dpans6.htm      6.1.2360
625. std UM/MOD              NOOP    core_ws         dpans6.htm      6.1.2370
626. std UNLOOP              NOOP    core_ws         dpans6.htm      6.1.2380
627. std UNTIL               NOOP    core_ws         dpans6.htm      6.1.2390
628. std VARIABLE            defvar  core_ws         dpans6.htm      6.1.2410
629. std WHILE               NOOP    core_ws         dpans6.htm      6.1.2430
630. std WORD                NOOP    core_ws         dpans6.htm      6.1.2450
631. std XOR                 NOOP    core_ws         dpans6.htm      6.1.2490
632. std [                  hstate=0 core_ws         dpans6.htm      6.1.2500
633. std [']                 skipw   numeric         dpans6.htm      6.1.2510
634. std [CHAR]              skipw   numeric         dpans6.htm      6.1.2520
635. std ]                  hstate=1 core_ws         dpans6.htm      6.1.2540
636. std #TIB                NOOP    core_ext_ws     dpans6.htm      6.2.0060
637. std .(                  skip)   commentary      dpans6.htm      6.2.0200
638. std .R                  NOOP    core_ext_ws     dpans6.htm      6.2.0210
639. std 0<>                 NOOP    core_ext_ws     dpans6.htm      6.2.0260
640. std 0>                  NOOP    core_ext_ws     dpans6.htm      6.2.0280
641. std 2>R                 NOOP    core_ext_ws     dpans6.htm      6.2.0340
642. std 2R>                 NOOP    core_ext_ws     dpans6.htm      6.2.0410
643. std 2R@                 NOOP    core_ext_ws     dpans6.htm      6.2.0415
644. std :NONAME             NOOP    core_ext_ws     dpans6.htm      6.2.0455
645. std <>                  NOOP    core_ext_ws     dpans6.htm      6.2.0500
646. std ?DO                 NOOP    core_ext_ws     dpans6.htm      6.2.0620
647. std AGAIN               NOOP    core_ext_ws     dpans6.htm      6.2.0700
648. std C"                  skip"   numeric         dpans6.htm      6.2.0855
649. std CASE                NOOP    core_ext_ws     dpans6.htm      6.2.0873
650. std COMPILE,            NOOP    core_ext_ws     dpans6.htm      6.2.0945
651. std CONVERT             NOOP    core_ext_ws     dpans6.htm      6.2.0970
652. std ENDCASE             NOOP    core_ext_ws     dpans6.htm      6.2.1342
653. std ENDOF               NOOP    core_ext_ws     dpans6.htm      6.2.1343
654. std ERASE               NOOP    core_ext_ws     dpans6.htm      6.2.1350
655. std EXPECT              NOOP    core_ext_ws     dpans6.htm      6.2.1390
656. std FALSE             spec=zero numeric         dpans6.htm      6.2.1485
657. std HEX                 HEX     core_ext_ws     dpans6.htm      6.2.1660
658. std MARKER              defusr  core_ext_ws     dpans6.htm      6.2.1850
659. std NIP                 NOOP    core_ext_ws     dpans6.htm      6.2.1930
660. std OF                  NOOP    core_ext_ws     dpans6.htm      6.2.1950
661. std PAD                 NOOP    core_ext_ws     dpans6.htm      6.2.2000
662. std PARSE               NOOP    core_ext_ws     dpans6.htm      6.2.2008
663. std PICK                NOOP    core_ext_ws     dpans6.htm      6.2.2030
664. std QUERY               NOOP    core_ext_ws     dpans6.htm      6.2.2040
665. std REFILL              NOOP    core_ext_ws     dpans6.htm      6.2.2125
666. std RESTORE-INPUT       NOOP    core_ext_ws     dpans6.htm      6.2.2148
667. std ROLL                NOOP    core_ext_ws     dpans6.htm      6.2.2150
668. std SAVE-INPUT          NOOP    core_ext_ws     dpans6.htm      6.2.2182
669. std SOURCE-ID           NOOP    core_ext_ws     dpans6.htm      6.2.2218
670. std SPAN                NOOP    core_ext_ws     dpans6.htm      6.2.2240
671. std TIB                 NOOP    core_ext_ws     dpans6.htm      6.2.2290
672. std TO                  NOOP    core_ext_ws     dpans6.htm      6.2.2295
673. std TRUE                NOOP    numeric         dpans6.htm      6.2.2298
674. std TUCK                NOOP    core_ext_ws     dpans6.htm      6.2.2300
675. std U.R                 NOOP    core_ext_ws     dpans6.htm      6.2.2330
676. std U>                  NOOP    core_ext_ws     dpans6.htm      6.2.2350
677. std UNUSED              NOOP    core_ext_ws     dpans6.htm      6.2.2395
678. std VALUE               defval  core_ext_ws     dpans6.htm      6.2.2405
679. std WITHIN              NOOP    core_ext_ws     dpans6.htm      6.2.2440
680. std [COMPILE]           NOOP    core_ext_ws     dpans6.htm      6.2.2530
681. std BLK                 NOOP    block_ws        dpans7.htm      7.6.1.0790
682. std BLOCK               NOOP    block_ws        dpans7.htm      7.6.1.0800
683. std BUFFER              NOOP    block_ws        dpans7.htm      7.6.1.0820
684. std FLUSH               NOOP    block_ws        dpans7.htm      7.6.1.1559
685. std LOAD                NOOP    block_ws        dpans7.htm      7.6.1.1790
686. std SAVE-BUFFERS        NOOP    block_ws        dpans7.htm      7.6.1.2180
687. std UPDATE              NOOP    block_ws        dpans7.htm      7.6.1.2400
688. std EMPTY-BUFFERS       NOOP    block_ws        dpans7.htm      7.6.2.1330
689. std LIST                NOOP    block_ws        dpans7.htm      7.6.2.1770
690. std SCR                 NOOP    block_ws        dpans7.htm      7.6.2.2190
691. std THRU                NOOP    block_ws        dpans7.htm      7.6.2.2280
692. std 2CONSTANT           defdat  double_ws       dpans8.htm      8.6.1.0360
693. std 2LITERAL            NOOP    double_ws       dpans8.htm      8.6.1.0390
694. std 2VARIABLE           defvar  double_ws       dpans8.htm      8.6.1.0440
695. std D+                  NOOP    double_ws       dpans8.htm      8.6.1.1040
696. std D-                  NOOP    double_ws       dpans8.htm      8.6.1.1050
697. std D.                  NOOP    double_ws       dpans8.htm      8.6.1.1060
698. std D.R                 NOOP    double_ws       dpans8.htm      8.6.1.1070
699. std D0<                 NOOP    double_ws       dpans8.htm      8.6.1.1075
700. std D0=                 NOOP    double_ws       dpans8.htm      8.6.1.1080
701. std D2*                 NOOP    double_ws       dpans8.htm      8.6.1.1090
702. std D2/                 NOOP    double_ws       dpans8.htm      8.6.1.1100
703. std D<                  NOOP    double_ws       dpans8.htm      8.6.1.1110
704. std D=                  NOOP    double_ws       dpans8.htm      8.6.1.1120
705. std D>S                 NOOP    double_ws       dpans8.htm      8.6.1.1140
706. std DABS                NOOP    double_ws       dpans8.htm      8.6.1.1160
707. std DMAX                NOOP    double_ws       dpans8.htm      8.6.1.1210
708. std DMIN                NOOP    double_ws       dpans8.htm      8.6.1.1220
709. std DNEGATE             NOOP    double_ws       dpans8.htm      8.6.1.1230
710. std M*/                 NOOP    double_ws       dpans8.htm      8.6.1.1820
711. std M+                  NOOP    double_ws       dpans8.htm      8.6.1.1830
712. std 2ROT                NOOP    double_ws       dpans8.htm      8.6.2.0420
713. std DU<                 NOOP    double_ws       dpans8.htm      8.6.2.1270
714. std CATCH               NOOP    exception_ws    dpans9.htm      9.6.1.0875
715. std THROW               NOOP    exception_ws    dpans9.htm      9.6.1.2275
716. std AT-XY               NOOP    facilities_ws   dpans10.htm     10.6.1.0742
717. std KEY?                NOOP    facilities_ws   dpans10.htm     10.6.1.1755
718. std PAGE                NOOP    facilities_ws   dpans10.htm     10.6.1.2005
719. std EKEY                NOOP    facilities_ws   dpans10.htm     10.6.2.1305
720. std EKEY<CHAR           NOOP    facilities_ws   dpans10.htm     10.6.2.1306
721. std EKEY?               NOOP    facilities_ws   dpans10.htm     10.6.2.1307
722. std EMIT?               NOOP    facilities_ws   dpans10.htm     10.6.2.1325
723. std MS                  NOOP    facilities_ws   dpans10.htm     10.6.2.1905
724. std TIME&DATE           NOOP    facilities_ws   dpans10.htm     10.6.2.2292
725. std BIN                 NOOP    file_ws         dpans11.htm     11.6.1.0765
726. std CLOSE-FILE          NOOP    file_ws         dpans11.htm     11.6.1.0900
727. std CREATE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.1010
728. std DELETE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.1190
729. std FILE-POSITION       NOOP    file_ws         dpans11.htm     11.6.1.1520
730. std FILE-SIZE           NOOP    file_ws         dpans11.htm     11.6.1.1522
731. std INCLUDE-FILE        NOOP    file_ws         dpans11.htm     11.6.1.1717
732. std INCLUDED            "incfil file_ws         dpans11.htm     11.6.1.1718
733. std OPEN-FILE           NOOP    file_ws         dpans11.htm     11.6.1.1970
734. std R/O                 NOOP    file_ws         dpans11.htm     11.6.1.2054
735. std R/W                 NOOP    file_ws         dpans11.htm     11.6.1.2056
736. std READ-FILE           NOOP    file_ws         dpans11.htm     11.6.1.2080
737. std READ-LINE           NOOP    file_ws         dpans11.htm     11.6.1.2090
738. std REPOSITION-FILE     NOOP    file_ws         dpans11.htm     11.6.1.2142
739. std RESIZE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.2147
740. std W/O                 NOOP    file_ws         dpans11.htm     11.6.1.2425
741. std WRITE-FILE          NOOP    file_ws         dpans11.htm     11.6.1.2480
742. std WRITE-LINE          NOOP    file_ws         dpans11.htm     11.6.1.2485
743. std FILE-STATUS         NOOP    file_ws         dpans11.htm     11.6.2.1524
744. std FLUSH-FILE          NOOP    file_ws         dpans11.htm     11.6.2.1560
745. std RENAME-FILE         NOOP    file_ws         dpans11.htm     11.6.2.2130
746. std >FLOAT              NOOP    fp_ws           dpans12.htm     12.6.1.0558
747. std D>F                 NOOP    fp_ws           dpans12.htm     12.6.1.1130
748. std F!                  NOOP    fp_ws           dpans12.htm     12.6.1.1400
749. std F*                  NOOP    fp_ws           dpans12.htm     12.6.1.1410
750. std F+                  NOOP    fp_ws           dpans12.htm     12.6.1.1420
751. std F-                  NOOP    fp_ws           dpans12.htm     12.6.1.1425
752. std F/                  NOOP    fp_ws           dpans12.htm     12.6.1.1430
753. std F0<                 NOOP    fp_ws           dpans12.htm     12.6.1.1440
754. std F0=                 NOOP    fp_ws           dpans12.htm     12.6.1.1450
755. std F<                  NOOP    fp_ws           dpans12.htm     12.6.1.1460
756. std F>D                 NOOP    fp_ws           dpans12.htm     12.6.1.1460
757. std F@                  NOOP    fp_ws           dpans12.htm     12.6.1.1472
758. std FALIGN              NOOP    fp_ws           dpans12.htm     12.6.1.1479
759. std FALIGNED            NOOP    fp_ws           dpans12.htm     12.6.1.1483
760. std FCONSTANT           defdat  fp_ws           dpans12.htm     12.6.1.1492
761. std FDEPTH              NOOP    fp_ws           dpans12.htm     12.6.1.1497
762. std FDROP               NOOP    fp_ws           dpans12.htm     12.6.1.1500
763. std FDUP                NOOP    fp_ws           dpans12.htm     12.6.1.1510
764. std FLITERAL            NOOP    fp_ws           dpans12.htm     12.6.1.1552
765. std FLOAT+              NOOP    fp_ws           dpans12.htm     12.6.1.1555
766. std FLOATS              NOOP    fp_ws           dpans12.htm     12.6.1.1556
767. std FLOOR               NOOP    fp_ws           dpans12.htm     12.6.1.1558
768. std FMAX                NOOP    fp_ws           dpans12.htm     12.6.1.1562
769. std FMIN                NOOP    fp_ws           dpans12.htm     12.6.1.1565
770. std FNEGATE             NOOP    fp_ws           dpans12.htm     12.6.1.1567
771. std FOVER               NOOP    fp_ws           dpans12.htm     12.6.1.1600
772. std FROT                NOOP    fp_ws           dpans12.htm     12.6.1.1610
773. std FROUND              NOOP    fp_ws           dpans12.htm     12.6.1.1612
774. std FSWAP               NOOP    fp_ws           dpans12.htm     12.6.1.1620
775. std FVARIABLE           defvar  fp_ws           dpans12.htm     12.6.1.1630
776. std REPRESENT           NOOP    fp_ws           dpans12.htm     12.6.1.2143
777. std DF!                 NOOP    fp_ws           dpans12.htm     12.6.2.1203
778. std DF@                 NOOP    fp_ws           dpans12.htm     12.6.2.1204
779. std DFALIGN             NOOP    fp_ws           dpans12.htm     12.6.2.1205
780. std DFALIGNED           NOOP    fp_ws           dpans12.htm     12.6.2.1207
781. std DFLOAT+             NOOP    fp_ws           dpans12.htm     12.6.2.1208
782. std DFLOATS             NOOP    fp_ws           dpans12.htm     12.6.2.1209
783. std F**                 NOOP    fp_ws           dpans12.htm     12.6.2.1415
784. std F.                  NOOP    fp_ws           dpans12.htm     12.6.2.1427
785. std FABS                NOOP    fp_ws           dpans12.htm     12.6.2.1474
786. std FACOS               NOOP    fp_ws           dpans12.htm     12.6.2.1476
787. std FACOSH              NOOP    fp_ws           dpans12.htm     12.6.2.1477
788. std FALOG               NOOP    fp_ws           dpans12.htm     12.6.2.1484
789. std FASIN               NOOP    fp_ws           dpans12.htm     12.6.2.1486
790. std FASINH              NOOP    fp_ws           dpans12.htm     12.6.2.1487
791. std FATAN               NOOP    fp_ws           dpans12.htm     12.6.2.1488
792. std FATAN2              NOOP    fp_ws           dpans12.htm     12.6.2.1489
793. std FATANH              NOOP    fp_ws           dpans12.htm     12.6.2.1491
794. std FCOS                NOOP    fp_ws           dpans12.htm     12.6.2.1493
795. std FCOSH               NOOP    fp_ws           dpans12.htm     12.6.2.1494
796. std FE.                 NOOP    fp_ws           dpans12.htm     12.6.2.1513
797. std FEXP                NOOP    fp_ws           dpans12.htm     12.6.2.1515
798. std FEXPM1              NOOP    fp_ws           dpans12.htm     12.6.2.1516
799. std FLN                 NOOP    fp_ws           dpans12.htm     12.6.2.1553
800. std FLNP1               NOOP    fp_ws           dpans12.htm     12.6.2.1554
801. std FLOG                NOOP    fp_ws           dpans12.htm     12.6.2.1557
802. std FS.                 NOOP    fp_ws           dpans12.htm     12.6.2.1613
803. std FSIN                NOOP    fp_ws           dpans12.htm     12.6.2.1614
804. std FSINCOS             NOOP    fp_ws           dpans12.htm     12.6.2.1616
805. std FSINH               NOOP    fp_ws           dpans12.htm     12.6.2.1617
806. std FSQRT               NOOP    fp_ws           dpans12.htm     12.6.2.1618
807. std FTAN                NOOP    fp_ws           dpans12.htm     12.6.2.1625
808. std FTANH               NOOP    fp_ws           dpans12.htm     12.6.2.1626
809. std F~                  NOOP    fp_ws           dpans12.htm     12.6.2.1640
810. std PRECISION           NOOP    fp_ws           dpans12.htm     12.6.2.2035
811. std SET-PRECISION       NOOP    fp_ws           dpans12.htm     12.6.2.2200
812. std SF!                 NOOP    fp_ws           dpans12.htm     12.6.2.2202
813. std SF@                 NOOP    fp_ws           dpans12.htm     12.6.2.2203
814. std SFALIGN             NOOP    fp_ws           dpans12.htm     12.6.2.2204
815. std SFALIGNED           NOOP    fp_ws           dpans12.htm     12.6.2.2206
816. std SFLOAT+             NOOP    fp_ws           dpans12.htm     12.6.2.2207
817. std SFLOATS             NOOP    fp_ws           dpans12.htm     12.6.2.2208
818. std (LOCAL)             NOOP    local_ws        dpans13.htm     13.6.1.0086
819. std LOCALS|             NOOP    local_ws        dpans13.htm     13.6.2.1795
820. std ALLOCATE            NOOP    malloc_ws       dpans14.htm     14.6.1.0707
821. std FREE                NOOP    malloc_ws       dpans14.htm     14.6.1.1605
822. std RESIZE              NOOP    malloc_ws       dpans14.htm     14.6.1.2145
823. std .S                  NOOP    progtools_ws    dpans15.htm     15.6.1.0220
824. std ?                   NOOP    progtools_ws    dpans15.htm     15.6.1.0600
825. std DUMP                NOOP    progtools_ws    dpans15.htm     15.6.1.1280
826. std SEE                 NOOP    progtools_ws    dpans15.htm     15.6.1.2194
827. std WORDS               NOOP    progtools_ws    dpans15.htm     15.6.1.2465
828. std ;CODE               resunk  progtools_ws    dpans15.htm     15.6.2.0470
829. std AHEAD               NOOP    progtools_ws    dpans15.htm     15.6.2.0702
830. std ASSEMBLER           NOOP    progtools_ws    dpans15.htm     15.6.2.0740
831. std BYE                 NOOP    progtools_ws    dpans15.htm     15.6.2.0830
832. std CODE                defusr  progtools_ws    dpans15.htm     15.6.2.0930
833. std CS-PICK             NOOP    progtools_ws    dpans15.htm     15.6.2.1015
834. std CS-ROLL             NOOP    progtools_ws    dpans15.htm     15.6.2.1020
835. std EDITOR              NOOP    progtools_ws    dpans15.htm     15.6.2.1300
836. std FORGET              NOOP    progtools_ws    dpans15.htm     15.6.2.1580
837. std [ELSE]              NOOP    progtools_ws    dpans15.htm     15.6.2.2531
838. std [IF]                bigif   progtools_ws    dpans15.htm     15.6.2.2532
839. std [THEN]              NOOP    progtools_ws    dpans15.htm     15.6.2.2533
840. std DEFINITIONS         NOOP    searchord_ws    dpans16.htm     16.6.1.1180
841. std FORTH-WORDLIST      NOOP    searchord_ws    dpans16.htm     16.6.1.1595
842. std GET-CURRENT         NOOP    searchord_ws    dpans16.htm     16.6.1.1643
843. std GET-ORDER           NOOP    searchord_ws    dpans16.htm     16.6.1.1647
844. std SEARCH-WORDLIST     NOOP    searchord_ws    dpans16.htm     16.6.1.2192
845. std SET-CURRENT         NOOP    searchord_ws    dpans16.htm     16.6.1.2195
846. std SET-ORDER           NOOP    searchord_ws    dpans16.htm     16.6.1.2197
847. std WORDLIST            NOOP    searchord_ws    dpans16.htm     16.6.1.2460
848. std ALSO                NOOP    searchord_ws    dpans16.htm     16.6.2.0715
849. std FORTH               NOOP    searchord_ws    dpans16.htm     16.6.2.1590
850. std ONLY                NOOP    searchord_ws    dpans16.htm     16.6.2.1965
851. std ORDER               NOOP    searchord_ws    dpans16.htm     16.6.2.1985
852. std PREVIOUS            NOOP    searchord_ws    dpans16.htm     16.6.2.2037
853. std -TRAILING           NOOP    string_ws       dpans17.htm     17.6.1.0170
854. std /STRING             NOOP    string_ws       dpans17.htm     17.6.1.0245
855. std BLANK               NOOP    string_ws       dpans17.htm     17.6.1.0780
856. std CMOVE               NOOP    string_ws       dpans17.htm     17.6.1.0910
857. std CMOVE>              NOOP    string_ws       dpans17.htm     17.6.1.0920
858. std COMPARE             NOOP    string_ws       dpans17.htm     17.6.1.0935
859. std SEARCH              NOOP    string_ws       dpans17.htm     17.6.1.2191
860. std SLITERAL            NOOP    string_ws       dpans17.htm     17.6.1.2212
861. 
862. _DEFINITIONS
863. 
864. \ Revision history
865. \ 0. 1st release to guinea pigs via comp.lang.forth
866. \ 1. Added multi-line comment 0 [IF]. Colored CHAR outside definitions.
867. \ 2. (EJB) Added missing definitions for common but nonstandard words
868. \    and cleaned up to account for case sensitivity.
869. \ 3. (EJB) Fixed up to create conforming XHTML 1.0 Strict
870. \ 4. (BNE) File check before nesting, moved file names to the hyperlink table,
871. \    added some option flags, cleared hyperlink list for each run. Added more
872. \    multiline comment words. Expands tabs to spaces. Title uses %20 for blanks.
873. \ 4a. (DBU) Added dpanspath to configure the path to the dpans-files. Added
874. \     linksource to output a hyperlink to the original source file. Added
875. \     some words used in Win32Forth. Added copyright to output a copyright text
876. \     at the bottom of the HTML-file.
877. \ 4b. (DBU) Fixed some HTML-Error's found with "CSE HTML Validator Lite v3.50"
878. \ 4c. (EJB/DBU) Consolidated some strings
879. \ 4d. (DBU) Cleanup of 4c and renaming copyright to footer 
1. 0 [IF]
2.    Forth to HTML converter
3. 
4.    Main contributors: Brad Eckert, Ed Beroset & Dirk Busch
5.    Revision 4d. See bottom for revision history.
6. 
7.    This ANS Forth program is public domain. It translates ANS Forth to colorized
8.    HTML. Hyperlinks to the ANS Forth draft standard are inserted for all ANS
9.    standard words. Hyperlinks to user definitions are included.
10. 
11.    Usage: HTML FileName    Generates HTML file from Forth source.
12.                            Output file is Filename with .HTM extension.
13.           Q [forth code]   Outputs HTML for 1 line to screen
14. 
15.    Q is used for debugging. You can use "linenum ?" to show the line number if an
16.    ABORT occurs. The HTML is about 10 times as big as the Forth source because of
17.    all the links, color changes and whitespace.
18. 
19.    INCLUDEd files produce corresponding HTML pages. Most browsers get severely
20.    bogged down with large files. If you're converting a large Forth program to
21.    HTML, try to keep the source files under 500 lines each by splitting long
22.    source into multiple INCLUDE files.
23. 
24.    When you INCLUDE this file some redefinition complaints may occur. That's
25.    okay since you won't be loading an application on top of this.
26. 
27.    Users of specific Forths can extend the hyperlink table to point to words
28.    in a glossary for that particular Forth.
29. [THEN]
30. 
31. ONLY FORTH ALSO DEFINITIONS
32. 
33. \ ------------------------------------------------------------------------------
34. \ Configuration - You can change the options:
35. 0 VALUE bold                                      \ T if bold text
36. 1 VALUE italic                                    \ T if italic comments
37. 1 VALUE nestable                                  \ T if INCLUDE nested files
38. 1 VALUE linksource                                \ T link to the org. file /4a/
39. create  dpanspath ," .\win32forth-defs\"          \ path to the ANS-Files   /4a/
40. create  footer    ," "                            \ text to output at       /4a/
41.                                                   \ the bottom of the HTML-file
42. \ ------------------------------------------------------------------------------
43. 
44. : undefined ( <name> -- f ) BL WORD FIND NIP 0= ;
45. undefined C+!    [IF] : C+! SWAP OVER C@ + SWAP C! ;                      [THEN]
46. undefined BOUNDS [IF] : BOUNDS OVER + SWAP ;                              [THEN]
47. undefined SCAN   [IF] : SCAN
48.    >R
49.    BEGIN DUP WHILE OVER C@ R@ <> WHILE 1 /STRING REPEAT THEN
50.    R> DROP ;                                                              [THEN]
51. undefined SKIP   [IF] : SKIP
52.    >R
53.    BEGIN DUP WHILE OVER C@ R@ = WHILE 1 /STRING REPEAT THEN
54.    R> DROP ;                                                              [THEN]
55. undefined NOOP   [IF] : NOOP ;                                            [THEN]
56. undefined +PLACE [IF] : +PLACE 2DUP 2>R COUNT CHARS + SWAP MOVE 2R> C+! ; [THEN]
57. undefined PLACE  [IF] : PLACE  0 OVER C! +PLACE ;                         [THEN]
58. undefined FDROP  [IF] : FDROP ;                                           [THEN]
59. undefined >FLOAT [IF] : >FLOAT DROP C@ [CHAR] 0 [CHAR] 9 1+ WITHIN ;      [THEN]
60. 
61. 0 VALUE outf                                    \ output to file
62. 1 VALUE screen-only                             \ screen is for testing
63. : werr     ( n -- )      ABORT" Error writing file" ;
64. : out      ( a len -- )  screen-only IF TYPE    ELSE outf WRITE-FILE werr THEN ;
65. : outln    ( a len -- )  screen-only IF TYPE CR ELSE outf WRITE-LINE werr THEN ;
66. : ,$       ( a len -- )  DUP C, BOUNDS ?DO I C@ C, LOOP ; \ text to dictionary
67. : text     ( <text> -- ) -1 WORD COUNT -TRAILING ,$ ;
68. : boiler   ( addr -- )   BEGIN COUNT DUP WHILE 2DUP + >R outln R> REPEAT 2DROP ;
69. : html-num ( n -- )      BASE @ >R 0 HEX <# # # # # # # #> out R> BASE ! ;
70. 
71. \ create a named text string terminated by char
72. \ when executed, emits the named text using out
73. : namedtext ( char <name> <text> -- )
74.    CREATE WORD COUNT BL SKIP -TRAILING ,$ \ /4c/
75.    DOES> COUNT out ;
76. 
77. \ new and improved strings are now named
78.    CHAR ! namedtext _<a_href="   <a href="!
79.    CHAR ! namedtext _<a_href="#x <a href="#x!
80.    CHAR ! namedtext _<a_name="x  <a name="x!
81. 
82.    CHAR ! namedtext <span_style="color:# <span style="color:#!
83.    CHAR ! namedtext </span>      </span>!
84.    CHAR ! namedtext <hr>         <hr />!
85.    CHAR ! namedtext </hr>        </hr>!
86.    CHAR ! namedtext <h1>         <h1>!
87.    CHAR ! namedtext </h1>        </h1>!
88.    CHAR ! namedtext <h4>         <h4 style="color:black">!
89.    CHAR ! namedtext </h4>        </h4>!
90.    CHAR ! namedtext <html>       <html>!
91.    CHAR ! namedtext </html>      </html>!
92.    CHAR ! namedtext <head>       <head>!
93.    CHAR ! namedtext </head>      </head>!
94.    CHAR ! namedtext <title>      <title>!
95.    CHAR ! namedtext </title>     </title>!
96.    CHAR ! namedtext <body>       <body>!
97.    CHAR ! namedtext </body>      </body>!
98.    CHAR ! namedtext <p>          <p>!
99.    CHAR ! namedtext </p>         </p>!
100.    CHAR ! namedtext <br>         <br />
101.    CHAR ! namedtext ">           ">!
102. 
103. VARIABLE attrib
104. : <a_href="   ( -- )  _<a_href="   1 attrib ! ;
105. : <a_href="#x ( -- )  _<a_href="#x 1 attrib ! ;
106. : <a_name="x  ( -- )  _<a_name="x  1 attrib ! ;
107. : </a>        ( -- )  attrib @ IF s" </a>" out 0 attrib ! THEN ;
108. : <i>         ( -- )  italic IF s" <i>" out THEN ;
109. : </i>        ( -- )  italic IF s" </i>" out THEN ;
110. : <b>         ( -- )  bold IF s" <b>" out THEN ;
111. : </b>        ( -- )  bold IF s" </b>" out THEN ;
112. 
113. VARIABLE infont                                 \ within <font> tag
114. : fontcolor ( color -- )                        \ change font color
115.    1 infont !
116.    <span_style="color:#   html-num   "> ;
117. 
118. : closefont ( -- )                              \ colse <font> tag
119.    infont @ IF </span> 0 infont ! THEN ;
120. 
121. VARIABLE color                                  \ current color
122. : fcol ( color <name> -- )                      \ define a font color
123.    CREATE , DOES> @ color ! ;
124. 
125. HEX
126. 808080 fcol unknown
127. 008000 fcol commentary
128. CC0000 fcol numeric
129. 990080 fcol values
130. 000000 fcol userwords
131. 009999 fcol userdefiner
132. CC00CC fcol variables
133. 0000FF fcol core_ws
134. 0000FF fcol core_ext_ws
135. 0000FF fcol block_ws
136. 0000FF fcol double_ws
137. 0000FF fcol exception_ws
138. 0000FF fcol facilities_ws
139. 0000FF fcol file_ws
140. 0000FF fcol fp_ws
141. 0000FF fcol local_ws
142. 0000FF fcol malloc_ws
143. 0000FF fcol progtools_ws
144. 0000FF fcol searchord_ws
145. 0000FF fcol string_ws
146. DECIMAL
147. 
148. HEX
149. : setcolor ( -- )                               \ select next color
150.    attrib @ 1 = color @ 0000FF = AND 0=         \ blue link: don't color
151.    DROP TRUE                                    \ /4/ vlinks are still purple
152.    IF color @ fontcolor THEN ;
153. DECIMAL
154. 
155. VARIABLE bltally
156. : outh    ( a n -- )                            \ HTMLized text output
157.    999 bltally !
158.    BOUNDS ?DO I C@ CASE
159.       [CHAR] & OF S" &amp;"     out ENDOF
160.       [CHAR] < OF S" &lt;"      out ENDOF
161.       [CHAR] > OF S" &gt;"      out ENDOF
162.       [CHAR] " OF S" &quot;"    out ENDOF
163.       [CHAR] © OF S" &copy;"    out ENDOF       \ /4a/
164.       BL       OF bltally @ 0= IF S"  " ELSE S" &nbsp;" THEN out
165.                 1 bltally +!     ENDOF
166.       I 1 out   0 bltally !
167.    ENDCASE LOOP ;
168. 
169. : outhattr  ( a n -- )                          \ HTMLized text output
170.    BOUNDS ?DO I C@ CASE
171.       [CHAR] & OF S" amp"       out ENDOF
172.       [CHAR] < OF S" lt"        out ENDOF
173.       [CHAR] > OF S" gt"        out ENDOF
174.       [CHAR] " OF S" quot"      out ENDOF
175.       [CHAR] + OF S" plus"      out ENDOF
176.       [CHAR] ! OF S" bang"      out ENDOF
177.       [CHAR] / OF S" slash"     out ENDOF
178.       [CHAR] \ OF S" backslash" out ENDOF
179.       [CHAR] ' OF S" apos"      out ENDOF
180.       [CHAR] = OF S" equal"     out ENDOF
181.       [CHAR] - OF S" dash"      out ENDOF
182.       [CHAR] @ OF S" at"        out ENDOF
183.       [CHAR] ; OF S" semi"      out ENDOF
184.       [CHAR] * OF S" star"      out ENDOF
185.       [CHAR] ? OF S" question"  out ENDOF
186.       [CHAR] ~ OF S" tilde"     out ENDOF
187.       [CHAR] # OF S" pound"     out ENDOF
188.       [CHAR] , OF S" comma"     out ENDOF
189.       [CHAR] $ OF S" dollar"    out ENDOF
190.       [CHAR] | OF S" bar"       out ENDOF
191.       [CHAR] [ OF S" leftbracket"  out ENDOF
192.       [CHAR] ( OF S" leftparen"    out ENDOF
193.       [CHAR] { OF S" leftbrace"    out ENDOF
194.       [CHAR] ] OF S" rightbracket" out ENDOF
195.       [CHAR] ) OF S" rightparen"   out ENDOF
196.       [CHAR] } OF S" rightbrace"   out ENDOF
197.       BL       OF S" _"            out ENDOF
198.       I 1 out   
199.    ENDCASE LOOP ;
200. 
201. CREATE begin_header                             \ begin of HTML file part 1
202.    text <?xml version="1.0"?>
203.    text <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Strict//EN"
204.    text     "http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd">
205.    text <html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
206.    text <head>
207.    text <meta http-equiv="Content-Type" content="text/xml; charset=iso-8859-1" />
208.    text <meta name="GENERATOR" content="Forth2HTML 0.4" />
209.    text <style type="text/css">
210.    text body {background: #FFFFEE;}
211.    text h1 {color: #000000;}
212.    text p {font-family: monospace;}
213.    text a {text-decoration:none;}
214.    text </style>
215.    text <title>
216.    0 C,
217. 
218. : mid_header ( -- )                             \ begin of HTML file part 2
219.    </title>
220.    </head>
221.    <body>
222. ;
223. 
224. : end_header ( -- )                             \ end of HTML file /4a/
225.    footer COUNT ?DUP IF <hr> <h4> outh </h4> ELSE drop THEN
226.    </body> </html> ;
227. 
228. : label ( addr len -- ) </a>                    \ associate a label with a word
229.    <a_name="x outhattr "> ;
230. 
231. \ Assuming this is running on a PC, we allocate enough storage that crashes from
232. \ string overflows can't happen.                /4/
233. 
234. CREATE inbuf 260 CHARS ALLOT                    \ current line from file
235. CREATE token 260 CHARS ALLOT                    \ the last blank delimited string
236. CREATE XPAD  260 CHARS ALLOT                    \ temporary pad for word storage
237. CREATE EPAD  260 CHARS ALLOT                    \ temporary pad for evaluation
238. CREATE fn    260 CHARS ALLOT                    \ file name
239. CREATE fn1   260 CHARS ALLOT                    \ file name backup
240. CREATE "str" 260 CHARS ALLOT                    \ parsed string storage
241. CREATE uname 260 CHARS ALLOT                    \ : definition name
242. 0 VALUE inf
243. VARIABLE nufile                                 \ T if nesting a file
244. VARIABLE utype                                  \ type of defined word
245. VARIABLE hstate
246. VARIABLE linenum
247. VARIABLE special                                \ special action, 0=none
248. WORDLIST CONSTANT hyperlinks
249. 
250. : std    ( word 2nd_fn color filename label -- )
251.    CREATE ' , ' , BL WORD COUNT ,$ BL WORD COUNT ,$
252.    DOES> </a> DUP >R  2 CELLS +
253.    <a_href="                                    \ begin hyperlink
254.    dpanspath COUNT out                          \ output path to ANS files /4a/
255.    COUNT 2DUP + >R  out S" #" out               \ output file name      /4/
256.    R> COUNT out ">                              \ and anchor name
257.    R> 2@ SWAP EXECUTE EXECUTE ;                 \ extra attributes
258. 
259. : genHTML ( -- )                                \ generate pending HTML
260.    token COUNT DUP IF setcolor THEN outh closefont </a>  0 token ! ;
261. 
262. : isnumber? ( addr len -- f )                   \ string converts to number?
263.    0 0 2SWAP >NUMBER NIP NIP NIP 0= ;
264. 
265. : hparse ( a len char -- a' len' )
266.    >R 2DUP R@ SKIP R> SCAN BL SCAN
267.    2SWAP 2 PICK - token +PLACE ;
268. 
269. : >XPAD ( -- ) token COUNT BL SKIP XPAD PLACE ; \ move to temporary pad
270. 
271. : hint  ( addr len -- )                         \ interpret one line...
272.    BEGIN
273.       0 token !  BL hparse token C@
274.    WHILE unknown                                \ default color
275.       >XPAD XPAD COUNT hyperlinks SEARCH-WORDLIST \ got a hyperlink for this?
276.       IF DEPTH >R EXECUTE
277.          R> DEPTH <> ABORT" stack depth change in HTML generator"
278.       ELSE
279.          XPAD COUNT BASE @ 10 = IF
280.             >FLOAT IF FDROP numeric THEN        \ valid float or integer
281.          ELSE
282.             isnumber? IF numeric THEN
283.          THEN
284.       THEN genHTML
285.    REPEAT 2DROP
286.    <br> ;                                        \ new line
287. 
288. : ofn   ( -- addr len )                         \ output file name
289.    fn COUNT 2DUP [CHAR] . SCAN NIP - EPAD PLACE
290.    S" .htm" EPAD +PLACE   EPAD COUNT ;
291. 
292. : hcreate ( addr len -- )
293.    DUP 0= IF 2DROP S" fakename" THEN            \ in case the name is missing
294.    S" CREATE " EPAD PLACE  EPAD +PLACE
295.    GET-CURRENT >R hyperlinks SET-CURRENT
296.    EPAD COUNT EVALUATE    R> SET-CURRENT ;      \ create a hyperlink generator
297. 
298. \ The user defined words use the following data structure:
299. \ CELL   xt of coloring word
300. \ STRING name of reference word
301. \ STRING name of file
302. 
303. : deflink ( addr -- )                           \ make hyperlink from data structure
304.    DUP @ EXECUTE CELL+                          \ set color
305.    DUP COUNT + COUNT ofn COMPARE                \ in an external file?
306.    IF   <a_href=" DUP COUNT + COUNT out         \ yes, put file name
307.         S" #" out COUNT outh ">
308.    ELSE <a_href="#x COUNT outhattr ">           \ no, just use the name
309.    THEN ;
310. 
311. : defx  ( a len xt -- a' len' )
312.    >R genHTML BL hparse >XPAD                   \ output defining word
313.    XPAD COUNT 2DUP hcreate R> , ,$ ofn ,$
314.    DOES> deflink ;
315. 
316. : labelnow   genHTML XPAD COUNT label ;         \ /4/
317. : defdat ['] numeric   defx numeric   labelnow ;
318. : defvar ['] variables defx variables labelnow ;
319. : defusr ['] userwords defx userwords labelnow ;
320. : defval ['] values    defx values    labelnow ;
321. : defdef ['] userdefiner defx userdefiner labelnow ;
322. 
323. : hstate=0 ( -- )             0 hstate ! ;
324. : hstate=1 ( -- )             1 hstate ! ;
325. : spec=zero ( -- )            1 special ! ;
326. : skip)  ( a len -- a' len' ) [CHAR] ) hparse ;
327. : skip}  ( a len -- a' len' ) [CHAR] } hparse ; \ /4a/
328. : skipw  ( a len -- a' len' ) BL hparse ;
329. : skipc  ( a len -- a len )   hstate @ 0= IF numeric skipw THEN ;
330. : skip"  ( a len -- a' len' )                   \ copy string to "str"
331.    genHTML [CHAR] " hparse token COUNT 1- "str" PLACE ;
332. 
333. \ ------------------------------------------------------------------------------
334. \ ":" definitions might be defining words, so they can't be assumed to be defusr
335. \ types. ":" makes a label and saves the name for later use by ";" which makes
336. \ a hyperlink or a hyperlink defining word.
337. 
338. :NONAME                                         \ normal : definition
339.    uname COUNT ['] userwords defx 2DROP  0 token !
340. ; CONSTANT normal_def
341. 
342. :NONAME
343.    uname COUNT 2DUP hcreate ['] userwords , ,$ ofn ,$
344.    DOES> deflink defdef
345. ; CONSTANT defining_def
346. 
347. : defunk ( a len -- a' len' )                   \ starting unknown definition
348.    hstate=1  normal_def utype !                 \ save name of : definition
349.    genHTML skipw userwords token COUNT BL SKIP 2DUP uname PLACE label ;
350. 
351. : resunk ( -- )                                 \ resolve unknown defined word
352.    genHTML utype @ EXECUTE hstate=0 ;
353. 
354. : created ( -- ) hstate @
355.    IF   defining_def utype !                    \ make ; create a defining word
356.    ELSE defdat                                  \ not compiling
357.    THEN ;
358. 
359. \ ------------------------------------------------------------------------------
360. 
361. : header  ( addr len -- )                       \ output big header text /4b/
362.    <hr> <h1>
363.    linksource
364.    IF   2dup <a_href=" out "> outln </a>
365.    ELSE outln
366.    THEN </h1> <hr> <p> ;
367. 
368. : _incfil ( addr -- )                           \ trigger file nesting      /4/
369.    nestable 0= IF DROP EXIT THEN                \ don't nest files if disabled
370.    COUNT BL SKIP  2DUP R/O OPEN-FILE            \ can the file be opened?
371.    IF   DROP 2DROP                              \ no
372.    ELSE CLOSE-FILE DROP                         \ yes
373.         fn COUNT fn1 PLACE  fn PLACE 1 nufile !
374.    THEN ;
375. 
376. : incfile ( a len -- a' len' )                  \ include a file
377.    genHTML skipw token _incfil ;
378. 
379. : "incfil ( a len -- a' len' )                  \ include file from S" filename"
380.    skipw "str" _incfil ;
381. 
382. : hfill  ( -- len ior )                         \ read next line of file
383.    inbuf 256 BL FILL
384.    XPAD 256 inf READ-LINE ABORT" Error reading file"
385.    >R >R 0 XPAD R> BOUNDS                       ( idx . . )
386.    ?DO  I C@ 9 = IF 3 RSHIFT 1+ 3 LSHIFT        \ tab
387.         ELSE I C@ OVER 255 AND CHARS inbuf + C!
388.            1+ DUP 256 = IF CR ." Input line too long" THEN
389.         THEN
390.    LOOP R>
391.    1 linenum +! ;
392. 
393. : open  ( -- ) CR ." Reading " fn COUNT TYPE ."  at line " linenum @ .
394.    0 linenum !
395.    fn COUNT R/O OPEN-FILE ABORT" Error opening source file" TO inf ;
396. 
397. : close  ( -- ) CR ." closing " fn COUNT TYPE
398.    inf CLOSE-FILE ABORT" Error closing file" ;
399. 
400. : .title ( addr len -- )                        \ output as title string
401.    BOUNDS ?DO I C@ BL = IF S" %20" out ELSE I 1 out THEN LOOP ;
402. 
403. : oopen  ( -- )
404.    ofn W/O CREATE-FILE ABORT" Error creating file" TO outf
405.    begin_header boiler                          \ begin boilerplate
406.    fn COUNT .title  mid_header                  \ title and end boilerplate
407.    <b>
408.    fn COUNT header ;
409. 
410. : HTML  ( <infile> -- )
411.    S" /basic-links/" hyperlinks SEARCH-WORDLIST
412.    IF   EXECUTE  THEN                           \ remove user hyperlinks
413.    GET-CURRENT >R hyperlinks SET-CURRENT        \ replace the fence
414.    S" MARKER /basic-links/" EVALUATE
415.    R> SET-CURRENT
416.    0 TO screen-only  0 nufile !  1 linenum !    \ force usage of file
417.    0 infont ! 0 attrib !                        \ /4b/ /4d/
418.    BL WORD COUNT fn PLACE open oopen            \ open input and output files
419.    -1 DUP >R outf >R                            \ file nest uses stacks
420.    hstate=0
421.    BEGIN
422.       BEGIN 0 special !                         \ process line
423.          nufile @                               \ nest a file?
424.          IF   inf outf
425.               open oopen  outf >R               \ open new files
426.               0 nufile !
427.          THEN hfill
428.       WHILE inbuf SWAP hint
429.       REPEAT DROP
430.       close fn1 COUNT fn PLACE                  \ restore file name
431.       DUP -1 <>
432.       IF   TO outf TO inf FALSE                 \ unnest files
433.       ELSE TRUE
434.       THEN
435.    UNTIL DROP
436.    BEGIN R> DUP -1 <>                            \ close all output files
437.    WHILE </p> </b>                               \ /4b/
438.       end_header                                 \ finish up HTML
439.       CLOSE-FILE ABORT" Error closing file"
440.    REPEAT DROP ;
441. 
442. : q  ( -- ) 1 TO screen-only                    \ single line test
443.    -1 WORD COUNT inbuf PLACE inbuf COUNT hint ;
444. 
445. \ 0 [IF] is often used as a comment. If it is used as a comment, scan the file
446. \ for a [THEN]. [THEN] must be on the next line or beyond.
447. 
448. : upp ( an--) BOUNDS ?DO I C@ [CHAR] a > IF I C@ 32 - I C! THEN LOOP \ uppercase
449. ;
450. 
451. CREATE terminator 16 CHARS ALLOT                \ multiline comment terminator
452. 
453. : multicomment ( a len searchstring -- a' len' )
454.    terminator PLACE
455.    genHTML <i> commentary setcolor outh       \ finish up this line /4b/
456.    BEGIN hfill      <br>
457.    WHILE >R inbuf EPAD R@ MOVE
458.       EPAD R@ upp                               \ uppercase for search
459.       EPAD R@ terminator COUNT SEARCH
460.       IF   DROP EPAD - inbuf OVER token PLACE   \ before [THEN] is comment
461.            genHTML
462.            inbuf R> ROT /STRING
463.            </i> closefont EXIT
464.       ELSE 2DROP inbuf R> outh                  \ whole line is comment
465.       THEN
466.    REPEAT inbuf SWAP </i> closefont ;          \ EOF found
467. 
468. : bigif  ( a len -- a len )  special @ 1 =
469.    IF S" [THEN]" multicomment THEN ;
470. 
471. \ =============================================================================
472. 
473. : _DEFINITIONS DEFINITIONS ;
474. : _order order ;  : _words words ; : _see see ;
475. 
476. hyperlinks SET-CURRENT
477. \ The following words are not in the ANS standard but are very common.
478. : VOCABULARY    defusr ;
479. : DEFER         defusr ;
480. : INCLUDE       hstate @ 0= IF incfile THEN ;
481. : FLOAD         hstate @ 0= IF incfile THEN ;
482. : BINARY        2 BASE ! ;
483. : OCTAL         8 BASE ! ;
484. : 0             numeric spec=zero ;
485. : 1             numeric  ;
486. : -1            numeric  ;
487. : COMMENT:      S" COMMENT;" multicomment ;
488. : ((            S" ))"       multicomment ;
489. 
490. \ The following words are not in the ANS standard but are used in Win32Forth
491. : ANEW          skipw ;                    \ /4a/
492. : {             commentary genHTML skip} ; \ /4a/
493. : CallBack:     defunk ;                   \ /4a/
494. : :M            defunk ;                   \ /4a/
495. : ;M            resunk ;                   \ /4a/
496. 
497. \ The rest is ANS Forth standard
498. 
499. : \             commentary <i> genHTML token PLACE genHTML </i> token 0 ;
500. 
501. (   NAME                ACTION  COLOR           FILENAME        REFERENCE )
502. (   ------------------  ------  --------------  -----------     --------- )
503. std !                   NOOP    core_ws         dpans6.htm      6.1.0010
504. std #                   NOOP    core_ws         dpans6.htm      6.1.0030
505. std #>                  NOOP    core_ws         dpans6.htm      6.1.0040
506. std #S                  NOOP    core_ws         dpans6.htm      6.1.0050
507. std '                   NOOP    core_ws         dpans6.htm      6.1.0070
508. std (                   skip)   commentary      dpans6.htm      6.1.0080
509. std *                   NOOP    core_ws         dpans6.htm      6.1.0090
510. std */                  NOOP    core_ws         dpans6.htm      6.1.0100
511. std */MOD               NOOP    core_ws         dpans6.htm      6.1.0110
512. std +                   NOOP    core_ws         dpans6.htm      6.1.0120
513. std +!                  NOOP    core_ws         dpans6.htm      6.1.0130
514. std +LOOP               NOOP    core_ws         dpans6.htm      6.1.0140
515. std ,                   NOOP    core_ws         dpans6.htm      6.1.0150
516. std -                   NOOP    core_ws         dpans6.htm      6.1.0160
517. std .                   NOOP    core_ws         dpans6.htm      6.1.0180
518. std ."                  skip"   numeric         dpans6.htm      6.1.0190
519. std /                   NOOP    core_ws         dpans6.htm      6.1.0230
520. std /MOD                NOOP    core_ws         dpans6.htm      6.1.0240
521. std 0<                  NOOP    core_ws         dpans6.htm      6.1.0250
522. std 0=                  NOOP    core_ws         dpans6.htm      6.1.0270
523. std 1+                  NOOP    core_ws         dpans6.htm      6.1.0290
524. std 1-                  NOOP    core_ws         dpans6.htm      6.1.0300
525. std 2!                  NOOP    core_ws         dpans6.htm      6.1.0310
526. std 2*                  NOOP    core_ws         dpans6.htm      6.1.0320
527. std 2/                  NOOP    core_ws         dpans6.htm      6.1.0330
528. std 2@                  NOOP    core_ws         dpans6.htm      6.1.0350
529. std 2DROP               NOOP    core_ws         dpans6.htm      6.1.0370
530. std 2DUP                NOOP    core_ws         dpans6.htm      6.1.0380
531. std 2OVER               NOOP    core_ws         dpans6.htm      6.1.0400
532. std 2SWAP               NOOP    core_ws         dpans6.htm      6.1.0430
533. std :                   defunk  core_ws         dpans6.htm      6.1.0450
534. std ;                   resunk  core_ws         dpans6.htm      6.1.0460
535. std <                   NOOP    core_ws         dpans6.htm      6.1.0480
536. std <#                  NOOP    core_ws         dpans6.htm      6.1.0490
537. std =                   NOOP    core_ws         dpans6.htm      6.1.0530
538. std >                   NOOP    core_ws         dpans6.htm      6.1.0540
539. std >BODY               NOOP    core_ws         dpans6.htm      6.1.0550
540. std >IN                 NOOP    core_ws         dpans6.htm      6.1.0560
541. std >NUMBER             NOOP    core_ws         dpans6.htm      6.1.0570
542. std >R                  NOOP    core_ws         dpans6.htm      6.1.0580
543. std ?DUP                NOOP    core_ws         dpans6.htm      6.1.0630
544. std @                   NOOP    core_ws         dpans6.htm      6.1.0650
545. std ABORT               NOOP    core_ws         dpans6.htm      6.1.0670
546. std ABORT"              skip"   numeric         dpans6.htm      6.1.0680
547. std ABS                 NOOP    core_ws         dpans6.htm      6.1.0690
548. std ACCEPT              NOOP    core_ws         dpans6.htm      6.1.0695
549. std ALIGN               NOOP    core_ws         dpans6.htm      6.1.0705
550. std ALIGNED             NOOP    core_ws         dpans6.htm      6.1.0706
551. std ALLOT               NOOP    core_ws         dpans6.htm      6.1.0710
552. std AND                 NOOP    core_ws         dpans6.htm      6.1.0720
553. std BASE                NOOP    core_ws         dpans6.htm      6.1.0750
554. std BEGIN               NOOP    core_ws         dpans6.htm      6.1.0760
555. std BL                  NOOP    numeric         dpans6.htm      6.1.0770
556. std C!                  NOOP    core_ws         dpans6.htm      6.1.0850
557. std C,                  NOOP    core_ws         dpans6.htm      6.1.0860
558. std C@                  NOOP    core_ws         dpans6.htm      6.1.0870
559. std CELL+               NOOP    core_ws         dpans6.htm      6.1.0880
560. std CELLS               NOOP    core_ws         dpans6.htm      6.1.0890
561. std CHAR                skipc   core_ws         dpans6.htm      6.1.0895
562. std CHAR+               NOOP    core_ws         dpans6.htm      6.1.0897
563. std CHARS               NOOP    core_ws         dpans6.htm      6.1.0898
564. std CONSTANT            defdat  core_ws         dpans6.htm      6.1.0950
565. std COUNT               NOOP    core_ws         dpans6.htm      6.1.0980
566. std CR                  NOOP    core_ws         dpans6.htm      6.1.0990
567. std CREATE              created core_ws         dpans6.htm      6.1.1000
568. std DECIMAL             DECIMAL core_ws         dpans6.htm      6.1.1170
569. std DEPTH               NOOP    core_ws         dpans6.htm      6.1.1200
570. std DO                  NOOP    core_ws         dpans6.htm      6.1.1240
571. std DOES>               NOOP    core_ws         dpans6.htm      6.1.1250
572. std DROP                NOOP    core_ws         dpans6.htm      6.1.1260
573. std DUP                 NOOP    core_ws         dpans6.htm      6.1.1290
574. std ELSE                NOOP    core_ws         dpans6.htm      6.1.1310
575. std EMIT                NOOP    core_ws         dpans6.htm      6.1.1320
576. std ENVIRONMENT?        NOOP    core_ws         dpans6.htm      6.1.1345
577. std EVALUATE            NOOP    core_ws         dpans6.htm      6.1.1360
578. std EXECUTE             NOOP    core_ws         dpans6.htm      6.1.1370
579. std EXIT                NOOP    core_ws         dpans6.htm      6.1.1380
580. std FILL                NOOP    core_ws         dpans6.htm      6.1.1540
581. std FIND                NOOP    core_ws         dpans6.htm      6.1.1550
582. std FM/MOD              NOOP    core_ws         dpans6.htm      6.1.1561
583. std HERE                NOOP    core_ws         dpans6.htm      6.1.1650
584. std HOLD                NOOP    core_ws         dpans6.htm      6.1.1670
585. std I                   NOOP    core_ws         dpans6.htm      6.1.1680
586. std IF                  NOOP    core_ws         dpans6.htm      6.1.1700
587. std IMMEDIATE           NOOP    core_ws         dpans6.htm      6.1.1710
588. std INVERT              NOOP    core_ws         dpans6.htm      6.1.1720
589. std J                   NOOP    core_ws         dpans6.htm      6.1.1730
590. std KEY                 NOOP    core_ws         dpans6.htm      6.1.1750
591. std LEAVE               NOOP    core_ws         dpans6.htm      6.1.1760
592. std LITERAL             NOOP    core_ws         dpans6.htm      6.1.1780
593. std LOOP                NOOP    core_ws         dpans6.htm      6.1.1800
594. std LSHIFT              NOOP    core_ws         dpans6.htm      6.1.1805
595. std M*                  NOOP    core_ws         dpans6.htm      6.1.1810
596. std MAX                 NOOP    core_ws         dpans6.htm      6.1.1870
597. std MIN                 NOOP    core_ws         dpans6.htm      6.1.1880
598. std MOD                 NOOP    core_ws         dpans6.htm      6.1.1890
599. std MOVE                NOOP    core_ws         dpans6.htm      6.1.1900
600. std NEGATE              NOOP    core_ws         dpans6.htm      6.1.1910
601. std OR                  NOOP    core_ws         dpans6.htm      6.1.1980
602. std OVER                NOOP    core_ws         dpans6.htm      6.1.1990
603. std POSTPONE            NOOP    core_ws         dpans6.htm      6.1.2033
604. std QUIT                NOOP    core_ws         dpans6.htm      6.1.2050
605. std R>                  NOOP    core_ws         dpans6.htm      6.1.2060
606. std R@                  NOOP    core_ws         dpans6.htm      6.1.2070
607. std RECURSE             NOOP    core_ws         dpans6.htm      6.1.2120
608. std REPEAT              NOOP    core_ws         dpans6.htm      6.1.2140
609. std ROT                 NOOP    core_ws         dpans6.htm      6.1.2160
610. std RSHIFT              NOOP    core_ws         dpans6.htm      6.1.2162
611. std S"                  skip"   numeric         dpans6.htm      6.1.2165
612. std S>D                 NOOP    core_ws         dpans6.htm      6.1.2170
613. std SIGN                NOOP    core_ws         dpans6.htm      6.1.2210
614. std SM/REM              NOOP    core_ws         dpans6.htm      6.1.2214
615. std SOURCE              NOOP    core_ws         dpans6.htm      6.1.2216
616. std SPACE               NOOP    core_ws         dpans6.htm      6.1.2220
617. std SPACES              NOOP    core_ws         dpans6.htm      6.1.2230
618. std STATE               NOOP    core_ws         dpans6.htm      6.1.2250
619. std SWAP                NOOP    core_ws         dpans6.htm      6.1.2260
620. std THEN                NOOP    core_ws         dpans6.htm      6.1.2270
621. std TYPE                NOOP    core_ws         dpans6.htm      6.1.2310
622. std U.                  NOOP    core_ws         dpans6.htm      6.1.2320
623. std U<                  NOOP    core_ws         dpans6.htm      6.1.2340
624. std UM*                 NOOP    core_ws         dpans6.htm      6.1.2360
625. std UM/MOD              NOOP    core_ws         dpans6.htm      6.1.2370
626. std UNLOOP              NOOP    core_ws         dpans6.htm      6.1.2380
627. std UNTIL               NOOP    core_ws         dpans6.htm      6.1.2390
628. std VARIABLE            defvar  core_ws         dpans6.htm      6.1.2410
629. std WHILE               NOOP    core_ws         dpans6.htm      6.1.2430
630. std WORD                NOOP    core_ws         dpans6.htm      6.1.2450
631. std XOR                 NOOP    core_ws         dpans6.htm      6.1.2490
632. std [                  hstate=0 core_ws         dpans6.htm      6.1.2500
633. std [']                 skipw   numeric         dpans6.htm      6.1.2510
634. std [CHAR]              skipw   numeric         dpans6.htm      6.1.2520
635. std ]                  hstate=1 core_ws         dpans6.htm      6.1.2540
636. std #TIB                NOOP    core_ext_ws     dpans6.htm      6.2.0060
637. std .(                  skip)   commentary      dpans6.htm      6.2.0200
638. std .R                  NOOP    core_ext_ws     dpans6.htm      6.2.0210
639. std 0<>                 NOOP    core_ext_ws     dpans6.htm      6.2.0260
640. std 0>                  NOOP    core_ext_ws     dpans6.htm      6.2.0280
641. std 2>R                 NOOP    core_ext_ws     dpans6.htm      6.2.0340
642. std 2R>                 NOOP    core_ext_ws     dpans6.htm      6.2.0410
643. std 2R@                 NOOP    core_ext_ws     dpans6.htm      6.2.0415
644. std :NONAME             NOOP    core_ext_ws     dpans6.htm      6.2.0455
645. std <>                  NOOP    core_ext_ws     dpans6.htm      6.2.0500
646. std ?DO                 NOOP    core_ext_ws     dpans6.htm      6.2.0620
647. std AGAIN               NOOP    core_ext_ws     dpans6.htm      6.2.0700
648. std C"                  skip"   numeric         dpans6.htm      6.2.0855
649. std CASE                NOOP    core_ext_ws     dpans6.htm      6.2.0873
650. std COMPILE,            NOOP    core_ext_ws     dpans6.htm      6.2.0945
651. std CONVERT             NOOP    core_ext_ws     dpans6.htm      6.2.0970
652. std ENDCASE             NOOP    core_ext_ws     dpans6.htm      6.2.1342
653. std ENDOF               NOOP    core_ext_ws     dpans6.htm      6.2.1343
654. std ERASE               NOOP    core_ext_ws     dpans6.htm      6.2.1350
655. std EXPECT              NOOP    core_ext_ws     dpans6.htm      6.2.1390
656. std FALSE             spec=zero numeric         dpans6.htm      6.2.1485
657. std HEX                 HEX     core_ext_ws     dpans6.htm      6.2.1660
658. std MARKER              defusr  core_ext_ws     dpans6.htm      6.2.1850
659. std NIP                 NOOP    core_ext_ws     dpans6.htm      6.2.1930
660. std OF                  NOOP    core_ext_ws     dpans6.htm      6.2.1950
661. std PAD                 NOOP    core_ext_ws     dpans6.htm      6.2.2000
662. std PARSE               NOOP    core_ext_ws     dpans6.htm      6.2.2008
663. std PICK                NOOP    core_ext_ws     dpans6.htm      6.2.2030
664. std QUERY               NOOP    core_ext_ws     dpans6.htm      6.2.2040
665. std REFILL              NOOP    core_ext_ws     dpans6.htm      6.2.2125
666. std RESTORE-INPUT       NOOP    core_ext_ws     dpans6.htm      6.2.2148
667. std ROLL                NOOP    core_ext_ws     dpans6.htm      6.2.2150
668. std SAVE-INPUT          NOOP    core_ext_ws     dpans6.htm      6.2.2182
669. std SOURCE-ID           NOOP    core_ext_ws     dpans6.htm      6.2.2218
670. std SPAN                NOOP    core_ext_ws     dpans6.htm      6.2.2240
671. std TIB                 NOOP    core_ext_ws     dpans6.htm      6.2.2290
672. std TO                  NOOP    core_ext_ws     dpans6.htm      6.2.2295
673. std TRUE                NOOP    numeric         dpans6.htm      6.2.2298
674. std TUCK                NOOP    core_ext_ws     dpans6.htm      6.2.2300
675. std U.R                 NOOP    core_ext_ws     dpans6.htm      6.2.2330
676. std U>                  NOOP    core_ext_ws     dpans6.htm      6.2.2350
677. std UNUSED              NOOP    core_ext_ws     dpans6.htm      6.2.2395
678. std VALUE               defval  core_ext_ws     dpans6.htm      6.2.2405
679. std WITHIN              NOOP    core_ext_ws     dpans6.htm      6.2.2440
680. std [COMPILE]           NOOP    core_ext_ws     dpans6.htm      6.2.2530
681. std BLK                 NOOP    block_ws        dpans7.htm      7.6.1.0790
682. std BLOCK               NOOP    block_ws        dpans7.htm      7.6.1.0800
683. std BUFFER              NOOP    block_ws        dpans7.htm      7.6.1.0820
684. std FLUSH               NOOP    block_ws        dpans7.htm      7.6.1.1559
685. std LOAD                NOOP    block_ws        dpans7.htm      7.6.1.1790
686. std SAVE-BUFFERS        NOOP    block_ws        dpans7.htm      7.6.1.2180
687. std UPDATE              NOOP    block_ws        dpans7.htm      7.6.1.2400
688. std EMPTY-BUFFERS       NOOP    block_ws        dpans7.htm      7.6.2.1330
689. std LIST                NOOP    block_ws        dpans7.htm      7.6.2.1770
690. std SCR                 NOOP    block_ws        dpans7.htm      7.6.2.2190
691. std THRU                NOOP    block_ws        dpans7.htm      7.6.2.2280
692. std 2CONSTANT           defdat  double_ws       dpans8.htm      8.6.1.0360
693. std 2LITERAL            NOOP    double_ws       dpans8.htm      8.6.1.0390
694. std 2VARIABLE           defvar  double_ws       dpans8.htm      8.6.1.0440
695. std D+                  NOOP    double_ws       dpans8.htm      8.6.1.1040
696. std D-                  NOOP    double_ws       dpans8.htm      8.6.1.1050
697. std D.                  NOOP    double_ws       dpans8.htm      8.6.1.1060
698. std D.R                 NOOP    double_ws       dpans8.htm      8.6.1.1070
699. std D0<                 NOOP    double_ws       dpans8.htm      8.6.1.1075
700. std D0=                 NOOP    double_ws       dpans8.htm      8.6.1.1080
701. std D2*                 NOOP    double_ws       dpans8.htm      8.6.1.1090
702. std D2/                 NOOP    double_ws       dpans8.htm      8.6.1.1100
703. std D<                  NOOP    double_ws       dpans8.htm      8.6.1.1110
704. std D=                  NOOP    double_ws       dpans8.htm      8.6.1.1120
705. std D>S                 NOOP    double_ws       dpans8.htm      8.6.1.1140
706. std DABS                NOOP    double_ws       dpans8.htm      8.6.1.1160
707. std DMAX                NOOP    double_ws       dpans8.htm      8.6.1.1210
708. std DMIN                NOOP    double_ws       dpans8.htm      8.6.1.1220
709. std DNEGATE             NOOP    double_ws       dpans8.htm      8.6.1.1230
710. std M*/                 NOOP    double_ws       dpans8.htm      8.6.1.1820
711. std M+                  NOOP    double_ws       dpans8.htm      8.6.1.1830
712. std 2ROT                NOOP    double_ws       dpans8.htm      8.6.2.0420
713. std DU<                 NOOP    double_ws       dpans8.htm      8.6.2.1270
714. std CATCH               NOOP    exception_ws    dpans9.htm      9.6.1.0875
715. std THROW               NOOP    exception_ws    dpans9.htm      9.6.1.2275
716. std AT-XY               NOOP    facilities_ws   dpans10.htm     10.6.1.0742
717. std KEY?                NOOP    facilities_ws   dpans10.htm     10.6.1.1755
718. std PAGE                NOOP    facilities_ws   dpans10.htm     10.6.1.2005
719. std EKEY                NOOP    facilities_ws   dpans10.htm     10.6.2.1305
720. std EKEY<CHAR           NOOP    facilities_ws   dpans10.htm     10.6.2.1306
721. std EKEY?               NOOP    facilities_ws   dpans10.htm     10.6.2.1307
722. std EMIT?               NOOP    facilities_ws   dpans10.htm     10.6.2.1325
723. std MS                  NOOP    facilities_ws   dpans10.htm     10.6.2.1905
724. std TIME&DATE           NOOP    facilities_ws   dpans10.htm     10.6.2.2292
725. std BIN                 NOOP    file_ws         dpans11.htm     11.6.1.0765
726. std CLOSE-FILE          NOOP    file_ws         dpans11.htm     11.6.1.0900
727. std CREATE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.1010
728. std DELETE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.1190
729. std FILE-POSITION       NOOP    file_ws         dpans11.htm     11.6.1.1520
730. std FILE-SIZE           NOOP    file_ws         dpans11.htm     11.6.1.1522
731. std INCLUDE-FILE        NOOP    file_ws         dpans11.htm     11.6.1.1717
732. std INCLUDED            "incfil file_ws         dpans11.htm     11.6.1.1718
733. std OPEN-FILE           NOOP    file_ws         dpans11.htm     11.6.1.1970
734. std R/O                 NOOP    file_ws         dpans11.htm     11.6.1.2054
735. std R/W                 NOOP    file_ws         dpans11.htm     11.6.1.2056
736. std READ-FILE           NOOP    file_ws         dpans11.htm     11.6.1.2080
737. std READ-LINE           NOOP    file_ws         dpans11.htm     11.6.1.2090
738. std REPOSITION-FILE     NOOP    file_ws         dpans11.htm     11.6.1.2142
739. std RESIZE-FILE         NOOP    file_ws         dpans11.htm     11.6.1.2147
740. std W/O                 NOOP    file_ws         dpans11.htm     11.6.1.2425
741. std WRITE-FILE          NOOP    file_ws         dpans11.htm     11.6.1.2480
742. std WRITE-LINE          NOOP    file_ws         dpans11.htm     11.6.1.2485
743. std FILE-STATUS         NOOP    file_ws         dpans11.htm     11.6.2.1524
744. std FLUSH-FILE          NOOP    file_ws         dpans11.htm     11.6.2.1560
745. std RENAME-FILE         NOOP    file_ws         dpans11.htm     11.6.2.2130
746. std >FLOAT              NOOP    fp_ws           dpans12.htm     12.6.1.0558
747. std D>F                 NOOP    fp_ws           dpans12.htm     12.6.1.1130
748. std F!                  NOOP    fp_ws           dpans12.htm     12.6.1.1400
749. std F*                  NOOP    fp_ws           dpans12.htm     12.6.1.1410
750. std F+                  NOOP    fp_ws           dpans12.htm     12.6.1.1420
751. std F-                  NOOP    fp_ws           dpans12.htm     12.6.1.1425
752. std F/                  NOOP    fp_ws           dpans12.htm     12.6.1.1430
753. std F0<                 NOOP    fp_ws           dpans12.htm     12.6.1.1440
754. std F0=                 NOOP    fp_ws           dpans12.htm     12.6.1.1450
755. std F<                  NOOP    fp_ws           dpans12.htm     12.6.1.1460
756. std F>D                 NOOP    fp_ws           dpans12.htm     12.6.1.1460
757. std F@                  NOOP    fp_ws           dpans12.htm     12.6.1.1472
758. std FALIGN              NOOP    fp_ws           dpans12.htm     12.6.1.1479
759. std FALIGNED            NOOP    fp_ws           dpans12.htm     12.6.1.1483
760. std FCONSTANT           defdat  fp_ws           dpans12.htm     12.6.1.1492
761. std FDEPTH              NOOP    fp_ws           dpans12.htm     12.6.1.1497
762. std FDROP               NOOP    fp_ws           dpans12.htm     12.6.1.1500
763. std FDUP                NOOP    fp_ws           dpans12.htm     12.6.1.1510
764. std FLITERAL            NOOP    fp_ws           dpans12.htm     12.6.1.1552
765. std FLOAT+              NOOP    fp_ws           dpans12.htm     12.6.1.1555
766. std FLOATS              NOOP    fp_ws           dpans12.htm     12.6.1.1556
767. std FLOOR               NOOP    fp_ws           dpans12.htm     12.6.1.1558
768. std FMAX                NOOP    fp_ws           dpans12.htm     12.6.1.1562
769. std FMIN                NOOP    fp_ws           dpans12.htm     12.6.1.1565
770. std FNEGATE             NOOP    fp_ws           dpans12.htm     12.6.1.1567
771. std FOVER               NOOP    fp_ws           dpans12.htm     12.6.1.1600
772. std FROT                NOOP    fp_ws           dpans12.htm     12.6.1.1610
773. std FROUND              NOOP    fp_ws           dpans12.htm     12.6.1.1612
774. std FSWAP               NOOP    fp_ws           dpans12.htm     12.6.1.1620
775. std FVARIABLE           defvar  fp_ws           dpans12.htm     12.6.1.1630
776. std REPRESENT           NOOP    fp_ws           dpans12.htm     12.6.1.2143
777. std DF!                 NOOP    fp_ws           dpans12.htm     12.6.2.1203
778. std DF@                 NOOP    fp_ws           dpans12.htm     12.6.2.1204
779. std DFALIGN             NOOP    fp_ws           dpans12.htm     12.6.2.1205
780. std DFALIGNED           NOOP    fp_ws           dpans12.htm     12.6.2.1207
781. std DFLOAT+             NOOP    fp_ws           dpans12.htm     12.6.2.1208
782. std DFLOATS             NOOP    fp_ws           dpans12.htm     12.6.2.1209
783. std F**                 NOOP    fp_ws           dpans12.htm     12.6.2.1415
784. std F.                  NOOP    fp_ws           dpans12.htm     12.6.2.1427
785. std FABS                NOOP    fp_ws           dpans12.htm     12.6.2.1474
786. std FACOS               NOOP    fp_ws           dpans12.htm     12.6.2.1476
787. std FACOSH              NOOP    fp_ws           dpans12.htm     12.6.2.1477
788. std FALOG               NOOP    fp_ws           dpans12.htm     12.6.2.1484
789. std FASIN               NOOP    fp_ws           dpans12.htm     12.6.2.1486
790. std FASINH              NOOP    fp_ws           dpans12.htm     12.6.2.1487
791. std FATAN               NOOP    fp_ws           dpans12.htm     12.6.2.1488
792. std FATAN2              NOOP    fp_ws           dpans12.htm     12.6.2.1489
793. std FATANH              NOOP    fp_ws           dpans12.htm     12.6.2.1491
794. std FCOS                NOOP    fp_ws           dpans12.htm     12.6.2.1493
795. std FCOSH               NOOP    fp_ws           dpans12.htm     12.6.2.1494
796. std FE.                 NOOP    fp_ws           dpans12.htm     12.6.2.1513
797. std FEXP                NOOP    fp_ws           dpans12.htm     12.6.2.1515
798. std FEXPM1              NOOP    fp_ws           dpans12.htm     12.6.2.1516
799. std FLN                 NOOP    fp_ws           dpans12.htm     12.6.2.1553
800. std FLNP1               NOOP    fp_ws           dpans12.htm     12.6.2.1554
801. std FLOG                NOOP    fp_ws           dpans12.htm     12.6.2.1557
802. std FS.                 NOOP    fp_ws           dpans12.htm     12.6.2.1613
803. std FSIN                NOOP    fp_ws           dpans12.htm     12.6.2.1614
804. std FSINCOS             NOOP    fp_ws           dpans12.htm     12.6.2.1616
805. std FSINH               NOOP    fp_ws           dpans12.htm     12.6.2.1617
806. std FSQRT               NOOP    fp_ws           dpans12.htm     12.6.2.1618
807. std FTAN                NOOP    fp_ws           dpans12.htm     12.6.2.1625
808. std FTANH               NOOP    fp_ws           dpans12.htm     12.6.2.1626
809. std F~                  NOOP    fp_ws           dpans12.htm     12.6.2.1640
810. std PRECISION           NOOP    fp_ws           dpans12.htm     12.6.2.2035
811. std SET-PRECISION       NOOP    fp_ws           dpans12.htm     12.6.2.2200
812. std SF!                 NOOP    fp_ws           dpans12.htm     12.6.2.2202
813. std SF@                 NOOP    fp_ws           dpans12.htm     12.6.2.2203
814. std SFALIGN             NOOP    fp_ws           dpans12.htm     12.6.2.2204
815. std SFALIGNED           NOOP    fp_ws           dpans12.htm     12.6.2.2206
816. std SFLOAT+             NOOP    fp_ws           dpans12.htm     12.6.2.2207
817. std SFLOATS             NOOP    fp_ws           dpans12.htm     12.6.2.2208
818. std (LOCAL)             NOOP    local_ws        dpans13.htm     13.6.1.0086
819. std LOCALS|             NOOP    local_ws        dpans13.htm     13.6.2.1795
820. std ALLOCATE            NOOP    malloc_ws       dpans14.htm     14.6.1.0707
821. std FREE                NOOP    malloc_ws       dpans14.htm     14.6.1.1605
822. std RESIZE              NOOP    malloc_ws       dpans14.htm     14.6.1.2145
823. std .S                  NOOP    progtools_ws    dpans15.htm     15.6.1.0220
824. std ?                   NOOP    progtools_ws    dpans15.htm     15.6.1.0600
825. std DUMP                NOOP    progtools_ws    dpans15.htm     15.6.1.1280
826. std SEE                 NOOP    progtools_ws    dpans15.htm     15.6.1.2194
827. std WORDS               NOOP    progtools_ws    dpans15.htm     15.6.1.2465
828. std ;CODE               resunk  progtools_ws    dpans15.htm     15.6.2.0470
829. std AHEAD               NOOP    progtools_ws    dpans15.htm     15.6.2.0702
830. std ASSEMBLER           NOOP    progtools_ws    dpans15.htm     15.6.2.0740
831. std BYE                 NOOP    progtools_ws    dpans15.htm     15.6.2.0830
832. std CODE                defusr  progtools_ws    dpans15.htm     15.6.2.0930
833. std CS-PICK             NOOP    progtools_ws    dpans15.htm     15.6.2.1015
834. std CS-ROLL             NOOP    progtools_ws    dpans15.htm     15.6.2.1020
835. std EDITOR              NOOP    progtools_ws    dpans15.htm     15.6.2.1300
836. std FORGET              NOOP    progtools_ws    dpans15.htm     15.6.2.1580
837. std [ELSE]              NOOP    progtools_ws    dpans15.htm     15.6.2.2531
838. std [IF]                bigif   progtools_ws    dpans15.htm     15.6.2.2532
839. std [THEN]              NOOP    progtools_ws    dpans15.htm     15.6.2.2533
840. std DEFINITIONS         NOOP    searchord_ws    dpans16.htm     16.6.1.1180
841. std FORTH-WORDLIST      NOOP    searchord_ws    dpans16.htm     16.6.1.1595
842. std GET-CURRENT         NOOP    searchord_ws    dpans16.htm     16.6.1.1643
843. std GET-ORDER           NOOP    searchord_ws    dpans16.htm     16.6.1.1647
844. std SEARCH-WORDLIST     NOOP    searchord_ws    dpans16.htm     16.6.1.2192
845. std SET-CURRENT         NOOP    searchord_ws    dpans16.htm     16.6.1.2195
846. std SET-ORDER           NOOP    searchord_ws    dpans16.htm     16.6.1.2197
847. std WORDLIST            NOOP    searchord_ws    dpans16.htm     16.6.1.2460
848. std ALSO                NOOP    searchord_ws    dpans16.htm     16.6.2.0715
849. std FORTH               NOOP    searchord_ws    dpans16.htm     16.6.2.1590
850. std ONLY                NOOP    searchord_ws    dpans16.htm     16.6.2.1965
851. std ORDER               NOOP    searchord_ws    dpans16.htm     16.6.2.1985
852. std PREVIOUS            NOOP    searchord_ws    dpans16.htm     16.6.2.2037
853. std -TRAILING           NOOP    string_ws       dpans17.htm     17.6.1.0170
854. std /STRING             NOOP    string_ws       dpans17.htm     17.6.1.0245
855. std BLANK               NOOP    string_ws       dpans17.htm     17.6.1.0780
856. std CMOVE               NOOP    string_ws       dpans17.htm     17.6.1.0910
857. std CMOVE>              NOOP    string_ws       dpans17.htm     17.6.1.0920
858. std COMPARE             NOOP    string_ws       dpans17.htm     17.6.1.0935
859. std SEARCH              NOOP    string_ws       dpans17.htm     17.6.1.2191
860. std SLITERAL            NOOP    string_ws       dpans17.htm     17.6.1.2212
861. 
862. _DEFINITIONS
863. 
864. \ Revision history
865. \ 0. 1st release to guinea pigs via comp.lang.forth
866. \ 1. Added multi-line comment 0 [IF]. Colored CHAR outside definitions.
867. \ 2. (EJB) Added missing definitions for common but nonstandard words
868. \    and cleaned up to account for case sensitivity.
869. \ 3. (EJB) Fixed up to create conforming XHTML 1.0 Strict
870. \ 4. (BNE) File check before nesting, moved file names to the hyperlink table,
871. \    added some option flags, cleared hyperlink list for each run. Added more
872. \    multiline comment words. Expands tabs to spaces. Title uses %20 for blanks.
873. \ 4a. (DBU) Added dpanspath to configure the path to the dpans-files. Added
874. \     linksource to output a hyperlink to the original source file. Added
875. \     some words used in Win32Forth. Added copyright to output a copyright text
876. \     at the bottom of the HTML-file.
877. \ 4b. (DBU) Fixed some HTML-Error's found with "CSE HTML Validator Lite v3.50"
878. \ 4c. (EJB/DBU) Consolidated some strings
879. \ 4d. (DBU) Cleanup of 4c and renaming copyright to footer 
 
880. \ 4d. (EJB) Fixed case sensitivity of a few words
880. 
881.