{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.WebKit2.Objects.ResponsePolicyDecision
    ( 

-- * Exported types
    ResponsePolicyDecision(..)              ,
    IsResponsePolicyDecision                ,
    toResponsePolicyDecision                ,
    noResponsePolicyDecision                ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveResponsePolicyDecisionMethod     ,
#endif


-- ** getRequest #method:getRequest#

#if defined(ENABLE_OVERLOADING)
    ResponsePolicyDecisionGetRequestMethodInfo,
#endif
    responsePolicyDecisionGetRequest        ,


-- ** getResponse #method:getResponse#

#if defined(ENABLE_OVERLOADING)
    ResponsePolicyDecisionGetResponseMethodInfo,
#endif
    responsePolicyDecisionGetResponse       ,


-- ** isMimeTypeSupported #method:isMimeTypeSupported#

#if defined(ENABLE_OVERLOADING)
    ResponsePolicyDecisionIsMimeTypeSupportedMethodInfo,
#endif
    responsePolicyDecisionIsMimeTypeSupported,




 -- * Properties
-- ** request #attr:request#
-- | This property contains the t'GI.WebKit2.Objects.URIRequest.URIRequest' associated with this
-- policy decision.

#if defined(ENABLE_OVERLOADING)
    ResponsePolicyDecisionRequestPropertyInfo,
#endif
    getResponsePolicyDecisionRequest        ,
#if defined(ENABLE_OVERLOADING)
    responsePolicyDecisionRequest           ,
#endif


-- ** response #attr:response#
-- | This property contains the t'GI.WebKit2.Objects.URIResponse.URIResponse' associated with this
-- policy decision.

#if defined(ENABLE_OVERLOADING)
    ResponsePolicyDecisionResponsePropertyInfo,
#endif
    getResponsePolicyDecisionResponse       ,
#if defined(ENABLE_OVERLOADING)
    responsePolicyDecisionResponse          ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2.Objects.PolicyDecision as WebKit2.PolicyDecision
import {-# SOURCE #-} qualified GI.WebKit2.Objects.URIRequest as WebKit2.URIRequest
import {-# SOURCE #-} qualified GI.WebKit2.Objects.URIResponse as WebKit2.URIResponse

-- | Memory-managed wrapper type.
newtype ResponsePolicyDecision = ResponsePolicyDecision (ManagedPtr ResponsePolicyDecision)
    deriving (ResponsePolicyDecision -> ResponsePolicyDecision -> Bool
(ResponsePolicyDecision -> ResponsePolicyDecision -> Bool)
-> (ResponsePolicyDecision -> ResponsePolicyDecision -> Bool)
-> Eq ResponsePolicyDecision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponsePolicyDecision -> ResponsePolicyDecision -> Bool
$c/= :: ResponsePolicyDecision -> ResponsePolicyDecision -> Bool
== :: ResponsePolicyDecision -> ResponsePolicyDecision -> Bool
$c== :: ResponsePolicyDecision -> ResponsePolicyDecision -> Bool
Eq)
foreign import ccall "webkit_response_policy_decision_get_type"
    c_webkit_response_policy_decision_get_type :: IO GType

instance GObject ResponsePolicyDecision where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_response_policy_decision_get_type
    

-- | Convert 'ResponsePolicyDecision' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue ResponsePolicyDecision where
    toGValue :: ResponsePolicyDecision -> IO GValue
toGValue o :: ResponsePolicyDecision
o = do
        GType
gtype <- IO GType
c_webkit_response_policy_decision_get_type
        ResponsePolicyDecision
-> (Ptr ResponsePolicyDecision -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ResponsePolicyDecision
o (GType
-> (GValue -> Ptr ResponsePolicyDecision -> IO ())
-> Ptr ResponsePolicyDecision
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ResponsePolicyDecision -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO ResponsePolicyDecision
fromGValue gv :: GValue
gv = do
        Ptr ResponsePolicyDecision
ptr <- GValue -> IO (Ptr ResponsePolicyDecision)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ResponsePolicyDecision)
        (ManagedPtr ResponsePolicyDecision -> ResponsePolicyDecision)
-> Ptr ResponsePolicyDecision -> IO ResponsePolicyDecision
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ResponsePolicyDecision -> ResponsePolicyDecision
ResponsePolicyDecision Ptr ResponsePolicyDecision
ptr
        
    

-- | Type class for types which can be safely cast to `ResponsePolicyDecision`, for instance with `toResponsePolicyDecision`.
class (GObject o, O.IsDescendantOf ResponsePolicyDecision o) => IsResponsePolicyDecision o
instance (GObject o, O.IsDescendantOf ResponsePolicyDecision o) => IsResponsePolicyDecision o

instance O.HasParentTypes ResponsePolicyDecision
type instance O.ParentTypes ResponsePolicyDecision = '[WebKit2.PolicyDecision.PolicyDecision, GObject.Object.Object]

-- | Cast to `ResponsePolicyDecision`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toResponsePolicyDecision :: (MonadIO m, IsResponsePolicyDecision o) => o -> m ResponsePolicyDecision
toResponsePolicyDecision :: o -> m ResponsePolicyDecision
toResponsePolicyDecision = IO ResponsePolicyDecision -> m ResponsePolicyDecision
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ResponsePolicyDecision -> m ResponsePolicyDecision)
-> (o -> IO ResponsePolicyDecision)
-> o
-> m ResponsePolicyDecision
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ResponsePolicyDecision -> ResponsePolicyDecision)
-> o -> IO ResponsePolicyDecision
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ResponsePolicyDecision -> ResponsePolicyDecision
ResponsePolicyDecision

-- | A convenience alias for `Nothing` :: `Maybe` `ResponsePolicyDecision`.
noResponsePolicyDecision :: Maybe ResponsePolicyDecision
noResponsePolicyDecision :: Maybe ResponsePolicyDecision
noResponsePolicyDecision = Maybe ResponsePolicyDecision
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveResponsePolicyDecisionMethod (t :: Symbol) (o :: *) :: * where
    ResolveResponsePolicyDecisionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveResponsePolicyDecisionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveResponsePolicyDecisionMethod "download" o = WebKit2.PolicyDecision.PolicyDecisionDownloadMethodInfo
    ResolveResponsePolicyDecisionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveResponsePolicyDecisionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveResponsePolicyDecisionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveResponsePolicyDecisionMethod "ignore" o = WebKit2.PolicyDecision.PolicyDecisionIgnoreMethodInfo
    ResolveResponsePolicyDecisionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveResponsePolicyDecisionMethod "isMimeTypeSupported" o = ResponsePolicyDecisionIsMimeTypeSupportedMethodInfo
    ResolveResponsePolicyDecisionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveResponsePolicyDecisionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveResponsePolicyDecisionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveResponsePolicyDecisionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveResponsePolicyDecisionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveResponsePolicyDecisionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveResponsePolicyDecisionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveResponsePolicyDecisionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveResponsePolicyDecisionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveResponsePolicyDecisionMethod "use" o = WebKit2.PolicyDecision.PolicyDecisionUseMethodInfo
    ResolveResponsePolicyDecisionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveResponsePolicyDecisionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveResponsePolicyDecisionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveResponsePolicyDecisionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveResponsePolicyDecisionMethod "getRequest" o = ResponsePolicyDecisionGetRequestMethodInfo
    ResolveResponsePolicyDecisionMethod "getResponse" o = ResponsePolicyDecisionGetResponseMethodInfo
    ResolveResponsePolicyDecisionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveResponsePolicyDecisionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveResponsePolicyDecisionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveResponsePolicyDecisionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveResponsePolicyDecisionMethod t ResponsePolicyDecision, O.MethodInfo info ResponsePolicyDecision p) => OL.IsLabel t (ResponsePolicyDecision -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "request"
   -- Type: TInterface (Name {namespace = "WebKit2", name = "URIRequest"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@request@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' responsePolicyDecision #request
-- @
getResponsePolicyDecisionRequest :: (MonadIO m, IsResponsePolicyDecision o) => o -> m WebKit2.URIRequest.URIRequest
getResponsePolicyDecisionRequest :: o -> m URIRequest
getResponsePolicyDecisionRequest obj :: o
obj = IO URIRequest -> m URIRequest
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIRequest -> m URIRequest) -> IO URIRequest -> m URIRequest
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe URIRequest) -> IO URIRequest
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getResponsePolicyDecisionRequest" (IO (Maybe URIRequest) -> IO URIRequest)
-> IO (Maybe URIRequest) -> IO URIRequest
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr URIRequest -> URIRequest)
-> IO (Maybe URIRequest)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "request" ManagedPtr URIRequest -> URIRequest
WebKit2.URIRequest.URIRequest

#if defined(ENABLE_OVERLOADING)
data ResponsePolicyDecisionRequestPropertyInfo
instance AttrInfo ResponsePolicyDecisionRequestPropertyInfo where
    type AttrAllowedOps ResponsePolicyDecisionRequestPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ResponsePolicyDecisionRequestPropertyInfo = IsResponsePolicyDecision
    type AttrSetTypeConstraint ResponsePolicyDecisionRequestPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ResponsePolicyDecisionRequestPropertyInfo = (~) ()
    type AttrTransferType ResponsePolicyDecisionRequestPropertyInfo = ()
    type AttrGetType ResponsePolicyDecisionRequestPropertyInfo = WebKit2.URIRequest.URIRequest
    type AttrLabel ResponsePolicyDecisionRequestPropertyInfo = "request"
    type AttrOrigin ResponsePolicyDecisionRequestPropertyInfo = ResponsePolicyDecision
    attrGet = getResponsePolicyDecisionRequest
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "response"
   -- Type: TInterface (Name {namespace = "WebKit2", name = "URIResponse"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@response@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' responsePolicyDecision #response
-- @
getResponsePolicyDecisionResponse :: (MonadIO m, IsResponsePolicyDecision o) => o -> m WebKit2.URIResponse.URIResponse
getResponsePolicyDecisionResponse :: o -> m URIResponse
getResponsePolicyDecisionResponse obj :: o
obj = IO URIResponse -> m URIResponse
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIResponse -> m URIResponse)
-> IO URIResponse -> m URIResponse
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe URIResponse) -> IO URIResponse
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getResponsePolicyDecisionResponse" (IO (Maybe URIResponse) -> IO URIResponse)
-> IO (Maybe URIResponse) -> IO URIResponse
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr URIResponse -> URIResponse)
-> IO (Maybe URIResponse)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "response" ManagedPtr URIResponse -> URIResponse
WebKit2.URIResponse.URIResponse

#if defined(ENABLE_OVERLOADING)
data ResponsePolicyDecisionResponsePropertyInfo
instance AttrInfo ResponsePolicyDecisionResponsePropertyInfo where
    type AttrAllowedOps ResponsePolicyDecisionResponsePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ResponsePolicyDecisionResponsePropertyInfo = IsResponsePolicyDecision
    type AttrSetTypeConstraint ResponsePolicyDecisionResponsePropertyInfo = (~) ()
    type AttrTransferTypeConstraint ResponsePolicyDecisionResponsePropertyInfo = (~) ()
    type AttrTransferType ResponsePolicyDecisionResponsePropertyInfo = ()
    type AttrGetType ResponsePolicyDecisionResponsePropertyInfo = WebKit2.URIResponse.URIResponse
    type AttrLabel ResponsePolicyDecisionResponsePropertyInfo = "response"
    type AttrOrigin ResponsePolicyDecisionResponsePropertyInfo = ResponsePolicyDecision
    attrGet = getResponsePolicyDecisionResponse
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ResponsePolicyDecision
type instance O.AttributeList ResponsePolicyDecision = ResponsePolicyDecisionAttributeList
type ResponsePolicyDecisionAttributeList = ('[ '("request", ResponsePolicyDecisionRequestPropertyInfo), '("response", ResponsePolicyDecisionResponsePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
responsePolicyDecisionRequest :: AttrLabelProxy "request"
responsePolicyDecisionRequest = AttrLabelProxy

responsePolicyDecisionResponse :: AttrLabelProxy "response"
responsePolicyDecisionResponse = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ResponsePolicyDecision = ResponsePolicyDecisionSignalList
type ResponsePolicyDecisionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method ResponsePolicyDecision::get_request
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "decision"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "ResponsePolicyDecision" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitResponsePolicyDecision"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "WebKit2" , name = "URIRequest" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_response_policy_decision_get_request" webkit_response_policy_decision_get_request :: 
    Ptr ResponsePolicyDecision ->           -- decision : TInterface (Name {namespace = "WebKit2", name = "ResponsePolicyDecision"})
    IO (Ptr WebKit2.URIRequest.URIRequest)

-- | Return the t'GI.WebKit2.Objects.URIRequest.URIRequest' associated with the response decision.
-- Modifications to the returned object are \<emphasis>not\<\/emphasis> taken
-- into account when the request is sent over the network, and is intended
-- only to aid in evaluating whether a response decision should be taken or
-- not. To modify requests before they are sent over the network the
-- @/WebKitPage::send-request/@ signal can be used instead.
responsePolicyDecisionGetRequest ::
    (B.CallStack.HasCallStack, MonadIO m, IsResponsePolicyDecision a) =>
    a
    -- ^ /@decision@/: a t'GI.WebKit2.Objects.ResponsePolicyDecision.ResponsePolicyDecision'
    -> m WebKit2.URIRequest.URIRequest
    -- ^ __Returns:__ The URI request that is associated with this policy decision.
responsePolicyDecisionGetRequest :: a -> m URIRequest
responsePolicyDecisionGetRequest decision :: a
decision = IO URIRequest -> m URIRequest
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIRequest -> m URIRequest) -> IO URIRequest -> m URIRequest
forall a b. (a -> b) -> a -> b
$ do
    Ptr ResponsePolicyDecision
decision' <- a -> IO (Ptr ResponsePolicyDecision)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decision
    Ptr URIRequest
result <- Ptr ResponsePolicyDecision -> IO (Ptr URIRequest)
webkit_response_policy_decision_get_request Ptr ResponsePolicyDecision
decision'
    Text -> Ptr URIRequest -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "responsePolicyDecisionGetRequest" Ptr URIRequest
result
    URIRequest
result' <- ((ManagedPtr URIRequest -> URIRequest)
-> Ptr URIRequest -> IO URIRequest
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr URIRequest -> URIRequest
WebKit2.URIRequest.URIRequest) Ptr URIRequest
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decision
    URIRequest -> IO URIRequest
forall (m :: * -> *) a. Monad m => a -> m a
return URIRequest
result'

#if defined(ENABLE_OVERLOADING)
data ResponsePolicyDecisionGetRequestMethodInfo
instance (signature ~ (m WebKit2.URIRequest.URIRequest), MonadIO m, IsResponsePolicyDecision a) => O.MethodInfo ResponsePolicyDecisionGetRequestMethodInfo a signature where
    overloadedMethod = responsePolicyDecisionGetRequest

#endif

-- method ResponsePolicyDecision::get_response
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "decision"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "ResponsePolicyDecision" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitResponsePolicyDecision"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "WebKit2" , name = "URIResponse" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_response_policy_decision_get_response" webkit_response_policy_decision_get_response :: 
    Ptr ResponsePolicyDecision ->           -- decision : TInterface (Name {namespace = "WebKit2", name = "ResponsePolicyDecision"})
    IO (Ptr WebKit2.URIResponse.URIResponse)

-- | Gets the value of the t'GI.WebKit2.Objects.ResponsePolicyDecision.ResponsePolicyDecision':@/response/@ property.
responsePolicyDecisionGetResponse ::
    (B.CallStack.HasCallStack, MonadIO m, IsResponsePolicyDecision a) =>
    a
    -- ^ /@decision@/: a t'GI.WebKit2.Objects.ResponsePolicyDecision.ResponsePolicyDecision'
    -> m WebKit2.URIResponse.URIResponse
    -- ^ __Returns:__ The URI response that is associated with this policy decision.
responsePolicyDecisionGetResponse :: a -> m URIResponse
responsePolicyDecisionGetResponse decision :: a
decision = IO URIResponse -> m URIResponse
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIResponse -> m URIResponse)
-> IO URIResponse -> m URIResponse
forall a b. (a -> b) -> a -> b
$ do
    Ptr ResponsePolicyDecision
decision' <- a -> IO (Ptr ResponsePolicyDecision)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decision
    Ptr URIResponse
result <- Ptr ResponsePolicyDecision -> IO (Ptr URIResponse)
webkit_response_policy_decision_get_response Ptr ResponsePolicyDecision
decision'
    Text -> Ptr URIResponse -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "responsePolicyDecisionGetResponse" Ptr URIResponse
result
    URIResponse
result' <- ((ManagedPtr URIResponse -> URIResponse)
-> Ptr URIResponse -> IO URIResponse
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr URIResponse -> URIResponse
WebKit2.URIResponse.URIResponse) Ptr URIResponse
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decision
    URIResponse -> IO URIResponse
forall (m :: * -> *) a. Monad m => a -> m a
return URIResponse
result'

#if defined(ENABLE_OVERLOADING)
data ResponsePolicyDecisionGetResponseMethodInfo
instance (signature ~ (m WebKit2.URIResponse.URIResponse), MonadIO m, IsResponsePolicyDecision a) => O.MethodInfo ResponsePolicyDecisionGetResponseMethodInfo a signature where
    overloadedMethod = responsePolicyDecisionGetResponse

#endif

-- method ResponsePolicyDecision::is_mime_type_supported
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "decision"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "ResponsePolicyDecision" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitResponsePolicyDecision"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_response_policy_decision_is_mime_type_supported" webkit_response_policy_decision_is_mime_type_supported :: 
    Ptr ResponsePolicyDecision ->           -- decision : TInterface (Name {namespace = "WebKit2", name = "ResponsePolicyDecision"})
    IO CInt

-- | Gets whether the MIME type of the response can be displayed in the t'GI.WebKit2.Objects.WebView.WebView'
-- that triggered this policy decision request. See also 'GI.WebKit2.Objects.WebView.webViewCanShowMimeType'.
-- 
-- /Since: 2.4/
responsePolicyDecisionIsMimeTypeSupported ::
    (B.CallStack.HasCallStack, MonadIO m, IsResponsePolicyDecision a) =>
    a
    -- ^ /@decision@/: a t'GI.WebKit2.Objects.ResponsePolicyDecision.ResponsePolicyDecision'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the MIME type of the response is supported or 'P.False' otherwise
responsePolicyDecisionIsMimeTypeSupported :: a -> m Bool
responsePolicyDecisionIsMimeTypeSupported decision :: a
decision = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ResponsePolicyDecision
decision' <- a -> IO (Ptr ResponsePolicyDecision)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decision
    CInt
result <- Ptr ResponsePolicyDecision -> IO CInt
webkit_response_policy_decision_is_mime_type_supported Ptr ResponsePolicyDecision
decision'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decision
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ResponsePolicyDecisionIsMimeTypeSupportedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsResponsePolicyDecision a) => O.MethodInfo ResponsePolicyDecisionIsMimeTypeSupportedMethodInfo a signature where
    overloadedMethod = responsePolicyDecisionIsMimeTypeSupported

#endif