module Graphics.UI.Gtk.WebKit.DOM.ProcessingInstruction(
getTarget,
getSheet,
ProcessingInstruction,
castToProcessingInstruction,
gTypeProcessingInstruction,
ProcessingInstructionClass,
toProcessingInstruction,
) 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
import Graphics.UI.Gtk.WebKit.DOM.Enums
getTarget ::
(MonadIO m, ProcessingInstructionClass self, GlibString string) =>
self -> m (Maybe string)
getTarget self
= liftIO
(((\(ProcessingInstruction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_processing_instruction_get_target argPtr1)
(toProcessingInstruction self))
>>=
maybePeek readUTFString)
getSheet ::
(MonadIO m, ProcessingInstructionClass self) =>
self -> m (Maybe StyleSheet)
getSheet self
= liftIO
(maybeNull (makeNewGObject mkStyleSheet)
((\(ProcessingInstruction arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_processing_instruction_get_sheet argPtr1)
(toProcessingInstruction self)))
foreign import ccall safe "webkit_dom_processing_instruction_get_target"
webkit_dom_processing_instruction_get_target :: ((Ptr ProcessingInstruction) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_processing_instruction_get_sheet"
webkit_dom_processing_instruction_get_sheet :: ((Ptr ProcessingInstruction) -> (IO (Ptr StyleSheet)))