{-# LANGUAGE OverloadedStrings #-} ----------------------------------------------------------------------------- -- | -- Module : Text.Trifecta.Highlight.Rendering.HTML -- Copyright : (C) 2011 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable -- ---------------------------------------------------------------------------- module Text.Trifecta.Highlight.Rendering.HTML ( Doc(..) , doc ) where import Data.Monoid import Prelude hiding (head) import Text.Blaze import Text.Blaze.Html5 hiding (b,i) import Text.Blaze.Html5.Attributes hiding (title) import Text.Trifecta.Highlight.Class import Text.Trifecta.Rope.Highlighted -- | Represents a source file like an HsColour rendered document data Doc = Doc { docTitle :: String , docCss :: String -- href for the css file , docContent :: HighlightedRope } -- | -- -- > renderHtml $ toHtml $ addHighlights highlightedRope $ doc "Foo.hs" doc :: String -> Doc doc t = Doc t "trifecta.css" mempty instance ToHtml Doc where toHtml (Doc t css cs) = docTypeHtml $ do head $ do preEscapedString "\n" title $ toHtml t link ! rel "stylesheet" ! type_ "text/css" ! href (toValue css) body $ toHtml cs instance Highlightable Doc where addHighlights h (Doc t c r) = Doc t c (addHighlights h r)