From: Marco Baringer
Subject: html generation API
Date: 
Message-ID: <m2d6g09ixl.fsf@bese.it>
i'm looking at all the diferent html-gen packages out there and i've
got a stylistic question: how come everybody prefers to have a html or
some such macro within which certain keywords in certain positions are
"special" and produce html as opposed to just writing macros called
html, body, table, ecc.?

-- 
-Marco
Ring the bells that still can ring.
Forget your perfect offering.
There is a crack in everything.
That's how the light gets in.
     -Leonard Cohen

From: Wade Humeniuk
Subject: Re: html generation API
Date: 
Message-ID: <diXTa.28922$xn5.4638319@news0.telusplanet.net>
"Marco Baringer" <··@bese.it> wrote in message ···················@bese.it...
> 
> i'm looking at all the diferent html-gen packages out there and i've
> got a stylistic question: how come everybody prefers to have a html or
> some such macro within which certain keywords in certain positions are
> "special" and produce html as opposed to just writing macros called
> html, body, table, ecc.?

This is not true, I have my own html package called primitive-html.
Actually the macros are named like the tags <html>, <body>, </body>,
etc, etc, etc.....

See

http://www3.telus.net/public/whumeniu/primitive-html.lisp

and a real-life example

http://www3.telus.net/public/whumeniu/html-report.lisp

This is part of a windows app written in LWW called "The Runner's Log"

http://www3.telus.net/public/whumeniu/runnerslog-140.exe

Manual

http://www3.telus.net/public/whumeniu/Manual.html

Wade
From: Gareth McCaughan
Subject: Re: html generation API
Date: 
Message-ID: <87u19bvcq4.fsf@g.mccaughan.ntlworld.com>
Marco Baringer <··@bese.it> writes:

> i'm looking at all the diferent html-gen packages out there and i've
> got a stylistic question: how come everybody prefers to have a html or
> some such macro within which certain keywords in certain positions are
> "special" and produce html as opposed to just writing macros called
> html, body, table, ecc.?

Because
  - doing that would require defining a separate macro
    for every HTML tag.
  - it wouldn't automatically continue to work when the
    W3C defines some new tags.
  - it wouldn't be usable for other simple *ML applications.
  - if someone has a function called P or TR or TABLE it's
    rude to force them either to call that CL-USER:P or to
    call the HTML-generating one HTML-GEN:P.
  - the most natural way to represent tags with attributes
    would seem to be ((tag attr value attr value) content...)
    and you can't define macros that work that way.

-- 
Gareth McCaughan
.sig under construc
From: Peter Seibel
Subject: Re: html generation API
Date: 
Message-ID: <m3wue61or8.fsf@javamonkey.com>
Marco Baringer <··@bese.it> writes:

> i'm looking at all the diferent html-gen packages out there and i've
> got a stylistic question: how come everybody prefers to have a html or
> some such macro within which certain keywords in certain positions are
> "special" and produce html as opposed to just writing macros called
> html, body, table, ecc.?

FWIW, when I played around with my own HTML generation code (these
things are getting more numerous than Scheme implementations ;-)) I
did do that. Of course I didn't write the individual macros by hand
but defined a DEFTAG macro that let me declare tags. I'm not sure if
it was a big win but it felt right at the time. One consequence (which
may also have been achievable otherways) was that the macro expansion
could be a bit smart and coalesce the output of nested tag macros. For
instance something like this that consists only of "literal" HTML:

(html
 (head (title "Foo"))
 (body
  (p "This is a paragraph.")
  (p :style "second" "This is another")))

Would expand into a single FORMAT statement:

(PROGN
  (FORMAT
   HTML::*HTML-OUTPUT*
   "<HTML><HEAD><TITLE>Foo</TITLE></HEAD><BODY><P>This is a paragraph.</P><P STYLE=\"second\">This is another</P></BODY></HTML>"))

Also it did--it seems--make it easier to deal with attributes since
the generated tag macros knew to eat up as many keyword/value pairs as
occured in the call and make them into attributes as you can see in
the second P tag above.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Marco Antoniotti
Subject: Re: html generation API
Date: 
Message-ID: <3F219DE8.2090905@cs.nyu.edu>
Peter Seibel wrote:
> Marco Baringer <··@bese.it> writes:
> 
> 
>>i'm looking at all the diferent html-gen packages out there and i've
>>got a stylistic question: how come everybody prefers to have a html or
>>some such macro within which certain keywords in certain positions are
>>"special" and produce html as opposed to just writing macros called
>>html, body, table, ecc.?
> 
> 
> FWIW, when I played around with my own HTML generation code (these
> things are getting more numerous than Scheme implementations ;-)) I
> did do that. Of course I didn't write the individual macros by hand
> but defined a DEFTAG macro that let me declare tags. I'm not sure if
> it was a big win but it felt right at the time. One consequence (which
> may also have been achievable otherways) was that the macro expansion
> could be a bit smart and coalesce the output of nested tag macros. For
> instance something like this that consists only of "literal" HTML:
> 
> (html
>  (head (title "Foo"))
>  (body
>   (p "This is a paragraph.")
>   (p :style "second" "This is another")))
> 
> Would expand into a single FORMAT statement:
> 
> (PROGN
>   (FORMAT
>    HTML::*HTML-OUTPUT*
>    "<HTML><HEAD><TITLE>Foo</TITLE></HEAD><BODY><P>This is a paragraph.</P><P STYLE=\"second\">This is another</P></BODY></HTML>"))
> 
> Also it did--it seems--make it easier to deal with attributes since
> the generated tag macros knew to eat up as many keyword/value pairs as
> occured in the call and make them into attributes as you can see in
> the second P tag above.

Does it mean that you are generating the full string in memory before 
writing it out?

Do you have ways to control this behavior?

Cheers

--
Marco
From: Peter Seibel
Subject: Re: html generation API
Date: 
Message-ID: <m3adb21avw.fsf@javamonkey.com>
Marco Antoniotti <·······@cs.nyu.edu> writes:

> Peter Seibel wrote:
> > Marco Baringer <··@bese.it> writes:
> >
> 
> >>i'm looking at all the diferent html-gen packages out there and i've
> >>got a stylistic question: how come everybody prefers to have a html or
> >>some such macro within which certain keywords in certain positions are
> >>"special" and produce html as opposed to just writing macros called
> >>html, body, table, ecc.?
> > FWIW, when I played around with my own HTML generation code (these
> 
> > things are getting more numerous than Scheme implementations ;-)) I
> > did do that. Of course I didn't write the individual macros by hand
> > but defined a DEFTAG macro that let me declare tags. I'm not sure if
> > it was a big win but it felt right at the time. One consequence (which
> > may also have been achievable otherways) was that the macro expansion
> > could be a bit smart and coalesce the output of nested tag macros. For
> > instance something like this that consists only of "literal" HTML:
> > (html
> 
> >  (head (title "Foo"))
> >  (body
> >   (p "This is a paragraph.")
> >   (p :style "second" "This is another")))
> > Would expand into a single FORMAT statement:
> 
> > (PROGN
> 
> >   (FORMAT
> >    HTML::*HTML-OUTPUT*
> >    "<HTML><HEAD><TITLE>Foo</TITLE></HEAD><BODY><P>This is a paragraph.</P><P STYLE=\"second\">This is another</P></BODY></HTML>"))
> > Also it did--it seems--make it easier to deal with attributes since
> 
> > the generated tag macros knew to eat up as many keyword/value pairs as
> > occured in the call and make them into attributes as you can see in
> > the second P tag above.
> 
> Does it mean that you are generating the full string in memory
> before writing it out?

Well, I'm generating the string at complie time. I suppose it's in
memory as part of the code but I it shouldn't involve consing up a big
string at runtime.

On the other hand when I'm actually generating dynamic stuff the
strings obviously have to get broken up. For instance, this:

  (ul (dolist (item some-list) (li item)))

expands into:

  (PROGN
    (FORMAT HTML::*HTML-OUTPUT* "<UL>")
    (DOLIST (ITEM SOME-LIST) 
      (PROGN (FORMAT HTML::*HTML-OUTPUT* "<LI>~A</LI>" ITEM)))
    (FORMAT HTML::*HTML-OUTPUT* "</UL>"))

But where it can, the macro expansion coalesces adjacent tags and even
attributes when they are literal values. Some examples:

This code coalesces the <li> and the <b> tags since they are textually
adjacent:

  (ul (dolist (item some-list) (li (b item)))) ==> 

  (PROGN
    (FORMAT HTML::*HTML-OUTPUT* "<UL>")
    (DOLIST (ITEM SOME-LIST) 
      (PROGN (FORMAT HTML::*HTML-OUTPUT* "<LI><B>~A</B></LI>" ITEM)))
    (FORMAT HTML::*HTML-OUTPUT* "</UL>"))

This code does the same and also inlines the literal value "foo" in
the format control string:

  (ul (dolist (item some-list) (li :style "foo" (b item)))) ==> 

  (PROGN
    (FORMAT HTML::*HTML-OUTPUT* "<UL>")
    (DOLIST (ITEM SOME-LIST) 
      (PROGN (FORMAT HTML::*HTML-OUTPUT* "<LI STYLE=\"foo\"><B>~A</B></LI>" ITEM)))
    (FORMAT HTML::*HTML-OUTPUT* "</UL>"))

But this code has to interpolate the value of the variable:

  (ul (dolist (item some-list) (li :style *foo* (b item))))

  (PROGN
    (FORMAT HTML::*HTML-OUTPUT* "<UL>")
    (DOLIST (ITEM SOME-LIST) 
      (PROGN (FORMAT HTML::*HTML-OUTPUT* "<LI STYLE=\"~A\"><B>~A</B></LI>" *FOO* ITEM)))
    (FORMAT HTML::*HTML-OUTPUT* "</UL>"))


> Do you have ways to control this behavior?

Nope. I haven't noticed that I need any yet. Which is not to say it
mightn't be a good idea--I haven't really used this stuff on anything
particularly serious. I suppose if one was writing large static pages
with these macros it'd just turn into code that prints a big ol'
string to a stream which might lose in various ways. Of course this
code isn't optimized for generating large static pages: it's for
generating dynamic HTML. In those case it seemed that the value of
issuing fewer calls to FORMAT was a win. Though now that I think about
it, I don't know if I really benchmarked things to determine that this
approach is more efficient; I may have just playing around with
various macro techniques and decided to see if I could do this for the
heck of it.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Eduardo Muñoz
Subject: Re: html generation API
Date: 
Message-ID: <u65lqnram.fsf@terra.es>
* Marco Antoniotti <·······@cs.nyu.edu>
| Does it mean that you are generating the full string in memory before
| writing it out?
| 
| Do you have ways to control this behavior?

htout does it too:

* (with-html-output (*standard-output*) (:html (:h1 "Hi") (:p "foo" "bar" "baz")))
<HTML><H1>Hi</H1><P>foobarbaz</P></HTML>
NIL
* (macroexpand '(with-html-output (*standard-output*) (:html (:h1 "Hi") (:p "foo" "bar" "baz"))))
(LET ((*STANDARD-OUTPUT* *STANDARD-OUTPUT*))
  (WRITE-SEQUENCE "<HTML><H1>Hi</H1><P>foobarbaz</P></HTML>" *STANDARD-OUTPUT*)
  NIL)
T

BTW Tim Bradshaw's page (http://www.tfeb.org/) seems to be
up again. 

-- 
Eduardo Mu�oz          | (prog () 10 (print "Hello world!")
http://213.97.131.125/ |          20 (go 10))
From: Rob Warnock
Subject: Re: html generation API
Date: 
Message-ID: <vO2cndvsvqixBr6iXTWc-g@speakeasy.net>
Eduardo Mu�oz  <······@terra.es> wrote:
+---------------
| * Marco Antoniotti <·······@cs.nyu.edu>
| | Does it mean that you are generating the full string in memory before
| | writing it out?
| | Do you have ways to control this behavior?
| 
| htout does it too:
| 
| * (with-html-output (*standard-output*) (:html (:h1 "Hi") (:p "foo"
| "bar" "baz")))
| <HTML><H1>Hi</H1><P>foobarbaz</P></HTML>
| NIL
| * (macroexpand '(with-html-output (*standard-output*) (:html (:h1 "Hi")
| (:p "foo" "bar" "baz"))))
| (LET ((*STANDARD-OUTPUT* *STANDARD-OUTPUT*))
|   (WRITE-SEQUENCE "<HTML><H1>Hi</H1><P>foobarbaz</P></HTML>"
|                   *STANDARD-OUTPUT*)
|   NIL)
+---------------

The problem with HTOUT [which I cheerfully continue to use anyway --
thanks, Tim!] is that it only does this aggregation if *ALL* of the
forms of the entire WITH-HTML-OUTPUT call result in constant strings.
Compare this with Edi Weitz's CL-WHO <URL:http://weitz.de/cl-who/>
[*very* similar to HTOUT], which tries to aggregate runs of constant
strings together [I'm using explicit package names here cuz I normally
have a (use-package :htout) in my init file]:

    > (macroexpand
	'(cl-who:with-html-output (*standard-output* *standard-output*
				   :prologue nil)
	   (:html (:h1 "Hi") (:p "foo" "bar" "baz"))))
    (LET ((*STANDARD-OUTPUT* *STANDARD-OUTPUT*))
      (PROGN
       NIL
       (WRITE-STRING "<html><h1>Hi</h1><p>foobarbaz</p></html>"
		     *STANDARD-OUTPUT*)))
    T
    >

The same as HTOUT so far, yes? [Except for the ":prologue nil" to
suppress the "<!DOCTYPE...>" that CL-WHO wants to put in for you
by default every time. Ugh.] Now let's add just one little STR call
to print a free string variable:

    > (macroexpand
        '(cl-who:with-html-output (*standard-output* *standard-output*
				                     :prologue nil)
	   (:html (:h1 "Hi")
		  (:p "foo" (cl-who:str some-string-var) "bar" "baz"))))
    (LET ((*STANDARD-OUTPUT* *STANDARD-OUTPUT*))
      (PROGN
       NIL
       (WRITE-STRING "<html><h1>Hi</h1><p>foo" *STANDARD-OUTPUT*)
       (PRINC SOME-STRING-VAR *STANDARD-OUTPUT*)
       (WRITE-STRING "barbaz</p></html>" *STANDARD-OUTPUT*)))
    T
    >

Again, exactly what one would expect [or at least hope], yes?

Unfortunately, as noted above HTOUT doesn't do any aggregation at all if
it can't aggregate the entire macro call, and so just that one reference
to STR blows the code size up *way* out of sight [oops!]:

    > (macroexpand
        '(with-html-output (*standard-output*)
	   (:html (:h1 "Hi")
		  (:p "foo" (str some-string-var) "bar" "baz"))))
    (LET ((*STANDARD-OUTPUT* *STANDARD-OUTPUT*))
      (MACROLET ((HTM (&BODY ORG.TFEB.TML::FORMS)
		   `(WITH-HTML-OUTPUT (*STANDARD-OUTPUT* *STANDARD-OUTPUT* NIL)
				      ,@ORG.TFEB.TML::FORMS))
		 (FMT (ORG.TFEB.TML::FORMAT-STRING &REST ORG.TFEB.TML::ARGS)
		   `(FORMAT *STANDARD-OUTPUT*
			    ,ORG.TFEB.TML::FORMAT-STRING
			    ,@ORG.TFEB.TML::ARGS))
		 (LFD (&OPTIONAL (ORG.TFEB.TML::N 1))
		   (IF (= ORG.TFEB.TML::N 1)
		       '(TERPRI *STANDARD-OUTPUT*)
		       `(LOOP ORG.TFEB.TML::REPEAT
			      ,ORG.TFEB.TML::N
			      DO
			      (TERPRI *STANDARD-OUTPUT*))))
		 (ESC (STRING &OPTIONAL MAP)
		   (IF MAP
		       `(WRITE-SEQUENCE (ESCAPE-STRING ,STRING ,MAP)
					*STANDARD-OUTPUT*)
		       `(WRITE-SEQUENCE (ESCAPE-STRING ,STRING)
					*STANDARD-OUTPUT*)))
		 (STR (STRING)
		   `(WRITE-SEQUENCE ,STRING *STANDARD-OUTPUT*)))
	(PROGN
	 (EMIT-TAG ':HTML *STANDARD-OUTPUT* :TYPE :OPEN)
	 (PROGN
	  (EMIT-TAG ':H1 *STANDARD-OUTPUT* :TYPE :OPEN)
	  (WRITE-SEQUENCE "Hi" *STANDARD-OUTPUT*)
	  (EMIT-TAG ':H1 *STANDARD-OUTPUT* :TYPE :CLOSE))
	 (PROGN
	  (EMIT-TAG ':P *STANDARD-OUTPUT* :TYPE :OPEN)
	  (WRITE-SEQUENCE "foo" *STANDARD-OUTPUT*)
	  (STR SOME-STRING-VAR)
	  (WRITE-SEQUENCE "bar" *STANDARD-OUTPUT*)
	  (WRITE-SEQUENCE "baz" *STANDARD-OUTPUT*)
	  (EMIT-TAG ':P *STANDARD-OUTPUT* :TYPE :CLOSE))
	 (EMIT-TAG ':HTML *STANDARD-OUTPUT* :TYPE :CLOSE))))
    T
    >

[The EMIT-TAGs are the generic functions HTOUT uses for the general cases.
All well and good, but it would be nice to do some more constant-string
aggregation around their occurences.]

That said, HTOUT is plenty fast for my current applications
(especially when compiled), so I haven't found a need yet to
convert to CL-WHO. (Yet...)


-Rob

-----
Rob Warnock, PP-ASEL-IA		<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Edi Weitz
Subject: Re: html generation API
Date: 
Message-ID: <87y8ykxpue.fsf@bird.agharta.de>
····@rpw3.org (Rob Warnock) writes:

> The problem with HTOUT [which I cheerfully continue to use anyway --
> thanks, Tim!] is that it only does this aggregation if *ALL* of the
> forms of the entire WITH-HTML-OUTPUT call result in constant
> strings.  Compare this with Edi Weitz's CL-WHO
> <URL:http://weitz.de/cl-who/> [*very* similar to HTOUT], which tries
> to aggregate runs of constant strings together

Thanks for reminding me, Rob. I wrote in the CL-WHO docs that I don't
actually remember why I wrote my own library while HTOUT was
available. I think this was the main reason. (Now that I recall the
*PRINT-PRETTY* hint Douglas Crosher gave me at that time I'm pretty
sure I was desperately trying to speed up some HTML output and thought
I could improve the code's performance by aggregating constant
strings. Turned out this wasn't really necessary but *PRINT-PRETTY*
was the main culprit.)

And, yes, CL-WHO's syntax is *very* similar to HTOUT's. HTOUT was my
main source of inspiration.

> The same as HTOUT so far, yes? [Except for the ":prologue nil" to
> suppress the "<!DOCTYPE...>" that CL-WHO wants to put in for you by
> default every time. Ugh.]

Not good? I usually have one big WITH-HTML-OUTPUT per page so the
:PROLOGUE default is fine for me. If other people use it and the
majority of them is annoyed by this I'll happily change the default in
the next release.

Cheers,
Edi.
From: Rob Warnock
Subject: Re: html generation API
Date: 
Message-ID: <GeycnSvMzsNBMr6iXTWc-g@speakeasy.net>
Edi Weitz  <···@agharta.de> wrote:
+---------------
| ····@rpw3.org (Rob Warnock) writes:
| > The same as HTOUT so far, yes? [Except for the ":prologue nil" to
| > suppress the "<!DOCTYPE...>" that CL-WHO wants to put in for you by
| > default every time. Ugh.]
| 
| Not good? I usually have one big WITH-HTML-OUTPUT per page so the
| :PROLOGUE default is fine for me. If other people use it and the
| majority of them is annoyed by this I'll happily change the default in
| the next release.
+---------------

Well, I don't know about other people, but it would certainly be an
issue for me, if I were to convert to CL-WHO (so much so I would probably
fork a local variant myself, if the default remained the same).

I find that I tend to write my code (especially the SQL-related stuff)
so that bits & sections of pages get factored out into little utility
routines (e.g., headers, footers, top & left nav bars, buttons, sidebars,
etc.), each of which does its own WITH-HTML-OUTPUT. E.g., here from one
of my apps are several uses of WITH-HTML-OUTPUT which are *not* at the
top of a page (and thus would have to have ":prologue nil" added to each):

;;;
;;; Canned "buttons"
;;;

(defun search-again-button (s self)
  (with-html-output (s s t)
    (:form (:method "POST" :action self) (lfd)
      (when *debug*
        (htm "[debug = " *debug* "]" :br (lfd)
             (:input (:type "hidden" :name "debug" :value "yes")) (lfd)))
      (:input (:type "submit" :value "Search Again"))
      (lfd))
    (lfd)))

(defun addnew-button (s self)
  (with-html-output (s s t)
    (:form (:method "POST" :action self) (lfd)
      (when *debug*
        (htm "[debug = " *debug* "]" :br (lfd)
             (:input (:type "hidden" :name "debug" :value "yes")) (lfd)))
      (:input (:type "hidden" :name "state" :value "addnew")) (lfd)
      (:input (:type "submit" :value "Add New Entry"))
      (lfd))
    (lfd)))

(defun image-edit-button (s seq &optional (image +editkey-url+))
  "Given a SEQ value N, outputs an HTML <input type=image name=seq_N>
  \"edit button\" for it."
  (with-html-output (s s t)
    (:input (:type "image" :src image :border 1
             :name (format nil "seq_~a" seq)))))

;;; Generic SQL query error message within an already-opened HTML context.
(defun sql-error-html (s error)
  (with-html-output (s s t)
    (:h1 () (:font (:color "red") "Error in SQL Processing!"))
      (:pre ()
        (fmt "~&~a~%" (escape-string (format nil "~a" error))))
      (debug-bindings-html s)))		; Show the query that caused this.

I also use WITH-HTML-OUTPUT within "callbacks". That is, I have some
routines for outputting HTML tables that provide optional callbacks at
various points in the processing so the caller can tweak the processing
in various ways (all the way up to adding extra rows or columns! -- as
in the following example). Another call to WITH-HTML-OUTPUT thus gets
used in the FLET of the callback, like so:

;;; RESULTS-EDIT-PAGE
;;; Display search results with a graphical "Edit" button in front of
;;; each row. Processing is slightly more complicated in this case.
;;; We need to strip the "seq" & "vseq" columns off the results, add
;;; a column for the edit buttons, and then preface each data row with
;;; a matching button. Most of the ugliness comes from the fact that
;;; LIST-HTML-TABLE applies ESCAPE-STRING to all its input data (which
;;; would ruin our edit buttons!), so to get around that we're going
;;; to use its callback feature to write the first column ourselves.
;;; We remember the stripped OIDs locally and step through them in
;;; the callback in parallel with LIST-HTML-TABLE's enumeration of
;;; the rows (admittedly somewhat messy, downright ugly even).

(defun results-edit-page (s self query-results)
  (let* ((seqs (mapcar #'car query-results))	; strip off & save SEQ column
         (rest (mapcar #'cddr query-results)))  ; throw away VSEQ column
    (flet ((callback (item s flag)
             (declare (ignore item))
             (case flag
               ((:before-first-row)
                (with-html-output (s s t)
                  (:th () "&nbsp;")))	; Blank the top-left corner box.
               ((:before-other-rows)	; Add SEQ back, with special processing
                (setf seqs (cdr seqs))  ; [step in parallel w/ L-H-T below]
                (with-html-output (s s t)
                  (:td (:bgcolor "#f0f0ff")
                    (image-edit-button (car seqs) s)))))))
      (results-template-page s self "Search Results (Edit)"
        (lambda ()
          (with-html-output (s s t)
            (:form (:method "POST" :action self)
              (build-continuation :state "edit" :stream s)
              (list-html-table rest :stream s :callback #'callback))))
        :addnew t))))   ; Add handy link to insert user if not found in search.

So right there we have a single routine with *three* WITH-HTML-OUTPUT calls,
none of which are at the "top level" of the page. [That gets generated
inside the RESULTS-TEMPLATE-PAGE.]


-Rob

p.s. Yes, yes, I know: RESULTS-TEMPLATE-PAGE should probably be a macro
(with S and SELF defaulted to the usual values), so you could write that
FLET body like this instead:

      (with-results-template-page (:title "Search Results (Edit)" :addnew t)
	(:form (:method "POST" :action self)
	  (build-continuation :state "edit" :stream s)
	  (list-html-table rest :stream s :callback #'callback)))

[Wouldn't cut down the dynamic stack depth of *uses* of WITH-HTML-OUTPUT,
but it would hide one of them, and the LAMBDA.]

Someday, someday...  ;-}  ;-}

-----
Rob Warnock, PP-ASEL-IA		<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Eduardo Muñoz
Subject: Re: html generation API
Date: 
Message-ID: <un0f0t9wn.fsf@terra.es>
* ····@rpw3.org (Rob Warnock)
| The problem with HTOUT [which I cheerfully continue to use anyway --
| thanks, Tim!] is that it only does this aggregation if *ALL* of the
| forms of the entire WITH-HTML-OUTPUT call result in constant strings.
| Compare this with Edi Weitz's CL-WHO <URL:http://weitz.de/cl-who/>
| [*very* similar to HTOUT], which tries to aggregate runs of constant
| strings together. ...

I had already noticed this and thougth that it was the
culprit of the excessive consing of my pages. So I tried Edi's
cl-who to solve the problem. It does more constant folding,
but the culprit was *print-pretty* after all (Doh!). It
would be a good thing to bind *print-pretty* to nil in these
html-generation packages or at least make a note on the
documentation. 

So I will stick to htout by now since I am not really
concerned with I/O performance of my toy server. I am a
mechanical engineer and this is just a hobby for me :). 

| ... [Except for the ":prologue nil" to
| suppress the "<!DOCTYPE...>" that CL-WHO wants to put in for you
| by default every time. Ugh.] ...

I agree with this. I add the prologue in a macro used for
every page while sub-items (index, footer, etc) don't need it.


-- 
Eduardo Mu�oz          | (prog () 10 (print "Hello world!")
http://213.97.131.125/ |          20 (go 10))
From: Edi Weitz
Subject: Re: html generation API
Date: 
Message-ID: <87k7a33j47.fsf@bird.agharta.de>
Eduardo Mu�oz <······@terra.es> writes:

> | ... [Except for the ":prologue nil" to suppress the
> | "<!DOCTYPE...>" that CL-WHO wants to put in for you by default
> | every time. Ugh.] ...
> 
> I agree with this. I add the prologue in a macro used for every page
> while sub-items (index, footer, etc) don't need it.

Er, I just checked my own usage of CL-WHO and realized that I do the
same, of course. In other words: There's exactly one place where I
need the "prologue", all other calls to WITH-HTML-OUTPUT explicitely
set it to NIL.

How embarassing! I've just uploaded a new version which fixes this
ugly wart.

Thanks to you and Rob,
Edi.