Safe Haskell | Safe-Inferred |
---|
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 :: LaTeXT IO () anotherExample = lift (readFileTex "foo") >>= verbatim
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.
Another thing you should know about the LaTeX Writer Monad. Don't try to get values
from computations with no results (like raw foo
).
- data LaTeXT m a
- type LaTeXT_ m = LaTeXT m ()
- runLaTeXT :: Monad m => LaTeXT m a -> m (Either String 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 b -> LaTeXT m b
- throwError :: Monad m => String -> 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
- liftIO :: MonadIO m => forall a. IO a -> m a
LaTeXT
writer
MonadTrans LaTeXT | |
Monad m => Monad (LaTeXT m) | |
Functor f => Functor (LaTeXT f) | |
Applicative f => Applicative (LaTeXT f) | |
MonadIO m => MonadIO (LaTeXT m) | |
Monad m => Eq (LaTeXT m a) | Warning: this instance only exists for the |
Monad m => Floating (LaTeXT m a) | |
Monad m => Fractional (LaTeXT m a) | Division uses the LaTeX |
Monad m => Num (LaTeXT m a) | Careful! Method |
Monad m => Show (LaTeXT m a) | Warning: this instance only exists for the |
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 m ()Source
Errors
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.