{-# LANGUAGE DeriveDataTypeable #-}

{-# LINE 2 "./Graphics/UI/Gtk/Poppler/Poppler.chs" #-}
-- GIMP Toolkit (GTK) Binding for Haskell: binding to poppler -*-haskell-*-
--
-- Author : Andy Stewart
-- Created: 18-Jun-2010
--
-- Copyright (c) 2010 Andy Stewart
--
-- This library is free software: you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public License
-- as published by the Free Software Foundation, either version 3 of
-- the License, or (at your option) any later version.
--
-- This library 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
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this program. If not, see
-- <http:
--
-- POPPLER, the C library which this Haskell library depends on, is
-- available under LGPL Version 2. The documentation included with
-- this library is based on the original POPPLER documentation.
--
-- | Maintainer : gtk2hs-devel@lists.sourceforge.net
-- Stability : alpha
-- Portability : portable (depends on GHC)
module Graphics.UI.Gtk.Poppler.Poppler (
-- * Types
    Backend(..),

-- * Methods
    getBackend,
    getVersion,
    ) where

import Control.Monad
import Data.Typeable
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GObject
import System.Glib.UTFString
import Graphics.UI.Gtk.Poppler.Enums


{-# LINE 49 "./Graphics/UI/Gtk/Poppler/Poppler.chs" #-}

-- | Returns the backend compiled into the poppler library.
getBackend :: IO Backend
getBackend =
  liftM (toEnum . fromIntegral) $ poppler_get_backend
{-# LINE 54 "./Graphics/UI/Gtk/Poppler/Poppler.chs" #-}

-- | Returns the version of poppler in use. This result is not to be freed.
getVersion :: IO String
getVersion =
   poppler_get_version >>= peekUTFString

foreign import ccall safe "poppler_get_backend"
  poppler_get_backend :: (IO CInt)

foreign import ccall safe "poppler_get_version"
  poppler_get_version :: (IO (Ptr CChar))