Annotation of gforth/wf.fs, revision 1.9

1.1       pazsan      1: \ wiki forth
                      2: 
                      3: require string.fs
                      4: 
                      5: \ tag handling
                      6: 
                      7: : .' '' parse postpone SLiteral postpone type ; immediate
1.3       pazsan      8: : s' '' parse postpone SLiteral ; immediate
1.1       pazsan      9: 
1.3       pazsan     10: Variable tag-option
                     11: s" " tag-option $!
                     12: 
                     13: : tag ( addr u -- ) '< emit type tag-option $@ type '> emit
                     14:     s" " tag-option $! ;
1.1       pazsan     15: : /tag ( addr u -- ) '< emit '/ emit type '> emit ;
1.2       pazsan     16: : tagged ( addr1 u1 addr2 u2 -- )  2dup 2>r tag type 2r> /tag ;
1.1       pazsan     17: 
1.3       pazsan     18: : opt ( addr u opt u -- )  s"  " tag-option $+!
                     19:     tag-option $+! s' ="' tag-option $+! tag-option $+!
                     20:     s' "' tag-option $+! ;
                     21: : href= ( addr u -- )  s" href" opt ;
                     22: : src=  ( addr u -- )  s" src" opt ;
1.4       pazsan     23: : alt=  ( addr u -- )  s" alt" opt ;
1.7       pazsan     24: : width=  ( addr u -- )  s" width" opt ;
                     25: : height=  ( addr u -- )  s" height" opt ;
1.3       pazsan     26: : align= ( addr u -- ) s" align" opt ;
                     27: : mailto: ( addr u -- ) s'  href="mailto:' tag-option $+!
                     28:     tag-option $+! s' "' tag-option $+! ;
                     29: 
1.1       pazsan     30: \ environment handling
                     31: 
                     32: Variable oldenv
                     33: Variable envs 10 0 [DO] 0 , [LOOP]
                     34: 
                     35: : env$ ( -- addr ) envs dup @ 1+ cells + ;
                     36: : env ( addr u -- ) env$ $! ;
                     37: : env? ( -- ) envs @ oldenv @
                     38:     2dup > IF  env$ $@ tag  THEN
                     39:     2dup < IF  env$ cell+ $@ /tag  env$ cell+ $off  THEN
                     40:     drop oldenv ! ;
                     41: : +env  1 envs +! ;
                     42: : -env -1 envs +! env? ;
                     43: : -envs envs @ 0 ?DO  -env cr  LOOP ;
1.2       pazsan     44: : >env ( addr u -- ) +env env env? ;
1.1       pazsan     45: 
1.6       pazsan     46: \ alignment
                     47: 
                     48: : >align ( c -- )
                     49:     CASE
                     50:        'l OF  s" left"   align=  ENDOF
                     51:        'r OF  s" right"  align=  ENDOF
                     52:        'c OF  s" center" align=  ENDOF
                     53:        '< OF  s" left"   align=  ENDOF
                     54:        '> OF  s" right"  align=  ENDOF
                     55:        '| OF  s" center" align=  ENDOF
                     56:     ENDCASE ;
                     57: 
1.7       pazsan     58: \ image handling
                     59: 
                     60: Create imgbuf $20 allot
                     61: 
                     62: Create pngsig $89 c, $50 c, $4E c, $47 c, $0D c, $0A c, $1A c, $0A c,
                     63: Create jfif   $FF c, $D8 c, $FF c, $E0 c, $00 c, $10 c, $4A c, $46 c,
                     64:               $49 c, $46 c,
                     65: 
                     66: : b@ ( addr -- x )   0 swap 4 bounds ?DO  8 lshift I c@ +  LOOP ;
                     67: : bw@ ( addr -- x )  0 swap 2 bounds ?DO  8 lshift I c@ +  LOOP ;
                     68: 
                     69: : gif? ( -- flag )
                     70:     s" GIF89a" imgbuf over compare 0=
                     71:     s" GIF87a" imgbuf over compare 0= or ;
                     72: : gif-size ( -- w h )
                     73:     imgbuf 6 + c@ imgbuf 7 + c@ 8 lshift +
                     74:     imgbuf 8 + c@ imgbuf 9 + c@ 8 lshift + ;
                     75: 
                     76: : png? ( -- flag )
                     77:     pngsig 8 imgbuf over compare 0= ;
                     78: : png-size ( -- w h )
                     79:     imgbuf $10 + b@ imgbuf $14 + b@ ;
                     80: 
                     81: : jpg? ( -- flag )
                     82:     jfif 10 imgbuf over compare 0= ;
                     83: : jpg-size ( fd -- w h )  >r
                     84:     2.  BEGIN
                     85:        2dup r@ reposition-file throw
                     86:        imgbuf $10 r@ read-file throw 0<>
1.8       pazsan     87:        imgbuf bw@ $FFC0 $FFD0 within 0= and  WHILE
1.7       pazsan     88:        imgbuf 2 + bw@ 2 + 0 d+  REPEAT
                     89:     2drop imgbuf 5 + bw@ imgbuf 7 + bw@  rdrop ;
                     90: 
                     91: : img-size ( fd -- w h )  >r
                     92:     gif? IF  gif-size  rdrop EXIT  THEN
                     93:     jpg? IF  r> jpg-size  EXIT  THEN
                     94:     png? IF  png-size  rdrop EXIT  THEN
                     95:     0 0 ;
                     96: 
                     97: : .img-size ( addr u -- )
                     98:     r/o open-file throw >r
                     99:     imgbuf $20 r@ read-file throw drop
                    100:     r@ img-size
                    101:     r> close-file throw
                    102:     ?dup IF  0 <# #S #> width=   THEN
                    103:     ?dup IF  0 <# #S #> height=  THEN ;
                    104: 
1.1       pazsan    105: \ link creation
                    106: 
                    107: Variable link
                    108: Variable link-suffix
1.3       pazsan    109: Variable iconpath
1.1       pazsan    110: 
1.2       pazsan    111: Variable do-size
1.9     ! pazsan    112: Variable do-icon
1.2       pazsan    113: 
1.8       pazsan    114: Defer parse-line
                    115: 
1.7       pazsan    116: : alt-suffix ( -- )
                    117:     link-suffix $@len 2 - link-suffix $!len
                    118:     s" [" link-suffix 0 $ins
                    119:     s" ]" link-suffix $+!
                    120:     link-suffix $@ alt= ;
                    121: 
1.6       pazsan    122: : get-icon ( addr u -- )  iconpath @ IF  2drop  EXIT  THEN
                    123:     link-suffix $! s" .*" link-suffix $+!
1.1       pazsan    124:     s" icons" open-dir throw >r
                    125:     BEGIN
                    126:        pad $100 r@ read-dir throw  WHILE
                    127:        pad swap 2dup link-suffix $@ filename-match
1.3       pazsan    128:        IF  s" icons/" iconpath $! iconpath $+!
1.7       pazsan    129:            iconpath $@ 2dup .img-size src=
                    130:            alt-suffix  s" img" tag true
1.1       pazsan    131:        ELSE  2drop  false  THEN
1.6       pazsan    132:     UNTIL  ELSE  drop  THEN
1.1       pazsan    133:     r> close-dir throw ;
                    134: 
1.9     ! pazsan    135: : link-icon? ( -- )  do-icon @ 0= ?EXIT
        !           136:     iconpath @  IF  iconpath $off  THEN
        !           137:     link $@ + 1- c@ '/ = IF  s" index.html"  ELSE  link $@  THEN
1.8       pazsan    138:     BEGIN  '. $split 2swap 2drop dup  WHILE
                    139:        2dup get-icon  REPEAT  2drop ;
1.6       pazsan    140: 
1.2       pazsan    141: : link-size? ( -- )  do-size @ 0= ?EXIT
1.1       pazsan    142:     link $@ r/o open-file IF  drop  EXIT  THEN >r
                    143:     r@ file-size throw $400 um/mod nip ."  (" 0 u.r ." k)"
                    144:     r> close-file throw ;
                    145: 
1.2       pazsan    146: : link-options ( addr u -- addr' u' )
1.9     ! pazsan    147:     do-size off  do-icon on
        !           148:     over c@ '% = over 0> and IF  do-size on  1 /string  THEN
        !           149:     over c@ '\ = over 0> and IF  do-icon off 1 /string  THEN ;
1.2       pazsan    150: 
1.8       pazsan    151: : parse-string ( addr u -- )
                    152:     evaluate-input cell new-tib #tib ! tib !
                    153:     ['] parse-line catch pop-file throw ;
                    154: 
1.9     ! pazsan    155: : .link ( addr u -- ) '| $split 
1.2       pazsan    156:     link-options link $!
1.1       pazsan    157:     link $@len 0= IF  2dup link $! s" .html" link $+!  THEN
1.8       pazsan    158:     link-icon? link $@ href= s" a" tag
1.9     ! pazsan    159:     parse-string s" a" /tag link-size? ;
        !           160: : >link ( -- )  '[ parse type '] parse .link ;
1.1       pazsan    161: 
1.9     ! pazsan    162: : .img ( addr u -- ) '| $split 
1.6       pazsan    163:     dup IF  2swap alt=  ELSE  2drop  THEN
                    164:     tag-option $@len >r over c@ >align tag-option $@len r> = 1+ /string
1.7       pazsan    165:     2dup .img-size src= s" img" tag ;
1.9     ! pazsan    166: : >img ( -- )   '{ parse type '} parse .img ;
1.4       pazsan    167: 
1.1       pazsan    168: \ line handling
                    169: 
1.4       pazsan    170: : char? ( -- c )  >in @ char swap >in ! ;
1.1       pazsan    171: : parse-tag ( addr u char -- )
                    172:     >r r@ parse type
1.2       pazsan    173:     r> parse 2swap tagged ;
1.1       pazsan    174: 
1.6       pazsan    175: : .text ( -- )         >in @ >r char drop
1.9     ! pazsan    176:     source r@ /string >in @ r> - nip
        !           177:     bounds ?DO  I c@
        !           178:        case
        !           179:            '& of  ." &amp;"  endof
        !           180:            '< of  ." &lt;"   endof
        !           181:            dup emit
        !           182:        endcase
        !           183:     LOOP ;
1.6       pazsan    184: 
                    185: Create do-words  $100 0 [DO] ' .text , [LOOP]
                    186: 
1.9     ! pazsan    187: :noname '( emit 1 >in +! ; '( cells do-words + !
        !           188: 
1.6       pazsan    189: : bind-char ( xt -- )  char cells do-words + ! ;
                    190: 
                    191: : char>tag ( -- ) char >r
                    192: :noname bl sword postpone SLiteral r@ postpone Literal
                    193:     postpone parse-tag postpone ; r> cells do-words + ! ;
1.1       pazsan    194: 
1.6       pazsan    195: char>tag * b
                    196: char>tag _ em
                    197: char>tag # code
                    198: 
1.9     ! pazsan    199: ' >link bind-char [
        !           200: ' >img  bind-char {
1.6       pazsan    201: 
                    202: : do-word ( char -- )  cells do-words + perform ;
1.4       pazsan    203: 
1.9     ! pazsan    204: : word? ( -- addr u )  >in @ >r bl sword r> >in ! ;
        !           205: 
        !           206: wordlist Constant autoreplacements
        !           207: 
1.8       pazsan    208: :noname ( -- )
1.9     ! pazsan    209:     BEGIN char? do-word source nip >in @ = UNTIL ; is parse-line
        !           210: 
        !           211: : parse-line+ ( -- )
        !           212:     BEGIN
        !           213:        word? autoreplacements search-wordlist
        !           214:        IF    execute  bl sword 2drop
        !           215:            source >in @ 1- /string drop c@ bl = >in +!
        !           216:        ELSE  char? do-word  THEN
        !           217:        source nip >in @ = UNTIL ;
1.4       pazsan    218: 
                    219: : parse-to ( char -- ) >r
                    220:     BEGIN  char? dup r@ <> WHILE
                    221:        do-word source nip >in @ = UNTIL  ELSE  drop  THEN
                    222:     r> parse type ;
1.1       pazsan    223: 
1.9     ! pazsan    224: \ autoreplace
        !           225: 
        !           226: : autoreplace ( <[string|url]> -- )
        !           227:     get-current autoreplacements set-current
        !           228:     Create set-current
        !           229:     here 0 , '[ parse 2drop '] parse rot $!
        !           230:     DOES> $@ .link ;
        !           231:     
1.1       pazsan    232: \ paragraph handling
                    233: 
                    234: : parse-par ( -- )
1.9     ! pazsan    235:     BEGIN  parse-line+ cr refill  WHILE
1.1       pazsan    236:        source nip 0= UNTIL  THEN ;
                    237: 
                    238: : par ( addr u -- ) env? 2dup tag parse-par /tag cr cr ;
1.9     ! pazsan    239: : line ( addr u -- ) env? 2dup tag parse-line+ /tag cr cr ;
1.1       pazsan    240: 
                    241: \ handle global tags
                    242: 
1.8       pazsan    243: Variable indentlevel
                    244: : indent ( n -- )  indentlevel @
                    245:     2dup < IF  2dup swap DO  -env -env  LOOP  THEN
                    246:     2dup > IF  2dup      DO  s" dl" >env  LOOP  THEN
                    247:     2dup = IF  -env  THEN
                    248:     drop indentlevel ! s" dt" >env ;
                    249: : +indent ( -- )  -env s" dd" >env ;
                    250: 
1.1       pazsan    251: wordlist constant longtags
                    252: 
                    253: Variable end-sec
                    254: 
                    255: longtags set-current
                    256: 
1.8       pazsan    257: : --- 1 indent cr s" hr" tag cr +indent ;
                    258: : *   1 indent s" h1" line +indent ;
                    259: : **  1 indent s" h2" line +indent ;
                    260: : *** 2 indent s" h3" line +indent ;
1.1       pazsan    261: : - s" ul" env s" li" par ;
                    262: : + s" ol" env s" li" par ;
                    263: : << +env ;
1.3       pazsan    264: : <* s" center" >env ;
1.1       pazsan    265: : >> -env ;
1.3       pazsan    266: : *> -env ;
1.9     ! pazsan    267: : :: interpret ;
1.8       pazsan    268: : . end-sec on indentlevel off ;
1.9     ! pazsan    269: : :code s" pre" >env
        !           270:     BEGIN  source >in @ /string type cr refill  WHILE
        !           271:        source s" :endcode" compare 0= UNTIL  THEN
        !           272:   -env ;
1.1       pazsan    273: : \ postpone \ ;
                    274: 
                    275: definitions
1.3       pazsan    276:     
                    277: \ Table
                    278: 
                    279: Variable table-format
                    280: Variable table#
                    281: 
1.6       pazsan    282: : |tag  table-format $@ table# @ /string drop c@ >align
                    283:     >env  1 table# +! ;
1.3       pazsan    284: : |d  table# @ IF  -env  THEN  s" td" |tag ;
                    285: : |h  table# @ IF  -env  THEN  s" th" |tag ;
                    286: : |line  s" tr" >env  table# off ;
                    287: : line|  -env -env cr ;
                    288: 
1.5       pazsan    289: : next-char ( -- char )  source drop >in @ + c@ ;
                    290: 
1.3       pazsan    291: longtags set-current
                    292: 
                    293: : <| s" table" >env bl sword table-format $! ;
                    294: : |> -env ;
                    295: : +| |line
                    296:     BEGIN
1.5       pazsan    297:        |h '| parse-to next-char '+ =  UNTIL line| ;
1.3       pazsan    298: : -| |line
                    299:     BEGIN
1.5       pazsan    300:        |d '| parse-to next-char '- =  UNTIL line| ;
1.3       pazsan    301: 
                    302: definitions
1.1       pazsan    303: 
                    304: \ parse a section
                    305: 
1.8       pazsan    306: : section-line ( -- )  >in off
1.9     ! pazsan    307:     bl sword longtags search-wordlist
        !           308:     IF    execute
1.8       pazsan    309:     ELSE  source nip IF  >in off s" p" par  THEN  THEN ;
1.1       pazsan    310: : refill-loop ( -- )  end-sec off
1.8       pazsan    311:     BEGIN  refill  WHILE
                    312:        section-line end-sec @ UNTIL  THEN ;
1.1       pazsan    313: : parse-section ( -- )
1.9     ! pazsan    314:     refill-loop ;
1.1       pazsan    315: 
                    316: \ HTML head
                    317: 
                    318: : .title ( addr u -- )
                    319:     .' <!doctype html public "-//w3c//dtd html 4.0 transitional//en">' cr
1.2       pazsan    320:     s" html" >env s" head" >env
1.1       pazsan    321:     .'   <meta http-equiv="Content-Type" content="text/html; charset=iso-8859-1">' cr
1.2       pazsan    322:     s" title" tagged cr
1.1       pazsan    323:     -env ;
                    324: 
                    325: \ HTML trailer
                    326: 
                    327: Variable mail
                    328: Variable mail-name
                    329: 
                    330: : .trailer
1.2       pazsan    331:     s" address" >env s" center" >env
                    332:     ." Last modified: " time&date rot 0 u.r swap 1-
1.1       pazsan    333:     s" janfebmaraprmayjunjulaugsepoctnovdec" rot 3 * /string 3 min type
1.3       pazsan    334:     0 u.r ."  by "
                    335:     mail $@ mailto: mail-name $@ s" a" tagged
1.1       pazsan    336:     -envs ;
                    337: 
                    338: \ top word
                    339: 
1.6       pazsan    340: : parse" ( -- addr u ) '" parse 2drop '" parse ;
                    341: 
1.1       pazsan    342: : maintainer
1.6       pazsan    343:     bl sword mail $! parse" mail-name $! ;
                    344: 
                    345: Variable style$
                    346: : style> style$ @ 0= IF  s" " style$ $!  THEN  style$ $@ tag-option $! ;
                    347: : >style tag-option $@ style$ $! s" " tag-option $! ;
                    348: 
                    349: : style  style> opt >style ;
                    350: : background ( -- )  parse" s" background" style ;
                    351: : text ( -- )  parse" s" text" style ;
                    352:     warnings @ warnings off
                    353: : link ( -- )  parse" s" link" style ;
                    354:     warnings !
                    355: : vlink ( -- ) parse" s" vlink" style ;
                    356: : marginheight ( -- ) parse" s" marginheight" style ;
1.1       pazsan    357: 
                    358: : wf ( -- )
                    359:     outfile-id >r
                    360:     bl sword r/w create-file throw to outfile-id
1.6       pazsan    361:     parse" .title
                    362:     +env style> s" body" env env?
1.1       pazsan    363:     ['] parse-section catch .trailer
                    364:     outfile-id close-file throw
                    365:     r> to outfile-id
                    366:     dup 0< IF  throw  ELSE  drop  THEN ;
                    367: 
1.8       pazsan    368: : eval-par ( addr u -- )
                    369:   s" wf-temp.wf" r/w create-file throw >r
                    370:   r@ write-file r> close-file throw
                    371:   push-file s" wf-temp.wf" r/o open-file throw loadfile !
                    372:   parse-par parse-section
                    373:   loadfile @ close-file swap 2dup or
                    374:   pop-file  drop throw throw
                    375:   s" wf-temp.wf" delete-file throw ;
                    376: 
1.2       pazsan    377: \ simple text data base
                    378: 
                    379: : get-rest ( addr -- ) 0 parse -trailing rot $! ;
1.8       pazsan    380: Create $lf 1 c, #lf c,
                    381: : get-par ( addr -- )  >r  s" " r@ $+!
                    382:     BEGIN  0 parse 2dup s" ." compare  WHILE
                    383:        r@ $@len IF  $lf count r@ $+!  THEN  r@ $+!
                    384:        refill 0= UNTIL  ELSE  2drop  THEN
                    385:     rdrop ;
1.2       pazsan    386: 
                    387: Variable last-entry
                    388: Variable field#
                    389: 
                    390: : table: ( xt n -- )  Create , ,  1 field# !
                    391:     DOES> 2@ >in @ >r longtags set-current
                    392:     Create definitions swap , r> >in !
                    393:     here last-entry !
                    394:     dup 0 DO  0 ,  LOOP
                    395:     1 DO  s" " last-entry @ I cells + $!  LOOP
                    396:     last-entry @ get-rest
                    397:     DOES> dup cell+ swap perform ;
                    398: 
                    399: : field:  Create field# @ , 1 field# +!
                    400: DOES> @ cells last-entry @ + get-rest ;
1.8       pazsan    401: : par:  Create field# @ , 1 field# +!
                    402: DOES> @ cells last-entry @ + get-par ;
1.3       pazsan    403: 
                    404: : >field  ' >body @ cells postpone Literal postpone + ; immediate

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>