From: Peter Seibel
Subject: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <m33bw2fzkz.fsf@javamonkey.com>
I had coffee today with buddy of mine who is, sadly, a Lispnot. We
were talking about language advocacy and he pointed to an essay he
wrote about using the Bloglines API from Groovy (the dynamic language
based on Java that runs on the JVM) to write an RSS/Atom reader. The
whole thing is 150 lines of code and he was telling me how folks who
emailed him to tell him what a good advertisement for Groovy it was.

I haven't gotten around to playing around with GUI programming in
Common Lisp and I have this other project I'm trying to finish at the
moment. But if anyone is looking for a smallish project to try out,
I'd be interested to see what a Common Lisp version of his program
would look like.

Groovy gets some wins, in this app anyway, from having access to Java
libraries. Maybe some ArmedBear hacker could take a crack at this.

Anyway, my buddy's article is at:

  <http://www.oreillynet.com/pub/a/network/2004/09/28/bloglines.html>

The code is on the second page.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp

From: drewc
Subject: Re: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <MQyQd.403164$6l.11120@pd7tw2no>
I'm not a gui programmer, but since nobody else took the bait, i figured 
i'd give it a shot.

Peter Seibel wrote:
> 
> I haven't gotten around to playing around with GUI programming in
> Common Lisp and I have this other project I'm trying to finish at the
> moment. But if anyone is looking for a smallish project to try out,
> I'd be interested to see what a Common Lisp version of his program
> would look like.

I used the most portable GUI i know, HTML. I have never build a gui 
application in Lisp, but I can't imagine it being any more difficult 
than UCW. Web stuff is generally more verbose.

The code is about 200 lines. it could probably be made shorter with a 
few creative macros, but i'm done with it for now :). Most of the code 
is HTML components, because i built the interface from scratch.

It took me about 3 hours to write. The initial quick hack version took 
only about an hour and was about 120 lines, but it was not as nice as 
this one :).

Big wins for lisp :

do-bloglines-request is quite lispy. I wanted to show some lisp 
functionality right off the bat, so we've got code as data and apply in 
this one.

XMLS: There was never any need to convert the XML to an 'object'. XMLS 
just passes you a list that represents the XML. Working with XML like 
this is very cool.

UCW (components/continuations): Webapps are a pain in the ass. UCW makes 
  it painless. If render-on generated McClim code (or whatever) instead 
of HTML, you could have a desktop application sharing most of the same 
code with the UCW version.

I suspect a bored lisper with GUI chops could take what i've done here 
and turn out a GUI desktop application in 45 minutes. Could be shorter 
as well, which probably matters to your friend the lispnot.

Screenshots at http://merlin.tech.coop/~drewc/bloglines.jpg

Demo app at: http://merlin.tech.coop:8080/bl/index.ucw

Pretty source at http://paste.lisp.org/display/5833

*warning* My ISP has been up and down all day, so those links may not 
work. keep trying.

Here is the source code . Tested only in SBCL with an older version of 
UCW. Enjoy :)
-- 

(defpackage :cl-bloglines
   (:use :cl :it.bese.ucw :it.bese.ucw-user))

(in-package :cl-bloglines)

(require 'xmls)
(require 'aserve)

(setf ucw::*debug-on-error* t)

(defparameter *rpc-url* "http://rpc.bloglines.com/")

(defun do-bloglines-request (username password &key (feed nil) (update 0))
   "Does a listsubs, or a getitems if FEED is non-nil.
    Set UPDATE to 1 to mark a feed read"
   (let ((args `(:basic-authorization ,(cons username password)))
	(url (concatenate 'string *rpc-url* (if feed "getitems"	"listsubs"))))
     (when feed (setf args (append `(:query (("s" . ,feed) ("n" . 
,update))) args)))
     (apply #'net.aserve.client:do-http-request
	   url args)))

;;;some xmls utilities functions
(defun assoc-value (key alist)
   (cadr (assoc key alist :test #'equalp)))

(defun get-by-name (name node)
   (let ((n (find-if #'(lambda (x) (equalp (car x) name))
		    (xmls:node-children node))))
     (if (atom (third n))
	(values (third n) (second n))
	n)))

(defun get-all-by-name (name node)
   (remove nil (mapcar #'(lambda (x)
			  (when (equalp (car x) name) x))
		      (xmls:node-children node))))

(defapplication cl-bloglines
   (:url-prefix "/bl/"))

;;;; define the window component

(defclass bl-window (simple-window-component)
   ((body :initarg :body
          :accessor body
          :component bl-login))
   (:default-initargs
       :title "CL-Bloglines"
     :stylesheet "stylesheet.css")
   (:metaclass standard-component-class))

(defentry-point "index.ucw" (:application cl-bloglines) ()
   (call 'bl-window))

(defmethod render-on ((res response) (win bl-window))
   (<:h1 (<:as-html "CL-Bloglines RSS Reader"))
   (render-on res (body win)))

;;; a base class for all UI objects.
(defclass bl-class ()
   ((feeds :accessor feeds
	  :initarg :feeds :initform "")
    (items :accessor items
	  :initarg :items :initform nil)
    (current-feed :accessor current-feed
		 :initarg :current-feed :initform nil)
    (current-item :accessor current-item
		 :initarg :current-item :initform nil)
    (auth :accessor auth :initarg :auth :initform nil))
   (:metaclass standard-component-class))

(defmethod get-feeds ((bl bl-class))
   "Returns the XML text in outline format and sets (feeds self). nil on 
errors"
   (multiple-value-bind (feeds result)
       (do-bloglines-request (car (auth bl)) (cdr (auth bl)))
     (when (equal 200 result) (setf (feeds bl) feeds))))

(defmethod get-items ((bl bl-class))
   "Returns the RSS XML for the current feed"
   (multiple-value-bind (items result)
	(do-bloglines-request (car (auth bl)) (cdr (auth bl))
			      :feed (current-feed bl))
   (if (equal 200 result)
       (setf (items bl) items)
       (setf (items bl) nil))))

(defmethod extract-feeds ((bl bl-class))
   "Extracts the feed outine from the xml. returns an xmls node"
   (cddr (third (fourth (xmls:parse (feeds bl))))))

(defmethod extract-items ((bl bl-class))
   "extracts the rss items from the XML. Returns an xmls node"
   (caddr (xmls:parse (items bl))))

(defaction select-item ((bl bl-class) item)
   "Makes item the current item"
   (setf (current-item bl) item))

(defaction select-feed ((bl bl-class) feed)
   "Makes feed the current feed"
   (setf (current-feed bl) feed))

(defclass bl-login (login bl-class)
   ()
   (:metaclass standard-component-class)
    (:documentation "Gets the username and password and retrieves the 
feed"))

(defmethod check-credentials ((login bl-login))
   (setf (auth login)
	(cons (login.username login)
	      (login.password login)))
   (get-feeds login))

;;;this has to be ini the ucw package. possibly a bug in ucw.
(defaction it.bese.ucw::login-successful ((login bl-login))
   (call 'rss-reader
	:feeds (feeds login)
	:auth (auth login)))

(defclass feeds-pane (widget-component bl-class)
   ((feeds-outline :accessor feeds-outline))
   (:metaclass standard-component-class)
   (:documentation "a UI class to hold the list of feeds"))

(defmethod render-on ((res response) (f feeds-pane))
   (<:h3 (<:as-html "Subscriptions"))
   (dolist (x (feeds-outline f))
     (let ((id (assoc-value "BloglinesSubId" (second x)))
	  (title (assoc-value "title" (second x)))
	  (unread (assoc-value "BloglinesUnread" (second x))))
       (<:div (<ucw:a :action (select-feed f id)
		     (if (equalp "0" unread)
			 (<:as-html title)
			 (<:as-html
			  (format nil "~A (~A)" title unread))))))))

(defclass items-pane (widget-component bl-class)
   ()
   (:metaclass standard-component-class)
   (:documentation "A UI pane to hold the Titles of the RSS feed"))

(defmethod render-on ((res response) (ip items-pane))
   (<:h3 (<:a :href (get-by-name "link" (items ip))
	     (<:as-html (get-by-name "title" (items ip)))))
   (dolist (item (get-all-by-name "item" (items ip)))
     (<:div :class "item" (<ucw:a :action (select-item ip item)
	    (<:as-html (get-by-name "title" item))))))

(defclass body-pane (widget-component bl-class)
   ()
   (:metaclass standard-component-class)
   (:documentation "a UI pane to hold the bdy of the blog post"))

(defmethod render-on ((res response) (b body-pane))
   (<:h3 (<:as-html (get-by-name "title" (current-item b))))
   (<:a :href (get-by-name "link" (current-item b))
        (<:as-html "(link)"))
   (<:div :class "content"
	 (<:as-is (get-by-name "description" (current-item b)))))

(defclass rss-reader (widget-component bl-class)
   ((feeds-pane :accessor feeds-pane :component feeds-pane)
    (items-pane :accessor items-pane :component items-pane)
    (body-pane :accessor body-pane :component body-pane))
   (:metaclass standard-component-class)
   (:documentation "the RSS reader application itself"))

(defmethod render-on :before ((res response) (rss rss-reader))
   "Propogates the state of the current-feed/item throughout the application
Also gets the current RSS Feed if needed"
   (with-slots (current-feed current-item feeds-pane
			    items-pane body-pane) rss
					;set the current-feed/item
     (setf current-feed (current-feed feeds-pane)
	  current-item (current-item items-pane))
     (setf  (current-item body-pane) current-item)
					;update if current-feed has changed.
     (when (not (equal current-feed (current-feed items-pane)))
       (get-items rss)
       (setf (current-feed items-pane) current-feed
	    (items items-pane) (extract-items rss)))))

(defmethod shared-initialize :after ((rss rss-reader) foo &rest bar)
   "Sets up the initial feed pane"
   (declare (ignore foo bar))
   (setf (feeds-outline (feeds-pane rss))
	(extract-feeds rss)))

(defmethod render-on ((res response) (rss rss-reader))
   (<:table :width "100%" :style "{border:1px solid black}"
    (<:tr (<:td :rowspan 2 :valign "top" :width "20%" :style 
"{border-right : 1px solid black}"
	       (render-on res (feeds-pane rss)))
	 (<:td (render-on res (items-pane rss))))
    (<:tr (<:td (<:hr)(render-on res (body-pane rss))))))





-- 
Drew Crampsie
drewc at tech dot coop
--- Lambda, the Love That Dare Not Speak Its Name? ---
From: Peter Seibel
Subject: Re: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <m31xbh6r2n.fsf@javamonkey.com>
drewc <·····@rift.com> writes:

> I'm not a gui programmer, but since nobody else took the bait, i
> figured i'd give it a shot.
>
> Peter Seibel wrote:
>> I haven't gotten around to playing around with GUI programming in
>> Common Lisp and I have this other project I'm trying to finish at the
>> moment. But if anyone is looking for a smallish project to try out,
>> I'd be interested to see what a Common Lisp version of his program
>> would look like.
>
> I used the most portable GUI i know, HTML. I have never build a gui
> application in Lisp, but I can't imagine it being any more difficult
> than UCW. Web stuff is generally more verbose.
>
> The code is about 200 lines. it could probably be made shorter with a
> few creative macros, but i'm done with it for now :). Most of the code
> is HTML components, because i built the interface from scratch.
>
> It took me about 3 hours to write. The initial quick hack version took
> only about an hour and was about 120 lines, but it was not as nice as
> this one :).
>
> Big wins for lisp :
>
> do-bloglines-request is quite lispy. I wanted to show some lisp
> functionality right off the bat, so we've got code as data and apply
> in this one.
>
> XMLS: There was never any need to convert the XML to an 'object'. XMLS
> just passes you a list that represents the XML. Working with XML like
> this is very cool.
>
> UCW (components/continuations): Webapps are a pain in the ass. UCW
> makes it painless. If render-on generated McClim code (or whatever)
> instead of HTML, you could have a desktop application sharing most of
> the same code with the UCW version.
>
> I suspect a bored lisper with GUI chops could take what i've done here
> and turn out a GUI desktop application in 45 minutes. Could be shorter
> as well, which probably matters to your friend the lispnot.

Cool. Thanks for taking a crack at this.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: richhickey
Subject: Re: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <1108788067.060866.261370@g14g2000cwa.googlegroups.com>
Peter Seibel wrote:
> I had coffee today with buddy of mine who is, sadly, a Lispnot. We
> were talking about language advocacy and he pointed to an essay he
> wrote about using the Bloglines API from Groovy (the dynamic language
> based on Java that runs on the JVM) to write an RSS/Atom reader. The
> whole thing is 150 lines of code and he was telling me how folks who
> emailed him to tell him what a good advertisement for Groovy it was.
>
> I haven't gotten around to playing around with GUI programming in
> Common Lisp and I have this other project I'm trying to finish at the
> moment. But if anyone is looking for a smallish project to try out,
> I'd be interested to see what a Common Lisp version of his program
> would look like.
>
> Groovy gets some wins, in this app anyway, from having access to Java
> libraries. Maybe some ArmedBear hacker could take a crack at this.
>
> Anyway, my buddy's article is at:
>
>   <http://www.oreillynet.com/pub/a/network/2004/09/28/bloglines.html>
>
> The code is on the second page.
>
> -Peter
>
> --
> Peter Seibel
·····@javamonkey.com
>
>          Lisp is the red pill. -- John Fraser, comp.lang.lisp


Ok, I'll bite.

Someone already did a nice Lisp+Web version. This one highlights Lisp
in a role similar to Groovy - leveraging Java libraries. I built it
using Lispworks and Foil, my successor to jfli. Instead of using Swing
I used SWT. I kept the structure similar so it could be compared to
Groovy by those who know only one or the other.

Some things that might not be evident from looking at it are:

 - I wrote this in a very sophisticated IDE, with complete support for
the syntax of Lisp, sexpr manipulation, tracing, profiling,
breakpoints, inspector etc. Lack of this kind of support can be a
severe limitation of scripting languages, especially new ones.

 - I had full symbol completion for all the Java stuff - I never had to
fully type anything, and could prompt for a list choices when I
couldn't remember the exact names.

 - I had graphical class hierarchy browsing for all the libs, including
Java

 - I had direct linking from the Java symbols to their function
signatures

 - When the app runs, even though its UI is modal, I still have a
listener, and can chang/fix the code, add controls, move stuff around,
add event listeners etc.

Experienced Lispers know that, although not needed for this app, should
I have encountered any repetition or awkwardness I could eliminate it
with macros. And if I needed to do any serious logic or data
manipulation I would have available the full power and speed of
compiled Lisp - no need to switch to non-script.

The code length is about the same. I don't see any wins for Groovy
here.

Screenshot:

http://www.richhickey.com/lisp/bloglines.png

lisppaste of the code:

http://paste.lisp.org/display/5914

Foil will be released real soon now -

Rich

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;homegrown Lisp <-> Java/CLI bridge library
(load "/dev/foil/foil")
(use-package :foil)
;generated wrappers for java libs
(load "/foil/java-lang")
(load "/foil/java-util")
(load "/foil/swt")
(load "/foil/commons-httpclient")
;Miles Egan's XML parser for Lisp - thanks Miles!
(load "/dev/xmls-1.2/xmls")

(require "comm") ;Lispworks socket stuff

(defpackage :bloglines-demo
 (:use :cl :foil "org.eclipse.swt" "org.eclipse.swt.widgets"
"org.eclipse.swt.events"
  "org.eclipse.swt.layout" "org.eclipse.swt.custom"
"org.eclipse.swt.browser"
  "org.apache.commons.httpclient"
"org.apache.commons.httpclient.methods" :xmls)
 (:export  :*display*  :init-display  :run-ui  :swt-bloglines))

(in-package :bloglines-demo)

;;;;;;;;;;;;;;;;; SWT Boilerplate ;;;;;;;;;;;;;;;;;;;;;;;
;included here for completeness, will be the same for any Foil/SWT app

;presumes Foil java server running on these 2 ports, first will be for
ui
(defvar *ui-stream* (comm:open-tcp-stream "localhost" 13578))
(defvar *non-ui-stream* (comm:open-tcp-stream "localhost" 13579))
(defvar *display*) ;hang onto the display for use in the listener
thread

;create the Foil foreign VM
(setf *fvm* (make-instance 'foreign-vm :stream *non-ui-stream*))

;a helper class that comes with Foil that runs the SWT message pump
(def-foil-class "com.richhickey.foil.SWTHelper")

(defun run-ui (fn)
  "Sets up a separate thread to run the GUI, and binds to a
ui-dedicated Foil socket"
  (let ((mp:*process-initial-bindings*
         (append '((*display* . *display*)
                   (*standard-output* . *standard-output*)
                   (*fvm* . *fvm*)
                   (*thread-fvm-stream* . *ui-stream*)
                   (*thread-fvm* . *fvm*))
                 mp:*process-initial-bindings*)))
    (mp:process-run-function "ui-proc" '() fn )))
;;;;;;;;;;;;;;;;; end SWT Boilerplate ;;;;;;;;;;;;;;;;;;;;;;;

;;;;;;;;;;; Bloglines Demo ;;;;;;;;;;;;;;;
#|
inspired by Marc Hedlund's Article on using Bloglines web service from
Groovy
http://www.oreillynet.com/pub/a/network/2004/09/28/bloglines.html

Here is a version in Lisp, using my Foil library

A typical use of Foil, it leverages Java libs to interface with the
outside world (SWT for UI,
Jakarta Commons for HTTP client), and Lisp for the data model/logic

I've mimicked the Groovy code to some extent to allow for comparison by
those who know only Lisp or Groovy
|#

;I don't have a wrapper for swing, but need to use its InputDialog (why
doesn't SWT have this?)
;so create one on the fly
(def-foil-class "javax.swing.JOptionPane")
(use-package "javax.swing")

(defparameter +SERVER+ "rpc.bloglines.com")

(defun find-child (node name)
  (find name (node-children node) :key #'node-name :test #'equal))

(defun find-attr (node attr)
  (second (find attr (node-attrs node) :key #'first :test #'equal)))

(defun api-url (method)
  (format nil "http://~A/~A" +SERVER+ method))

(defun add-nodes (nodes parent node-map)
  (dolist (node nodes)
    (let* ((is-folder (not (find-attr node "xmlUrl")))
           (title (find-attr node "title"))
           (tree-item
            (treeitem.new parent *SWT.NONE*
                          :text (if is-folder
                                    title
                                  (format nil "~A (~A)" title
(find-attr node "BloglinesUnread"))))))
      (setf (gethash tree-item node-map) node)
      (when is-folder
        (add-nodes (node-children node) tree-item node-map)))))

(defun list-items (client node list)
  (let ((rss-text (call-bloglines client
                                  (api-url (format nil
"getitems?s=~A&n=0"
                                                   (find-attr node
"BloglinesSubId")))))
        (descriptions nil))
    (when rss-text
      (let* ((rss (parse rss-text))
             (items (remove "item" (node-children (find-child rss
"channel"))
                            :key #'first :test-not #'equal)))
        (list.removeall list)
        (dolist (item items)
          (list.add list (third (find-child item "title")))
          (push (third (find-child item "description")) descriptions))
        (nreverse descriptions)))))

(defun call-bloglines (client url)
  (let ((get (new getmethod. (url) :doauthentication t)))
    (httpclient.executemethod client get)
    (httpmethod.getresponsebodyasstring get)))

(defun swt-bloglines ()
  (let* ((email (joptionpane.showinputdialog nil "Email address:" "Log
in to Bloglines"
			      *joptionpane.question_message*))
         (password (joptionpane.showinputdialog nil "Password:" "Log in
to Bloglines"
			      *joptionpane.question_message*))
         (client (httpclient.new))
         (credentials (usernamepasswordcredentials.new email password))
         (node-map (make-hash-table)))
    (httpstate.setcredentials (httpclient.state client) "Bloglines RPC"
+SERVER+ credentials)
    (let* ((*display* (display.getdefault))
           (shell (new shell. (*display* :text "SWT Bloglines Client"
:layout (gridlayout.new 1 t ))
                  (.setsize 800 600)
                  (.setlocation 100 100)))
           (base-pane (sashform.new shell *SWT.HORIZONTAL*
                                    :layoutdata (griddata.new
*GRIDDATA.FILL_BOTH*)))
           (feed-tree (tree.new base-pane (logior *SWT.SINGLE*
*SWT.BORDER*)
                                :layoutdata (griddata.new
*GRIDDATA.FILL_BOTH*)))
           (item-pane (sashform.new base-pane *SWT.VERTICAL*
                                    :layoutdata (griddata.new
*GRIDDATA.FILL_BOTH*)))
           (item-list (list.new item-pane (logior *SWT.SINGLE*
*SWT.BORDER*)
                                :layoutdata (griddata.new
*GRIDDATA.FILL_BOTH*)))
           (item-text (browser.new item-pane *SWT.BORDER*))
           (opml (parse (call-bloglines client (api-url "listsubs"))))
           (subs (node-children (find-child opml "body")))
           (descriptions nil))
      (add-nodes subs feed-tree node-map)
      (tree.addselectionlistener feed-tree
           (new-proxy p +MARSHALL-ID+ 0
                      (selectionlistener.
                       (widgetselected (event)
                         (let* ((item (selectionevent.item event))
                                (node (gethash item node-map)))
                           ;if it's a subscription, update list
                           (when (find-attr node "xmlUrl")
                             (setf descriptions (list-items client node
item-list)))
                           nil)))))
      (list.addselectionlistener item-list
           (new-proxy p +MARSHALL-ID+ 0
                      (selectionlistener.
                       (widgetselected (event)
                         (declare (ignore event))
                         (browser.settext item-text (nth
(list.selectionindex item-list) descriptions))
                         nil))))
      (|com.richhickey.foil|::swthelper.rundispatchloop *display*
shell))))

;yes, you can treat Lisp like a scripting language
(run-ui #'swt-bloglines)
From: Peter Seibel
Subject: Re: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <m3zmxvdfkk.fsf@gigamonkeys.com>
"richhickey" <··········@gmail.com> writes:

> Peter Seibel wrote:
>> I had coffee today with buddy of mine who is, sadly, a Lispnot. We
>> were talking about language advocacy and he pointed to an essay he
>> wrote about using the Bloglines API from Groovy (the dynamic language
>> based on Java that runs on the JVM) to write an RSS/Atom reader. The
>> whole thing is 150 lines of code and he was telling me how folks who
>> emailed him to tell him what a good advertisement for Groovy it was.
>>
>> I haven't gotten around to playing around with GUI programming in
>> Common Lisp and I have this other project I'm trying to finish at the
>> moment. But if anyone is looking for a smallish project to try out,
>> I'd be interested to see what a Common Lisp version of his program
>> would look like.
>>
>> Groovy gets some wins, in this app anyway, from having access to Java
>> libraries. Maybe some ArmedBear hacker could take a crack at this.
>>
>> Anyway, my buddy's article is at:
>>
>>   <http://www.oreillynet.com/pub/a/network/2004/09/28/bloglines.html>
>>
>> The code is on the second page.
>>
>> -Peter
>>
>> --
>> Peter Seibel
> ·····@javamonkey.com
>>
>>          Lisp is the red pill. -- John Fraser, comp.lang.lisp
>
>
> Ok, I'll bite.

Just wanted to let you know, I've got this saved to look at later.
Thanks for taking a crack at it.

-Peter

-- 
Peter Seibel                                     ·····@gigamonkeys.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Chris Gray
Subject: Re: Looking for bored Lisper with GUI chops.
Date: 
Message-ID: <p0b3bvnttlo.fsf@mail.mcgill.ca>
On Fri, 11 Feb 2005, Peter Seibel wrote:
> I haven't gotten around to playing around with GUI programming in
> Common Lisp and I have this other project I'm trying to finish at
> the moment. But if anyone is looking for a smallish project to try
> out, I'd be interested to see what a Common Lisp version of his
> program would look like.

I have been using emacs lisp for this basic application for a while
now.  It doesn't use bloglines, instead parsing RSS directly.  It
outputs HTML using the bit of emacs duct tape and chewing gum that
keeps the rest of my website together. 

The aggregator is at http://www.win.tue.nl/~cgray/aggregator.html
and you can find out about the rest of the website publishing
machinery at http://www.win.tue.nl/~cgray/about.html

The source is about 300 lines long.  If I get bored I might look at
using bloglines and see if that cuts down on the LOC.

Cheers,
Chris

-- 
Chris Gray                                  Ph.D student 
Mobile: +31 065 092 4719                    TU Eindhoven
Website: http://www.win.tue.nl/~cgray/