HaTeX-3.22.4.1: The Haskell LaTeX library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LaTeX.Base.Writer

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 :: 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.

Synopsis

LaTeXT writer

data LaTeXT m a Source #

WriterT monad transformer applied to LaTeX values.

Instances

Instances details
MonadTrans LaTeXT Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

lift :: Monad m => m a -> LaTeXT m a #

MonadIO m => MonadIO (LaTeXT m) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

liftIO :: IO a -> LaTeXT m a #

Applicative f => Applicative (LaTeXT f) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

pure :: a -> LaTeXT f a #

(<*>) :: LaTeXT f (a -> b) -> LaTeXT f a -> LaTeXT f b #

liftA2 :: (a -> b -> c) -> LaTeXT f a -> LaTeXT f b -> LaTeXT f c #

(*>) :: LaTeXT f a -> LaTeXT f b -> LaTeXT f b #

(<*) :: LaTeXT f a -> LaTeXT f b -> LaTeXT f a #

Functor f => Functor (LaTeXT f) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

fmap :: (a -> b) -> LaTeXT f a -> LaTeXT f b #

(<$) :: a -> LaTeXT f b -> LaTeXT f a #

Monad m => Monad (LaTeXT m) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

(>>=) :: LaTeXT m a -> (a -> LaTeXT m b) -> LaTeXT m b #

(>>) :: LaTeXT m a -> LaTeXT m b -> LaTeXT m b #

return :: a -> LaTeXT m a #

(Monad m, a ~ ()) => LaTeXC (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

liftListL :: ([LaTeX] -> LaTeX) -> [LaTeXT m a] -> LaTeXT m a Source #

(Monad m, a ~ ()) => IsString (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

fromString :: String -> LaTeXT m a #

(Monad m, Monoid a) => Monoid (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

mempty :: LaTeXT m a #

mappend :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

mconcat :: [LaTeXT m a] -> LaTeXT m a #

(Applicative m, Semigroup a) => Semigroup (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

(<>) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

sconcat :: NonEmpty (LaTeXT m a) -> LaTeXT m a #

stimes :: Integral b => b -> LaTeXT m a -> LaTeXT m a #

(Monad m, a ~ ()) => Floating (LaTeXT m a) Source #

Undefined methods: asinh, atanh and acosh. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Defined in Text.LaTeX.Base.Math

Methods

pi :: LaTeXT m a #

exp :: LaTeXT m a -> LaTeXT m a #

log :: LaTeXT m a -> LaTeXT m a #

sqrt :: LaTeXT m a -> LaTeXT m a #

(**) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

logBase :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

sin :: LaTeXT m a -> LaTeXT m a #

cos :: LaTeXT m a -> LaTeXT m a #

tan :: LaTeXT m a -> LaTeXT m a #

asin :: LaTeXT m a -> LaTeXT m a #

acos :: LaTeXT m a -> LaTeXT m a #

atan :: LaTeXT m a -> LaTeXT m a #

sinh :: LaTeXT m a -> LaTeXT m a #

cosh :: LaTeXT m a -> LaTeXT m a #

tanh :: LaTeXT m a -> LaTeXT m a #

asinh :: LaTeXT m a -> LaTeXT m a #

acosh :: LaTeXT m a -> LaTeXT m a #

atanh :: LaTeXT m a -> LaTeXT m a #

log1p :: LaTeXT m a -> LaTeXT m a #

expm1 :: LaTeXT m a -> LaTeXT m a #

log1pexp :: LaTeXT m a -> LaTeXT m a #

log1mexp :: LaTeXT m a -> LaTeXT m a #

(Monad m, a ~ ()) => Num (LaTeXT m a) Source #

Careful! Method signum is undefined. Don't use it! This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Defined in Text.LaTeX.Base.Math

Methods

(+) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

(-) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

(*) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

negate :: LaTeXT m a -> LaTeXT m a #

abs :: LaTeXT m a -> LaTeXT m a #

signum :: LaTeXT m a -> LaTeXT m a #

fromInteger :: Integer -> LaTeXT m a #

(Monad m, a ~ ()) => Fractional (LaTeXT m a) Source #

Division uses the LaTeX frac command. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Defined in Text.LaTeX.Base.Math

Methods

(/) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

recip :: LaTeXT m a -> LaTeXT m a #

fromRational :: Rational -> LaTeXT m a #

runLaTeXT :: LaTeXT m a -> m (a, LaTeX) Source #

Running a LaTeXT computation returns the final LaTeX value.

execLaTeXT :: Monad m => LaTeXT m a -> m LaTeX Source #

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

execLaTeXT = liftM snd . runLaTeXT

If anExample is defined as above (at the top of this module documentation), use the following to get the LaTeX value generated out.

myLaTeX :: Monad m => m LaTeX
myLaTeX = execLaTeXT anExample

Synonyms

type LaTeXT_ m = LaTeXT m () Source #

Type synonym for empty LaTeXT computations.

type LaTeXM = LaTeXT Identity Source #

The LaTeXT monad transformed applied to Identity.

runLaTeXM :: LaTeXM a -> (a, LaTeX) Source #

A particular case of runLaTeXT.

runLaTeXM = runIdentity . runLaTeXT

execLaTeXM :: LaTeXM a -> LaTeX Source #

A particular case of execLaTeXT.

execLaTeXM = runIdentity . execLaTeXT

Utils

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.

extractLaTeX_ :: Monad m => LaTeXT m a -> LaTeXT m LaTeX Source #

Executes a LaTeXT computation, embedding it again in the LaTeXT monad.

extractLaTeX_ = liftM snd . extractLaTeX

This function was heavily used in the past by HaTeX-meta to generate those .Monad modules. The current purpose is to implement the LaTeXC instance of LaTeXT, which is closely related.

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 a Source #

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 b Source #

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.

mapLaTeXT :: (m (a, LaTeX) -> m (a, LaTeX)) -> LaTeXT m a -> LaTeXT m a Source #

A helper function for building monad transformers, e.g.

instance MonadReader r m => MonadReader r (LaTeXT m) where
  ask = lift ask
  local = mapLaTeXT . local

This declaration could be included here, but it would add a dependency on mtl.

Re-exports

lift :: (MonadTrans t, Monad m) => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3