knit-haskell-0.8.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

Description

Polysemy PandocMonad effect. Allows a polysemy monad to handle actions with a PandocMonad contraint via polysemy effects and IO. Has an "absorber" to convert functions with a PandocMonad constraint.

Synopsis

Types

data Pandoc m r Source #

Pandoc Effect

type PandocEffects effs = (Member Pandoc effs, Member Template 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 (Embed IO) effs) Source #

Constraint helper for using this set of effects in IO.

Actions

lookupEnv :: forall r. MemberWithError Pandoc r => PandocText -> Sem r (Maybe PandocText) Source #

openURL :: forall r. MemberWithError Pandoc r => PandocText -> Sem r (ByteString, Maybe MimeType) Source #

getsCommonState :: forall r a. MemberWithError Pandoc r => (CommonState -> a) -> Sem r a Source #

trace :: forall r. MemberWithError Pandoc r => PandocText -> Sem r () Source #

Pandoc <2.8 compatibility

textToPandocText :: Text -> PandocText Source #

pandocTextToText :: PandocText -> Text Source #

absorbTemplateMonad :: Member Template r => (TemplateMonad (Sem r) => Sem r a) -> Sem r a Source #

use a Polysemy stack containing the Template effect to run an TemplateMonad m action.

data Template m a Source #

interpretTemplateIO :: forall effs a. Member (Embed IO) effs => Sem (Template ': effs) a -> Sem effs a Source #

Interpret a Template effect in any stack with IO (via the IO instance in DocTemplates)

Interpreters

interpretInPandocMonad :: forall m effs a. (PandocMonad m, Member (Embed m) effs, Member (Logger LogEntry) effs) => Sem (Pandoc ': effs) a -> Sem 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 (Embed IO) effs, Member (Error PandocError) effs) => Sem (Pandoc ': effs) a -> Sem effs a Source #

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

Runners

Interop

absorbPandocMonad :: Members '[Error PandocError, Pandoc] r => (PandocMonad (Sem r) => Sem r a) -> Sem r a Source #

absorb a PandocMonad constraint into Members [Pandoc, Error PandocError] r => Sem r

Re-Exports

data PandocError #

Instances

Instances details
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 PandocPure 
Instance details

Defined in Text.Pandoc.Class.PandocPure

type Rep PandocError 
Instance details

Defined in Text.Pandoc.Error

type Rep PandocError = D1 ('MetaData "PandocError" "Text.Pandoc.Error" "pndc-2.10-7bfadb12" 'False) ((((C1 ('MetaCons "PandocIOError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IOError)) :+: (C1 ('MetaCons "PandocHttpError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HttpException)) :+: C1 ('MetaCons "PandocShouldNeverHappenError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: (C1 ('MetaCons "PandocSomeError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "PandocParseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: 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 Text)) :+: (C1 ('MetaCons "PandocOptionError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocSyntaxMapError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: (C1 ('MetaCons "PandocFailOnWarningError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PandocPDFProgramNotFoundError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocPDFError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))) :+: (((C1 ('MetaCons "PandocFilterError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "PandocLuaError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocCouldNotFindDataFileError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: (C1 ('MetaCons "PandocResourceNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "PandocTemplateError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocAppError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) :+: ((C1 ('MetaCons "PandocEpubSubdirectoryError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "PandocMacroLoop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocUTF8DecodingError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (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 Text)) :+: C1 ('MetaCons "PandocUnknownReaderError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "PandocUnknownWriterError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PandocUnsupportedExtensionError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))))