Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data LaTeXT m a
- runLaTeXT :: LaTeXT m a -> m (a, LaTeX)
- execLaTeXT :: Monad m => LaTeXT m a -> m LaTeX
- type LaTeXT_ m = LaTeXT m ()
- type LaTeXM = LaTeXT Identity
- runLaTeXM :: LaTeXM a -> (a, LaTeX)
- execLaTeXM :: LaTeXM a -> 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
- mapLaTeXT :: (m (a, LaTeX) -> m (a, LaTeX)) -> LaTeXT m a -> LaTeXT m a
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- liftIO :: MonadIO m => IO a -> m a
LaTeXT
writer
Instances
Synonyms
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.
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
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
, we would have ended up with this error:liftIO
• 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
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3