use --- a syntax highlighter middleware note, do not use this on rss feed, i.e. make a middleware in your hack middleware chain: none_rss_highlight :: Middleware none_rss_highlight app = \env -> do if env.path_info.ends_with "rss.xml" then app env else highlight app env and use this! css --- underneath, it's just [highlighting-kate](http://johnmacfarlane.net/highlighting-kate/), so grab those css. Add them to `config/theme/blueprint.txt`, e.g. css = screen, blueprint-wp, highlight/ascetic, hk-kate, custom also customized in custom, if you want, e.g. /* highlight */ table.sourceCode { border-top: 1px solid #eee; padding-top: 20px; padding-bottom: 20px; margin-bottom: 20px; border-bottom: 1px solid #eee; border-left: 5px solid #eee; border-right: 0; width: 530px; } td.lineNumbers { display: none; } sample main: module Main where import Hack.Contrib.Middleware.Debug -- import Hack.Contrib.Request (inputs) -- import Hack.Contrib.Middleware.Inspect -- import Hack.Contrib.Middleware.SimpleAccessLogger import Bamboo import Bamboo.Theme.Blueprint import Hack import Hack.Contrib.Middleware.BounceFavicon import Hack.Contrib.Middleware.ContentLength import Hack.Contrib.Middleware.ContentType import Hack.Contrib.Middleware.ETag import Hack.Contrib.Middleware.Lambda import Hack.Contrib.Middleware.Lucky import Hack.Contrib.Middleware.ShowExceptions import Hack.Contrib.Middleware.ShowStatus import Hack.Contrib.Middleware.Static import Hack.Contrib.Utils import Hack.Contrib.Middleware.URLMap import Hack.Handler.Happstack import qualified Hack.Contrib.Middleware.Head as H import Bamboo.Plugin.Highlight import Control.Arrow ((<<<)) import MPSUTF8 import Prelude hiding ((.), (>)) default_content_type :: String default_content_type = "text/plain; charset=UTF-8" stack :: [Middleware] stack = [ dummy_middleware -- filter , bounce_favicon -- setup --, parse_multipart -- debug -- , inspect -- , debug (\e r -> e.print) -- completeness , content_length , content_type default_content_type , etag -- debuging , show_exceptions Nothing , show_status -- optimization , H.head -- log --, simple_access_logger Nothing -- for fun , lucky , lambda , url_map [("", bamboo)] ] where bamboo = use [bamboo_serve, no_rss <<< bamboo_with_theme blueprint] dummy_app -- show_env = debug (\e r -> e.print) bamboo_serve = static (Just "db/public") ["/theme", "/images", "/plugin", "/favicon.ico", "/media"] no_rss app = \env -> do if env.path_info.ends_with "rss.xml" then app env else highlight app env -- test_app = \env -> return $ def .set_body (env.inputs.show) app :: Application app = use stack dummy_app main :: IO () main = run app