{-# LANGUAGE OverloadedStrings,TypeSynonymInstances #-}

module Text.LaTeX.Monad (
    -- * @LaTeX@ Monad
    LaTeXT
  , LaTeX
    -- * Basic functions over @LaTeX@ Monad
  , lx
  , lxany
  , lxw
  , lxanyw
  , nlx
  , mlx
  , reslx
    -- * Generalizing
  , genlx , ungenlx
  ) where

import Control.Monad.Writer
import Data.Monoid
import Data.String
import System.IO.Unsafe
import Text.LaTeX.Result

import Data.String.Combinators(fromShow)

----------------------------

-- | 'LaTeXT' is the monadic transformer that represents LaTeX code.
-- Bind operator plays as concatenator.
--
-- Instances of 'LaTeXT':
--
-- * 'IsString'
--
-- * 'Num'
--
-- * 'Fractional'
--
-- * 'Floating'
--
-- * 'Monoid'
type LaTeXT m a = WriterT Result m a

type LaTeX m = LaTeXT m ()

----------------------------
-- Running the Monad

-- | Run a 'LaTeXT' computation.
nlx :: Monad m => LaTeXT m a -> m Result
nlx = execWriterT

----------------------------

-- | Write a result.
lx :: Monad m => Result -> LaTeX m
lx = tell

-- | Write anything of 'Show' class.
lxany :: (Monad m , Show a) => a -> LaTeX m
lxany = ungenlx . lxanyw

-- | Like 'lx', but returns an undefined value.
lxw :: Monad m => Result -> LaTeXT m a
lxw = genlx . lx

-- | Like 'lxany', but returns an undefined value.
lxanyw :: (Monad m , Show b) => b -> LaTeXT m a
lxanyw = fromShow

-- | Performs a monadic computation, returning his value in the 'LaTeXT' monad.
mlx :: Monad m => m a -> LaTeXT m a
mlx = lift

-- | Transform a 'Result' modifier in a 'LaTeXT' modifier.
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 = (>>)

-- Generalizing

genlx :: Monad m => LaTeX m -> LaTeXT m a
genlx = (>> return undefined)

ungenlx :: Monad m => LaTeXT m a -> LaTeX m
ungenlx = (>> return ())