HaTeX-3.4: The Haskell LaTeX library.

Safe HaskellNone

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.

Synopsis

LaTeXT writer

data LaTeXT m a Source

Instances

MonadTrans LaTeXT 
Monad m => Monad (LaTeXT m) 
Functor m => Functor (LaTeXT m) 
(Monad (LaTeXT m), MonadIO m) => MonadIO (LaTeXT m) 
Monad m => Eq (LaTeXT m a)

Warning: this instance only exist for the Num instance.

(Num (LaTeXT m a), Monad m) => Fractional (LaTeXT m a)

Division uses the LaTeX frac command.

Monad m => Num (LaTeXT m a)

Careful! Method signum is undefined. Don't use it!

Monad m => Show (LaTeXT m a)

Warning: this instance only exist for the Num instance.

Monad m => IsString (LaTeXT m a)

Be careful when using fromString over a LaTeXT value, the returned value of the computation is bottom (i.e. undefined).

Monad m => Monoid (LaTeXT m a)

mappend = >>.

(Monoid (LaTeXT m a), IsString (LaTeXT m a), Monad m) => LaTeXC (LaTeXT m a) 

type LaTeXT_ m = LaTeXT m ()Source

execLaTeXT :: Monad m => LaTeXT m a -> m LaTeXSource

This is the usual way to run the LaTeXT monad and obtain a LaTeX value.

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.

textell :: Monad m => LaTeX -> LaTeXT m ()Source

With textell you can append LaTeX values to the state of the LaTeXT monad.

rendertexM :: (Render a, Monad m) => a -> LaTeXT m ()Source

Just like rendertex, but with LaTeXT output.

 rendertexM = textell . rendertex

liftFun :: Monad m => (LaTeX -> LaTeX) -> LaTeXT m a -> LaTeXT m aSource

Lift a function over LaTeX values to a function acting over the state of a LaTeXT computation.

liftOp :: Monad m => (LaTeX -> LaTeX -> LaTeX) -> LaTeXT m a -> LaTeXT m b -> LaTeXT m bSource

Lift an operator over LaTeX values to an operator acting over the state of two LaTeXT computations.

Note: The returned value is the one returned by the second argument of the lifted operator.

Errors

merror :: Monad m => String -> LaTeXT m a -> LaTeXT m bSource

Function merror casts a value contained in a monad m to the bottom value of another type. If you try to evaluate this value, you will get an error message with the String passed as argument to merror.

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.

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.