-- | Gemini lightwight hypertext format, mime type text/gemini, -- see module Gemini where import Data.List(mapAccumL,stripPrefix) --import Html import HtmlTags import HtmlConOps as H -- | Convert a text/gemini document to HTML gemini2html = (:[]) . body . map (ctx DIV).snd.mapAccumL renderLine False . lines where renderLine pre l = maybe (pre,plain) toggle (stripPrefix "```" l) where toggle _ = (not pre,[]) plain | null l = [txt " "] | pre = [H.pre [txt l]] | take 3 l == "=> " = case words l of ar:url:ws-> [ctx SPAN [txt "=> ",href url [txt linktext]]] where linktext | null ws = url | otherwise = unwords ws -- !! | take 2 l == "* " = [ul [li [txt (drop 2 l)]]] -- !! | take 1 l == ">" = [ctx BLOCKQUOTE [txt (tail l)]] | level>0 = [m0 ([H1,H2,H3] !! (level-1)) [txt l']] | otherwise = [txt l] (hashes,l') = dropWhile (==' ') <$> span (=='#') l level = min 3 (length hashes) m0 t = ctx' t [("STYLE","margin:0")]