{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gio.Objects.SocketClient
    ( 

-- * Exported types
    SocketClient(..)                        ,
    SocketClientK                           ,
    toSocketClient                          ,
    noSocketClient                          ,


 -- * Methods
-- ** socketClientAddApplicationProxy
    socketClientAddApplicationProxy         ,


-- ** socketClientConnect
    socketClientConnect                     ,


-- ** socketClientConnectAsync
    socketClientConnectAsync                ,


-- ** socketClientConnectFinish
    socketClientConnectFinish               ,


-- ** socketClientConnectToHost
    socketClientConnectToHost               ,


-- ** socketClientConnectToHostAsync
    socketClientConnectToHostAsync          ,


-- ** socketClientConnectToHostFinish
    socketClientConnectToHostFinish         ,


-- ** socketClientConnectToService
    socketClientConnectToService            ,


-- ** socketClientConnectToServiceAsync
    socketClientConnectToServiceAsync       ,


-- ** socketClientConnectToServiceFinish
    socketClientConnectToServiceFinish      ,


-- ** socketClientConnectToUri
    socketClientConnectToUri                ,


-- ** socketClientConnectToUriAsync
    socketClientConnectToUriAsync           ,


-- ** socketClientConnectToUriFinish
    socketClientConnectToUriFinish          ,


-- ** socketClientGetEnableProxy
    socketClientGetEnableProxy              ,


-- ** socketClientGetFamily
    socketClientGetFamily                   ,


-- ** socketClientGetLocalAddress
    socketClientGetLocalAddress             ,


-- ** socketClientGetProtocol
    socketClientGetProtocol                 ,


-- ** socketClientGetProxyResolver
    socketClientGetProxyResolver            ,


-- ** socketClientGetSocketType
    socketClientGetSocketType               ,


-- ** socketClientGetTimeout
    socketClientGetTimeout                  ,


-- ** socketClientGetTls
    socketClientGetTls                      ,


-- ** socketClientGetTlsValidationFlags
    socketClientGetTlsValidationFlags       ,


-- ** socketClientNew
    socketClientNew                         ,


-- ** socketClientSetEnableProxy
    socketClientSetEnableProxy              ,


-- ** socketClientSetFamily
    socketClientSetFamily                   ,


-- ** socketClientSetLocalAddress
    socketClientSetLocalAddress             ,


-- ** socketClientSetProtocol
    socketClientSetProtocol                 ,


-- ** socketClientSetProxyResolver
    socketClientSetProxyResolver            ,


-- ** socketClientSetSocketType
    socketClientSetSocketType               ,


-- ** socketClientSetTimeout
    socketClientSetTimeout                  ,


-- ** socketClientSetTls
    socketClientSetTls                      ,


-- ** socketClientSetTlsValidationFlags
    socketClientSetTlsValidationFlags       ,




 -- * Properties
-- ** EnableProxy
    SocketClientEnableProxyPropertyInfo     ,
    constructSocketClientEnableProxy        ,
    getSocketClientEnableProxy              ,
    setSocketClientEnableProxy              ,


-- ** Family
    SocketClientFamilyPropertyInfo          ,
    constructSocketClientFamily             ,
    getSocketClientFamily                   ,
    setSocketClientFamily                   ,


-- ** LocalAddress
    SocketClientLocalAddressPropertyInfo    ,
    constructSocketClientLocalAddress       ,
    getSocketClientLocalAddress             ,
    setSocketClientLocalAddress             ,


-- ** Protocol
    SocketClientProtocolPropertyInfo        ,
    constructSocketClientProtocol           ,
    getSocketClientProtocol                 ,
    setSocketClientProtocol                 ,


-- ** ProxyResolver
    SocketClientProxyResolverPropertyInfo   ,
    constructSocketClientProxyResolver      ,
    getSocketClientProxyResolver            ,
    setSocketClientProxyResolver            ,


-- ** Timeout
    SocketClientTimeoutPropertyInfo         ,
    constructSocketClientTimeout            ,
    getSocketClientTimeout                  ,
    setSocketClientTimeout                  ,


-- ** Tls
    SocketClientTlsPropertyInfo             ,
    constructSocketClientTls                ,
    getSocketClientTls                      ,
    setSocketClientTls                      ,


-- ** TlsValidationFlags
    SocketClientTlsValidationFlagsPropertyInfo,
    constructSocketClientTlsValidationFlags ,
    getSocketClientTlsValidationFlags       ,
    setSocketClientTlsValidationFlags       ,


-- ** Type
    SocketClientTypePropertyInfo            ,
    constructSocketClientType               ,
    getSocketClientType                     ,
    setSocketClientType                     ,




 -- * Signals
-- ** Event
    SocketClientEventCallback               ,
    SocketClientEventCallbackC              ,
    SocketClientEventSignalInfo             ,
    afterSocketClientEvent                  ,
    mkSocketClientEventCallback             ,
    noSocketClientEventCallback             ,
    onSocketClientEvent                     ,
    socketClientEventCallbackWrapper        ,
    socketClientEventClosure                ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GObject as GObject

newtype SocketClient = SocketClient (ForeignPtr SocketClient)
foreign import ccall "g_socket_client_get_type"
    c_g_socket_client_get_type :: IO GType

type instance ParentTypes SocketClient = SocketClientParentTypes
type SocketClientParentTypes = '[GObject.Object]

instance GObject SocketClient where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_socket_client_get_type
    

class GObject o => SocketClientK o
instance (GObject o, IsDescendantOf SocketClient o) => SocketClientK o

toSocketClient :: SocketClientK o => o -> IO SocketClient
toSocketClient = unsafeCastTo SocketClient

noSocketClient :: Maybe SocketClient
noSocketClient = Nothing

-- signal SocketClient::event
type SocketClientEventCallback =
    SocketClientEvent ->
    SocketConnectable ->
    IOStream ->
    IO ()

noSocketClientEventCallback :: Maybe SocketClientEventCallback
noSocketClientEventCallback = Nothing

type SocketClientEventCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Ptr SocketConnectable ->
    Ptr IOStream ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkSocketClientEventCallback :: SocketClientEventCallbackC -> IO (FunPtr SocketClientEventCallbackC)

socketClientEventClosure :: SocketClientEventCallback -> IO Closure
socketClientEventClosure cb = newCClosure =<< mkSocketClientEventCallback wrapped
    where wrapped = socketClientEventCallbackWrapper cb

socketClientEventCallbackWrapper ::
    SocketClientEventCallback ->
    Ptr () ->
    CUInt ->
    Ptr SocketConnectable ->
    Ptr IOStream ->
    Ptr () ->
    IO ()
socketClientEventCallbackWrapper _cb _ event connectable connection _ = do
    let event' = (toEnum . fromIntegral) event
    connectable' <- (newObject SocketConnectable) connectable
    connection' <- (newObject IOStream) connection
    _cb  event' connectable' connection'

onSocketClientEvent :: (GObject a, MonadIO m) => a -> SocketClientEventCallback -> m SignalHandlerId
onSocketClientEvent obj cb = liftIO $ connectSocketClientEvent obj cb SignalConnectBefore
afterSocketClientEvent :: (GObject a, MonadIO m) => a -> SocketClientEventCallback -> m SignalHandlerId
afterSocketClientEvent obj cb = connectSocketClientEvent obj cb SignalConnectAfter

connectSocketClientEvent :: (GObject a, MonadIO m) =>
                            a -> SocketClientEventCallback -> SignalConnectMode -> m SignalHandlerId
connectSocketClientEvent obj cb after = liftIO $ do
    cb' <- mkSocketClientEventCallback (socketClientEventCallbackWrapper cb)
    connectSignalFunPtr obj "event" cb' after

-- VVV Prop "enable-proxy"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientEnableProxy :: (MonadIO m, SocketClientK o) => o -> m Bool
getSocketClientEnableProxy obj = liftIO $ getObjectPropertyBool obj "enable-proxy"

setSocketClientEnableProxy :: (MonadIO m, SocketClientK o) => o -> Bool -> m ()
setSocketClientEnableProxy obj val = liftIO $ setObjectPropertyBool obj "enable-proxy" val

constructSocketClientEnableProxy :: Bool -> IO ([Char], GValue)
constructSocketClientEnableProxy val = constructObjectPropertyBool "enable-proxy" val

data SocketClientEnableProxyPropertyInfo
instance AttrInfo SocketClientEnableProxyPropertyInfo where
    type AttrAllowedOps SocketClientEnableProxyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientEnableProxyPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint SocketClientEnableProxyPropertyInfo = SocketClientK
    type AttrGetType SocketClientEnableProxyPropertyInfo = Bool
    type AttrLabel SocketClientEnableProxyPropertyInfo = "SocketClient::enable-proxy"
    attrGet _ = getSocketClientEnableProxy
    attrSet _ = setSocketClientEnableProxy
    attrConstruct _ = constructSocketClientEnableProxy

-- VVV Prop "family"
   -- Type: TInterface "Gio" "SocketFamily"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientFamily :: (MonadIO m, SocketClientK o) => o -> m SocketFamily
getSocketClientFamily obj = liftIO $ getObjectPropertyEnum obj "family"

setSocketClientFamily :: (MonadIO m, SocketClientK o) => o -> SocketFamily -> m ()
setSocketClientFamily obj val = liftIO $ setObjectPropertyEnum obj "family" val

constructSocketClientFamily :: SocketFamily -> IO ([Char], GValue)
constructSocketClientFamily val = constructObjectPropertyEnum "family" val

data SocketClientFamilyPropertyInfo
instance AttrInfo SocketClientFamilyPropertyInfo where
    type AttrAllowedOps SocketClientFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientFamilyPropertyInfo = (~) SocketFamily
    type AttrBaseTypeConstraint SocketClientFamilyPropertyInfo = SocketClientK
    type AttrGetType SocketClientFamilyPropertyInfo = SocketFamily
    type AttrLabel SocketClientFamilyPropertyInfo = "SocketClient::family"
    attrGet _ = getSocketClientFamily
    attrSet _ = setSocketClientFamily
    attrConstruct _ = constructSocketClientFamily

-- VVV Prop "local-address"
   -- Type: TInterface "Gio" "SocketAddress"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientLocalAddress :: (MonadIO m, SocketClientK o) => o -> m SocketAddress
getSocketClientLocalAddress obj = liftIO $ getObjectPropertyObject obj "local-address" SocketAddress

setSocketClientLocalAddress :: (MonadIO m, SocketClientK o, SocketAddressK a) => o -> a -> m ()
setSocketClientLocalAddress obj val = liftIO $ setObjectPropertyObject obj "local-address" val

constructSocketClientLocalAddress :: (SocketAddressK a) => a -> IO ([Char], GValue)
constructSocketClientLocalAddress val = constructObjectPropertyObject "local-address" val

data SocketClientLocalAddressPropertyInfo
instance AttrInfo SocketClientLocalAddressPropertyInfo where
    type AttrAllowedOps SocketClientLocalAddressPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientLocalAddressPropertyInfo = SocketAddressK
    type AttrBaseTypeConstraint SocketClientLocalAddressPropertyInfo = SocketClientK
    type AttrGetType SocketClientLocalAddressPropertyInfo = SocketAddress
    type AttrLabel SocketClientLocalAddressPropertyInfo = "SocketClient::local-address"
    attrGet _ = getSocketClientLocalAddress
    attrSet _ = setSocketClientLocalAddress
    attrConstruct _ = constructSocketClientLocalAddress

-- VVV Prop "protocol"
   -- Type: TInterface "Gio" "SocketProtocol"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientProtocol :: (MonadIO m, SocketClientK o) => o -> m SocketProtocol
getSocketClientProtocol obj = liftIO $ getObjectPropertyEnum obj "protocol"

setSocketClientProtocol :: (MonadIO m, SocketClientK o) => o -> SocketProtocol -> m ()
setSocketClientProtocol obj val = liftIO $ setObjectPropertyEnum obj "protocol" val

constructSocketClientProtocol :: SocketProtocol -> IO ([Char], GValue)
constructSocketClientProtocol val = constructObjectPropertyEnum "protocol" val

data SocketClientProtocolPropertyInfo
instance AttrInfo SocketClientProtocolPropertyInfo where
    type AttrAllowedOps SocketClientProtocolPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientProtocolPropertyInfo = (~) SocketProtocol
    type AttrBaseTypeConstraint SocketClientProtocolPropertyInfo = SocketClientK
    type AttrGetType SocketClientProtocolPropertyInfo = SocketProtocol
    type AttrLabel SocketClientProtocolPropertyInfo = "SocketClient::protocol"
    attrGet _ = getSocketClientProtocol
    attrSet _ = setSocketClientProtocol
    attrConstruct _ = constructSocketClientProtocol

-- VVV Prop "proxy-resolver"
   -- Type: TInterface "Gio" "ProxyResolver"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientProxyResolver :: (MonadIO m, SocketClientK o) => o -> m ProxyResolver
getSocketClientProxyResolver obj = liftIO $ getObjectPropertyObject obj "proxy-resolver" ProxyResolver

setSocketClientProxyResolver :: (MonadIO m, SocketClientK o, ProxyResolverK a) => o -> a -> m ()
setSocketClientProxyResolver obj val = liftIO $ setObjectPropertyObject obj "proxy-resolver" val

constructSocketClientProxyResolver :: (ProxyResolverK a) => a -> IO ([Char], GValue)
constructSocketClientProxyResolver val = constructObjectPropertyObject "proxy-resolver" val

data SocketClientProxyResolverPropertyInfo
instance AttrInfo SocketClientProxyResolverPropertyInfo where
    type AttrAllowedOps SocketClientProxyResolverPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientProxyResolverPropertyInfo = ProxyResolverK
    type AttrBaseTypeConstraint SocketClientProxyResolverPropertyInfo = SocketClientK
    type AttrGetType SocketClientProxyResolverPropertyInfo = ProxyResolver
    type AttrLabel SocketClientProxyResolverPropertyInfo = "SocketClient::proxy-resolver"
    attrGet _ = getSocketClientProxyResolver
    attrSet _ = setSocketClientProxyResolver
    attrConstruct _ = constructSocketClientProxyResolver

-- VVV Prop "timeout"
   -- Type: TBasicType TUInt32
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientTimeout :: (MonadIO m, SocketClientK o) => o -> m Word32
getSocketClientTimeout obj = liftIO $ getObjectPropertyCUInt obj "timeout"

setSocketClientTimeout :: (MonadIO m, SocketClientK o) => o -> Word32 -> m ()
setSocketClientTimeout obj val = liftIO $ setObjectPropertyCUInt obj "timeout" val

constructSocketClientTimeout :: Word32 -> IO ([Char], GValue)
constructSocketClientTimeout val = constructObjectPropertyCUInt "timeout" val

data SocketClientTimeoutPropertyInfo
instance AttrInfo SocketClientTimeoutPropertyInfo where
    type AttrAllowedOps SocketClientTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientTimeoutPropertyInfo = (~) Word32
    type AttrBaseTypeConstraint SocketClientTimeoutPropertyInfo = SocketClientK
    type AttrGetType SocketClientTimeoutPropertyInfo = Word32
    type AttrLabel SocketClientTimeoutPropertyInfo = "SocketClient::timeout"
    attrGet _ = getSocketClientTimeout
    attrSet _ = setSocketClientTimeout
    attrConstruct _ = constructSocketClientTimeout

-- VVV Prop "tls"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientTls :: (MonadIO m, SocketClientK o) => o -> m Bool
getSocketClientTls obj = liftIO $ getObjectPropertyBool obj "tls"

setSocketClientTls :: (MonadIO m, SocketClientK o) => o -> Bool -> m ()
setSocketClientTls obj val = liftIO $ setObjectPropertyBool obj "tls" val

constructSocketClientTls :: Bool -> IO ([Char], GValue)
constructSocketClientTls val = constructObjectPropertyBool "tls" val

data SocketClientTlsPropertyInfo
instance AttrInfo SocketClientTlsPropertyInfo where
    type AttrAllowedOps SocketClientTlsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientTlsPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint SocketClientTlsPropertyInfo = SocketClientK
    type AttrGetType SocketClientTlsPropertyInfo = Bool
    type AttrLabel SocketClientTlsPropertyInfo = "SocketClient::tls"
    attrGet _ = getSocketClientTls
    attrSet _ = setSocketClientTls
    attrConstruct _ = constructSocketClientTls

-- VVV Prop "tls-validation-flags"
   -- Type: TInterface "Gio" "TlsCertificateFlags"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientTlsValidationFlags :: (MonadIO m, SocketClientK o) => o -> m [TlsCertificateFlags]
getSocketClientTlsValidationFlags obj = liftIO $ getObjectPropertyFlags obj "tls-validation-flags"

setSocketClientTlsValidationFlags :: (MonadIO m, SocketClientK o) => o -> [TlsCertificateFlags] -> m ()
setSocketClientTlsValidationFlags obj val = liftIO $ setObjectPropertyFlags obj "tls-validation-flags" val

constructSocketClientTlsValidationFlags :: [TlsCertificateFlags] -> IO ([Char], GValue)
constructSocketClientTlsValidationFlags val = constructObjectPropertyFlags "tls-validation-flags" val

data SocketClientTlsValidationFlagsPropertyInfo
instance AttrInfo SocketClientTlsValidationFlagsPropertyInfo where
    type AttrAllowedOps SocketClientTlsValidationFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientTlsValidationFlagsPropertyInfo = (~) [TlsCertificateFlags]
    type AttrBaseTypeConstraint SocketClientTlsValidationFlagsPropertyInfo = SocketClientK
    type AttrGetType SocketClientTlsValidationFlagsPropertyInfo = [TlsCertificateFlags]
    type AttrLabel SocketClientTlsValidationFlagsPropertyInfo = "SocketClient::tls-validation-flags"
    attrGet _ = getSocketClientTlsValidationFlags
    attrSet _ = setSocketClientTlsValidationFlags
    attrConstruct _ = constructSocketClientTlsValidationFlags

-- VVV Prop "type"
   -- Type: TInterface "Gio" "SocketType"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSocketClientType :: (MonadIO m, SocketClientK o) => o -> m SocketType
getSocketClientType obj = liftIO $ getObjectPropertyEnum obj "type"

setSocketClientType :: (MonadIO m, SocketClientK o) => o -> SocketType -> m ()
setSocketClientType obj val = liftIO $ setObjectPropertyEnum obj "type" val

constructSocketClientType :: SocketType -> IO ([Char], GValue)
constructSocketClientType val = constructObjectPropertyEnum "type" val

data SocketClientTypePropertyInfo
instance AttrInfo SocketClientTypePropertyInfo where
    type AttrAllowedOps SocketClientTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SocketClientTypePropertyInfo = (~) SocketType
    type AttrBaseTypeConstraint SocketClientTypePropertyInfo = SocketClientK
    type AttrGetType SocketClientTypePropertyInfo = SocketType
    type AttrLabel SocketClientTypePropertyInfo = "SocketClient::type"
    attrGet _ = getSocketClientType
    attrSet _ = setSocketClientType
    attrConstruct _ = constructSocketClientType

type instance AttributeList SocketClient = SocketClientAttributeList
type SocketClientAttributeList = ('[ '("enable-proxy", SocketClientEnableProxyPropertyInfo), '("family", SocketClientFamilyPropertyInfo), '("local-address", SocketClientLocalAddressPropertyInfo), '("protocol", SocketClientProtocolPropertyInfo), '("proxy-resolver", SocketClientProxyResolverPropertyInfo), '("timeout", SocketClientTimeoutPropertyInfo), '("tls", SocketClientTlsPropertyInfo), '("tls-validation-flags", SocketClientTlsValidationFlagsPropertyInfo), '("type", SocketClientTypePropertyInfo)] :: [(Symbol, *)])

data SocketClientEventSignalInfo
instance SignalInfo SocketClientEventSignalInfo where
    type HaskellCallbackType SocketClientEventSignalInfo = SocketClientEventCallback
    connectSignal _ = connectSocketClientEvent

type instance SignalList SocketClient = SocketClientSignalList
type SocketClientSignalList = ('[ '("event", SocketClientEventSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method SocketClient::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gio" "SocketClient"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_new" g_socket_client_new :: 
    IO (Ptr SocketClient)


socketClientNew ::
    (MonadIO m) =>
    m SocketClient
socketClientNew  = liftIO $ do
    result <- g_socket_client_new
    checkUnexpectedReturnNULL "g_socket_client_new" result
    result' <- (wrapObject SocketClient) result
    return result'

-- method SocketClient::add_application_proxy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_add_application_proxy" g_socket_client_add_application_proxy :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- protocol : TBasicType TUTF8
    IO ()


socketClientAddApplicationProxy ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- protocol
    m ()
socketClientAddApplicationProxy _obj protocol = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    protocol' <- textToCString protocol
    g_socket_client_add_application_proxy _obj' protocol'
    touchManagedPtr _obj
    freeMem protocol'
    return ()

-- method SocketClient::connect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "connectable", argType = TInterface "Gio" "SocketConnectable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "connectable", argType = TInterface "Gio" "SocketConnectable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect" g_socket_client_connect :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr SocketConnectable ->                -- connectable : TInterface "Gio" "SocketConnectable"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnect ::
    (MonadIO m, SocketClientK a, SocketConnectableK b, CancellableK c) =>
    a ->                                    -- _obj
    b ->                                    -- connectable
    Maybe (c) ->                            -- cancellable
    m SocketConnection
socketClientConnect _obj connectable cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let connectable' = unsafeManagedPtrCastPtr connectable
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_client_connect _obj' connectable' maybeCancellable
        checkUnexpectedReturnNULL "g_socket_client_connect" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        touchManagedPtr connectable
        whenJust cancellable touchManagedPtr
        return result'
     ) (do
        return ()
     )

-- method SocketClient::connect_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "connectable", argType = TInterface "Gio" "SocketConnectable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "connectable", argType = TInterface "Gio" "SocketConnectable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_connect_async" g_socket_client_connect_async :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr SocketConnectable ->                -- connectable : TInterface "Gio" "SocketConnectable"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


socketClientConnectAsync ::
    (MonadIO m, SocketClientK a, SocketConnectableK b, CancellableK c) =>
    a ->                                    -- _obj
    b ->                                    -- connectable
    Maybe (c) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
socketClientConnectAsync _obj connectable cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let connectable' = unsafeManagedPtrCastPtr connectable
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_socket_client_connect_async _obj' connectable' maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    touchManagedPtr connectable
    whenJust cancellable touchManagedPtr
    return ()

-- method SocketClient::connect_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_finish" g_socket_client_connect_finish :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectFinish ::
    (MonadIO m, SocketClientK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m SocketConnection
socketClientConnectFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    onException (do
        result <- propagateGError $ g_socket_client_connect_finish _obj' result_'
        checkUnexpectedReturnNULL "g_socket_client_connect_finish" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        touchManagedPtr result_
        return result'
     ) (do
        return ()
     )

-- method SocketClient::connect_to_host
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host_and_port", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host_and_port", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_host" g_socket_client_connect_to_host :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- host_and_port : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToHost ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- host_and_port
    Word16 ->                               -- default_port
    Maybe (b) ->                            -- cancellable
    m SocketConnection
socketClientConnectToHost _obj host_and_port default_port cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    host_and_port' <- textToCString host_and_port
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_host _obj' host_and_port' default_port maybeCancellable
        checkUnexpectedReturnNULL "g_socket_client_connect_to_host" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem host_and_port'
        return result'
     ) (do
        freeMem host_and_port'
     )

-- method SocketClient::connect_to_host_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host_and_port", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host_and_port", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_host_async" g_socket_client_connect_to_host_async :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- host_and_port : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


socketClientConnectToHostAsync ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- host_and_port
    Word16 ->                               -- default_port
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
socketClientConnectToHostAsync _obj host_and_port default_port cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    host_and_port' <- textToCString host_and_port
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_socket_client_connect_to_host_async _obj' host_and_port' default_port maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    freeMem host_and_port'
    return ()

-- method SocketClient::connect_to_host_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_host_finish" g_socket_client_connect_to_host_finish :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToHostFinish ::
    (MonadIO m, SocketClientK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m SocketConnection
socketClientConnectToHostFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_host_finish _obj' result_'
        checkUnexpectedReturnNULL "g_socket_client_connect_to_host_finish" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        touchManagedPtr result_
        return result'
     ) (do
        return ()
     )

-- method SocketClient::connect_to_service
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "service", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "service", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_service" g_socket_client_connect_to_service :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- service : TBasicType TUTF8
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToService ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- domain
    T.Text ->                               -- service
    Maybe (b) ->                            -- cancellable
    m SocketConnection
socketClientConnectToService _obj domain service cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    domain' <- textToCString domain
    service' <- textToCString service
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_service _obj' domain' service' maybeCancellable
        checkUnexpectedReturnNULL "g_socket_client_connect_to_service" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem domain'
        freeMem service'
        return result'
     ) (do
        freeMem domain'
        freeMem service'
     )

-- method SocketClient::connect_to_service_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "service", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "service", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_service_async" g_socket_client_connect_to_service_async :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- service : TBasicType TUTF8
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


socketClientConnectToServiceAsync ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- domain
    T.Text ->                               -- service
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
socketClientConnectToServiceAsync _obj domain service cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    domain' <- textToCString domain
    service' <- textToCString service
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_socket_client_connect_to_service_async _obj' domain' service' maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    freeMem domain'
    freeMem service'
    return ()

-- method SocketClient::connect_to_service_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_service_finish" g_socket_client_connect_to_service_finish :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToServiceFinish ::
    (MonadIO m, SocketClientK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m SocketConnection
socketClientConnectToServiceFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_service_finish _obj' result_'
        checkUnexpectedReturnNULL "g_socket_client_connect_to_service_finish" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        touchManagedPtr result_
        return result'
     ) (do
        return ()
     )

-- method SocketClient::connect_to_uri
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_uri" g_socket_client_connect_to_uri :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- uri : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToUri ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- uri
    Word16 ->                               -- default_port
    Maybe (b) ->                            -- cancellable
    m SocketConnection
socketClientConnectToUri _obj uri default_port cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    uri' <- textToCString uri
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_uri _obj' uri' default_port maybeCancellable
        checkUnexpectedReturnNULL "g_socket_client_connect_to_uri" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem uri'
        return result'
     ) (do
        freeMem uri'
     )

-- method SocketClient::connect_to_uri_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "default_port", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_uri_async" g_socket_client_connect_to_uri_async :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CString ->                              -- uri : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


socketClientConnectToUriAsync ::
    (MonadIO m, SocketClientK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- uri
    Word16 ->                               -- default_port
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
socketClientConnectToUriAsync _obj uri default_port cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    uri' <- textToCString uri
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_socket_client_connect_to_uri_async _obj' uri' default_port maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    freeMem uri'
    return ()

-- method SocketClient::connect_to_uri_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketConnection"
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_client_connect_to_uri_finish" g_socket_client_connect_to_uri_finish :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SocketConnection)


socketClientConnectToUriFinish ::
    (MonadIO m, SocketClientK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m SocketConnection
socketClientConnectToUriFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    onException (do
        result <- propagateGError $ g_socket_client_connect_to_uri_finish _obj' result_'
        checkUnexpectedReturnNULL "g_socket_client_connect_to_uri_finish" result
        result' <- (wrapObject SocketConnection) result
        touchManagedPtr _obj
        touchManagedPtr result_
        return result'
     ) (do
        return ()
     )

-- method SocketClient::get_enable_proxy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_enable_proxy" g_socket_client_get_enable_proxy :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CInt


socketClientGetEnableProxy ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m Bool
socketClientGetEnableProxy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_enable_proxy _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_family
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketFamily"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_family" g_socket_client_get_family :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CUInt


socketClientGetFamily ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m SocketFamily
socketClientGetFamily _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_family _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_local_address
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketAddress"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_local_address" g_socket_client_get_local_address :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO (Ptr SocketAddress)


socketClientGetLocalAddress ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m SocketAddress
socketClientGetLocalAddress _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_local_address _obj'
    checkUnexpectedReturnNULL "g_socket_client_get_local_address" result
    result' <- (newObject SocketAddress) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_protocol
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketProtocol"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_protocol" g_socket_client_get_protocol :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CUInt


socketClientGetProtocol ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m SocketProtocol
socketClientGetProtocol _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_protocol _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_proxy_resolver
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "ProxyResolver"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_proxy_resolver" g_socket_client_get_proxy_resolver :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO (Ptr ProxyResolver)


socketClientGetProxyResolver ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m ProxyResolver
socketClientGetProxyResolver _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_proxy_resolver _obj'
    checkUnexpectedReturnNULL "g_socket_client_get_proxy_resolver" result
    result' <- (newObject ProxyResolver) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_socket_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SocketType"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_socket_type" g_socket_client_get_socket_type :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CUInt


socketClientGetSocketType ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m SocketType
socketClientGetSocketType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_socket_type _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_timeout
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_timeout" g_socket_client_get_timeout :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO Word32


socketClientGetTimeout ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m Word32
socketClientGetTimeout _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_timeout _obj'
    touchManagedPtr _obj
    return result

-- method SocketClient::get_tls
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_tls" g_socket_client_get_tls :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CInt


socketClientGetTls ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m Bool
socketClientGetTls _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_tls _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method SocketClient::get_tls_validation_flags
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "TlsCertificateFlags"
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_get_tls_validation_flags" g_socket_client_get_tls_validation_flags :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    IO CUInt


socketClientGetTlsValidationFlags ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    m [TlsCertificateFlags]
socketClientGetTlsValidationFlags _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_socket_client_get_tls_validation_flags _obj'
    let result' = wordToGFlags result
    touchManagedPtr _obj
    return result'

-- method SocketClient::set_enable_proxy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "enable", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "enable", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_enable_proxy" g_socket_client_set_enable_proxy :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CInt ->                                 -- enable : TBasicType TBoolean
    IO ()


socketClientSetEnableProxy ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- enable
    m ()
socketClientSetEnableProxy _obj enable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let enable' = (fromIntegral . fromEnum) enable
    g_socket_client_set_enable_proxy _obj' enable'
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_family
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "family", argType = TInterface "Gio" "SocketFamily", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "family", argType = TInterface "Gio" "SocketFamily", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_family" g_socket_client_set_family :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CUInt ->                                -- family : TInterface "Gio" "SocketFamily"
    IO ()


socketClientSetFamily ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    SocketFamily ->                         -- family
    m ()
socketClientSetFamily _obj family = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let family' = (fromIntegral . fromEnum) family
    g_socket_client_set_family _obj' family'
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_local_address
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_local_address" g_socket_client_set_local_address :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr SocketAddress ->                    -- address : TInterface "Gio" "SocketAddress"
    IO ()


socketClientSetLocalAddress ::
    (MonadIO m, SocketClientK a, SocketAddressK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- address
    m ()
socketClientSetLocalAddress _obj address = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeAddress <- case address of
        Nothing -> return nullPtr
        Just jAddress -> do
            let jAddress' = unsafeManagedPtrCastPtr jAddress
            return jAddress'
    g_socket_client_set_local_address _obj' maybeAddress
    touchManagedPtr _obj
    whenJust address touchManagedPtr
    return ()

-- method SocketClient::set_protocol
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TInterface "Gio" "SocketProtocol", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TInterface "Gio" "SocketProtocol", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_protocol" g_socket_client_set_protocol :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CUInt ->                                -- protocol : TInterface "Gio" "SocketProtocol"
    IO ()


socketClientSetProtocol ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    SocketProtocol ->                       -- protocol
    m ()
socketClientSetProtocol _obj protocol = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let protocol' = (fromIntegral . fromEnum) protocol
    g_socket_client_set_protocol _obj' protocol'
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_proxy_resolver
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "proxy_resolver", argType = TInterface "Gio" "ProxyResolver", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "proxy_resolver", argType = TInterface "Gio" "ProxyResolver", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_proxy_resolver" g_socket_client_set_proxy_resolver :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Ptr ProxyResolver ->                    -- proxy_resolver : TInterface "Gio" "ProxyResolver"
    IO ()


socketClientSetProxyResolver ::
    (MonadIO m, SocketClientK a, ProxyResolverK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- proxy_resolver
    m ()
socketClientSetProxyResolver _obj proxy_resolver = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeProxy_resolver <- case proxy_resolver of
        Nothing -> return nullPtr
        Just jProxy_resolver -> do
            let jProxy_resolver' = unsafeManagedPtrCastPtr jProxy_resolver
            return jProxy_resolver'
    g_socket_client_set_proxy_resolver _obj' maybeProxy_resolver
    touchManagedPtr _obj
    whenJust proxy_resolver touchManagedPtr
    return ()

-- method SocketClient::set_socket_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gio" "SocketType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gio" "SocketType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_socket_type" g_socket_client_set_socket_type :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CUInt ->                                -- type : TInterface "Gio" "SocketType"
    IO ()


socketClientSetSocketType ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    SocketType ->                           -- type
    m ()
socketClientSetSocketType _obj type_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let type_' = (fromIntegral . fromEnum) type_
    g_socket_client_set_socket_type _obj' type_'
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_timeout
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_timeout" g_socket_client_set_timeout :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    Word32 ->                               -- timeout : TBasicType TUInt32
    IO ()


socketClientSetTimeout ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    Word32 ->                               -- timeout
    m ()
socketClientSetTimeout _obj timeout = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    g_socket_client_set_timeout _obj' timeout
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_tls
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tls", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tls", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_tls" g_socket_client_set_tls :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CInt ->                                 -- tls : TBasicType TBoolean
    IO ()


socketClientSetTls ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- tls
    m ()
socketClientSetTls _obj tls = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let tls' = (fromIntegral . fromEnum) tls
    g_socket_client_set_tls _obj' tls'
    touchManagedPtr _obj
    return ()

-- method SocketClient::set_tls_validation_flags
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gio" "TlsCertificateFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SocketClient", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gio" "TlsCertificateFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_client_set_tls_validation_flags" g_socket_client_set_tls_validation_flags :: 
    Ptr SocketClient ->                     -- _obj : TInterface "Gio" "SocketClient"
    CUInt ->                                -- flags : TInterface "Gio" "TlsCertificateFlags"
    IO ()


socketClientSetTlsValidationFlags ::
    (MonadIO m, SocketClientK a) =>
    a ->                                    -- _obj
    [TlsCertificateFlags] ->                -- flags
    m ()
socketClientSetTlsValidationFlags _obj flags = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let flags' = gflagsToWord flags
    g_socket_client_set_tls_validation_flags _obj' flags'
    touchManagedPtr _obj
    return ()