| Safe Haskell | None |
|---|
Text.LaTeX.Base.Writer
Contents
Description
The writer monad applied to LaTeX values. Useful to compose LaTeX values
using the do notation:
anExample :: Monad m => LaTeXT m ()
anExample = do
documentclass [] article
author "Daniel Monad"
title "LaTeX and do notation"
document $ do
maketitle
section "Some words"
"Using " ; texttt "do" ; " notation "
"you avoid many ocurrences of the "
texttt "(<>)" ; " operator and a lot of "
"parentheses. With the cost of a monad."
Since LaTeXT is a monad transformer, you can do also:
anotherExample :: Monad m => LaTeXT m () anotherExample = lift (readFile "foo") >>= verbatim . fromString
This way, it is easy (without carrying arguments) to include IO outputs in the LaTeX document, like files, times or random objects.
Another approach could be to have custom counters, label management or any other user-defined feature.
Of course, you can always use the simpler interface provided by the plain LaTeX type.
- data LaTeXT m a
- type LaTeXT_ m = LaTeXT m ()
- runLaTeXT :: LaTeXT m a -> m (a, LaTeX)
- execLaTeXT :: Monad m => LaTeXT m a -> m LaTeX
- execLaTeXTWarn :: Monad m => LaTeXT m a -> m (LaTeX, [Warning])
- extractLaTeX :: Monad m => LaTeXT m a -> LaTeXT m (a, LaTeX)
- extractLaTeX_ :: Monad m => LaTeXT m a -> LaTeXT m LaTeX
- textell :: Monad m => LaTeX -> LaTeXT m ()
- rendertexM :: (Render a, Monad m) => a -> LaTeXT_ m
- liftFun :: Monad m => (LaTeX -> LaTeX) -> LaTeXT m a -> LaTeXT m a
- liftOp :: Monad m => (LaTeX -> LaTeX -> LaTeX) -> LaTeXT m a -> LaTeXT m a -> LaTeXT m a
- merror :: Monad m => String -> LaTeXT m a -> LaTeXT m b
- lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
LaTeXT writer
Instances
| MonadTrans LaTeXT | |
| Monad m => Monad (LaTeXT m) | |
| Functor m => Functor (LaTeXT m) | |
| Applicative m => Applicative (LaTeXT m) | |
| MonadIO m => MonadIO (LaTeXT m) | |
| Monad m => IsString (LaTeXT m a) | Be careful when using |
| Monad m => Monoid (LaTeXT m a) | |
| Monad m => LaTeXC (LaTeXT m a) |
execLaTeXT :: Monad m => LaTeXT m a -> m LaTeXSource
execLaTeXTWarn :: Monad m => LaTeXT m a -> m (LaTeX, [Warning])Source
Version of execLaTeXT with possible warning messages.
This function applies checkAll to the LaTeX output.
extractLaTeX :: Monad m => LaTeXT m a -> LaTeXT m (a, LaTeX)Source
This function run a LaTeXT computation,
lifting the result again in the monad.
rendertexM :: (Render a, Monad m) => a -> LaTeXT_ mSource
Re-export
lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
Lift a computation from the argument monad to the constructed monad.