knit-haskell-0.3.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.Report

Contents

Description

This module re-exports the basic pieces to build reports using Pandoc as well as providing functions to do the "knitting"--produce the documents. That is, it is intended as one-stop-shopping for using this library to produce Html from various fragments which Pandoc can read.

Examples are available, and might be useful for seeing how all this works.

Notes:

  1. The Knit.Effect.RandomFu effect is not imported since the names might clash with Polysemy.Random. Import either effect directly if you need it.
  2. You can add logging from within document creation using logLE.
  3. The Knit.Report.Input.MarkDown.PandocMarkDown module is exported so if you want to use a different markdown flavor you may need to hide "addMarkDown" when you import this module.
  4. If you use any other effects in your polysemy stack (e.g., Random or RandomFu), you will need to interpretrun them before calling knitHtmlknitHtmls.
Synopsis

Knit

knitHtml Source #

Arguments

:: MonadIO m 
=> Maybe Text

outer logging prefix

-> [LogSeverity]

what to output in log

-> PandocWriterConfig

configuration for the Pandoc Html Writer

-> Sem (KnitEffectDocStack m) () 
-> m (Either PandocError Text) 

Create HTML Text from pandoc fragments In use, you may need a type-application to specify m. This allows use of any underlying monad to handle the Pandoc effects. NB: Resulting document is *Lazy* Text, as produced by the Blaze render function.

knitHtmls Source #

Arguments

:: MonadIO m 
=> Maybe Text

outer logging prefix

-> [LogSeverity]

what to output in log

-> PandocWriterConfig

configuration for the Pandoc Html Writer

-> Sem (KnitEffectDocsStack m) () 
-> m (Either PandocError [NamedDoc Text]) 

Create multiple HTML docs (as Text) from the named sets of pandoc fragments. In use, you may need a type-application to specify m. This allows use of any underlying monad to handle the Pandoc effects. NB: Resulting documents are *Lazy* Text, as produced by the Blaze render function.

liftKnit :: Member (Lift m) r => m a -> Sem r a Source #

lift an action in a base monad into a Polysemy monad. This is just a renaming for convenience.

knitError :: Member (Error PandocError) r => Text -> Sem r () Source #

Throw an error with a specific message. This will emerge as a PandocSomeError in order to avoid complicating the error type. NB: The Member constraint is satisfied by KnitEffectStack m.

type KnitEffects r = (PandocEffects r, Member UnusedId r) Source #

Constraint alias for the effects we need when calling Knit

type KnitOne r = (KnitEffects r, Member ToPandoc r) Source #

Constraint alias for the effects we need to knit one document

type KnitMany r = (KnitEffects r, Member (Docs PandocWithRequirements) r) Source #

Constraint alias for the effects we need to knit multiple documents.

type KnitBase m effs = (MonadIO m, Member (Lift m) effs) Source #

Constraints required to knit a document using effects from a base monad m.

Inputs

addMarkDown :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs () Source #

Add a Pandoc MarkDown fragment with default options

addStrictTextHtml :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs () Source #

Add Strict Text Html to current Pandoc

addLazyTextHtml :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs () Source #

Add Lazy Text Html to current Pandoc

addBlaze :: (PandocEffects effs, Member ToPandoc effs) => Html -> Sem effs () Source #

Add Blaze Html

addLucid :: (PandocEffects effs, Member ToPandoc effs) => Html () -> Sem effs () Source #

Add Lucid Html

addLatex :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs () Source #

Add LaTeX

addHvega Source #

Arguments

:: (PandocEffects effs, Member ToPandoc effs, Member UnusedId effs) 
=> Maybe Text

figure id, will get next unused with prefix "figure" if Nothing

-> Maybe Text

figure caption, none if Nothing

-> VegaLite 
-> Sem effs Text 

Add hvega (via html). Requires html since vega-lite renders using javascript.

Output

data PandocWriterConfig Source #

Constructors

PandocWriterConfig 

Fields

pandocWriterToBlazeDocument Source #

Arguments

:: PandocEffects effs 
=> PandocWriterConfig

Configuration info for the Pandoc writer

-> Sem (ToPandoc ': effs) ()

Effects stack to run to get Pandoc

-> Sem effs Html

Blaze Html (in remaining effects)

Convert current Pandoc document (from the ToPandoc effect) into a Blaze Html document. Incudes support for template and template variables and changes to the default writer options.

mindocOptionsF :: WriterOptions -> WriterOptions Source #

options for the mindoc template

Effects

data Sem (r :: [(Type -> Type) -> Type -> Type]) a #

The Sem monad handles computations of arbitrary extensible effects. A value of type Sem r describes a program with the capabilities of r. For best results, r should always be kept polymorphic, but you can add capabilities via the Member constraint.

The value of the Sem monad is that it allows you to write programs against a set of effects without a predefined meaning, and provide that meaning later. For example, unlike with mtl, you can decide to interpret an Error effect tradtionally as an Either, or instead significantly faster as an IO Exception. These interpretations (and others that you might add) may be used interchangably without needing to write any newtypes or Monad instances. The only change needed to swap interpretations is to change a call from runError to runErrorInIO.

The effect stack r can contain arbitrary other monads inside of it. These monads are lifted into effects via the Lift effect. Monadic values can be lifted into a Sem via sendM.

A Sem can be interpreted as a pure value (via run) or as any traditional Monad (via runM). Each effect E comes equipped with some interpreters of the form:

runE :: Sem (E ': r) a -> Sem r a

which is responsible for removing the effect E from the effect stack. It is the order in which you call the interpreters that determines the monomorphic representation of the r parameter.

After all of your effects are handled, you'll be left with either a Sem '[] a or a Sem '[ Lift m ] a value, which can be consumed respectively by run and runM.

Examples

As an example of keeping r polymorphic, we can consider the type

Member (State String) r => Sem r ()

to be a program with access to

get :: Sem r String
put :: String -> Sem r ()

methods.

By also adding a

Member (Error Bool) r

constraint on r, we gain access to the

throw :: Bool -> Sem r a
catch :: Sem r a -> (Bool -> Sem r a) -> Sem r a

functions as well.

In this sense, a Member (State s) r constraint is analogous to mtl's MonadState s m and should be thought of as such. However, unlike mtl, a Sem monad may have an arbitrary number of the same effect.

For example, we can write a Sem program which can output either Ints or Bools:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       )
    => Sem r ()
foo = do
  output @Int  5
  output True

Notice that we must use -XTypeApplications to specify that we'd like to use the (Output Int) effect.

Since: polysemy-0.1.2.0

Instances
Member (Error PandocError :: (Type -> Type) -> Type -> Type) effs => MonadError PandocError (Sem 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 -> Sem effs a #

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

Monad (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

(>>=) :: Sem f a -> (a -> Sem f b) -> Sem f b #

(>>) :: Sem f a -> Sem f b -> Sem f b #

return :: a -> Sem f a #

fail :: String -> Sem f a #

Functor (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

fmap :: (a -> b) -> Sem f a -> Sem f b #

(<$) :: a -> Sem f b -> Sem f a #

Member Fixpoint r => MonadFix (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

mfix :: (a -> Sem r a) -> Sem r a #

Applicative (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

pure :: a -> Sem f a #

(<*>) :: Sem f (a -> b) -> Sem f a -> Sem f b #

liftA2 :: (a -> b -> c) -> Sem f a -> Sem f b -> Sem f c #

(*>) :: Sem f a -> Sem f b -> Sem f b #

(<*) :: Sem f a -> Sem f b -> Sem f a #

Member NonDet r => Alternative (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

empty :: Sem r a #

(<|>) :: Sem r a -> Sem r a -> Sem r a #

some :: Sem r a -> Sem r [a] #

many :: Sem r a -> Sem r [a] #

Member (Lift IO) r => MonadIO (Sem r)

This instance will only lift IO actions. If you want to lift into some other MonadIO type, use this instance, and handle it via the runIO interpretation.

Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Sem r a #

PandocEffects effs => PandocMonad (Sem effs) Source #

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

Instance details

Defined in Knit.Effect.PandocMonad

Member (Random :: (Type -> Type) -> Type -> Type) effs => MonadRandom (Sem effs) Source #

supply instance of MonadRandom for functions which require it

Instance details

Defined in Knit.Effect.RandomFu

type Member (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) = Member' e r #

A proof that the effect e is available somewhere inside of the effect stack r.

data Lift (m :: Type -> Type) (z :: Type -> Type) a #

An effect which allows a regular Monad m into the Sem ecosystem. Monadic actions in m can be lifted into Sem via sendM.

For example, you can use this effect to lift IO actions directly into Sem:

sendM (putStrLn "hello") :: Member (Lift IO) r => Sem r ()

That being said, you lose out on a significant amount of the benefits of Sem by using sendM directly in application code; doing so will tie your application code directly to the underlying monad, and prevent you from interpreting it differently. For best results, only use Lift in your effect interpreters.

Consider using trace and runTraceIO as a substitute for using putStrLn directly.

type Pandocs = Docs PandocWithRequirements Source #

Type-alias for use with the Docs effect.

data ToPandoc m r Source #

Pandoc writer, add any read format to current doc

data Requirement Source #

ADT to allow inputs to request support, if necessary or possible, in the output format. E.g., Latex output in Html needs MathJax. But Latex needs to nothing to output in Latex. Vega-lite needs some script headers to output in Html and can't be output in other formats. For now, we support all the things we can in any output format so this just results in a runtime test.

Constructors

VegaSupport

Supported only for Html output.

LatexSupport

Supported in Html output (via MathJax) and Latex output.

newPandoc Source #

Arguments

:: (PandocEffects effs, Member Pandocs effs) 
=> Text

name of document

-> Sem (ToPandoc ': effs) () 
-> Sem effs () 

Add the Pandoc stored in the writer-style ToPandoc effect to the named docs collection with the given name.

data NamedDoc a Source #

Data type to hold one named document of type a.

Constructors

NamedDoc 

Fields

Instances
Functor NamedDoc Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

fmap :: (a -> b) -> NamedDoc a -> NamedDoc b #

(<$) :: a -> NamedDoc b -> NamedDoc a #

Foldable NamedDoc Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

fold :: Monoid m => NamedDoc m -> m #

foldMap :: Monoid m => (a -> m) -> NamedDoc a -> m #

foldr :: (a -> b -> b) -> b -> NamedDoc a -> b #

foldr' :: (a -> b -> b) -> b -> NamedDoc a -> b #

foldl :: (b -> a -> b) -> b -> NamedDoc a -> b #

foldl' :: (b -> a -> b) -> b -> NamedDoc a -> b #

foldr1 :: (a -> a -> a) -> NamedDoc a -> a #

foldl1 :: (a -> a -> a) -> NamedDoc a -> a #

toList :: NamedDoc a -> [a] #

null :: NamedDoc a -> Bool #

length :: NamedDoc a -> Int #

elem :: Eq a => a -> NamedDoc a -> Bool #

maximum :: Ord a => NamedDoc a -> a #

minimum :: Ord a => NamedDoc a -> a #

sum :: Num a => NamedDoc a -> a #

product :: Num a => NamedDoc a -> a #

Traversable NamedDoc Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

traverse :: Applicative f => (a -> f b) -> NamedDoc a -> f (NamedDoc b) #

sequenceA :: Applicative f => NamedDoc (f a) -> f (NamedDoc a) #

mapM :: Monad m => (a -> m b) -> NamedDoc a -> m (NamedDoc b) #

sequence :: Monad m => NamedDoc (m a) -> m (NamedDoc a) #

type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs Source #

Constraint helper for LogEntry type with prefixes

logAll :: [LogSeverity] Source #

LogSeverity list used in order to output everything.

nonDiagnostic :: [LogSeverity] Source #

LogSeverity list used to output all but Diagnostic. Diagnostic messages are sometimes useful for debugging but can get noisy depending on how you use it.

logLE :: Member (Logger LogEntry) effs => LogSeverity -> Text -> Sem effs () Source #

Add one log-entry of the LogEntry type.

wrapPrefix :: Member PrefixLog effs => Text -> Sem effs a -> Sem effs a Source #

Add a prefix for the block of code.

filteredLogEntriesToIO :: MonadIO (Sem effs) => [LogSeverity] -> Sem (Logger LogEntry ': (PrefixLog ': effs)) x -> Sem effs x Source #

Run the Logger and PrefixLog effects using the preferred handler and filter output in any Polysemy monad with IO in the union.

getNextUnusedId :: Member UnusedId r => Text -> Sem r Text Source #

Get an unused id with prefix as specified. Useful for figures, etc.