{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Objects that describe one or more potential socket endpoints
-- implement t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable'. Callers can then use
-- 'GI.Gio.Interfaces.SocketConnectable.socketConnectableEnumerate' to get a t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator'
-- to try out each socket address in turn until one succeeds, as shown
-- in the sample code below.
-- 
-- 
-- === /C code/
-- >
-- >MyConnectionType *
-- >connect_to_host (const char    *hostname,
-- >                 guint16        port,
-- >                 GCancellable  *cancellable,
-- >                 GError       **error)
-- >{
-- >  MyConnection *conn = NULL;
-- >  GSocketConnectable *addr;
-- >  GSocketAddressEnumerator *enumerator;
-- >  GSocketAddress *sockaddr;
-- >  GError *conn_error = NULL;
-- >
-- >  addr = g_network_address_new (hostname, port);
-- >  enumerator = g_socket_connectable_enumerate (addr);
-- >  g_object_unref (addr);
-- >
-- >  // Try each sockaddr until we succeed. Record the first connection error,
-- >  // but not any further ones (since they'll probably be basically the same
-- >  // as the first).
-- >  while (!conn && (sockaddr = g_socket_address_enumerator_next (enumerator, cancellable, error))
-- >    {
-- >      conn = connect_to_sockaddr (sockaddr, conn_error ? NULL : &conn_error);
-- >      g_object_unref (sockaddr);
-- >    }
-- >  g_object_unref (enumerator);
-- >
-- >  if (conn)
-- >    {
-- >      if (conn_error)
-- >        {
-- >          // We couldn't connect to the first address, but we succeeded
-- >          // in connecting to a later address.
-- >          g_error_free (conn_error);
-- >        }
-- >      return conn;
-- >    }
-- >  else if (error)
-- >    {
-- >      /// Either initial lookup failed, or else the caller cancelled us.
-- >      if (conn_error)
-- >        g_error_free (conn_error);
-- >      return NULL;
-- >    }
-- >  else
-- >    {
-- >      g_error_propagate (error, conn_error);
-- >      return NULL;
-- >    }
-- >}
-- 

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

module GI.Gio.Interfaces.SocketConnectable
    ( 

-- * Exported types
    SocketConnectable(..)                   ,
    IsSocketConnectable                     ,
    toSocketConnectable                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [enumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:enumerate"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [proxyEnumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:proxyEnumerate"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Interfaces.SocketConnectable#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveSocketConnectableMethod          ,
#endif

-- ** enumerate #method:enumerate#

#if defined(ENABLE_OVERLOADING)
    SocketConnectableEnumerateMethodInfo    ,
#endif
    socketConnectableEnumerate              ,


-- ** proxyEnumerate #method:proxyEnumerate#

#if defined(ENABLE_OVERLOADING)
    SocketConnectableProxyEnumerateMethodInfo,
#endif
    socketConnectableProxyEnumerate         ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    SocketConnectableToStringMethodInfo     ,
#endif
    socketConnectableToString               ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator

-- interface SocketConnectable 
-- | Memory-managed wrapper type.
newtype SocketConnectable = SocketConnectable (SP.ManagedPtr SocketConnectable)
    deriving (SocketConnectable -> SocketConnectable -> Bool
(SocketConnectable -> SocketConnectable -> Bool)
-> (SocketConnectable -> SocketConnectable -> Bool)
-> Eq SocketConnectable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SocketConnectable -> SocketConnectable -> Bool
== :: SocketConnectable -> SocketConnectable -> Bool
$c/= :: SocketConnectable -> SocketConnectable -> Bool
/= :: SocketConnectable -> SocketConnectable -> Bool
Eq)

instance SP.ManagedPtrNewtype SocketConnectable where
    toManagedPtr :: SocketConnectable -> ManagedPtr SocketConnectable
toManagedPtr (SocketConnectable ManagedPtr SocketConnectable
p) = ManagedPtr SocketConnectable
p

foreign import ccall "g_socket_connectable_get_type"
    c_g_socket_connectable_get_type :: IO B.Types.GType

instance B.Types.TypedObject SocketConnectable where
    glibType :: IO GType
glibType = IO GType
c_g_socket_connectable_get_type

instance B.Types.GObject SocketConnectable

-- | Type class for types which can be safely cast to `SocketConnectable`, for instance with `toSocketConnectable`.
class (SP.GObject o, O.IsDescendantOf SocketConnectable o) => IsSocketConnectable o
instance (SP.GObject o, O.IsDescendantOf SocketConnectable o) => IsSocketConnectable o

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

-- | Cast to `SocketConnectable`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSocketConnectable :: (MIO.MonadIO m, IsSocketConnectable o) => o -> m SocketConnectable
toSocketConnectable :: forall (m :: * -> *) o.
(MonadIO m, IsSocketConnectable o) =>
o -> m SocketConnectable
toSocketConnectable = IO SocketConnectable -> m SocketConnectable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SocketConnectable -> m SocketConnectable)
-> (o -> IO SocketConnectable) -> o -> m SocketConnectable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SocketConnectable -> SocketConnectable)
-> o -> IO SocketConnectable
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SocketConnectable -> SocketConnectable
SocketConnectable

-- | Convert 'SocketConnectable' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe SocketConnectable) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_socket_connectable_get_type
    gvalueSet_ :: Ptr GValue -> Maybe SocketConnectable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SocketConnectable
P.Nothing = Ptr GValue -> Ptr SocketConnectable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SocketConnectable
forall a. Ptr a
FP.nullPtr :: FP.Ptr SocketConnectable)
    gvalueSet_ Ptr GValue
gv (P.Just SocketConnectable
obj) = SocketConnectable -> (Ptr SocketConnectable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SocketConnectable
obj (Ptr GValue -> Ptr SocketConnectable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe SocketConnectable)
gvalueGet_ Ptr GValue
gv = do
        Ptr SocketConnectable
ptr <- Ptr GValue -> IO (Ptr SocketConnectable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SocketConnectable)
        if Ptr SocketConnectable
ptr Ptr SocketConnectable -> Ptr SocketConnectable -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SocketConnectable
forall a. Ptr a
FP.nullPtr
        then SocketConnectable -> Maybe SocketConnectable
forall a. a -> Maybe a
P.Just (SocketConnectable -> Maybe SocketConnectable)
-> IO SocketConnectable -> IO (Maybe SocketConnectable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SocketConnectable -> SocketConnectable)
-> Ptr SocketConnectable -> IO SocketConnectable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SocketConnectable -> SocketConnectable
SocketConnectable Ptr SocketConnectable
ptr
        else Maybe SocketConnectable -> IO (Maybe SocketConnectable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SocketConnectable
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SocketConnectable
type instance O.AttributeList SocketConnectable = SocketConnectableAttributeList
type SocketConnectableAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketConnectableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSocketConnectableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketConnectableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketConnectableMethod "enumerate" o = SocketConnectableEnumerateMethodInfo
    ResolveSocketConnectableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketConnectableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketConnectableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketConnectableMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketConnectableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketConnectableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketConnectableMethod "proxyEnumerate" o = SocketConnectableProxyEnumerateMethodInfo
    ResolveSocketConnectableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketConnectableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketConnectableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketConnectableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketConnectableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketConnectableMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketConnectableMethod "toString" o = SocketConnectableToStringMethodInfo
    ResolveSocketConnectableMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketConnectableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketConnectableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketConnectableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketConnectableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketConnectableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketConnectableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketConnectableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketConnectableMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSocketConnectableMethod t SocketConnectable, O.OverloadedMethod info SocketConnectable p, R.HasField t SocketConnectable p) => R.HasField t SocketConnectable p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveSocketConnectableMethod t SocketConnectable, O.OverloadedMethodInfo info SocketConnectable) => OL.IsLabel t (O.MethodProxy info SocketConnectable) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- method SocketConnectable::enumerate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "connectable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketConnectable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketConnectable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SocketAddressEnumerator" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_connectable_enumerate" g_socket_connectable_enumerate :: 
    Ptr SocketConnectable ->                -- connectable : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    IO (Ptr Gio.SocketAddressEnumerator.SocketAddressEnumerator)

-- | Creates a t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator' for /@connectable@/.
-- 
-- /Since: 2.22/
socketConnectableEnumerate ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketConnectable a) =>
    a
    -- ^ /@connectable@/: a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable'
    -> m Gio.SocketAddressEnumerator.SocketAddressEnumerator
    -- ^ __Returns:__ a new t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator'.
socketConnectableEnumerate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocketConnectable a) =>
a -> m SocketAddressEnumerator
socketConnectableEnumerate a
connectable = IO SocketAddressEnumerator -> m SocketAddressEnumerator
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddressEnumerator -> m SocketAddressEnumerator)
-> IO SocketAddressEnumerator -> m SocketAddressEnumerator
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketConnectable
connectable' <- a -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connectable
    Ptr SocketAddressEnumerator
result <- Ptr SocketConnectable -> IO (Ptr SocketAddressEnumerator)
g_socket_connectable_enumerate Ptr SocketConnectable
connectable'
    Text -> Ptr SocketAddressEnumerator -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketConnectableEnumerate" Ptr SocketAddressEnumerator
result
    SocketAddressEnumerator
result' <- ((ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator)
-> Ptr SocketAddressEnumerator -> IO SocketAddressEnumerator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator
Gio.SocketAddressEnumerator.SocketAddressEnumerator) Ptr SocketAddressEnumerator
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connectable
    SocketAddressEnumerator -> IO SocketAddressEnumerator
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddressEnumerator
result'

#if defined(ENABLE_OVERLOADING)
data SocketConnectableEnumerateMethodInfo
instance (signature ~ (m Gio.SocketAddressEnumerator.SocketAddressEnumerator), MonadIO m, IsSocketConnectable a) => O.OverloadedMethod SocketConnectableEnumerateMethodInfo a signature where
    overloadedMethod = socketConnectableEnumerate

instance O.OverloadedMethodInfo SocketConnectableEnumerateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.SocketConnectable.socketConnectableEnumerate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Interfaces-SocketConnectable.html#v:socketConnectableEnumerate"
        })


#endif

-- method SocketConnectable::proxy_enumerate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "connectable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketConnectable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketConnectable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SocketAddressEnumerator" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_connectable_proxy_enumerate" g_socket_connectable_proxy_enumerate :: 
    Ptr SocketConnectable ->                -- connectable : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    IO (Ptr Gio.SocketAddressEnumerator.SocketAddressEnumerator)

-- | Creates a t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator' for /@connectable@/ that will
-- return a t'GI.Gio.Objects.ProxyAddress.ProxyAddress' for each of its addresses that you must connect
-- to via a proxy.
-- 
-- If /@connectable@/ does not implement
-- 'GI.Gio.Interfaces.SocketConnectable.socketConnectableProxyEnumerate', this will fall back to
-- calling 'GI.Gio.Interfaces.SocketConnectable.socketConnectableEnumerate'.
-- 
-- /Since: 2.26/
socketConnectableProxyEnumerate ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketConnectable a) =>
    a
    -- ^ /@connectable@/: a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable'
    -> m Gio.SocketAddressEnumerator.SocketAddressEnumerator
    -- ^ __Returns:__ a new t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator'.
socketConnectableProxyEnumerate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocketConnectable a) =>
a -> m SocketAddressEnumerator
socketConnectableProxyEnumerate a
connectable = IO SocketAddressEnumerator -> m SocketAddressEnumerator
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddressEnumerator -> m SocketAddressEnumerator)
-> IO SocketAddressEnumerator -> m SocketAddressEnumerator
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketConnectable
connectable' <- a -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connectable
    Ptr SocketAddressEnumerator
result <- Ptr SocketConnectable -> IO (Ptr SocketAddressEnumerator)
g_socket_connectable_proxy_enumerate Ptr SocketConnectable
connectable'
    Text -> Ptr SocketAddressEnumerator -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketConnectableProxyEnumerate" Ptr SocketAddressEnumerator
result
    SocketAddressEnumerator
result' <- ((ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator)
-> Ptr SocketAddressEnumerator -> IO SocketAddressEnumerator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator
Gio.SocketAddressEnumerator.SocketAddressEnumerator) Ptr SocketAddressEnumerator
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connectable
    SocketAddressEnumerator -> IO SocketAddressEnumerator
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddressEnumerator
result'

#if defined(ENABLE_OVERLOADING)
data SocketConnectableProxyEnumerateMethodInfo
instance (signature ~ (m Gio.SocketAddressEnumerator.SocketAddressEnumerator), MonadIO m, IsSocketConnectable a) => O.OverloadedMethod SocketConnectableProxyEnumerateMethodInfo a signature where
    overloadedMethod = socketConnectableProxyEnumerate

instance O.OverloadedMethodInfo SocketConnectableProxyEnumerateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.SocketConnectable.socketConnectableProxyEnumerate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Interfaces-SocketConnectable.html#v:socketConnectableProxyEnumerate"
        })


#endif

-- method SocketConnectable::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "connectable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketConnectable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketConnectable"
--                 , 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 "g_socket_connectable_to_string" g_socket_connectable_to_string :: 
    Ptr SocketConnectable ->                -- connectable : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    IO CString

-- | Format a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' as a string. This is a human-readable format for
-- use in debugging output, and is not a stable serialization format. It is not
-- suitable for use in user interfaces as it exposes too much information for a
-- user.
-- 
-- If the t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' implementation does not support string formatting,
-- the implementation’s type name will be returned as a fallback.
-- 
-- /Since: 2.48/
socketConnectableToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketConnectable a) =>
    a
    -- ^ /@connectable@/: a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable'
    -> m T.Text
    -- ^ __Returns:__ the formatted string
socketConnectableToString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocketConnectable a) =>
a -> m Text
socketConnectableToString a
connectable = IO Text -> m Text
forall a. IO a -> m a
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 SocketConnectable
connectable' <- a -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connectable
    CString
result <- Ptr SocketConnectable -> IO CString
g_socket_connectable_to_string Ptr SocketConnectable
connectable'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketConnectableToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connectable
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SocketConnectableToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSocketConnectable a) => O.OverloadedMethod SocketConnectableToStringMethodInfo a signature where
    overloadedMethod = socketConnectableToString

instance O.OverloadedMethodInfo SocketConnectableToStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.SocketConnectable.socketConnectableToString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Interfaces-SocketConnectable.html#v:socketConnectableToString"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SocketConnectable = SocketConnectableSignalList
type SocketConnectableSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif