{-# LANGUAGE DeriveDataTypeable #-}

{-# LINE 2 "./Graphics/UI/Gtk/Poppler/Action.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.Action (
-- * Types,
    Action,
    Dest,

-- * Methods
    actionCopy,
    destCopy,
    makeNewAction,
    makeNewDest,
    ) where

import Control.Monad
import Data.Typeable
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GList
import System.Glib.GError
import System.Glib.GObject
import System.Glib.UTFString
import Graphics.UI.Gtk.Poppler.Enums
import Graphics.UI.Gtk.Poppler.Types
{-# LINE 52 "./Graphics/UI/Gtk/Poppler/Action.chs" #-}


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

newtype Action = Action (ForeignPtr (Action))
{-# LINE 56 "./Graphics/UI/Gtk/Poppler/Action.chs" #-}

makeNewAction :: Ptr Action -> IO Action
makeNewAction rPtr = do
  action <- newForeignPtr rPtr action_free
  return (Action action)

foreign import ccall unsafe "&poppler_action_free"
  action_free :: FinalizerPtr Action

newtype Dest = Dest (ForeignPtr (Dest))
{-# LINE 66 "./Graphics/UI/Gtk/Poppler/Action.chs" #-}

makeNewDest :: Ptr Dest -> IO Dest
makeNewDest rPtr = do
  dest <- newForeignPtr rPtr dest_free
  return (Dest dest)

foreign import ccall unsafe "&poppler_dest_free"
  dest_free :: FinalizerPtr Dest

-- | Copies action, creating an identical 'Action'.
actionCopy :: Action -> IO Action
actionCopy action =
  (\(Action arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_action_copy argPtr1) action
  >>= makeNewAction

-- | Copies dest, creating an identical 'Dest'.
destCopy :: Dest -> IO Dest
destCopy dest =
  (\(Dest arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_dest_copy argPtr1) dest
  >>= makeNewDest

foreign import ccall safe "poppler_action_copy"
  poppler_action_copy :: ((Ptr Action) -> (IO (Ptr Action)))

foreign import ccall safe "poppler_dest_copy"
  poppler_dest_copy :: ((Ptr Dest) -> (IO (Ptr Dest)))