[Haskell-cafe] Possibilities for website construction using
Haskell?
Don Stewart
dons at galois.com
Sun Jan 13 16:48:15 EST 2008
ndmitchell:
> Hi
>
> > > Hoogle (http://haskell.org/hoogle) uses Haskell Source Extensions
> > > (http://www.cs.chalmers.se/~d00nibro/haskell-src-exts/)
> >
> > I thought haskell-src-exts was an extended Language.Haskell parser?
> > Do you mean HSP -- haskell server pages?
>
> No, I mean haskell-src-exts. It's a translator from Haskell with
> embedded XML to pure Haskell.
>
> > > My academic website (http://www-users.cs.york.ac.uk/~ndm/) uses some
> > > custom code (http://www-users.cs.york.ac.uk/~ndm/Main.hs)
> >
> > So that's CGI, or offline page generation?
>
> Offline page generation.
Hugh asked on #haskell about how to do offline / cgi with xhtml
combinators, I threw together a little example (since it seems this
isn't widely known):
import Text.XHtml.Transitional
import System.Environment
import System.Time
main = do
time <- getClockTime
putStrLn . prettyHtml $
(header (thetitle (toHtml "testing")))
+++
(body $
(center $
h2 (toHtml (hotlink "http://haskell.org"
(toHtml "Haskell is fun"))))
+++ toHtml (show time))
Generates this page,
http://galois.com/~dons/tmp/test.html
Note that using string overloading we can remove some of the toHtml's...
{-# LANGUAGE OverloadedStrings #-}
instance IsString Html where fromString = toHtml
main = do
time <- getClockTime
putStrLn . prettyHtml $
(header (thetitle "testing"))
+++
(body $
center $
h2 (toHtml (hotlink "http://haskell.org" "Haskell is fun")))
+++ show time
Cheers,
Don
More information about the Haskell-Cafe
mailing list