module Text.LaTeX.Monad (
LaTeXT
, LaTeX
, lx
, lxany
, lxw
, lxanyw
, nlx
, mlx
, reslx
, genlx , ungenlx
) where
import Control.Monad.Writer
import Data.Monoid
import GHC.Exts
import System.IO.Unsafe
import Text.LaTeX.Result
import Data.String.Combinators(fromShow)
type LaTeXT m a = WriterT Result m a
type LaTeX m = LaTeXT m ()
nlx :: Monad m => LaTeXT m a -> m Result
nlx = execWriterT
lx :: Monad m => Result -> LaTeX m
lx = tell
lxany :: (Monad m , Show a) => a -> LaTeX m
lxany = ungenlx . lxanyw
lxw :: Monad m => Result -> LaTeXT m a
lxw = genlx . lx
lxanyw :: (Monad m , Show b) => b -> LaTeXT m a
lxanyw = fromShow
mlx :: Monad m => m a -> LaTeXT m a
mlx = lift
reslx :: Monad m => (Result -> Result) -> (LaTeXT m a -> LaTeXT m a)
reslx = censor
instance Monad m => IsString (LaTeXT m a) where
fromString = lxw . toResult
instance Monad m => Show (LaTeXT m a) where
show _ = ""
instance Monad m => Eq (LaTeXT m a) where
_ == _ = error "(==): LaTeXT values can't be compared."
instance Monad m => Monoid (LaTeXT m a) where
mempty = ""
mappend = (>>)
genlx :: Monad m => LaTeX m -> LaTeXT m a
genlx = (>> return undefined)
ungenlx :: Monad m => LaTeXT m a -> LaTeX m
ungenlx = (>> return ())