{-# OPTIONS_GHC -XOverloadedStrings #-}

-- | This is the main module of the HaTeX library.
--   For a complete understanding of this package, read \"/HaTeX, a monadic perspective of LaTeX/\"
--   at the HaTeX home page: <http://ddiaz.asofilak.es/packages/HaTeX>.
module Text.LaTeX 
     ( -- * How to use HaTeX
       -- ** About HaTeX
       -- $guide0

       -- ** Introduction
       -- $guide1

       -- ** LaTeX file structure
       -- $guide2

       -- ** A simple example
       -- $guide3

       -- ** Enriching your text
       -- $guide4

       -- ** Performing monadic computations
       -- $guide5

       -- ** Adding sections
       -- $guide6

       -- * HaTeX related functions
       hatex
     , hatexVersion
       -- * Exporting to /.tex/
     , render
     , export
       -- * Re-exports
     , module Text.LaTeX.Result
     , module Text.LaTeX.Monad
     , module Text.LaTeX.Define
     , module Text.LaTeX.Arguments
     , module Text.LaTeX.Packages
     , module Text.LaTeX.Commands
     , module Text.LaTeX.Macro
       -- * Data.String re-export
     , module Data.String
     ) where

import Text.LaTeX.Monad hiding (genlx,ungenlx)
import Text.LaTeX.Commands
import Text.LaTeX.Arguments
import Text.LaTeX.Define
import Text.LaTeX.Packages
import Text.LaTeX.Result
import Text.LaTeX.Macro
--
import Data.String
--
import System.FilePath (takeExtension)
import Control.Monad.Trans (MonadIO (..))

-- | HaTeX nice word.
hatex :: Monad m => LaTeX m
hatex = makebox [] [] $ do "H"
                           raisebox (ex (-0.51)) [] [] $
                             makebox [0.5 >> width] [] "A"
                           tex

-- | Your HaTeX version.
hatexVersion :: Monad m => LaTeX m
hatexVersion = do textbf "2" ; ".1.2"

-- | Render 'LaTeX' to 'String'.
render :: Monad m => LaTeX m -> m String
render = (>>= return . fromResult) . nlx

-- | Export the 'Result' of a 'LaTeX' sequence in a /.tex/ file.
export :: MonadIO m =>
     LaTeX m  -- ^ 'LaTeX' to export.
  -> FilePath -- ^ Path of export.
  -> m ()
export x fp = do y <- nlx x
                 let z = fromResult y
                 if takeExtension fp == ".tex" then liftIO $ writeFile fp z
                                               else liftIO $ writeFile (fp ++ ".tex") z

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

{- $guide0
HaTeX is a package which lets you to write LaTeX code from Haskell.

HaTeX page: <http://ddiaz.asofilak.es/packages/HaTeX>

Here a link to the package in Hackage: <http://hackage.haskell.org/package/HaTeX>
-}

-- Introduction

{- $guide1
If you know how to use LaTeX, you will easily understand how to use HaTeX.
Otherwise, you will need to read well the documentation.

A first step may be to know the LaTeX file structure.
-}

-- LaTeX file structure

{- $guide2
A LaTeX file has two parts:

- A /preamble/ where you define general settings (document class, page style, use of extern packages, ...) of your document.

- The document's content.
-}

-- A simple example

{- $guide3
We're going to write an example, the best for understanding.

*  Function 'documentclass' is used for determining if our document is an 'article', a 'book', a 'report', etc.

*  Function 'author' is used for specify document's authory.

*  Function 'title' for document's title.

Then, with this three functions, we will define a preamble in the 'LaTeX' monad.
'LaTeX' is a writer monad that concatenates the text generated by the programmer.
Usually, the text is generated simply writing it, or by functions.

> example = do documentclass [] article
>              author "Daniel Diaz"
>              title "Example"

The first argument of 'documentclass' is used for change certain settings of the class.
For example, you can set the document's main font size to 12pt, writing:

> documentclass [pt 12] article

Or set paper size to A4:

> documentclass [pt 12,a4paper] article

Now, I will write a content:

> hello = "Hello, world!"

To insert the content into the document, we have the function 'document'. Completing our first example:

> example = do documentclass [] article
>              author "Daniel Diaz"
>              title "Example"
>              document $ do maketitle
>                            hello

/Note: /'maketitle'/ doesn't work in some document classes./

At first glance, it seems that 'author', 'title' or 'document' receive a 'String' as argument.
Really, they require a 'LaTeX' argument. 'LaTeX' is the type that represents texts in HaTeX.
So, I recommend to use Overloaded Strings
(See <http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/type-class-extensions.html#overloaded-strings>).
-}

-- Enriching your text

{- $guide4
There are numerous functions to enrich your document.
One feature is change your font format. For example, in:

> texttt "Hello!"

'texttt' sets as monospaced font his content. Or composing:

> texttt $ textbf "Hello!"

'textbf' sets as bold font the monospaced font of '"Hello!"'.

If you only want '"ll"' with bold format:

> texttt $ do "He"
>             textbf "ll"
>             "o!"

Applying the function to only part of the text, we achieve modify just that part.
-}

-- Performing monadic computations

{- $guide5
All computations in HaTeX take place in the 'LaTeXT' monadic transformer.
To includes a monadic computation, use 'mlx'.

> gtime = do t <- mlx getClockTime
>            ...

-}

-- Adding sections

{- $guide6
Commands to adding sections are included in Text.LaTeX.Commands. Examples are 'section' or 'paragraph'. 

If you want sections without number, use 'section_'. This also avoid showing the section into the table of contents. 

If you want title of section to be different in the context than in the table of contents, use 'sectiontab'.
-}