{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Type.Reader where import Bamboo.Helper.PreludeEnv import qualified Data.Map as Map import Text.Pandoc import Text.XHtml.Strict import Data.Default data Reader = Markdown | RST | HTML | Latex deriving (Show, Eq) instance Default Reader where def = Markdown readers = [ (Markdown, ["markdown", "md"]) , (RST, ["rst"] ) , (HTML, ["html", "htm"]) , (Latex, ["tex", "latex"]) ] .map_snd (map ("." ++)) reader_map = readers.map gen_lookup.join'.to_h where gen_lookup (r, xs) = xs.labeling (const r) guess_reader ext = reader_map.Map.lookup ext to_html r = r defaultParserState > writeHtml defaultWriterOptions -- this list can go on, as long as there is a library that does -- the convertion. pretty extensible, isn't it. rr :: Reader -> String -> Html rr Markdown = to_html readMarkdown rr RST = to_html readRST rr HTML = primHtml rr Latex = to_html readLaTeX render_to_html = rr