knit-haskell-0.5.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 monad to handle functions actions with a PandocMonad contraint via polysemy effects and IO.

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

lookupEnv :: forall r. Member Pandoc r => String -> Sem r (Maybe [Char]) Source #

newStdGen :: forall r. Member Pandoc r => Sem r StdGen Source #

newUniqueHash :: forall r. Member Pandoc r => Sem r Int Source #

openURL :: forall r. Member Pandoc r => String -> Sem r (ByteString, Maybe [Char]) Source #

glob :: forall r. Member Pandoc r => String -> Sem r [[Char]] Source #

fileExists :: forall r. Member Pandoc r => FilePath -> Sem r Bool Source #

getCommonState :: forall r. Member Pandoc r => Sem r CommonState Source #

putCommonState :: forall r. Member Pandoc r => CommonState -> Sem r () Source #

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

modifyCommonState :: forall r. Member Pandoc r => (CommonState -> CommonState) -> Sem r () Source #

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

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

Interpreters

interpretInPandocMonad :: forall m effs a. (PandocMonad m, Member (Lift 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 (Lift 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

runIO :: [LogSeverity] -> Sem '[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.

Interop

absorbPandocMonad :: (Member (Error PandocError) r, PandocEffects r) => (forall m. PandocMonad m => m a) -> Sem r a Source #

Given an action constrained only by a PandocMonad constraint, absorb it into a Polysemy monad whose effect list contains the required effects.

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

Methods

throwError :: PandocError -> PandocIO a #

catchError :: PandocIO a -> (PandocError -> PandocIO a) -> PandocIO a #

MonadError PandocError PandocPure 
Instance details

Defined in Text.Pandoc.Class

Methods

throwError :: PandocError -> PandocPure a #

catchError :: PandocPure a -> (PandocError -> PandocPure a) -> PandocPure a #

type Rep PandocError 
Instance details

Defined in Text.Pandoc.Error

type Rep PandocError = D1 (MetaData "PandocError" "Text.Pandoc.Error" "pndc-2.7.3-d37e4fcc" 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)))))))