{-# LANGUAGE InstanceSigs #-}
module MdToHTML where
import Control.Applicative
import Control.Monad
import Data.List
import Debug.Trace
import Text.ParserCombinators.ReadP
import Text.Printf
type HeaderLevel = Int
newtype URL = URL {getUrl :: String}
newtype ImgPath = ImgPath {getPath :: String}
parseMany :: ReadP a -> ReadP [a]
parseMany = Text.ParserCombinators.ReadP.many
data MdToken
= Document [MdToken]
| Header HeaderLevel MdToken
| Para MdToken
| Line [MdToken]
| SingleNewline -- A single newline is rendered as a space.
| Linebreak
| HorizontalRule
| Blockquote MdToken
| UnordList [MdToken]
| OrdList [MdToken]
| Code String
| Codeblock String
| Link MdToken URL
| Image MdToken ImgPath
| Bold MdToken
| Italic MdToken
| Strikethrough MdToken
| Unit String
-- Deriving Show for MdToken
instance Show MdToken where
show :: MdToken -> String
show (Document tokens) = concatMap show tokens
show (Header level token) = "
" ++ show token ++ "
" show (Line tokens) = concatMap show tokens show Linebreak = "" ++ show token ++ "" show (UnordList tokens) = "UNORD" ++ concatMap show tokens show (OrdList tokens) = "ORD" ++ concatMap show tokens show (Code code) = show code show (Codeblock code) = show code show (Link txt url) = "" ++ show txt ++ "" show (Image txt imgPath) = "