{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use lambda-case" #-}
module MdToHTML where
import Control.Applicative hiding (many, some)
import Control.Monad
import Control.Monad.Combinators (count)
import Data.Char
import Data.List
import Data.Ord (comparing)
import Data.String.Utils
import qualified Data.Text as T
import Data.Void
import Debug.Trace
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Printf
import Text.Wrap
type Parser = Parsec Void T.Text
type HeaderLevel = Int
type CssClass = String
newtype URL = URL {getUrl :: String} deriving (Eq)
newtype ImgPath = ImgPath {getPath :: String} deriving (Eq)
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 MdToken
| Table [[MdToken]]
| Codeblock MdToken
| Link MdToken URL
| Image MdToken URL (Maybe [CssClass])
| Figure MdToken URL (Maybe [CssClass])
| Bold MdToken
| Italic MdToken
| Strikethrough MdToken
| Unit String
deriving (Eq)
-- Deriving Show for MdToken
instance Show MdToken where
show (Document tokens) = concatMap show tokens
show (Header level token) = "
" ++ show token ++ "
" show (Line tokens) = concatMap show tokens show Linebreak = "" ++ concatMap show tokens ++ "" show (UnordList tokens) = "
" ++ strip (show code) ++ "
"
show (Table (thead : tokenGrid)) = "" ++ rstrip (show x) ++ " | ") thead ++ "
---|
" ++ rstrip (show y) ++ " | ") x ++ "
" ++ show code ++ "
"
show (Link txt url) = "" ++ show txt ++ ""
show (Image txt url cssClasses) = "" ++ T.unpack (wrapText defaultWrapSettings 70 (T.pack $ prettyPrint token)) ++ "
\n" prettyPrint (Table (thead : tokenGrid)) = "" ++ rstrip (prettyPrint x) ++ " | \n") thead ++ "
---|
" ++ rstrip (prettyPrint y) ++ " | \n") x ++ "