Copyright | (c) Adam Conner-Sax 2019 |
---|---|
License | BSD-3-Clause |
Maintainer | adam_conner_sax@yahoo.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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:
- The Knit.Effect.RandomFu effect is not imported since the names might clash with Polysemy.Random. Import either effect directly if you need it.
- You can add logging from within document creation using
logLE
. - 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.
- 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
- knitHtml :: MonadIO m => Maybe Text -> [LogSeverity] -> PandocWriterConfig -> Sem (KnitEffectDocStack m) () -> m (Either PandocError Text)
- knitHtmls :: MonadIO m => Maybe Text -> [LogSeverity] -> PandocWriterConfig -> Sem (KnitEffectDocsStack m) () -> m (Either PandocError [NamedDoc Text])
- liftKnit :: Member (Lift m) r => m a -> Sem r a
- type KnitBase m effs = (MonadIO m, Member (Lift m) effs)
- addColonnadeTextTable :: (PandocEffects effs, Member ToPandoc effs, Foldable f) => Colonnade Headed a Text -> f a -> Sem effs ()
- addColonnadeHtmlTable :: (PandocEffects effs, Member ToPandoc effs, Foldable f) => Attribute -> Colonnade Headed a Html -> f a -> Sem effs ()
- addColonnadeCellTable :: (PandocEffects effs, Member ToPandoc effs, Foldable f) => Attribute -> Colonnade Headed a Cell -> f a -> Sem effs ()
- addMarkDown :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs ()
- addStrictTextHtml :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs ()
- addLazyTextHtml :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs ()
- addBlaze :: (PandocEffects effs, Member ToPandoc effs) => Html -> Sem effs ()
- addLucid :: (PandocEffects effs, Member ToPandoc effs) => Html () -> Sem effs ()
- addLatex :: (PandocEffects effs, Member ToPandoc effs) => Text -> Sem effs ()
- addHvega :: (PandocEffects effs, Member ToPandoc effs) => Text -> VegaLite -> Sem effs ()
- data PandocWriterConfig = PandocWriterConfig {}
- pandocWriterToBlazeDocument :: PandocEffects effs => PandocWriterConfig -> Sem (ToPandoc ': effs) () -> Sem effs Html
- mindocOptionsF :: WriterOptions -> WriterOptions
- data Sem (r :: [(Type -> Type) -> Type -> Type]) a
- type Member (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) = Member' e r
- data Lift (m :: Type -> Type) (z :: Type -> Type) a
- type Pandocs = Docs PandocWithRequirements
- data ToPandoc m r
- data Requirement
- data PandocWriteFormat a where
- data PandocReadFormat a where
- newPandoc :: (PandocEffects effs, Member Pandocs effs) => Text -> Sem (ToPandoc ': effs) () -> Sem effs ()
- data NamedDoc a = NamedDoc {}
- module Knit.Effect.PandocMonad
- module Knit.Effect.PandocMonad
- type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs
- data LogSeverity
- = Diagnostic
- | Info
- | Warning
- | Error
- logAll :: [LogSeverity]
- nonDiagnostic :: [LogSeverity]
- logLE :: Member (Logger LogEntry) effs => LogSeverity -> Text -> Sem effs ()
- wrapPrefix :: Member PrefixLog effs => Text -> Sem effs a -> Sem effs a
- filteredLogEntriesToIO :: MonadIO (Sem effs) => [LogSeverity] -> Sem (Logger LogEntry ': (PrefixLog ': effs)) x -> Sem effs x
Knit
:: 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.
:: 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.
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
addColonnadeTextTable Source #
:: (PandocEffects effs, Member ToPandoc effs, Foldable f) | |
=> Colonnade Headed a Text | How to encode data as columns |
-> f a | collection of data |
-> Sem effs () |
Add a table given a Colonnade representation producing text
addColonnadeHtmlTable Source #
:: (PandocEffects effs, Member ToPandoc effs, Foldable f) | |
=> Attribute | Attributes of table Html element, currently unused by knit-haskell |
-> Colonnade Headed a Html | How to encode data as columns |
-> f a | collection of data |
-> Sem effs () |
Add a Blaze-Colonnade Html Table
addColonnadeCellTable Source #
:: (PandocEffects effs, Member ToPandoc effs, Foldable f) | |
=> Attribute | Attributes of table Html element, currently unused by knit-haskell |
-> Colonnade Headed a Cell | How to encode data as columns |
-> f a | collection of data |
-> Sem effs () |
Add a Blaze-Colonnade Cell Table
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
addHvega :: (PandocEffects effs, Member ToPandoc effs) => Text -> VegaLite -> Sem effs () Source #
Add hvega (via html). Requires html since vega-lite renders using javascript.
Output
data PandocWriterConfig Source #
PandocWriterConfig | |
|
pandocWriterToBlazeDocument Source #
:: 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
or a Sem
'[] a
value, which can be
consumed respectively by Sem
'[ Lift
m ] arun
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 Stringput
:: String ->Sem
r ()
methods.
By also adding a
Member
(Error
Bool) r
constraint on r
, we gain access to the
throw
:: Bool ->Sem
r acatch
::Sem
r a -> (Bool ->Sem
r a) ->Sem
r a
functions as well.
In this sense, a
constraint is
analogous to mtl's Member
(State
s) r
and should
be thought of as such. However, unlike mtl, a MonadState
s mSem
monad may have
an arbitrary number of the same effect.
For example, we can write a Sem
program which can output either
Int
s or Bool
s:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ) =>Sem
r () foo = dooutput
@Int 5output
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
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 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.
VegaSupport | Supported only for Html output. |
LatexSupport | Supported in Html output (via MathJax) and Latex output. |
Instances
data PandocWriteFormat a where Source #
Supported formats for writing current Pandoc
Instances
Show (PandocWriteFormat a) Source # | |
Defined in Knit.Effect.Pandoc showsPrec :: Int -> PandocWriteFormat a -> ShowS # show :: PandocWriteFormat a -> String # showList :: [PandocWriteFormat a] -> ShowS # |
data PandocReadFormat a where Source #
Supported formats for adding to current Pandoc
Instances
Show (PandocReadFormat a) Source # | |
Defined in Knit.Effect.Pandoc showsPrec :: Int -> PandocReadFormat a -> ShowS # show :: PandocReadFormat a -> String # showList :: [PandocReadFormat a] -> ShowS # |
:: (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 type to hold one named document of type a
.
Instances
Functor NamedDoc Source # | |
Foldable NamedDoc Source # | |
Defined in Knit.Effect.Docs 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 # elem :: Eq a => a -> NamedDoc a -> Bool # maximum :: Ord a => NamedDoc a -> a # minimum :: Ord a => NamedDoc a -> a # | |
Traversable NamedDoc Source # | |
module Knit.Effect.PandocMonad
module Knit.Effect.PandocMonad
type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs Source #
Constraint helper for LogEntry
type with prefixes
data LogSeverity Source #
Severity of message. Based on monad-logger.
Instances
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.