module Graphics.UI.Gtk.WebKit.DOM.HTMLAppletElement
(htmlAppletElementSetAlign, htmlAppletElementGetAlign,
htmlAppletElementSetAlt, htmlAppletElementGetAlt,
htmlAppletElementSetArchive, htmlAppletElementGetArchive,
htmlAppletElementSetCode, htmlAppletElementGetCode,
htmlAppletElementSetCodeBase, htmlAppletElementGetCodeBase,
htmlAppletElementSetHeight, htmlAppletElementGetHeight,
htmlAppletElementSetHspace, htmlAppletElementGetHspace,
htmlAppletElementSetName, htmlAppletElementGetName,
htmlAppletElementSetObject, htmlAppletElementGetObject,
htmlAppletElementSetVspace, htmlAppletElementGetVspace,
htmlAppletElementSetWidth, htmlAppletElementGetWidth,
HTMLAppletElement, HTMLAppletElementClass, castToHTMLAppletElement,
gTypeHTMLAppletElement, toHTMLAppletElement)
where
import System.Glib.FFI
import System.Glib.UTFString
import Control.Applicative
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventM
htmlAppletElementSetAlign ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetAlign self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_align argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetAlign ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetAlign self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_align argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetAlt ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetAlt self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_alt argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetAlt ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetAlt self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_alt argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetArchive ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetArchive self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_archive argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetArchive ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetArchive self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_archive argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetCode ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetCode self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_code argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetCode ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetCode self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_code argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetCodeBase ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetCodeBase self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_code_base argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetCodeBase ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetCodeBase self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_code_base argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetHeight ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetHeight self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_height argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetHeight ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetHeight self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_height argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetHspace ::
(HTMLAppletElementClass self) => self -> Int -> IO ()
htmlAppletElementSetHspace self val
= (\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_hspace argPtr1 arg2)
(toHTMLAppletElement self)
(fromIntegral val)
htmlAppletElementGetHspace ::
(HTMLAppletElementClass self) => self -> IO Int
htmlAppletElementGetHspace self
= fromIntegral <$>
((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_hspace argPtr1)
(toHTMLAppletElement self))
htmlAppletElementSetName ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetName self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_name argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetName ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetName self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_name argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetObject ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetObject self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_object argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetObject ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetObject self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_object argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
htmlAppletElementSetVspace ::
(HTMLAppletElementClass self) => self -> Int -> IO ()
htmlAppletElementSetVspace self val
= (\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_vspace argPtr1 arg2)
(toHTMLAppletElement self)
(fromIntegral val)
htmlAppletElementGetVspace ::
(HTMLAppletElementClass self) => self -> IO Int
htmlAppletElementGetVspace self
= fromIntegral <$>
((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_vspace argPtr1)
(toHTMLAppletElement self))
htmlAppletElementSetWidth ::
(HTMLAppletElementClass self) => self -> String -> IO ()
htmlAppletElementSetWidth self val
= withUTFString val $
\ valPtr ->
(\(HTMLAppletElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_set_width argPtr1 arg2)
(toHTMLAppletElement self)
valPtr
htmlAppletElementGetWidth ::
(HTMLAppletElementClass self) => self -> IO String
htmlAppletElementGetWidth self
= ((\(HTMLAppletElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_applet_element_get_width argPtr1)
(toHTMLAppletElement self))
>>=
readUTFString
foreign import ccall safe "webkit_dom_html_applet_element_set_align"
webkit_dom_html_applet_element_set_align :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_align"
webkit_dom_html_applet_element_get_align :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_alt"
webkit_dom_html_applet_element_set_alt :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_alt"
webkit_dom_html_applet_element_get_alt :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_archive"
webkit_dom_html_applet_element_set_archive :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_archive"
webkit_dom_html_applet_element_get_archive :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_code"
webkit_dom_html_applet_element_set_code :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_code"
webkit_dom_html_applet_element_get_code :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_code_base"
webkit_dom_html_applet_element_set_code_base :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_code_base"
webkit_dom_html_applet_element_get_code_base :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_height"
webkit_dom_html_applet_element_set_height :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_height"
webkit_dom_html_applet_element_get_height :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_hspace"
webkit_dom_html_applet_element_set_hspace :: ((Ptr HTMLAppletElement) -> (CLong -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_hspace"
webkit_dom_html_applet_element_get_hspace :: ((Ptr HTMLAppletElement) -> (IO CLong))
foreign import ccall safe "webkit_dom_html_applet_element_set_name"
webkit_dom_html_applet_element_set_name :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_name"
webkit_dom_html_applet_element_get_name :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_object"
webkit_dom_html_applet_element_set_object :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_object"
webkit_dom_html_applet_element_get_object :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_applet_element_set_vspace"
webkit_dom_html_applet_element_set_vspace :: ((Ptr HTMLAppletElement) -> (CLong -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_vspace"
webkit_dom_html_applet_element_get_vspace :: ((Ptr HTMLAppletElement) -> (IO CLong))
foreign import ccall safe "webkit_dom_html_applet_element_set_width"
webkit_dom_html_applet_element_set_width :: ((Ptr HTMLAppletElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_applet_element_get_width"
webkit_dom_html_applet_element_get_width :: ((Ptr HTMLAppletElement) -> (IO (Ptr CChar)))