-- 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/DOMNamedFlowCollection.chs" #-}
module Graphics.UI.Gtk.WebKit.DOM.DOMNamedFlowCollection(
item,
namedItem,
getLength,
DOMNamedFlowCollection,
castToDOMNamedFlowCollection,
gTypeDOMNamedFlowCollection,
DOMNamedFlowCollectionClass,
toDOMNamedFlowCollection,
) 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 25 "./Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.chs" #-}
import Graphics.UI.Gtk.WebKit.DOM.Enums

 
item ::
     (MonadIO m, DOMNamedFlowCollectionClass self) =>
       self -> Word -> m (Maybe WebKitNamedFlow)
item self index
  = liftIO
      (maybeNull (makeNewGObject mkWebKitNamedFlow)
         ((\(DOMNamedFlowCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_named_flow_collection_item argPtr1 arg2)
{-# LINE 35 "./Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.chs" #-}
            (toDOMNamedFlowCollection self)
            (fromIntegral index)))
 
namedItem ::
          (MonadIO m, DOMNamedFlowCollectionClass self, GlibString string) =>
            self -> string -> m (Maybe WebKitNamedFlow)
namedItem self name
  = liftIO
      (maybeNull (makeNewGObject mkWebKitNamedFlow)
         (withUTFString name $
            \ namePtr ->
              (\(DOMNamedFlowCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_named_flow_collection_named_item argPtr1 arg2)
{-# LINE 47 "./Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.chs" #-}
                (toDOMNamedFlowCollection self)
                namePtr))
 
getLength ::
          (MonadIO m, DOMNamedFlowCollectionClass self) => self -> m Word
getLength self
  = liftIO
      (fromIntegral <$>
         ((\(DOMNamedFlowCollection arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_named_flow_collection_get_length argPtr1)
{-# LINE 56 "./Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.chs" #-}
            (toDOMNamedFlowCollection self)))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.h webkit_dom_dom_named_flow_collection_item"
  webkit_dom_dom_named_flow_collection_item :: ((Ptr DOMNamedFlowCollection) -> (CULong -> (IO (Ptr WebKitNamedFlow))))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.h webkit_dom_dom_named_flow_collection_named_item"
  webkit_dom_dom_named_flow_collection_named_item :: ((Ptr DOMNamedFlowCollection) -> ((Ptr CChar) -> (IO (Ptr WebKitNamedFlow))))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/DOMNamedFlowCollection.h webkit_dom_dom_named_flow_collection_get_length"
  webkit_dom_dom_named_flow_collection_get_length :: ((Ptr DOMNamedFlowCollection) -> (IO CULong))