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. 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:
- 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
- data KnitConfig sc ct k = KnitConfig {
- outerLogPrefix :: Maybe Text
- logIf :: LogSeverity -> Bool
- pandocWriterConfig :: PandocWriterConfig
- serializeDict :: SerializeDict sc ct
- persistCache :: forall r. (Member (Embed IO) r, MemberWithError (Error CacheError) r, LogWithPrefixesLE r) => InterpreterFor (Cache k ct) r
- defaultKnitConfig :: Maybe Text -> KnitConfig DefaultSerializer DefaultCacheData Text
- knitHtml :: (MonadIO m, Ord k, Show k) => KnitConfig c ct k -> Sem (KnitEffectDocStack c ct k m) () -> m (Either PandocError Text)
- knitHtmls :: (MonadIO m, Ord k, Show k) => KnitConfig c ct k -> Sem (KnitEffectDocsStack c ct k m) () -> m (Either PandocError [DocWithInfo PandocInfo Text])
- liftKnit :: Member (Embed m) r => m a -> Sem r a
- type KnitEffects r = (PandocEffects r, Members [UnusedId, Logger LogEntry, PrefixLog, Async, Error CacheError, Error SomeException, Error PandocError, Embed IO] r)
- type CacheEffects c ct k r = Members [SerializeEnv c ct, Cache k ct] r
- type CacheEffectsD r = CacheEffects DefaultSerializer DefaultCacheData Text r
- type KnitOne r = (KnitEffects r, Member ToPandoc r)
- type KnitMany r = (KnitEffects r, Member Pandocs r)
- type KnitBase m effs = (MonadIO m, Member (Embed m) effs)
- knitError :: Member (Error PandocError) r => Text -> Sem r a
- knitMaybe :: Member (Error PandocError) r => Text -> Maybe a -> Sem r a
- knitEither :: Member (Error PandocError) r => Either Text a -> Sem r a
- knitMapError :: forall e r a. KnitEffects r => (e -> Text) -> Sem (Error e ': r) a -> Sem r a
- module Knit.Report.Input.Table.Colonnade
- 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, Member UnusedId effs) => Maybe Text -> Maybe Text -> VegaLite -> Sem effs Text
- module Knit.Report.Input.Visualization.Diagrams
- module Knit.Report.Output
- pandocWriterToBlazeDocument :: PandocEffects effs => PandocWriterConfig -> Sem (ToPandoc ': effs) () -> Sem effs Html
- mindocOptionsF :: WriterOptions -> WriterOptions
- writeAllPandocResultsWithInfoAsHtml :: Text -> [DocWithInfo PandocInfo Text] -> IO ()
- writePandocResultWithInfoAsHtml :: Text -> DocWithInfo PandocInfo Text -> IO ()
- data Sem (r :: EffectRow) a
- type family Members (es :: [k]) (r :: [k]) where ...
- type Member (e :: k) (r :: [k]) = MemberNoError e r
- type Pandocs = Docs PandocInfo PandocWithRequirements
- data PandocInfo = PandocInfo {}
- data ToPandoc m r
- data Requirement
- data PandocWriteFormat a where
- data PandocReadFormat a where
- newPandoc :: (PandocEffects effs, Member Pandocs effs) => PandocInfo -> Sem (ToPandoc ': effs) () -> Sem effs ()
- data DocWithInfo i a = DocWithInfo {}
- module Knit.Effect.PandocMonad
- type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs
- type PrefixedLogEffectsLE = PrefixedLogEffects LogEntry
- data LogSeverity
- logAll :: LogSeverity -> Bool
- logDiagnostic :: LogSeverity -> Bool
- nonDiagnostic :: LogSeverity -> Bool
- logDebug :: Int -> LogSeverity -> Bool
- logLE :: Member (Logger LogEntry) effs => LogSeverity -> Text -> Sem effs ()
- wrapPrefix :: Member PrefixLog effs => Text -> Sem effs a -> Sem effs a
- filteredLogEntriesToIO :: MonadIO (Sem r) => (LogSeverity -> Bool) -> Sem (Logger LogEntry ': (PrefixLog ': r)) x -> Sem r x
- getNextUnusedId :: Member UnusedId r => Text -> Sem r Text
- type DefaultSerializer = Serialize
- type DefaultCacheData = Array Word8
- sequenceConcurrently :: forall t (r :: [(Type -> Type) -> Type -> Type]) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a))
- await :: forall (r :: [Effect]) a. MemberWithError Async r => Async a -> Sem r a
- async :: forall (r :: [Effect]) a. MemberWithError Async r => Sem r a -> Sem r (Async (Maybe a))
- module Knit.Report.Cache
Report Building
Configuraiton
data KnitConfig sc ct k Source #
Parameters for knitting. If possible, create this via, e.g.,
myConfig = (defaultKnitConfig $ Just "myCacheDir") { pandocWriterConfig = myConfig }
so that your code will still compile if parameters are added to this structure.
NB: the type parameters of this configuration specify the cache types:
sc :: Type -> Constraint
, wherec a
is the constraint to be satisfied for serializablea
.ct :: Type
, is the value type held in the in-memory cache.k :: Type
, is the key type of the cache.
The serializeDict
field holds functions for encoding (forall a. c a=> a -> ct
)
and decoding (forall a. c a => ct -> Either SerializationError a
).
The persistCache
field holds an interpreter for the persistence layer of
the cache. See AtomicCache
for examples of persistence layers.
If you want to use a different serializer ("binary" or "store") and/or a different type to hold cached values in-memory, you can set these fields accordingly.
KnitConfig | |
|
:: Maybe Text | Optional cache-directory. Defaults to ".knit-haskell-cache". |
-> KnitConfig DefaultSerializer DefaultCacheData Text | configuration |
Sensible defaults for a knit configuration.
Knit documents
:: (MonadIO m, Ord k, Show k) | |
=> KnitConfig c ct k | configuration |
-> Sem (KnitEffectDocStack c ct k m) () | computation producing a single document |
-> m (Either PandocError Text) | Resulting document or error, in base monad. Usually IO. |
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, Ord k, Show k) | |
=> KnitConfig c ct k | configuration |
-> Sem (KnitEffectDocsStack c ct k m) () | computation producing a list of documents |
-> m (Either PandocError [DocWithInfo PandocInfo Text]) | Resulting docs or error, in base monad, usually IO. |
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.
helpers
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 of embed
for convenience.
Constraints for knit-haskell actions (see examples)
type KnitEffects r = (PandocEffects r, Members [UnusedId, Logger LogEntry, PrefixLog, Async, Error CacheError, Error SomeException, Error PandocError, Embed IO] r) Source #
type CacheEffects c ct k r = Members [SerializeEnv c ct, Cache k ct] r Source #
Constraint alias for the effects we need to use the cache.
type CacheEffectsD r = CacheEffects DefaultSerializer DefaultCacheData Text r Source #
Constraint alias for the effects we need to use the default cache with Text
keys.
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.
Error combinators
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.
knitMaybe :: Member (Error PandocError) r => Text -> Maybe a -> Sem r a Source #
Throw on Nothing
with given message. This will emerge as a PandocSomeError
in order
to avoid complicating the error type.
knitEither :: Member (Error PandocError) r => Either Text a -> Sem r a Source #
Throw on Left
with message. This will emerge as a PandocSomeError
in order
to avoid complicating the error type.
knitMapError :: forall e r a. KnitEffects r => (e -> Text) -> Sem (Error e ': r) a -> Sem r a Source #
Map an error type, @e, into a PandocError
so it will be handled in this stack
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
:: (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
module Knit.Report.Output
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 given Pandoc to Blaze Html.
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
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 traditionally as an Either
, or instead
as (a significantly faster) IO
Exception
. These
interpretations (and others that you might add) may be used interchangeably
without needing to write any newtypes or Monad
instances. The only
change needed to swap interpretations is to change a call from
runError
to errorToIOFinal
.
The effect stack r
can contain arbitrary other monads inside of it. These
monads are lifted into effects via the Embed
effect. Monadic values can be
lifted into a Sem
via embed
.
Higher-order actions of another monad can be lifted into higher-order actions
of Sem
via the Final
effect, which is more powerful
than Embed
, but also less flexible to interpret.
A Sem
can be interpreted as a pure value (via run
) or as any
traditional Monad
(via runM
or runFinal
).
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.
Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:
>>>
:{
example :: Members '[State String, Error String] r => Sem r String example = do put "start" let throwing, catching :: Members '[State String, Error String] r => Sem r String throwing = do modify (++"-throw") throw "error" get catching = do modify (++"-catch") get catch @String throwing (\ _ -> catching) :}
when handling Error
first, state is preserved after error
occurs:
>>>
:{
example & runError & fmap (either id id) & evalState "" & runM & (print =<<) :} "start-throw-catch"
while handling State
first discards state in such cases:
>>>
:{
example & evalState "" & runError & fmap (either id id) & runM & (print =<<) :} "start-catch"
A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.
After all of your effects are handled, you'll be left with either
a
, a Sem
'[] a
, or a Sem
'[ Embed
m ] a
value, which can be consumed respectively by Sem
'[ Final
m ] arun
, runM
, and
runFinal
.
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
Monad (Sem f) | |
Functor (Sem f) | |
Member Fixpoint r => MonadFix (Sem r) | |
Defined in Polysemy.Internal | |
Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r) | Since: polysemy-1.1.0.0 |
Defined in Polysemy.Internal | |
Applicative (Sem f) | |
Member NonDet r => MonadPlus (Sem r) | Since: polysemy-0.2.1.0 |
Member NonDet r => Alternative (Sem r) | |
Member (Embed IO) r => MonadIO (Sem r) | This instance will only lift |
Defined in Polysemy.Internal |
type family Members (es :: [k]) (r :: [k]) where ... #
Makes constraints of functions that use multiple effects shorter by
translating single list of effects into multiple Member
constraints:
foo ::Members
'[Output
Int ,Output
Bool ,State
String ] r =>Sem
r ()
translates into:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ,Member
(State
String) r ) =>Sem
r ()
Since: polysemy-0.1.2.0
type Member (e :: k) (r :: [k]) = MemberNoError e r #
A proof that the effect e
is available somewhere inside of the effect
stack 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
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) | |
=> 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
.
Instances
Functor (DocWithInfo i) Source # | |
Defined in Knit.Effect.Docs fmap :: (a -> b) -> DocWithInfo i a -> DocWithInfo i b # (<$) :: a -> DocWithInfo i b -> DocWithInfo i a # | |
Foldable (DocWithInfo i) Source # | |
Defined in Knit.Effect.Docs fold :: Monoid m => DocWithInfo i m -> m # foldMap :: Monoid m => (a -> m) -> DocWithInfo i a -> 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 # | |
Defined in Knit.Effect.Docs 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) # |
module Knit.Effect.PandocMonad
type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs Source #
Constraint helper for LogEntry
type with prefixes
type PrefixedLogEffectsLE = PrefixedLogEffects LogEntry Source #
List of Logger effects for a prefixed log of type LogEntry
data LogSeverity Source #
Severity/importance of message.
Debug Int | Most detailed levels of logging. Int argument can be used adding fine distinctions between debug levels. |
Diagnostic | Minimal details about effects and what is being called. |
Info | Informational messages about progress of compuation or document knitting. |
Warning | Messages intended to alert the user to an issue in the computation or document production. |
Error | Likely unrecoverable issue in computation or document production. |
Instances
logAll :: LogSeverity -> Bool Source #
log everything.
logDiagnostic :: LogSeverity -> Bool Source #
log all but Debug
messages.
nonDiagnostic :: LogSeverity -> Bool Source #
log everything above Diagnostic
.
logDebug :: Int -> LogSeverity -> Bool Source #
log debug messages with level lower than or equal to the given Int
.
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 r) => (LogSeverity -> Bool) -> Sem (Logger LogEntry ': (PrefixLog ': r)) x -> Sem r x Source #
getNextUnusedId :: Member UnusedId r => Text -> Sem r Text Source #
Get an unused id with prefix as specified. Useful for figures, etc.
type DefaultSerializer = Serialize Source #
type-alias for default Serializer
type DefaultCacheData = Array Word8 Source #
type-alias for default in-memory storage type.
sequenceConcurrently :: forall t (r :: [(Type -> Type) -> Type -> Type]) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) #
Perform a sequence of effectful actions concurrently.
Since: polysemy-1.2.2.0
module Knit.Report.Cache