{-# 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 $
<% show d %> | ) r %>