-- Author:     Andy Stewart <lazycat.manatee@gmail.com>
-- Maintainer: Andy Stewart <lazycat.manatee@gmail.com>
-- 
-- Copyright (C) 2010 Andy Stewart, all rights reserved.
-- 
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- any later version.
-- 
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
-- 
-- You should have received a copy of the GNU General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

{-# LANGUAGE DeriveDataTypeable #-}
module Manatee.Extension.PdfViewer.PdfBuffer where

import Control.Applicative
import Control.Concurrent.STM 
import Control.Monad
import DBus.Client hiding (Signal)
import Data.ByteString.UTF8
import Data.Maybe
import Data.Typeable
import Graphics.UI.Gtk.Poppler.Document hiding (PageMode)
import Graphics.UI.Gtk.Poppler.Page
import Manatee.Core.Types
import Manatee.Extension.PdfViewer.PageMode
import Manatee.Toolkit.Gio.Gio

data PdfBuffer =
    PdfBuffer {pdfBufferPath                :: TVar String
              ,pdfBufferClient              :: Client
              ,pdfBufferPageId              :: PageId
              ,pdfBufferMode                :: PageMode
              ,pdfBufferDocument            :: Document
              ,pdfBufferNPages              :: Int
              ,pdfBufferPageSize            :: (Double, Double)
              }
    deriving Typeable

-- | New pdf viewer buffer.
pdfBufferNew :: String -> Client -> PageId -> IO PdfBuffer
pdfBufferNew path client pageId = do
  -- Get document.
  document <- liftM (fromMaybe (error $ "pdfBufferNew: error when open file " ++ filepath)) 
                    (documentNewFromFile ("file://" ++ filepath) Nothing)
  -- Get page number.
  nPages   <- documentGetNPages document

  -- Get page size.
  size <- pageGetSize =<< documentGetPage document 0
  
  -- Build buffer.
  PdfBuffer <$> newTVarIO path
            <*> pure client
            <*> pure pageId
            <*> pure pdfMode
            <*> pure document
            <*> pure nPages
            <*> pure size
      where filepath = filepathGetDisplayName (fromString path)