|
|
|
@@ -1,4 +1,6 @@
|
|
|
|
|
{-# LANGUAGE InstanceSigs #-}
|
|
|
|
|
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
|
|
|
|
|
|
|
|
|
|
{-# HLINT ignore "Use lambda-case" #-}
|
|
|
|
|
|
|
|
|
|
module MdToHTML where
|
|
|
|
|
|
|
|
|
@@ -40,7 +42,6 @@ data MdToken
|
|
|
|
|
|
|
|
|
|
-- Deriving Show for MdToken
|
|
|
|
|
instance Show MdToken where
|
|
|
|
|
show :: MdToken -> String
|
|
|
|
|
show (Document tokens) = concatMap show tokens
|
|
|
|
|
show (Header level token) = "<h" ++ show level ++ ">" ++ show token ++ "</h" ++ show level ++ ">"
|
|
|
|
|
show (Para token) = "<p>" ++ show token ++ "</p>"
|
|
|
|
@@ -48,9 +49,9 @@ instance Show MdToken where
|
|
|
|
|
show Linebreak = "<br>"
|
|
|
|
|
show SingleNewline = " "
|
|
|
|
|
show HorizontalRule = "---------"
|
|
|
|
|
show (Blockquote token) = "<blockquote>" ++ show token ++ "</blockquote>"
|
|
|
|
|
show (UnordList tokens) = "UNORD" ++ concatMap show tokens
|
|
|
|
|
show (OrdList tokens) = "ORD" ++ concatMap show tokens
|
|
|
|
|
show (Blockquote tokens) = "<blockquote>" ++ concatMap show tokens ++ "</blockquote>"
|
|
|
|
|
show (UnordList tokens) = "<ul>" ++ concatMap (prepend "<li>" . append "</li>" . show) tokens ++ "</ul>"
|
|
|
|
|
show (OrdList tokens) = "<ol>" ++ concatMap (prepend "<li>" . append "</li>" . show) tokens ++ "</ol>"
|
|
|
|
|
show (Code code) = show code
|
|
|
|
|
show (Codeblock code) = show code
|
|
|
|
|
show (Link txt url) = "<a href=\"" ++ getUrl url ++ "\">" ++ show txt ++ "</a>"
|
|
|
|
@@ -60,17 +61,29 @@ instance Show MdToken where
|
|
|
|
|
show (Strikethrough token) = "<s>" ++ show token ++ "</s>"
|
|
|
|
|
show (Unit unit) = printf "%s" unit
|
|
|
|
|
|
|
|
|
|
instance Semigroup MdToken where
|
|
|
|
|
a <> b = Document [a, b]
|
|
|
|
|
|
|
|
|
|
instance Monoid MdToken where
|
|
|
|
|
mempty = Unit ""
|
|
|
|
|
|
|
|
|
|
-- ---------------
|
|
|
|
|
-- Helpers
|
|
|
|
|
leftmostLongest :: (Foldable t) => [(a, t b)] -> (a, t b)
|
|
|
|
|
leftmostLongest :: (Foldable t) => [(a, t b)] -> Maybe (a, t b)
|
|
|
|
|
leftmostLongest xs =
|
|
|
|
|
let lastElem = last xs
|
|
|
|
|
filteredLst = filter (\val -> length (snd val) == length (snd lastElem)) xs
|
|
|
|
|
in head filteredLst
|
|
|
|
|
in case filteredLst of
|
|
|
|
|
[] -> Nothing
|
|
|
|
|
(x : xs) -> Just x
|
|
|
|
|
|
|
|
|
|
-- Get the first parse returned by readP_to_S that consumed the most input
|
|
|
|
|
leftmostLongestParse :: ReadP a -> String -> (a, String)
|
|
|
|
|
leftmostLongestParse parser input = leftmostLongest $ readP_to_S parser input
|
|
|
|
|
leftmostLongestParse :: (Monoid a) => ReadP a -> String -> (a, String)
|
|
|
|
|
leftmostLongestParse parser input =
|
|
|
|
|
let res = leftmostLongest $ readP_to_S parser input
|
|
|
|
|
in case res of
|
|
|
|
|
Nothing -> (mempty, mempty)
|
|
|
|
|
Just x -> x
|
|
|
|
|
|
|
|
|
|
-- Parse if the string that's left matches the string comparator function
|
|
|
|
|
lookaheadParse :: (String -> Bool) -> ReadP Char
|
|
|
|
@@ -196,6 +209,24 @@ parsePara = do
|
|
|
|
|
let parsedText = fst $ leftmostLongestParse parseLine text -- Parse a line
|
|
|
|
|
return (Para parsedText)
|
|
|
|
|
|
|
|
|
|
-- Parse a line starting with '>', return the line except for the '>'.
|
|
|
|
|
parseQuotedLine :: ReadP String
|
|
|
|
|
parseQuotedLine = do
|
|
|
|
|
char '>'
|
|
|
|
|
greedyParse (char ' ' +++ char '\t')
|
|
|
|
|
restOfLine <- munch (/= '\n')
|
|
|
|
|
Text.ParserCombinators.ReadP.optional (char '\n') >> return ""
|
|
|
|
|
return restOfLine
|
|
|
|
|
|
|
|
|
|
-- Parse many 'quoted lines' until I see a non-quoted line.
|
|
|
|
|
parseQuotedLines :: ReadP [String]
|
|
|
|
|
parseQuotedLines =
|
|
|
|
|
greedyParse1 $ do
|
|
|
|
|
look >>= \line ->
|
|
|
|
|
case line of
|
|
|
|
|
('>' : _) -> parseQuotedLine
|
|
|
|
|
_ -> pfail
|
|
|
|
|
|
|
|
|
|
-- Parse a blockquote, which is a greater-than sign followed by a paragraph.
|
|
|
|
|
parseBlockquote :: ReadP MdToken
|
|
|
|
|
parseBlockquote = do
|
|
|
|
|