{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Rib.Parser.MMark
(
parse,
parsePure,
parseWith,
parsePureWith,
defaultExts,
render,
getFirstImg,
getFirstParagraphText,
projectYaml,
MMark,
)
where
import Control.Foldl (Fold (..))
import Development.Shake (Action, readFile')
import Lucid.Base (HtmlT (..))
import Path
import Relude
import Rib.Shake (ribInputDir)
import Text.MMark (MMark, projectYaml)
import qualified Text.MMark as MMark
import qualified Text.MMark.Extension as Ext
import qualified Text.MMark.Extension.Common as Ext
import qualified Text.Megaparsec as M
import Text.URI (URI)
render :: Monad m => MMark -> HtmlT m ()
render = liftHtml . MMark.render
where
liftHtml :: Monad m => HtmlT Identity () -> HtmlT m ()
liftHtml = HtmlT . pure . runIdentity . runHtmlT
parsePureWith ::
[MMark.Extension] ->
FilePath ->
Text ->
Either Text MMark
parsePureWith exts k s = case MMark.parse k s of
Left e -> Left $ toText $ M.errorBundlePretty e
Right doc -> Right $ MMark.useExtensions exts $ useTocExt doc
parsePure ::
FilePath ->
Text ->
Either Text MMark
parsePure = parsePureWith defaultExts
parse :: Path Rel File -> Action MMark
parse = parseWith defaultExts
parseWith :: [MMark.Extension] -> Path Rel File -> Action MMark
parseWith exts f =
either (fail . toString) pure =<< do
inputDir <- ribInputDir
s <- toText <$> readFile' (toFilePath $ inputDir </> f)
pure $ parsePureWith exts (toFilePath f) s
getFirstImg :: MMark -> Maybe URI
getFirstImg = flip MMark.runScanner $ Fold f Nothing id
where
f acc blk = acc <|> listToMaybe (mapMaybe getImgUri (inlinesContainingImg blk))
getImgUri = \case
Ext.Image _ uri _ -> Just uri
_ -> Nothing
inlinesContainingImg :: Ext.Bni -> [Ext.Inline]
inlinesContainingImg = \case
Ext.Naked xs -> toList xs
Ext.Paragraph xs -> toList xs
_ -> []
getFirstParagraphText :: MMark -> Maybe Text
getFirstParagraphText =
flip MMark.runScanner $ Fold f Nothing id
where
f acc blk = acc <|> (Ext.asPlainText <$> getPara blk)
getPara = \case
Ext.Paragraph xs -> Just xs
_ -> Nothing
defaultExts :: [MMark.Extension]
defaultExts =
[ Ext.fontAwesome,
Ext.footnotes,
Ext.kbd,
Ext.linkTarget,
Ext.mathJax (Just '$'),
Ext.punctuationPrettifier,
Ext.skylighting
]
useTocExt :: MMark -> MMark
useTocExt doc = MMark.useExtension (Ext.toc "toc" toc) doc
where
toc = MMark.runScanner doc $ Ext.tocScanner (\x -> x > 1 && x < 5)