module Text.LaTeX.Monad (
    -- * @LaTeX@ Monad
    LaTeXM
  , LaTeX
    -- * Basic functions over @LaTeX@ Monad
  , lx
  , lxany
  , lxw
  , lxanyw
  , nlx
  , iolx
  , reslx
    -- * Generalizing
  , 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)

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

-- | 'LaTeXM' is the monad that represents LaTeX code.
-- Bind operator plays as concatenator.
--
-- Instances of 'LaTeXM' @a@:
--
-- * 'IsString'
--
-- * 'Show' (unsafe)
--
-- * 'Eq' (unsafe)
--
-- * 'Num'
--
-- * 'Fractional'
--
-- * 'Floating'
--
-- * 'Monoid'
type LaTeXM a = WriterT Result IO a

type LaTeX = LaTeXM ()

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

-- | Run a 'LaTeXM' computation, returning his result.
nlx :: LaTeXM a -> IO Result
nlx = execWriterT

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

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

-- | Write anything of 'Show' class.
lxany :: Show a => a -> LaTeX
lxany = ungenlx . lxanyw

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

-- | Like 'lxany', but returns an undefined value.
lxanyw :: Show b => b -> LaTeXM a
lxanyw = fromShow

-- | Performs an 'IO' computation, returning his value in the 'LaTeXM' monad.
iolx :: IO a -> LaTeXM a
iolx = liftIO

-- | Transform a 'Result' modifier in a 'LaTeXM' modifier.
reslx :: (Result -> Result) -> (LaTeXM a -> LaTeXM a)
reslx = censor

instance IsString (LaTeXM a) where
 fromString = lxw . toResult

instance Show (LaTeXM a) where
 show = fromResult . unsafePerformIO . nlx

instance Eq (LaTeXM a) where
 x == y = show x == show y

instance Monoid (LaTeXM a) where
 mempty = ""
 mappend = (>>)

-- Generalizing

genlx :: LaTeX -> LaTeXM a
genlx = (>> return undefined)

ungenlx :: LaTeXM a -> LaTeX
ungenlx = (>> return ())