-- GENERATED by C->Haskell Compiler, version 0.13.13 (gtk2hs branch) "Bin IO", 27 May 2012 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Graphics/UI/Gtk/WebKit/DOM/PluginArray.chs" #-}
module Graphics.UI.Gtk.WebKit.DOM.PluginArray(
item,
namedItem,
refresh,
getLength,
PluginArray,
castToPluginArray,
gTypePluginArray,
PluginArrayClass,
toPluginArray,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
{-# LINE 23 "./Graphics/UI/Gtk/WebKit/DOM/PluginArray.chs" #-}
import Graphics.UI.Gtk.WebKit.DOM.Enums

 
item ::
     (MonadIO m, PluginArrayClass self) =>
       self -> Word -> m (Maybe Plugin)
item self index
  = liftIO
      (maybeNull (makeNewGObject mkPlugin)
         ((\(PluginArray arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_plugin_array_item argPtr1 arg2) (toPluginArray self)
            (fromIntegral index)))
 
namedItem ::
          (MonadIO m, PluginArrayClass self, GlibString string) =>
            self -> string -> m (Maybe Plugin)
namedItem self name
  = liftIO
      (maybeNull (makeNewGObject mkPlugin)
         (withUTFString name $
            \ namePtr ->
              (\(PluginArray arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_plugin_array_named_item argPtr1 arg2)
{-# LINE 44 "./Graphics/UI/Gtk/WebKit/DOM/PluginArray.chs" #-}
                (toPluginArray self)
                namePtr))
 
refresh ::
        (MonadIO m, PluginArrayClass self) => self -> Bool -> m ()
refresh self reload
  = liftIO
      ((\(PluginArray arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_plugin_array_refresh argPtr1 arg2)
{-# LINE 52 "./Graphics/UI/Gtk/WebKit/DOM/PluginArray.chs" #-}
         (toPluginArray self)
         (fromBool reload))
 
getLength :: (MonadIO m, PluginArrayClass self) => self -> m Word
getLength self
  = liftIO
      (fromIntegral <$>
         ((\(PluginArray arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_plugin_array_get_length argPtr1)
{-# LINE 60 "./Graphics/UI/Gtk/WebKit/DOM/PluginArray.chs" #-}
            (toPluginArray self)))

foreign import ccall safe "webkit_dom_dom_plugin_array_item"
  webkit_dom_dom_plugin_array_item :: ((Ptr PluginArray) -> (CULong -> (IO (Ptr Plugin))))

foreign import ccall safe "webkit_dom_dom_plugin_array_named_item"
  webkit_dom_dom_plugin_array_named_item :: ((Ptr PluginArray) -> ((Ptr CChar) -> (IO (Ptr Plugin))))

foreign import ccall safe "webkit_dom_dom_plugin_array_refresh"
  webkit_dom_dom_plugin_array_refresh :: ((Ptr PluginArray) -> (CInt -> (IO ())))

foreign import ccall safe "webkit_dom_dom_plugin_array_get_length"
  webkit_dom_dom_plugin_array_get_length :: ((Ptr PluginArray) -> (IO CULong))