-----------------------------------------------------------------------------
-- |
-- Module      :  Text.CSL
-- Copyright   :  (c) Andrea Rossato
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Andrea Rossato <andrea.rossato@unitn.it>
-- Stability   :  unstable
-- Portability :  unportable
--
-- /citeproc-hs/ is a library for automatically formatting
-- bibliographic reference citations into a variety of styles using a
-- macro language called Citation Style Language (CSL). More details
-- on CSL can be found here: <http://xbiblio.sourceforge.net/>.
--
-- This module documents and exports the library API.
--
-----------------------------------------------------------------------------

module Text.CSL
    ( -- * Introduction
      -- $intro

      -- * Overview: A Simple Example
      -- $overview

      -- * Reading Bibliographic Databases
      readBiblioFile
    , readModsFile
    , readModsColletionFile

    -- ** Reference Representation
    , Reference (..)
    , getReference

    -- * CSL Parser, Representation, and Processing
    , readCSLFile

    -- ** The Style Types
    , Style (..)
    , Citation (..)
    , Bibliography (..)

    -- ** High Level Processing
    , citeproc
    , processCitations
    , processBibliography
    , BiblioData (..)

    -- * The output and the rendering functions
    , FormattedOutput (..)
    , renderPlain
    , renderPlainStrict
    , renderPandoc
    , renderPandoc'
    , renderPandocStrict
    ) where

import Text.CSL.Parser
import Text.CSL.Proc
import Text.CSL.Reference
import Text.CSL.Style
import Text.CSL.Input.Bibutils
import Text.CSL.Input.MODS
import Text.CSL.Output.Pandoc
import Text.CSL.Output.Plain


-- $intro
--
-- /citeproc-hs/ provides functions for reading bibliographic
-- databases, for reading and parsing CSL files and for generating
-- citations in an internal format, 'FormattedOutput', that can be
-- easily rendered into different final formats. At the present time
-- only 'Pandoc' and plain text rendering functions are provided by
-- the library.
--
-- The library also provides a wrapper around hs-bibutils, the Haskell
-- bindings to Chris Putnam's bibutils, a library that interconverts
-- between various bibliography formats using a common MODS-format XML
-- intermediate.
--
-- For more information about hs-bibutils see here:
-- <http://code.haskell.org/hs-bibutils/>.
--
-- /citeproc-hs/ can natively read MODS formatted bibliographic
-- databases.

-- $overview
--
-- The following example assumes you have properly installed
-- hs-bibutils. If not you can use bibutils to convert the following
-- bibtex bibliographic database into a MODS collection.
--
-- Suppose you have a small bibliographic database, like this one:
--
-- > @Book{Rossato2005,
-- > author="Andrea Rossato",
-- > title="My First Book",
-- > year="2005"
-- > }
-- >
-- > @Book{Rossato2006,
-- > author="Andrea Rossato",
-- > title="My Second Book",
-- > year="2006"
-- > }
-- >
-- > @Book{Caso2007,
-- > author="Roberto Caso",
-- > title="Roberto's Book",
-- > year="2007"
-- > }
--
-- Save it as @mybibdb.bib@.
--
-- Then you can grab one of the CSL style developed by the Zotero
-- community. Suppose this one:
--
-- <http://www.zotero.org/styles/apa>
--
-- saved locally as @apa.csl@.
--
-- This would be a simple program that formats a list of citations
-- according to that style:
--
-- > import Text.CSL
-- >
-- > main :: IO ()
-- > main = do
-- >   m <- readBiblioFile "mybibdb.bib" "bibtex"
-- >   s <- readCSLFile "apa.csl"
-- >   let result = citeproc s m $ [[("Caso2007","p. 10"),("Rossato2005","p. 10"),("Rossato2006","p. 15")]]
-- >   putStrLn . unlines . map (renderPlainStrict) . citations $ result
--
-- The result would be:
--
-- > (Caso, 2007, p. 10; Rossato, 2005, p. 10, 2006, p. 15)