knit-haskell-0.1.0.0: a minimal Rmarkdown sort-of-thing for haskell, by way of Pandoc

Copyright(c) Adam Conner-Sax 2019
LicenseBSD-3-Clause
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Knit.Effect.PandocMonad

Contents

Description

Polysemy PandocMonad effect. Allows a polysemy "stack" to satisfy a PandocMonad constraint. This still needs to run on top of PandocIO but that will likely be addressed at some point in the future, just requiring IO at base and the Logging and Random effects.

Synopsis

Types

data Pandoc m r Source #

Pandoc Effect

type PandocEffects effs = (Member Pandoc effs, Member (Error PandocError) effs, Member PrefixLog effs, Member (Logger LogEntry) effs) Source #

Constraint helper for using this set of effects in IO.

type PandocEffectsIO effs = (PandocEffects effs, Member (Lift IO) effs) Source #

Constraint helper for using this set of effects in IO.

Actions

glob :: forall r. Member Pandoc r => String -> Semantic r [FilePath] Source #

getsCommonState :: forall a. forall r. Member Pandoc r => (CommonState -> a) -> Semantic r a Source #

logOutput :: forall r. Member Pandoc r => LogMessage -> Semantic r () Source #

trace :: forall r. Member Pandoc r => String -> Semantic r () Source #

Interpreters

interpretInPandocMonad :: forall m effs a. (PandocMonad m, Member (Lift m) effs, Member (Logger LogEntry) effs) => Semantic (Pandoc ': effs) a -> Semantic effs a Source #

Interpret the Pandoc effect in another monad (which must satisy the PandocMonad constraint) and Knit.Effect.Logger

interpretInIO :: forall effs a. (Member (Logger LogEntry) effs, Member (Lift IO) effs, Member (Error PandocError) effs) => Semantic (Pandoc ': effs) a -> Semantic effs a Source #

Interpret the Pandoc effect using IO, Knit.Effect.Logger and PolySemy.Error PandocError

Runners

runIO :: [LogSeverity] -> Semantic '[Pandoc, Logger LogEntry, PrefixLog, Error PandocError, Lift IO] a -> IO (Either PandocError a) Source #

Run the Pandoc effects, and log messages with the given severity, over IO. If there is a Pandoc error, you will get a Left in the resulting Either.

Re-Exports

data PandocError #

Instances
Show PandocError 
Instance details

Defined in Text.Pandoc.Error

Generic PandocError 
Instance details

Defined in Text.Pandoc.Error

Associated Types

type Rep PandocError :: Type -> Type #

Exception PandocError 
Instance details

Defined in Text.Pandoc.Error

MonadError PandocError PandocIO 
Instance details

Defined in Text.Pandoc.Class

MonadError PandocError PandocPure 
Instance details

Defined in Text.Pandoc.Class

Member (Error PandocError :: (Type -> Type) -> Type -> Type) effs => MonadError PandocError (Semantic effs) Source #

Split off the error piece. We will handle directly with the polysemy Error effect

Instance details

Defined in Knit.Effect.PandocMonad

Methods

throwError :: PandocError -> Semantic effs a #

catchError :: Semantic effs a -> (PandocError -> Semantic effs a) -> Semantic effs a #

type Rep PandocError 
Instance details

Defined in Text.Pandoc.Error

type Rep PandocError = D1 (MetaData "PandocError" "Text.Pandoc.Error" "pandoc-2.7.2-JwWOYfETWUeHZoCcBLG0ix" False) ((((C1 (MetaCons "PandocIOError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IOError)) :+: C1 (MetaCons "PandocHttpError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HttpException))) :+: (C1 (MetaCons "PandocShouldNeverHappenError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "PandocSomeError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PandocParseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :+: ((C1 (MetaCons "PandocParsecError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Input) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParseError)) :+: C1 (MetaCons "PandocMakePDFError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :+: (C1 (MetaCons "PandocOptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "PandocSyntaxMapError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PandocFailOnWarningError" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "PandocPDFProgramNotFoundError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PandocPDFError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :+: (C1 (MetaCons "PandocFilterError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "PandocCouldNotFindDataFileError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PandocResourceNotFound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :+: ((C1 (MetaCons "PandocTemplateError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "PandocAppError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PandocEpubSubdirectoryError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) :+: (C1 (MetaCons "PandocMacroLoop" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "PandocUTF8DecodingError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8))) :+: C1 (MetaCons "PandocIpynbDecodingError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

Orphan instances

Member (Error PandocError :: (Type -> Type) -> Type -> Type) effs => MonadError PandocError (Semantic effs) Source #

Split off the error piece. We will handle directly with the polysemy Error effect

Instance details

Methods

throwError :: PandocError -> Semantic effs a #

catchError :: Semantic effs a -> (PandocError -> Semantic effs a) -> Semantic effs a #

PandocEffects effs => PandocMonad (Semantic effs) Source #

PandocMonad instance so that pandoc functions can be run in the polysemy union effect

Instance details