module Graphics.UI.Gtk.WebKit.DOM.SecurityPolicy(
allowsConnectionTo,
allowsFontFrom,
allowsFormAction,
allowsFrameFrom,
allowsImageFrom,
allowsMediaFrom,
allowsObjectFrom,
allowsPluginType,
allowsScriptFrom,
allowsStyleFrom,
getAllowsEval,
getAllowsInlineScript,
getAllowsInlineStyle,
getIsActive,
getReportURIs,
SecurityPolicy,
castToSecurityPolicy,
gTypeSecurityPolicy,
SecurityPolicyClass,
toSecurityPolicy,
) 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
allowsConnectionTo ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsConnectionTo self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_connection_to argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsFontFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsFontFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_font_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsFormAction ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsFormAction self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_form_action argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsFrameFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsFrameFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_frame_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsImageFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsImageFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_image_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsMediaFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsMediaFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_media_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsObjectFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsObjectFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_object_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsPluginType ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsPluginType self type'
= liftIO
(toBool <$>
(withUTFString type' $
\ typePtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_plugin_type argPtr1 arg2)
(toSecurityPolicy self)
typePtr))
allowsScriptFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsScriptFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_script_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
allowsStyleFrom ::
(MonadIO m, SecurityPolicyClass self, GlibString string) =>
self -> string -> m Bool
allowsStyleFrom self url
= liftIO
(toBool <$>
(withUTFString url $
\ urlPtr ->
(\(SecurityPolicy arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_allows_style_from argPtr1 arg2)
(toSecurityPolicy self)
urlPtr))
getAllowsEval ::
(MonadIO m, SecurityPolicyClass self) => self -> m Bool
getAllowsEval self
= liftIO
(toBool <$>
((\(SecurityPolicy arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_get_allows_eval argPtr1)
(toSecurityPolicy self)))
getAllowsInlineScript ::
(MonadIO m, SecurityPolicyClass self) => self -> m Bool
getAllowsInlineScript self
= liftIO
(toBool <$>
((\(SecurityPolicy arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_get_allows_inline_script argPtr1)
(toSecurityPolicy self)))
getAllowsInlineStyle ::
(MonadIO m, SecurityPolicyClass self) => self -> m Bool
getAllowsInlineStyle self
= liftIO
(toBool <$>
((\(SecurityPolicy arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_get_allows_inline_style argPtr1)
(toSecurityPolicy self)))
getIsActive ::
(MonadIO m, SecurityPolicyClass self) => self -> m Bool
getIsActive self
= liftIO
(toBool <$>
((\(SecurityPolicy arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_get_is_active argPtr1)
(toSecurityPolicy self)))
getReportURIs ::
(MonadIO m, SecurityPolicyClass self) =>
self -> m (Maybe DOMStringList)
getReportURIs self
= liftIO
(maybeNull (makeNewGObject mkDOMStringList)
((\(SecurityPolicy arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_security_policy_get_report_ur_is argPtr1)
(toSecurityPolicy self)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_connection_to"
webkit_dom_dom_security_policy_allows_connection_to :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_font_from"
webkit_dom_dom_security_policy_allows_font_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_form_action"
webkit_dom_dom_security_policy_allows_form_action :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_frame_from"
webkit_dom_dom_security_policy_allows_frame_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_image_from"
webkit_dom_dom_security_policy_allows_image_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_media_from"
webkit_dom_dom_security_policy_allows_media_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_object_from"
webkit_dom_dom_security_policy_allows_object_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_plugin_type"
webkit_dom_dom_security_policy_allows_plugin_type :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_script_from"
webkit_dom_dom_security_policy_allows_script_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_allows_style_from"
webkit_dom_dom_security_policy_allows_style_from :: ((Ptr SecurityPolicy) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_get_allows_eval"
webkit_dom_dom_security_policy_get_allows_eval :: ((Ptr SecurityPolicy) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_get_allows_inline_script"
webkit_dom_dom_security_policy_get_allows_inline_script :: ((Ptr SecurityPolicy) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_get_allows_inline_style"
webkit_dom_dom_security_policy_get_allows_inline_style :: ((Ptr SecurityPolicy) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_get_is_active"
webkit_dom_dom_security_policy_get_is_active :: ((Ptr SecurityPolicy) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/SecurityPolicy.h webkit_dom_dom_security_policy_get_report_ur_is"
webkit_dom_dom_security_policy_get_report_ur_is :: ((Ptr SecurityPolicy) -> (IO (Ptr DOMStringList)))