knit-haskell-0.7.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. You can add logging from within document creation using logLE.
  2. 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.
  3. 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 [DocWithInfo PandocInfo 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 (Embed 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 a 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, Members [UnusedId, Logger LogEntry, PrefixLog, Error PandocError, Embed IO] r) Source #

Constraint alias for the effects we need (and run) when calling Knit. Anything inside a call to Knit can use any of these effects. Any other effects will need to be run before knitHtml(s)

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 Pandocs r) Source #

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

type KnitBase m effs = (MonadIO m, Member (Embed 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

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

writeAllPandocResultsWithInfoAsHtml :: Text -> [DocWithInfo PandocInfo Text] -> IO () Source #

Write each lazy text from a list of DocWithInfo to disk. File names come from the PandocInfo Directory is a function arguments. File extension is "html"

writePandocResultWithInfoAsHtml :: Text -> DocWithInfo PandocInfo Text -> IO () Source #

Write the Lazy Text in a DocWithInfo to disk, Name comes from the PandocInfo Directory is an argument to the function File extension is "html" Create the parent directory or directories, if necessary.

Effects

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

data Sem (r :: EffectRow) a #

Instances
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 #

Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

fail :: String -> 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 (Embed IO) r => MonadIO (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Sem r 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 NonDet r => MonadPlus (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

mzero :: Sem r a #

mplus :: Sem r a -> Sem r a -> Sem r a #

type Member (e :: k) (r :: [k]) = MemberNoError e r #

type Pandocs = Docs PandocInfo PandocWithRequirements Source #

Type-alias for use with the Docs effect.

data PandocInfo Source #

Type to hold info about each document that will be required for rendering and output

Constructors

PandocInfo 

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) 
=> PandocInfo

name and template variables for 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 DocWithInfo i a Source #

Data type to hold one document with info of type i and doc of type a.

Constructors

DocWithInfo 

Fields

Instances
Functor (DocWithInfo i) Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

fmap :: (a -> b) -> DocWithInfo i a -> DocWithInfo i b #

(<$) :: a -> DocWithInfo i b -> DocWithInfo i a #

Foldable (DocWithInfo i) Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

fold :: Monoid m => DocWithInfo i m -> m #

foldMap :: Monoid m => (a -> m) -> DocWithInfo i a -> m #

foldr :: (a -> b -> b) -> b -> DocWithInfo i a -> b #

foldr' :: (a -> b -> b) -> b -> DocWithInfo i a -> b #

foldl :: (b -> a -> b) -> b -> DocWithInfo i a -> b #

foldl' :: (b -> a -> b) -> b -> DocWithInfo i a -> b #

foldr1 :: (a -> a -> a) -> DocWithInfo i a -> a #

foldl1 :: (a -> a -> a) -> DocWithInfo i a -> a #

toList :: DocWithInfo i a -> [a] #

null :: DocWithInfo i a -> Bool #

length :: DocWithInfo i a -> Int #

elem :: Eq a => a -> DocWithInfo i a -> Bool #

maximum :: Ord a => DocWithInfo i a -> a #

minimum :: Ord a => DocWithInfo i a -> a #

sum :: Num a => DocWithInfo i a -> a #

product :: Num a => DocWithInfo i a -> a #

Traversable (DocWithInfo i) Source # 
Instance details

Defined in Knit.Effect.Docs

Methods

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

sequenceA :: Applicative f => DocWithInfo i (f a) -> f (DocWithInfo i a) #

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

sequence :: Monad m => DocWithInfo i (m a) -> m (DocWithInfo i 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.