{-# LANGUAGE DeriveDataTypeable #-}

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

-- * Methods
    layerGetTitle,
    layerIsVisible,
    layerShow,
    layerHide,
    layerIsParent,
    layerGetRadioButtonGroupId,
    ) 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 54 "./Graphics/UI/Gtk/Poppler/Layer.chs" #-}


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

-- | Returns the name of the layer suitable for presentation as a title in a viewer's GUI
layerGetTitle :: LayerClass layer => layer
 -> IO String -- ^ returns a string containing the title of the layer
layerGetTitle layer =
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_get_title argPtr1) (toLayer layer)
  >>= peekUTFString

-- | Returns whether layer is visible
layerIsVisible :: LayerClass layer => layer
 -> IO Bool -- ^ returns 'True' if layer is visible
layerIsVisible layer =
  liftM toBool $
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_is_visible argPtr1) (toLayer layer)

-- | Shows layer
layerShow :: LayerClass layer => layer -> IO ()
layerShow layer =
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_show argPtr1) (toLayer layer)

-- | Hides layer. If layer is the parent of other nested layers, such layers will be also hidden and will
-- be blocked until layer is shown again
layerHide :: LayerClass layer => layer -> IO ()
layerHide layer =
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_hide argPtr1) (toLayer layer)

-- | Returns whether layer is parent of other nested layers.
layerIsParent :: LayerClass layer => layer
 -> IO Bool -- ^ returns 'True' if layer is parent
layerIsParent layer =
  liftM toBool $
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_is_parent argPtr1) (toLayer layer)

-- | Returns the numeric ID the radio button group associated with layer.
layerGetRadioButtonGroupId :: LayerClass layer => layer
 -> IO Int -- ^ returns the ID of the radio button group associated with layer, or 0 if the layer is not associated to any radio button
layerGetRadioButtonGroupId layer =
  liftM fromIntegral $
  (\(Layer arg1) -> withForeignPtr arg1 $ \argPtr1 ->poppler_layer_get_radio_button_group_id argPtr1) (toLayer layer)

foreign import ccall safe "poppler_layer_get_title"
  poppler_layer_get_title :: ((Ptr Layer) -> (IO (Ptr CChar)))

foreign import ccall safe "poppler_layer_is_visible"
  poppler_layer_is_visible :: ((Ptr Layer) -> (IO CInt))

foreign import ccall safe "poppler_layer_show"
  poppler_layer_show :: ((Ptr Layer) -> (IO ()))

foreign import ccall safe "poppler_layer_hide"
  poppler_layer_hide :: ((Ptr Layer) -> (IO ()))

foreign import ccall safe "poppler_layer_is_parent"
  poppler_layer_is_parent :: ((Ptr Layer) -> (IO CInt))

foreign import ccall safe "poppler_layer_get_radio_button_group_id"
  poppler_layer_get_radio_button_group_id :: ((Ptr Layer) -> (IO CInt))