{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Text.LaTeX.Base.Writer ( -- * @LaTeXT@ writer LaTeXT , LaTeXT_ , runLaTeXT , execLaTeXT , extractLaTeX , extractLaTeX_ , textell ) where import Control.Monad.Writer import Control.Applicative import Data.String -- import Text.LaTeX.Base.Syntax import Text.LaTeX.Base.Render -- | Newtype wrapper over the 'WriterT' monad transformer, with 'LaTeX' -- as writer state. newtype LaTeXT m a = LaTeXT { unwrapLaTeXT :: WriterT LaTeX m a } deriving (Functor,Applicative,Monad,MonadIO) type LaTeXT_ m = LaTeXT m () runLaTeXT :: LaTeXT m a -> m (a,LaTeX) runLaTeXT = runWriterT . unwrapLaTeXT -- | This is the usual way to run the 'LaTeXT' monad -- and obtain a 'LaTeX' value. execLaTeXT :: Functor m => LaTeXT m a -> m LaTeX execLaTeXT = fmap snd . runLaTeXT -- | This function run a 'LaTeXT' computation, -- lifting the result again in the monad. extractLaTeX :: Monad m => LaTeXT m a -> LaTeXT m (a,LaTeX) extractLaTeX = LaTeXT . lift . runLaTeXT extractLaTeX_ :: Monad m => LaTeXT m a -> LaTeXT m LaTeX extractLaTeX_ = (>>= return . snd) . LaTeXT . lift . runLaTeXT -- | With 'textell' you can append 'LaTeX' values to the -- state of the 'LaTeXT' monad. textell :: Monad m => LaTeX -> LaTeXT m () textell = LaTeXT . tell -- Overloaded Strings instance Monad m => IsString (LaTeXT m a) where fromString = (>> return undefined) . textell . fromString