module Graphics.UI.Gtk.WebKit.WebWindowFeatures (
  WebWindowFeatures,
  WebWindowFeaturesClass,
  webWindowFeaturesNew,
  webWindowFeaturesEqual,
  webWindowFeaturesFullscreen,
  webWindowFeaturesHeight,
  webWindowFeaturesWidth,
  webWindowFeaturesX,
  webWindowFeaturesY,
  webWindowFeaturesLocationbarVisible,
  webWindowFeaturesMenubarVisible,
  webWindowFeaturesScrollbarVisible,
  webWindowFeaturesStatusbarVisible,
  webWindowFeaturesToolbarVisible,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.GError
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Gdk.Events
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GObject
webWindowFeaturesNew :: IO WebWindowFeatures
webWindowFeaturesNew =
    wrapNewGObject mkWebWindowFeatures $ webkit_web_window_features_new
webWindowFeaturesEqual ::
   (WebWindowFeaturesClass winA, WebWindowFeaturesClass winB) => winA -> winB
 -> IO Bool
webWindowFeaturesEqual winA winB =
    liftM toBool $ (\(WebWindowFeatures arg1) (WebWindowFeatures arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_web_window_features_equal argPtr1 argPtr2) (toWebWindowFeatures winA) (toWebWindowFeatures winB)
webWindowFeaturesFullscreen :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesFullscreen = newAttrFromBoolProperty "fullscreen"
webWindowFeaturesHeight :: WebWindowFeaturesClass self => Attr self Int
webWindowFeaturesHeight = newAttrFromIntProperty "height"
webWindowFeaturesWidth :: WebWindowFeaturesClass self => Attr self Int
webWindowFeaturesWidth = newAttrFromIntProperty "width"
webWindowFeaturesLocationbarVisible :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesLocationbarVisible = newAttrFromBoolProperty "locationbar-visible"
webWindowFeaturesMenubarVisible :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesMenubarVisible = newAttrFromBoolProperty "menubar-visible"
webWindowFeaturesScrollbarVisible :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesScrollbarVisible = newAttrFromBoolProperty "scrollbar-visible"
webWindowFeaturesStatusbarVisible :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesStatusbarVisible = newAttrFromBoolProperty "statusbar-visible"
webWindowFeaturesToolbarVisible :: WebWindowFeaturesClass self => Attr self Bool
webWindowFeaturesToolbarVisible = newAttrFromBoolProperty "toolbar-visible"
webWindowFeaturesX :: WebWindowFeaturesClass self => Attr self Int
webWindowFeaturesX = newAttrFromIntProperty "x"
webWindowFeaturesY :: WebWindowFeaturesClass self => Attr self Int
webWindowFeaturesY = newAttrFromIntProperty "y"
foreign import ccall safe "webkit_web_window_features_new"
  webkit_web_window_features_new :: (IO (Ptr WebWindowFeatures))
foreign import ccall safe "webkit_web_window_features_equal"
  webkit_web_window_features_equal :: ((Ptr WebWindowFeatures) -> ((Ptr WebWindowFeatures) -> (IO CInt)))