{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Rib.Pandoc
( module Text.Pandoc.Readers
, parse
, parsePure
, render
, renderInlines
, render'
, renderInlines'
, getMeta
, setMeta
, parseMeta
, getH1
, getFirstImg
)
where
import Control.Monad
import Data.ByteString.Lazy (ByteString)
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as T
import Lucid (Html, toHtmlRaw)
import Text.Pandoc
import Text.Pandoc.Filter.IncludeCode (includeCode)
import Text.Pandoc.Readers
import Text.Pandoc.Readers.Markdown (yamlToMeta)
import Text.Pandoc.Shared (stringify)
import Text.Pandoc.Walk (query, walkM)
class IsMetaValue a where
parseMetaValue :: MetaValue -> a
instance IsMetaValue [Inline] where
parseMetaValue = \case
MetaInlines inlines -> inlines
_ -> error "Not a MetaInline"
instance IsMetaValue (Html ()) where
parseMetaValue = renderInlines . parseMetaValue @[Inline]
instance IsMetaValue Text where
parseMetaValue = T.pack . stringify . parseMetaValue @[Inline]
instance {-# Overlappable #-} IsMetaValue a => IsMetaValue [a] where
parseMetaValue = \case
MetaList vals -> parseMetaValue <$> vals
_ -> error "Not a MetaList"
instance {-# Overlappable #-} Read a => IsMetaValue a where
parseMetaValue = read . T.unpack . parseMetaValue @Text
getMeta :: IsMetaValue a => String -> Pandoc -> Maybe a
getMeta k (Pandoc meta _) = parseMetaValue <$> lookupMeta k meta
setMeta :: Show a => String -> a -> Pandoc -> Pandoc
setMeta k v (Pandoc (Meta meta) bs) = Pandoc (Meta meta') bs
where
meta' = Map.insert k v' meta
v' = MetaInlines [Str $ show v]
parsePure :: (ReaderOptions -> Text -> PandocPure Pandoc) -> Text -> Pandoc
parsePure r =
either (error . show) id . runPure . r settings
where
settings = def { readerExtensions = exts }
parse
:: (ReaderOptions -> Text -> PandocIO Pandoc)
-> Text
-> IO Pandoc
parse r =
either (error . show) (walkM includeSources) <=< runIO . r settings
where
settings = def { readerExtensions = exts }
includeSources = includeCode $ Just $ Format "html5"
parseMeta :: ByteString -> IO Meta
parseMeta = either (error . show) pure <=< runIO . yamlToMeta settings
where
settings = def { readerExtensions = exts }
render' :: Pandoc -> Either PandocError Text
render' = runPure . writeHtml5String settings
where
settings = def { writerExtensions = exts }
render :: Pandoc -> Html ()
render = either (error . show) toHtmlRaw . render'
renderInlines' :: [Inline] -> Either PandocError Text
renderInlines' = render' . Pandoc mempty . pure . Plain
renderInlines :: [Inline] -> Html ()
renderInlines = either (error . show) toHtmlRaw . renderInlines'
getH1 :: Pandoc -> Maybe (Html ())
getH1 (Pandoc _ bs) = fmap renderInlines $ flip query bs $ \case
Header 1 _ xs -> Just xs
_ -> Nothing
getFirstImg
:: Pandoc
-> Maybe Text
getFirstImg (Pandoc _ bs) = flip query bs $ \case
Image _ _ (url, _) -> Just $ T.pack url
_ -> Nothing
exts :: Extensions
exts = mconcat
[ extensionsFromList
[ Ext_yaml_metadata_block
, Ext_fenced_code_attributes
, Ext_auto_identifiers
, Ext_smart
]
, githubMarkdownExtensions
]