{-# LANGUAGE BangPatterns, OverloadedStrings #-} import Data.Monoid (mappend, mconcat) import Prelude hiding (putStr) import Data.Text.Lazy.Builder (Builder, fromText, toLazyText) import Data.Text.Lazy.IO (putStr) import qualified Data.Text as T main :: IO () main = do putStr "Content-Type: text/html\n\n" putStr . toLazyText $ mconcat (replicate 20000 makeRow) putStr "
" makeRow :: Builder makeRow = mconcat (map makeCol [1..50]) makeCol :: Int -> Builder makeCol 1 = fromText "1" makeCol 50 = fromText "50" makeCol i = fromText "" `mappend` (textInt i `mappend` fromText "") textInt :: Int -> Builder textInt = fromText . T.pack . show