{-# 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.AutomationSession
    ( 

-- * Exported types
    AutomationSession(..)                   ,
    IsAutomationSession                     ,
    toAutomationSession                     ,
    noAutomationSession                     ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAutomationSessionMethod          ,
#endif


-- ** getApplicationInfo #method:getApplicationInfo#

#if defined(ENABLE_OVERLOADING)
    AutomationSessionGetApplicationInfoMethodInfo,
#endif
    automationSessionGetApplicationInfo     ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    AutomationSessionGetIdMethodInfo        ,
#endif
    automationSessionGetId                  ,


-- ** setApplicationInfo #method:setApplicationInfo#

#if defined(ENABLE_OVERLOADING)
    AutomationSessionSetApplicationInfoMethodInfo,
#endif
    automationSessionSetApplicationInfo     ,




 -- * Properties
-- ** id #attr:id#
-- | The session unique identifier.
-- 
-- /Since: 2.18/

#if defined(ENABLE_OVERLOADING)
    AutomationSessionIdPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    automationSessionId                     ,
#endif
    constructAutomationSessionId            ,
    getAutomationSessionId                  ,




 -- * Signals
-- ** createWebView #signal:createWebView#

    AutomationSessionCreateWebViewCallback  ,
#if defined(ENABLE_OVERLOADING)
    AutomationSessionCreateWebViewSignalInfo,
#endif
    C_AutomationSessionCreateWebViewCallback,
    afterAutomationSessionCreateWebView     ,
    genClosure_AutomationSessionCreateWebView,
    mk_AutomationSessionCreateWebViewCallback,
    noAutomationSessionCreateWebViewCallback,
    onAutomationSessionCreateWebView        ,
    wrap_AutomationSessionCreateWebViewCallback,




    ) 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.WebView as WebKit2.WebView
import {-# SOURCE #-} qualified GI.WebKit2.Structs.ApplicationInfo as WebKit2.ApplicationInfo

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

instance GObject AutomationSession where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_automation_session_get_type
    

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

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

instance O.HasParentTypes AutomationSession
type instance O.ParentTypes AutomationSession = '[GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `AutomationSession`.
noAutomationSession :: Maybe AutomationSession
noAutomationSession :: Maybe AutomationSession
noAutomationSession = Maybe AutomationSession
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAutomationSessionMethod (t :: Symbol) (o :: *) :: * where
    ResolveAutomationSessionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAutomationSessionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAutomationSessionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAutomationSessionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAutomationSessionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAutomationSessionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAutomationSessionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAutomationSessionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAutomationSessionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAutomationSessionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAutomationSessionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAutomationSessionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAutomationSessionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAutomationSessionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAutomationSessionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAutomationSessionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAutomationSessionMethod "getApplicationInfo" o = AutomationSessionGetApplicationInfoMethodInfo
    ResolveAutomationSessionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAutomationSessionMethod "getId" o = AutomationSessionGetIdMethodInfo
    ResolveAutomationSessionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAutomationSessionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAutomationSessionMethod "setApplicationInfo" o = AutomationSessionSetApplicationInfoMethodInfo
    ResolveAutomationSessionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAutomationSessionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAutomationSessionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAutomationSessionMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal AutomationSession::create-web-view
-- | This signal is emitted when the automation client requests a new
-- browsing context to interact with it. The callback handler should
-- return a t'GI.WebKit2.Objects.WebView.WebView' created with t'GI.WebKit2.Objects.WebView.WebView':@/is-controlled-by-automation/@
-- construct property enabled. The returned t'GI.WebKit2.Objects.WebView.WebView' could be an existing
-- web view or a new one created and added to a new tab or window.
-- 
-- /Since: 2.18/
type AutomationSessionCreateWebViewCallback =
    IO WebKit2.WebView.WebView
    -- ^ __Returns:__ a t'GI.WebKit2.Objects.WebView.WebView' widget.

-- | A convenience synonym for @`Nothing` :: `Maybe` `AutomationSessionCreateWebViewCallback`@.
noAutomationSessionCreateWebViewCallback :: Maybe AutomationSessionCreateWebViewCallback
noAutomationSessionCreateWebViewCallback :: Maybe AutomationSessionCreateWebViewCallback
noAutomationSessionCreateWebViewCallback = Maybe AutomationSessionCreateWebViewCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_AutomationSessionCreateWebViewCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO (Ptr WebKit2.WebView.WebView)

-- | Generate a function pointer callable from C code, from a `C_AutomationSessionCreateWebViewCallback`.
foreign import ccall "wrapper"
    mk_AutomationSessionCreateWebViewCallback :: C_AutomationSessionCreateWebViewCallback -> IO (FunPtr C_AutomationSessionCreateWebViewCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_AutomationSessionCreateWebView :: MonadIO m => AutomationSessionCreateWebViewCallback -> m (GClosure C_AutomationSessionCreateWebViewCallback)
genClosure_AutomationSessionCreateWebView :: AutomationSessionCreateWebViewCallback
-> m (GClosure C_AutomationSessionCreateWebViewCallback)
genClosure_AutomationSessionCreateWebView cb :: AutomationSessionCreateWebViewCallback
cb = IO (GClosure C_AutomationSessionCreateWebViewCallback)
-> m (GClosure C_AutomationSessionCreateWebViewCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AutomationSessionCreateWebViewCallback)
 -> m (GClosure C_AutomationSessionCreateWebViewCallback))
-> IO (GClosure C_AutomationSessionCreateWebViewCallback)
-> m (GClosure C_AutomationSessionCreateWebViewCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AutomationSessionCreateWebViewCallback
cb' = AutomationSessionCreateWebViewCallback
-> C_AutomationSessionCreateWebViewCallback
wrap_AutomationSessionCreateWebViewCallback AutomationSessionCreateWebViewCallback
cb
    C_AutomationSessionCreateWebViewCallback
-> IO (FunPtr C_AutomationSessionCreateWebViewCallback)
mk_AutomationSessionCreateWebViewCallback C_AutomationSessionCreateWebViewCallback
cb' IO (FunPtr C_AutomationSessionCreateWebViewCallback)
-> (FunPtr C_AutomationSessionCreateWebViewCallback
    -> IO (GClosure C_AutomationSessionCreateWebViewCallback))
-> IO (GClosure C_AutomationSessionCreateWebViewCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AutomationSessionCreateWebViewCallback
-> IO (GClosure C_AutomationSessionCreateWebViewCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AutomationSessionCreateWebViewCallback` into a `C_AutomationSessionCreateWebViewCallback`.
wrap_AutomationSessionCreateWebViewCallback ::
    AutomationSessionCreateWebViewCallback ->
    C_AutomationSessionCreateWebViewCallback
wrap_AutomationSessionCreateWebViewCallback :: AutomationSessionCreateWebViewCallback
-> C_AutomationSessionCreateWebViewCallback
wrap_AutomationSessionCreateWebViewCallback _cb :: AutomationSessionCreateWebViewCallback
_cb _ _ = do
    WebView
result <- AutomationSessionCreateWebViewCallback
_cb 
    Ptr WebView
result' <- WebView -> IO (Ptr WebView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr WebView
result
    Ptr WebView -> IO (Ptr WebView)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr WebView
result'


-- | Connect a signal handler for the [createWebView](#signal:createWebView) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' automationSession #createWebView callback
-- @
-- 
-- 
onAutomationSessionCreateWebView :: (IsAutomationSession a, MonadIO m) => a -> AutomationSessionCreateWebViewCallback -> m SignalHandlerId
onAutomationSessionCreateWebView :: a -> AutomationSessionCreateWebViewCallback -> m SignalHandlerId
onAutomationSessionCreateWebView obj :: a
obj cb :: AutomationSessionCreateWebViewCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AutomationSessionCreateWebViewCallback
cb' = AutomationSessionCreateWebViewCallback
-> C_AutomationSessionCreateWebViewCallback
wrap_AutomationSessionCreateWebViewCallback AutomationSessionCreateWebViewCallback
cb
    FunPtr C_AutomationSessionCreateWebViewCallback
cb'' <- C_AutomationSessionCreateWebViewCallback
-> IO (FunPtr C_AutomationSessionCreateWebViewCallback)
mk_AutomationSessionCreateWebViewCallback C_AutomationSessionCreateWebViewCallback
cb'
    a
-> Text
-> FunPtr C_AutomationSessionCreateWebViewCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "create-web-view" FunPtr C_AutomationSessionCreateWebViewCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [createWebView](#signal:createWebView) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' automationSession #createWebView callback
-- @
-- 
-- 
afterAutomationSessionCreateWebView :: (IsAutomationSession a, MonadIO m) => a -> AutomationSessionCreateWebViewCallback -> m SignalHandlerId
afterAutomationSessionCreateWebView :: a -> AutomationSessionCreateWebViewCallback -> m SignalHandlerId
afterAutomationSessionCreateWebView obj :: a
obj cb :: AutomationSessionCreateWebViewCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AutomationSessionCreateWebViewCallback
cb' = AutomationSessionCreateWebViewCallback
-> C_AutomationSessionCreateWebViewCallback
wrap_AutomationSessionCreateWebViewCallback AutomationSessionCreateWebViewCallback
cb
    FunPtr C_AutomationSessionCreateWebViewCallback
cb'' <- C_AutomationSessionCreateWebViewCallback
-> IO (FunPtr C_AutomationSessionCreateWebViewCallback)
mk_AutomationSessionCreateWebViewCallback C_AutomationSessionCreateWebViewCallback
cb'
    a
-> Text
-> FunPtr C_AutomationSessionCreateWebViewCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "create-web-view" FunPtr C_AutomationSessionCreateWebViewCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data AutomationSessionCreateWebViewSignalInfo
instance SignalInfo AutomationSessionCreateWebViewSignalInfo where
    type HaskellCallbackType AutomationSessionCreateWebViewSignalInfo = AutomationSessionCreateWebViewCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AutomationSessionCreateWebViewCallback cb
        cb'' <- mk_AutomationSessionCreateWebViewCallback cb'
        connectSignalFunPtr obj "create-web-view" cb'' connectMode detail

#endif

-- VVV Prop "id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAutomationSessionId :: (IsAutomationSession o) => T.Text -> IO (GValueConstruct o)
constructAutomationSessionId :: Text -> IO (GValueConstruct o)
constructAutomationSessionId val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data AutomationSessionIdPropertyInfo
instance AttrInfo AutomationSessionIdPropertyInfo where
    type AttrAllowedOps AutomationSessionIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AutomationSessionIdPropertyInfo = IsAutomationSession
    type AttrSetTypeConstraint AutomationSessionIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AutomationSessionIdPropertyInfo = (~) T.Text
    type AttrTransferType AutomationSessionIdPropertyInfo = T.Text
    type AttrGetType AutomationSessionIdPropertyInfo = T.Text
    type AttrLabel AutomationSessionIdPropertyInfo = "id"
    type AttrOrigin AutomationSessionIdPropertyInfo = AutomationSession
    attrGet = getAutomationSessionId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructAutomationSessionId
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AutomationSession
type instance O.AttributeList AutomationSession = AutomationSessionAttributeList
type AutomationSessionAttributeList = ('[ '("id", AutomationSessionIdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
automationSessionId :: AttrLabelProxy "id"
automationSessionId = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "webkit_automation_session_get_application_info" webkit_automation_session_get_application_info :: 
    Ptr AutomationSession ->                -- session : TInterface (Name {namespace = "WebKit2", name = "AutomationSession"})
    IO (Ptr WebKit2.ApplicationInfo.ApplicationInfo)

-- | Get the t'GI.WebKit2.Objects.AutomationSession.AutomationSession' previously set with 'GI.WebKit2.Objects.AutomationSession.automationSessionSetApplicationInfo'.
-- 
-- /Since: 2.18/
automationSessionGetApplicationInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsAutomationSession a) =>
    a
    -- ^ /@session@/: a t'GI.WebKit2.Objects.AutomationSession.AutomationSession'
    -> m (Maybe WebKit2.ApplicationInfo.ApplicationInfo)
    -- ^ __Returns:__ the t'GI.WebKit2.Objects.AutomationSession.AutomationSession' of /@session@/, or 'P.Nothing' if no one has been set.
automationSessionGetApplicationInfo :: a -> m (Maybe ApplicationInfo)
automationSessionGetApplicationInfo session :: a
session = IO (Maybe ApplicationInfo) -> m (Maybe ApplicationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ApplicationInfo) -> m (Maybe ApplicationInfo))
-> IO (Maybe ApplicationInfo) -> m (Maybe ApplicationInfo)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AutomationSession
session' <- a -> IO (Ptr AutomationSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
    Ptr ApplicationInfo
result <- Ptr AutomationSession -> IO (Ptr ApplicationInfo)
webkit_automation_session_get_application_info Ptr AutomationSession
session'
    Maybe ApplicationInfo
maybeResult <- Ptr ApplicationInfo
-> (Ptr ApplicationInfo -> IO ApplicationInfo)
-> IO (Maybe ApplicationInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ApplicationInfo
result ((Ptr ApplicationInfo -> IO ApplicationInfo)
 -> IO (Maybe ApplicationInfo))
-> (Ptr ApplicationInfo -> IO ApplicationInfo)
-> IO (Maybe ApplicationInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr ApplicationInfo
result' -> do
        ApplicationInfo
result'' <- ((ManagedPtr ApplicationInfo -> ApplicationInfo)
-> Ptr ApplicationInfo -> IO ApplicationInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr ApplicationInfo -> ApplicationInfo
WebKit2.ApplicationInfo.ApplicationInfo) Ptr ApplicationInfo
result'
        ApplicationInfo -> IO ApplicationInfo
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
    Maybe ApplicationInfo -> IO (Maybe ApplicationInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplicationInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data AutomationSessionGetApplicationInfoMethodInfo
instance (signature ~ (m (Maybe WebKit2.ApplicationInfo.ApplicationInfo)), MonadIO m, IsAutomationSession a) => O.MethodInfo AutomationSessionGetApplicationInfoMethodInfo a signature where
    overloadedMethod = automationSessionGetApplicationInfo

#endif

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

foreign import ccall "webkit_automation_session_get_id" webkit_automation_session_get_id :: 
    Ptr AutomationSession ->                -- session : TInterface (Name {namespace = "WebKit2", name = "AutomationSession"})
    IO CString

-- | Get the unique identifier of a t'GI.WebKit2.Objects.AutomationSession.AutomationSession'
-- 
-- /Since: 2.18/
automationSessionGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsAutomationSession a) =>
    a
    -- ^ /@session@/: a t'GI.WebKit2.Objects.AutomationSession.AutomationSession'
    -> m T.Text
    -- ^ __Returns:__ the unique identifier of /@session@/
automationSessionGetId :: a -> m Text
automationSessionGetId session :: a
session = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr AutomationSession
session' <- a -> IO (Ptr AutomationSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
    CString
result <- Ptr AutomationSession -> IO CString
webkit_automation_session_get_id Ptr AutomationSession
session'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "automationSessionGetId" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data AutomationSessionGetIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAutomationSession a) => O.MethodInfo AutomationSessionGetIdMethodInfo a signature where
    overloadedMethod = automationSessionGetId

#endif

-- method AutomationSession::set_application_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "session"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "AutomationSession" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitAutomationSession"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "ApplicationInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitApplicationInfo"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_automation_session_set_application_info" webkit_automation_session_set_application_info :: 
    Ptr AutomationSession ->                -- session : TInterface (Name {namespace = "WebKit2", name = "AutomationSession"})
    Ptr WebKit2.ApplicationInfo.ApplicationInfo -> -- info : TInterface (Name {namespace = "WebKit2", name = "ApplicationInfo"})
    IO ()

-- | Set the application information to /@session@/. This information will be used by the driver service
-- to match the requested capabilities with the actual application information. If this information
-- is not provided to the session when a new automation session is requested, the creation might fail
-- if the client requested a specific browser name or version. This will not have any effect when called
-- after the automation session has been fully created, so this must be called in the callback of
-- [automationStarted]("GI.WebKit2.Objects.WebContext#signal:automationStarted") signal.
-- 
-- /Since: 2.18/
automationSessionSetApplicationInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsAutomationSession a) =>
    a
    -- ^ /@session@/: a t'GI.WebKit2.Objects.AutomationSession.AutomationSession'
    -> WebKit2.ApplicationInfo.ApplicationInfo
    -- ^ /@info@/: a t'GI.WebKit2.Structs.ApplicationInfo.ApplicationInfo'
    -> m ()
automationSessionSetApplicationInfo :: a -> ApplicationInfo -> m ()
automationSessionSetApplicationInfo session :: a
session info :: ApplicationInfo
info = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AutomationSession
session' <- a -> IO (Ptr AutomationSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
    Ptr ApplicationInfo
info' <- ApplicationInfo -> IO (Ptr ApplicationInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ApplicationInfo
info
    Ptr AutomationSession -> Ptr ApplicationInfo -> IO ()
webkit_automation_session_set_application_info Ptr AutomationSession
session' Ptr ApplicationInfo
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
    ApplicationInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ApplicationInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AutomationSessionSetApplicationInfoMethodInfo
instance (signature ~ (WebKit2.ApplicationInfo.ApplicationInfo -> m ()), MonadIO m, IsAutomationSession a) => O.MethodInfo AutomationSessionSetApplicationInfoMethodInfo a signature where
    overloadedMethod = automationSessionSetApplicationInfo

#endif