{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module Readme.Lhs
( para,
plain,
table,
table',
code,
link,
badge,
image,
Flavour (..),
readPandoc,
renderMarkdown,
Output (..),
OutputMap,
output,
runOutput,
tweakHaskellCodeBlock,
Block (..),
module Text.Pandoc.Definition,
Alignment (..),
)
where
import Control.Monad.IO.Class
import Control.Monad.Trans.State.Lazy
import Data.Bool
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Text as Text
import qualified Data.Text.IO as Text
import Text.Pandoc
import Text.Pandoc.Definition
import Prelude
data Output = Native [Block] | Replace Text | Fence Text
type OutputMap = Map Text Output
para :: Text -> Block
para = Para . fmap (Str . Text.unpack) . Text.lines
plain :: Text -> Block
plain = Plain . fmap (Str . Text.unpack) . Text.lines
inline :: Text -> [Inline]
inline = fmap (Str . Text.unpack) . Text.lines
link :: Text -> Text -> Inline
link name url = Link ("", [], []) [Str (Text.unpack name)] (Text.unpack url, "")
image :: Text -> Text -> Inline
image name url = Image ("", [], []) [Str (Text.unpack name)] (Text.unpack url, "")
badge :: Text -> Text -> Text -> Inline
badge label badge' url = Link ("", [], []) [Image ("", [], []) [Str (Text.unpack label)] (Text.unpack badge', "")] (Text.unpack url, "")
table :: Text -> [Text] -> [Alignment] -> [Int] -> [[Text]] -> Block
table caption hs as ws rs =
Table
(inline caption)
as
(fromIntegral <$> ws)
((: []) . para <$> hs)
(fmap ((: []) . para) <$> rs)
table' :: Text -> [Inline] -> [Alignment] -> [Int] -> [[Inline]] -> Block
table' caption hs as ws rs =
Table
(inline caption)
as
(fromIntegral <$> ws)
((: []) . Para . (: []) <$> hs)
(fmap ((: []) . Para . (: [])) <$> rs)
code :: Text -> [Text] -> Text -> Block
code name classes =
CodeBlock (Text.unpack name, Text.unpack <$> classes, []) . Text.unpack
data Flavour = GitHubMarkdown | LHS
exts :: Flavour -> Extensions
exts LHS = enableExtension Ext_literate_haskell $ getDefaultExtensions "markdown"
exts GitHubMarkdown =
enableExtension
Ext_fenced_code_attributes
githubMarkdownExtensions
tweakHaskellCodeBlock :: Block -> Block
tweakHaskellCodeBlock (CodeBlock (id', cs, kv) b) =
CodeBlock (id', bool cs ["haskell"] ("haskell" `elem` cs), kv) b
tweakHaskellCodeBlock x = x
readPandoc :: FilePath -> Flavour -> IO (Either PandocError Pandoc)
readPandoc fp f = do
t <- liftIO $ readFile fp
runIO $ readMarkdown (def :: ReaderOptions) {readerExtensions = exts f} (Text.pack t)
renderMarkdown :: Flavour -> Pandoc -> Either PandocError Text
renderMarkdown f (Pandoc meta bs) =
runPure $
writeMarkdown
(def :: WriterOptions) {writerExtensions = exts f}
(Pandoc meta (tweakHaskellCodeBlock <$> bs))
insertOutput :: OutputMap -> Block -> [Block]
insertOutput m b = case b of
b'@(CodeBlock (id', classes, kv) _) ->
bool
[b']
( maybe
[CodeBlock (id', classes, kv) mempty]
( \x ->
maybe
[CodeBlock (id', classes, kv) mempty]
( \case
Fence t -> [CodeBlock (id', classes, kv) . Text.unpack $ t]
Replace t -> [plain t]
Native bs -> bs
)
(Map.lookup x m)
)
(headMaybe . Prelude.filter ((`elem` classes) . Text.unpack) . Map.keys $ m)
)
("output" `elem` classes)
b' -> [b']
where
headMaybe [] = Nothing
headMaybe (x : _) = Just x
output :: (Monad m) => Text -> Output -> StateT OutputMap m ()
output k v = modify (Map.insert k v)
runOutput ::
(FilePath, Flavour) ->
(FilePath, Flavour) ->
StateT OutputMap IO () ->
IO (Either PandocError ())
runOutput (fi, flavi) (fo, flavo) out = do
m <- execStateT out Map.empty
p <- readPandoc fi flavi
let w = do
p' <- fmap (\(Pandoc meta bs) -> Pandoc meta (mconcat $ insertOutput m <$> bs)) p
renderMarkdown flavo p'
either (pure . Left) (\t -> Text.writeFile fo t >> pure (Right ())) w