Hello,

HSP does not use xhtml or any other library internally.

The trhsx pre-processor turns this:

bigTable :: [[Int]] -> String
bigTable t = renderAsHTML $ evalIdentity $
   <table>
    <% mapM (\r -> <tr><% mapM (\d -> <td><% show d %></td>) r %></tr>) t %>
   </table>

into:

bigTable :: [[Int]] -> String
{-# LINE 38 "hsp-blaze.hs" #-}
bigTable t
  = L.unpack $
      B.renderHtml $
        evalBlaze $
          (genElement (Nothing, "table") []
             [asChild
                ((asChild
                    (mapM
                       (\ r ->
                          (genElement (Nothing, "tr") []
                             [asChild
                                ((asChild
                                    (mapM
                                       (\ d ->
                                          (genElement (Nothing, "td") []
                                             [asChild ((asChild (show
d)))]))
                                       r)))]))
                       t)))])

Basically, it just calls genElement to create the elements, and asChild is a
class to turn things into things that can be children on an element.

The question remains, though, what is the type that genElement is producing?
The type is monad specific. genElement comes from this class,

-- | Generate XML values in some XMLGenerator monad.
class Monad m => XMLGen m where
 type XML m
 data Child m
 data Attribute m
 genElement  :: Name -> [XMLGenT m [Attribute m]] -> [XMLGenT m [Child m]]
-> XMLGenT m (XML m)
 genEElement :: Name -> [XMLGenT m [Attribute m]]
 -> XMLGenT m (XML m)
 genEElement n ats = genElement n ats []
 xmlToChild :: XML m -> Child m
 pcdataToChild :: String -> Child m

Most of the stuff in the HSX/HSP family now produces values of the type:

data XML = Element Name Attributes Children
         | CDATA Bool String

and you can use renderXML or renderAsHTML to convert that to a String
depending on what rendering rules you want in effect.

Anyway, on to the exciting stuff! The benchmarks:

As I test I have implemented the big-table benchmark for four cases:

1. the existing html test in benchmarkes/bigtable
2. plain-old blaze
3. hsp using the identity monad, the XML type, and String
4. hsp using blaze

html: mean: 15.86650 ms, lb 15.68054 ms, ub 16.22545 ms, ci 0.950
blaze:  mean: 28.86730 ms, lb 28.45495 ms, ub 29.63139 ms, ci 0.950
hsp+identity: mean: 50.05748 ms, lb 49.45395 ms, ub 50.97315 ms, ci 0.950
hsp+blaze: mean: 166.4717 ms, lb 161.7957 ms, ub 174.1437 ms, ci 0.950

As a chart:

http://chart.apis.google.com/chart?cht=bvg&chs=200x250&chd=t:29,50,166.5&chds=0,180&chdl=blaze|hsp+identity|hsp+blaze&chco=ff0000|00ff00|0000ff&chxt=y&chxr=0,0,180,25

I am not entirely sure I did these tests correctly. So, we should not really
trust these numbers at all for the moment.

Also, the 'nf' thing did not have a lazy ByteString instance, so for the
blaze stuff, I used L.unpack to turn the output back into a String -- which
is not really 'fair'. (And would also be bad if the tests actually contained
utf-8, and not just an ascii subset of it).

That said, my first attempts at using blaze to speed up HSP do not seem to
have worked :p

I think that 'speeding up' HSX is going to be somewhat dependent on what you
are trying to do with it. If you are just writing templates by hand, and the
data you are adding in is String data, then I think the current HSX stuff is
probably doing a descent job. Everything starts as String, and ends as a
String. Then if you want you can convert that String to a ByteString, etc.

The default instances for HSX would probably not perform as well if you had
a lot of data you wanted to splice in that was already pre-encoded utf-8
bytestrings. If that is your case, though, you could just implement an
alternative XML data type and matching monad, and use those with hsx
instead. Though, you still have to be careful. It is not enough to have just
utf-8 encoded bytestrings, they would also need to already have any special
html characters escaped (such as &). You can't just read utf-8 values out of
database and stick them straight into the html output.

Another option might be to implement a instance of XMLGen that does not have
an intermediate type -- it just goes directly to String, Text, ByteString,
or whatever you want. I am not sure how much overhead the intermediate type
is really causing though. One thing that slows the hsx html rendering down
is that it has to check each tag and see if it is one of the special tags
that has no close tag. (Such as meta, input, img, etc). Or if it is one of
the tags where the content is rendered as as CDATA instead of PCDATA, such
as script and style. And the only way to do that is to pattern match on the
tag name.

I have attached all three files I used to benchmark to this message.

Certainly making hsx/hsp faster would be nice (though it doesn't seem
especially slow to start with). And it would also be nice if you could use
use a mixture of hsx+blaze combinators.

- jeremy

ps. I also added, ghc-options: -O2 to my BlazeHtml.cabal file, but that
didn't seem to change anything


On Sun, May 30, 2010 at 10:58 AM, Thomas Hartman <tphya...@gmail.com> wrote:

> I'm a heavy hsp user. Could hsp benefit from this project by using
> blaze as a back end instead of whatever it's using now?
>
> IIUC, Hsp uses hsx (via the preprocessor program trhsx) to convert
> xml-containing hybrid hsp/xml/html files into compilable haskell.
>
> I expected hsx uses XHTML (which iiuc is what blaze would replace) on
> the backend but I don't see it listed in the dependencies at
>
> http://hackage.haskell.org/package/hsx-0.7.0
>
> so I guess it doesn't and uses something internal rather than xhtml.
> (Right?)
>
> My question as regards BlazeHTML is if there could be any performance
> win/tie in for the hsp/hsx toolchain.
>
> FWIW, wrt to blaze sclv commented on reddit "The idea is rather that
> this would be a replacement for the html combinator library, as
> distinct from templating (hamlet, hstringtemplate, bravo, chunks,
> press, & co) and as distinct from the *sp model of inlined code (hsp).
>
> Edit: Ideally, and generally for Haskell libs, the choices of
> persistence layer, html generation library, dispatch model, and server
> layer are largely orthogonal. Strong typing makes any ad-hoc plumbing
> a breeze."
>
>
> http://www.reddit.com/r/haskell/comments/bxa0a/blazehtml_a_blazingly_fast_html_combinator/
>
> thomas.
>
> 2010/5/30 Tom Lokhorst <t...@lokhorst.eu>:
> > +1 for HTML5.
> >
> > Also, I suggest focussing on the html serialization of HTML5.
> >
> > The xml serialization (XHTML5) is only useful in an XML environment.
> > For such environments pure xml libraries are more appropriate.
> >
> > Besides, I like html syntax better.
> >
> > On 30 May 2010 16:27, Jochem Berndsen <joc...@functor.nl> wrote:
> >> On 05/29/2010 08:05 PM, Gregory Collins wrote:
> >>>
> >>> Matt Parker<moonmaster9...@gmail.com>  writes:
> >>>
> >>>>     Q3: Which HTML version would you preferably use?
> >>>>
> >>>> HTML 5. google summer of code should be about pushing the new and
> >>>> exciting.
> >>>
> >>> Yes, definitely, this should be the default IMO.
> >>
> >> +1
> >>
> >>
> >> --
> >> Jochem Berndsen | joc...@functor.nl
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-- | BigTable benchmark using the HTML package from hackage.
--
import Criterion.Main
import qualified Data.ByteString.Lazy.Char8 as L
import Data.Monoid (mconcat)
import Text.Blaze 
import Text.Blaze.Html4.Strict hiding (map)

bigTable :: [[Int]] -> String
bigTable t = L.unpack $ renderHtml $ table $ mconcat $ map row t
  where
    row r = tr $ mconcat $ map (td . string . show) r

main = defaultMain
    [ bench "bigTable" $ nf bigTable myTable ]
  where
    rows :: Int
    rows = 1000

    myTable :: [[Int]]
    myTable = replicate rows [1..10]
    {-# NOINLINE myTable #-}
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances, TypeFamilies #-}
{-# OPTIONS -Wwarn -F -pgmFtrhsx #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Main where

import Criterion.Main
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import HSP
import Control.Monad.Identity (Identity(Identity, runIdentity))
import qualified HSX.XMLGenerator as HSX

instance HSX.XMLGen Identity where
    type HSX.XML Identity = XML
    newtype HSX.Child Identity = IChild { unIChild :: XML }
    newtype HSX.Attribute Identity = IAttr { unIAttr :: Attribute }
    genElement n attrs children = HSX.XMLGenT $ Identity (Element
                                                          (toName n)
                                                          (map unIAttr $ concatMap runIdentity $ map HSX.unXMLGenT attrs)
                                                          (map unIChild $ concatMap runIdentity $ map HSX.unXMLGenT children)
                                                         )
    xmlToChild = IChild
    pcdataToChild = HSX.xmlToChild . pcdata

evalIdentity :: XMLGenT Identity XML -> XML
evalIdentity = runIdentity . HSX.unXMLGenT


bigTable :: [[Int]] -> String
bigTable t = renderAsHTML $ evalIdentity $ 
   <table>
    <% mapM (\r -> <tr><% mapM (\d -> <td><% show d %></td>) r %></tr>) t %>
   </table>

main = defaultMain
    [ bench "bigTable" $ nf bigTable myTable ]
  where
    rows :: Int
    rows = 1000

    myTable :: [[Int]]
    myTable = replicate rows [1..10]
    {-# NOINLINE myTable #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS -Wwarn -F -pgmFtrhsx #-}
-- | BigTable benchmark using the HTML package from hackage.


import Criterion.Main
import Data.Monoid (mempty, mconcat)
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.Text as T
import HSP
import HSP.HTML
import qualified Text.Blaze as B
import qualified HSX.XMLGenerator as HSX

newtype HtmlM a = HtmlM { unHtmlM :: a }

instance Monad HtmlM where
    return a = HtmlM a
    (HtmlM a) >>= f = f a

instance HSX.XMLGen HtmlM where
    type    HSX.XML HtmlM       = B.Html
    newtype HSX.Child HtmlM     = HChild { unHChild :: B.Html }
    newtype HSX.Attribute HtmlM = HAttr  { unHAttr  :: B.Attribute }
    genElement (Nothing, n) attrs children = 
        HSX.XMLGenT $ HtmlM $ B.parent (T.pack n)
               (attributes (mconcat $ map unHChild $ concatMap unHtmlM $ map HSX.unXMLGenT children)
                           (map unHAttr $ concatMap unHtmlM $ map HSX.unXMLGenT attrs))
    xmlToChild = HChild
    pcdataToChild = HSX.xmlToChild . B.string

attributes h attrs = foldr (\a h -> h B.! a) h attrs

evalBlaze :: XMLGenT HtmlM B.Html -> B.Html
evalBlaze = unHtmlM . HSX.unXMLGenT

bigTable :: [[Int]] -> String
bigTable t = L.unpack $ B.renderHtml $ evalBlaze $ 
   <table>
    <% mapM (\r -> <tr><% mapM (\d -> <td><% show d %></td>) r %></tr>) t %>
   </table>

main = defaultMain
    [ bench "bigTable" $ nf bigTable myTable ]
  where
    rows :: Int
    rows = 1000

    myTable :: [[Int]]
    myTable = replicate rows [1..10]
    {-# NOINLINE myTable #-}
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to