Don Stewart wrote:
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
You can also eliminate the toHtmls by using the "<<" operator defined by
XHTML. It has type (HTML a) => (Html -> b) -> a -> b, where HTML is a
type class which has strings, among other things, already defined as
instances. So the above can be written as follows, without an
additional string overloading:
main = do
time <- getClockTime
putStrLn . prettyHtml $
(header (thetitle << "testing"))
+++
(body $
(center $
h2 << (hotlink "http://haskell.org" << "Haskell is fun"))
+++ p << show time)
(Wrapping the time in an HTML element like a paragraph allows the use of
<< to "fill" the paragraph.)
Anton
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe