{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
module Knit.Effect.Pandoc
(
ToPandoc
, FromPandoc
, Requirement(..)
, PandocWithRequirements
, PandocReadFormat(..)
, PandocWriteFormat(..)
, addFrom
, require
, writeTo
, toPandoc
, fromPandoc
, runPandocWriter
, Pandocs
, NamedDoc(..)
, newPandoc
, pandocsToNamed
, fromPandocE
)
where
import qualified Text.Pandoc as PA
import qualified Data.Text as T
import Data.ByteString.Lazy as LBS
import qualified Data.Foldable as F
import qualified Data.Monoid as Mon
import Data.Set as S
import qualified Text.Blaze.Html as Blaze
import Control.Monad.Except ( throwError )
import qualified Polysemy as P
import Polysemy.Internal ( send )
import qualified Polysemy.Writer as P
import qualified Knit.Effect.PandocMonad as PM
import Knit.Effect.Docs ( Docs
, NamedDoc(..)
, newDoc
, toNamedDocList
)
data PandocReadFormat a where
ReadDocX :: PandocReadFormat LBS.ByteString
ReadMarkDown :: PandocReadFormat T.Text
ReadCommonMark :: PandocReadFormat T.Text
ReadRST :: PandocReadFormat T.Text
ReadLaTeX :: PandocReadFormat T.Text
ReadHtml :: PandocReadFormat T.Text
deriving instance Show (PandocReadFormat a)
data PandocWriteFormat a where
WriteDocX :: PandocWriteFormat LBS.ByteString
WriteMarkDown :: PandocWriteFormat T.Text
WriteCommonMark :: PandocWriteFormat T.Text
WriteRST :: PandocWriteFormat T.Text
WriteLaTeX :: PandocWriteFormat T.Text
WriteHtml5 :: PandocWriteFormat Blaze.Html
WriteHtml5String :: PandocWriteFormat T.Text
deriving instance Show (PandocWriteFormat a)
data Requirement
=
VegaSupport
| LatexSupport
deriving (Show, Ord, Eq, Bounded, Enum)
handlesAll :: PandocWriteFormat a -> S.Set Requirement -> Bool
handlesAll f rs = Mon.getAll
$ F.fold (fmap (Mon.All . handles f) $ S.toList rs)
where
handles :: PandocWriteFormat a -> Requirement -> Bool
handles WriteHtml5 VegaSupport = True
handles WriteHtml5String VegaSupport = True
handles WriteHtml5 LatexSupport = True
handles WriteHtml5String LatexSupport = True
handles WriteLaTeX LatexSupport = True
handles _ _ = False
data PandocWithRequirements = PandocWithRequirements { doc :: PA.Pandoc, reqs :: S.Set Requirement }
instance Semigroup PandocWithRequirements where
(PandocWithRequirements da ra) <> (PandocWithRequirements db rb)
= PandocWithRequirements (da <> db) (ra <> rb)
instance Monoid PandocWithRequirements where
mempty = PandocWithRequirements mempty mempty
justDoc :: PA.Pandoc -> PandocWithRequirements
justDoc d = PandocWithRequirements d mempty
justRequirement :: Requirement -> PandocWithRequirements
justRequirement r = PandocWithRequirements mempty (S.singleton r)
data ToPandoc m r where
AddFrom :: PandocReadFormat a -> PA.ReaderOptions -> a -> ToPandoc m ()
Require :: Requirement -> ToPandoc m ()
data FromPandoc m r where
WriteTo :: PandocWriteFormat a -> PA.WriterOptions -> PA.Pandoc -> FromPandoc m a
addFrom
:: P.Member ToPandoc effs
=> PandocReadFormat a
-> PA.ReaderOptions
-> a
-> P.Semantic effs ()
addFrom prf pro doc' = send $ AddFrom prf pro doc'
require :: P.Member ToPandoc effs => Requirement -> P.Semantic effs ()
require r = send $ Require r
writeTo
:: P.Member FromPandoc effs
=> PandocWriteFormat a
-> PA.WriterOptions
-> PA.Pandoc
-> P.Semantic effs a
writeTo pwf pwo pdoc = send $ WriteTo pwf pwo pdoc
toPandoc
:: PA.PandocMonad m
=> PandocReadFormat a
-> PA.ReaderOptions
-> a
-> m PA.Pandoc
toPandoc prf pro x = readF pro x
where
readF = case prf of
ReadDocX -> PA.readDocx
ReadMarkDown -> PA.readMarkdown
ReadCommonMark -> PA.readCommonMark
ReadRST -> PA.readRST
ReadLaTeX -> PA.readLaTeX
ReadHtml -> PA.readHtml
fromPandoc
:: PA.PandocMonad m
=> PandocWriteFormat a
-> PA.WriterOptions
-> PandocWithRequirements
-> m a
fromPandoc pwf pwo (PandocWithRequirements pdoc rs) = case handlesAll pwf rs of
False ->
throwError
$ PA.PandocSomeError
$ "One of "
++ (show $ S.toList rs)
++ " cannot be output to "
++ show pwf
True -> write pwo pdoc
where
write = case pwf of
WriteDocX -> PA.writeDocx
WriteMarkDown -> PA.writeMarkdown
WriteCommonMark -> PA.writeCommonMark
WriteRST -> PA.writeRST
WriteLaTeX -> PA.writeLaTeX
WriteHtml5 -> PA.writeHtml5
WriteHtml5String -> PA.writeHtml5String
toWriter
:: PM.PandocEffects effs
=> P.Semantic (ToPandoc ': effs) a
-> P.Semantic (P.Writer PandocWithRequirements ': effs) a
toWriter = P.reinterpret $ \case
(AddFrom rf ro x) ->
P.raise (fmap justDoc $ toPandoc rf ro x) >>= P.tell @PandocWithRequirements
(Require r) -> P.tell (justRequirement r)
runPandocWriter
:: PM.PandocEffects effs
=> P.Semantic (ToPandoc ': effs) ()
-> P.Semantic effs PandocWithRequirements
runPandocWriter = fmap fst . P.runWriter . toWriter
type Pandocs = Docs PandocWithRequirements
newPandocPure
:: P.Member Pandocs effs
=> T.Text
-> PandocWithRequirements
-> P.Semantic effs ()
newPandocPure = newDoc
newPandoc
:: (PM.PandocEffects effs, P.Member Pandocs effs)
=> T.Text
-> P.Semantic (ToPandoc ': effs) ()
-> P.Semantic effs ()
newPandoc n l = fmap fst (P.runWriter $ toWriter l) >>= newPandocPure n
namedPandocFrom
:: PA.PandocMonad m
=> PandocWriteFormat a
-> PA.WriterOptions
-> NamedDoc PandocWithRequirements
-> m (NamedDoc a)
namedPandocFrom pwf pwo (NamedDoc n pdoc) = do
doc' <- fromPandoc pwf pwo pdoc
return $ NamedDoc n doc'
pandocsToNamed
:: PM.PandocEffects effs
=> PandocWriteFormat a
-> PA.WriterOptions
-> P.Semantic (Pandocs ': effs) ()
-> P.Semantic effs [NamedDoc a]
pandocsToNamed pwf pwo =
(traverse (namedPandocFrom pwf pwo) =<<) . toNamedDocList
fromPandocE
:: PM.PandocEffects effs
=> PandocWriteFormat a
-> PA.WriterOptions
-> P.Semantic (ToPandoc ': effs) ()
-> P.Semantic effs a
fromPandocE pwf pwo = ((fromPandoc pwf pwo . fst) =<<) . P.runWriter . toWriter