module Graphics.UI.Gtk.WebKit.WebNavigationAction (
  WebNavigationAction,
  WebNavigationActionClass,
  NavigationReason(..),
  webNavigationActionGetButton,
  webNavigationActionGetModifierState,
  webNavigationActionGetOriginalUri,
  webNavigationActionSetOriginalUri,
  webNavigationActionGetReason,
  webNavigationActionSetReason,
  webNavigationActionGetTargetFrame,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.GError
import Graphics.UI.Gtk.Gdk.Events
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GObject
data NavigationReason = WebNavigationReasonLinkClicked
                      | WebNavigationReasonFormSubmitted
                      | WebNavigationReasonBackForward
                      | WebNavigationReasonReload
                      | WebNavigationReasonFormResubmitted
                      | WebNavigationReasonOther
                      deriving (Enum,Eq,Show)
webNavigationActionGetButton ::
   WebNavigationActionClass self => self
 -> IO Int
webNavigationActionGetButton action =
    liftM fromIntegral $ (\(WebNavigationAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_get_button argPtr1) (toWebNavigationAction action)
webNavigationActionGetModifierState ::
   WebNavigationActionClass self => self
 -> IO Int
webNavigationActionGetModifierState action =
    liftM fromIntegral $ (\(WebNavigationAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_get_modifier_state argPtr1) (toWebNavigationAction action)
webNavigationActionGetOriginalUri ::
   (WebNavigationActionClass self, GlibString string) => self
 -> IO string
webNavigationActionGetOriginalUri action =
    (\(WebNavigationAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_get_original_uri argPtr1) (toWebNavigationAction action) >>= peekUTFString
webNavigationActionGetReason ::
   WebNavigationActionClass self => self
 -> IO NavigationReason
webNavigationActionGetReason action =
    liftM (toEnum . fromIntegral) $ (\(WebNavigationAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_get_reason argPtr1) (toWebNavigationAction action)
webNavigationActionGetTargetFrame ::
   (WebNavigationActionClass self, GlibString string) => self
 -> IO string
webNavigationActionGetTargetFrame action =
    (\(WebNavigationAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_get_target_frame argPtr1) (toWebNavigationAction action) >>= peekUTFString
webNavigationActionSetOriginalUri ::
   (WebNavigationActionClass self, GlibString string) => self
 -> string
 -> IO ()
webNavigationActionSetOriginalUri action uri =
    withUTFString uri $ \uriPtr ->
        (\(WebNavigationAction arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_set_original_uri argPtr1 arg2)
        (toWebNavigationAction action)
        uriPtr
webNavigationActionSetReason ::
   WebNavigationActionClass self => self
 -> NavigationReason
 -> IO ()
webNavigationActionSetReason action reason =
    (\(WebNavigationAction arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_navigation_action_set_reason argPtr1 arg2) (toWebNavigationAction action) (fromIntegral (fromEnum reason))
foreign import ccall safe "webkit_web_navigation_action_get_button"
  webkit_web_navigation_action_get_button :: ((Ptr WebNavigationAction) -> (IO CInt))
foreign import ccall safe "webkit_web_navigation_action_get_modifier_state"
  webkit_web_navigation_action_get_modifier_state :: ((Ptr WebNavigationAction) -> (IO CInt))
foreign import ccall safe "webkit_web_navigation_action_get_original_uri"
  webkit_web_navigation_action_get_original_uri :: ((Ptr WebNavigationAction) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_navigation_action_get_reason"
  webkit_web_navigation_action_get_reason :: ((Ptr WebNavigationAction) -> (IO CInt))
foreign import ccall safe "webkit_web_navigation_action_get_target_frame"
  webkit_web_navigation_action_get_target_frame :: ((Ptr WebNavigationAction) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_navigation_action_set_original_uri"
  webkit_web_navigation_action_set_original_uri :: ((Ptr WebNavigationAction) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_web_navigation_action_set_reason"
  webkit_web_navigation_action_set_reason :: ((Ptr WebNavigationAction) -> (CInt -> (IO ())))