{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE RankNTypes #-} module Text.Markdown ( -- * Functions markdown -- * Settings , MarkdownSettings , msXssProtect , msStandaloneHtml , msFencedHandlers , msBlockCodeRenderer , msLinkNewTab , msBlankBeforeBlockquote , msBlockFilter -- * Newtype , Markdown (..) -- * Fenced handlers , FencedHandler (..) , codeFencedHandler , htmlFencedHandler -- * Convenience re-exports , def ) where import Control.Arrow ((&&&)) import Text.Markdown.Inline import Text.Markdown.Block import Text.Markdown.Types import Prelude hiding (sequence, takeWhile) import Data.Default (Default (..)) import Data.Text (Text) import qualified Data.Text.Lazy as TL import Text.Blaze.Html (ToMarkup (..), Html) import Text.Blaze.Html.Renderer.Text (renderHtml) import Data.Conduit import qualified Data.Conduit.List as CL import Data.Monoid (Monoid (mappend, mempty, mconcat)) import Data.Functor.Identity (runIdentity) import qualified Text.Blaze.Html5 as H import qualified Text.Blaze.Html5.Attributes as HA import Text.HTML.SanitizeXSS (sanitizeBalance) import qualified Data.Map as Map import Data.String (IsString) -- | A newtype wrapper providing a @ToHtml@ instance. newtype Markdown = Markdown TL.Text deriving(Monoid, IsString) instance ToMarkup Markdown where toMarkup (Markdown t) = markdown def t -- | Convert the given textual markdown content to HTML. -- -- >>> :set -XOverloadedStrings -- >>> import Text.Blaze.Html.Renderer.Text -- >>> renderHtml $ markdown def "# Hello World!" -- "

Hello World!

" -- -- >>> renderHtml $ markdown def { msXssProtect = False } "" -- "" markdown :: MarkdownSettings -> TL.Text -> Html markdown ms tl = sanitize $ runIdentity $ CL.sourceList blocksH $= toHtmlB ms $$ CL.fold mappend mempty where sanitize | msXssProtect ms = preEscapedToMarkup . sanitizeBalance . TL.toStrict . renderHtml | otherwise = id blocksH :: [Block Html] blocksH = processBlocks blocks blocks :: [Block Text] blocks = runIdentity $ CL.sourceList (TL.toChunks tl) $$ toBlocks ms =$ CL.consume processBlocks :: [Block Text] -> [Block Html] processBlocks = map (fmap $ toHtmlI ms) . msBlockFilter ms . map (fmap $ toInline refs) refs = Map.unions $ map toRef blocks where toRef (BlockReference x y) = Map.singleton x y toRef _ = Map.empty data MState = NoState | InList ListType toHtmlB :: Monad m => MarkdownSettings -> Conduit (Block Html) m Html toHtmlB ms = loop NoState where loop state = await >>= maybe (closeState state) (\x -> do state' <- getState state x yield $ go x loop state') closeState NoState = return () closeState (InList Unordered) = yield $ escape "" closeState (InList Ordered) = yield $ escape "" getState NoState (BlockList ltype _) = do yield $ escape $ case ltype of Unordered -> "