{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.SocketAddressEnumerator
(
SocketAddressEnumerator(..) ,
IsSocketAddressEnumerator ,
toSocketAddressEnumerator ,
noSocketAddressEnumerator ,
#if defined(ENABLE_OVERLOADING)
ResolveSocketAddressEnumeratorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketAddressEnumeratorNextMethodInfo ,
#endif
socketAddressEnumeratorNext ,
#if defined(ENABLE_OVERLOADING)
SocketAddressEnumeratorNextAsyncMethodInfo,
#endif
socketAddressEnumeratorNextAsync ,
#if defined(ENABLE_OVERLOADING)
SocketAddressEnumeratorNextFinishMethodInfo,
#endif
socketAddressEnumeratorNextFinish ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
newtype SocketAddressEnumerator = SocketAddressEnumerator (ManagedPtr SocketAddressEnumerator)
deriving (SocketAddressEnumerator -> SocketAddressEnumerator -> Bool
(SocketAddressEnumerator -> SocketAddressEnumerator -> Bool)
-> (SocketAddressEnumerator -> SocketAddressEnumerator -> Bool)
-> Eq SocketAddressEnumerator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketAddressEnumerator -> SocketAddressEnumerator -> Bool
$c/= :: SocketAddressEnumerator -> SocketAddressEnumerator -> Bool
== :: SocketAddressEnumerator -> SocketAddressEnumerator -> Bool
$c== :: SocketAddressEnumerator -> SocketAddressEnumerator -> Bool
Eq)
foreign import ccall "g_socket_address_enumerator_get_type"
c_g_socket_address_enumerator_get_type :: IO GType
instance GObject SocketAddressEnumerator where
gobjectType :: IO GType
gobjectType = IO GType
c_g_socket_address_enumerator_get_type
instance B.GValue.IsGValue SocketAddressEnumerator where
toGValue :: SocketAddressEnumerator -> IO GValue
toGValue o :: SocketAddressEnumerator
o = do
GType
gtype <- IO GType
c_g_socket_address_enumerator_get_type
SocketAddressEnumerator
-> (Ptr SocketAddressEnumerator -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SocketAddressEnumerator
o (GType
-> (GValue -> Ptr SocketAddressEnumerator -> IO ())
-> Ptr SocketAddressEnumerator
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SocketAddressEnumerator -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO SocketAddressEnumerator
fromGValue gv :: GValue
gv = do
Ptr SocketAddressEnumerator
ptr <- GValue -> IO (Ptr SocketAddressEnumerator)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SocketAddressEnumerator)
(ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator)
-> Ptr SocketAddressEnumerator -> IO SocketAddressEnumerator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator
SocketAddressEnumerator Ptr SocketAddressEnumerator
ptr
class (GObject o, O.IsDescendantOf SocketAddressEnumerator o) => IsSocketAddressEnumerator o
instance (GObject o, O.IsDescendantOf SocketAddressEnumerator o) => IsSocketAddressEnumerator o
instance O.HasParentTypes SocketAddressEnumerator
type instance O.ParentTypes SocketAddressEnumerator = '[GObject.Object.Object]
toSocketAddressEnumerator :: (MonadIO m, IsSocketAddressEnumerator o) => o -> m SocketAddressEnumerator
toSocketAddressEnumerator :: o -> m SocketAddressEnumerator
toSocketAddressEnumerator = IO SocketAddressEnumerator -> m SocketAddressEnumerator
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddressEnumerator -> m SocketAddressEnumerator)
-> (o -> IO SocketAddressEnumerator)
-> o
-> m SocketAddressEnumerator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator)
-> o -> IO SocketAddressEnumerator
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr SocketAddressEnumerator -> SocketAddressEnumerator
SocketAddressEnumerator
noSocketAddressEnumerator :: Maybe SocketAddressEnumerator
noSocketAddressEnumerator :: Maybe SocketAddressEnumerator
noSocketAddressEnumerator = Maybe SocketAddressEnumerator
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSocketAddressEnumeratorMethod (t :: Symbol) (o :: *) :: * where
ResolveSocketAddressEnumeratorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSocketAddressEnumeratorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSocketAddressEnumeratorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSocketAddressEnumeratorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSocketAddressEnumeratorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSocketAddressEnumeratorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSocketAddressEnumeratorMethod "next" o = SocketAddressEnumeratorNextMethodInfo
ResolveSocketAddressEnumeratorMethod "nextAsync" o = SocketAddressEnumeratorNextAsyncMethodInfo
ResolveSocketAddressEnumeratorMethod "nextFinish" o = SocketAddressEnumeratorNextFinishMethodInfo
ResolveSocketAddressEnumeratorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSocketAddressEnumeratorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSocketAddressEnumeratorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSocketAddressEnumeratorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSocketAddressEnumeratorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSocketAddressEnumeratorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSocketAddressEnumeratorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSocketAddressEnumeratorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSocketAddressEnumeratorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSocketAddressEnumeratorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSocketAddressEnumeratorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSocketAddressEnumeratorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSocketAddressEnumeratorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSocketAddressEnumeratorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSocketAddressEnumeratorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSocketAddressEnumeratorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSocketAddressEnumeratorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSocketAddressEnumeratorMethod t SocketAddressEnumerator, O.MethodInfo info SocketAddressEnumerator p) => OL.IsLabel t (SocketAddressEnumerator -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SocketAddressEnumerator
type instance O.AttributeList SocketAddressEnumerator = SocketAddressEnumeratorAttributeList
type SocketAddressEnumeratorAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SocketAddressEnumerator = SocketAddressEnumeratorSignalList
type SocketAddressEnumeratorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_socket_address_enumerator_next" g_socket_address_enumerator_next ::
Ptr SocketAddressEnumerator ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr Gio.SocketAddress.SocketAddress)
socketAddressEnumeratorNext ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddressEnumerator a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m Gio.SocketAddress.SocketAddress
socketAddressEnumeratorNext :: a -> Maybe b -> m SocketAddress
socketAddressEnumeratorNext enumerator :: a
enumerator cancellable :: Maybe b
cancellable = IO SocketAddress -> m SocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddress -> m SocketAddress)
-> IO SocketAddress -> m SocketAddress
forall a b. (a -> b) -> a -> b
$ do
Ptr SocketAddressEnumerator
enumerator' <- a -> IO (Ptr SocketAddressEnumerator)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
enumerator
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO SocketAddress -> IO () -> IO SocketAddress
forall a b. IO a -> IO b -> IO a
onException (do
Ptr SocketAddress
result <- (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress))
-> (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a b. (a -> b) -> a -> b
$ Ptr SocketAddressEnumerator
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr SocketAddress)
g_socket_address_enumerator_next Ptr SocketAddressEnumerator
enumerator' Ptr Cancellable
maybeCancellable
Text -> Ptr SocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "socketAddressEnumeratorNext" Ptr SocketAddress
result
SocketAddress
result' <- ((ManagedPtr SocketAddress -> SocketAddress)
-> Ptr SocketAddress -> IO SocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketAddress -> SocketAddress
Gio.SocketAddress.SocketAddress) Ptr SocketAddress
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
enumerator
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketAddressEnumeratorNextMethodInfo
instance (signature ~ (Maybe (b) -> m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocketAddressEnumerator a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketAddressEnumeratorNextMethodInfo a signature where
overloadedMethod = socketAddressEnumeratorNext
#endif
foreign import ccall "g_socket_address_enumerator_next_async" g_socket_address_enumerator_next_async ::
Ptr SocketAddressEnumerator ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
socketAddressEnumeratorNextAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddressEnumerator a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
socketAddressEnumeratorNextAsync :: a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
socketAddressEnumeratorNextAsync enumerator :: a
enumerator cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr SocketAddressEnumerator
enumerator' <- a -> IO (Ptr SocketAddressEnumerator)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
enumerator
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jCallback :: AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr SocketAddressEnumerator
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_socket_address_enumerator_next_async Ptr SocketAddressEnumerator
enumerator' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
enumerator
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketAddressEnumeratorNextAsyncMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsSocketAddressEnumerator a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketAddressEnumeratorNextAsyncMethodInfo a signature where
overloadedMethod = socketAddressEnumeratorNextAsync
#endif
foreign import ccall "g_socket_address_enumerator_next_finish" g_socket_address_enumerator_next_finish ::
Ptr SocketAddressEnumerator ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr Gio.SocketAddress.SocketAddress)
socketAddressEnumeratorNextFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddressEnumerator a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m Gio.SocketAddress.SocketAddress
socketAddressEnumeratorNextFinish :: a -> b -> m SocketAddress
socketAddressEnumeratorNextFinish enumerator :: a
enumerator result_ :: b
result_ = IO SocketAddress -> m SocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddress -> m SocketAddress)
-> IO SocketAddress -> m SocketAddress
forall a b. (a -> b) -> a -> b
$ do
Ptr SocketAddressEnumerator
enumerator' <- a -> IO (Ptr SocketAddressEnumerator)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
enumerator
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO SocketAddress -> IO () -> IO SocketAddress
forall a b. IO a -> IO b -> IO a
onException (do
Ptr SocketAddress
result <- (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress))
-> (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a b. (a -> b) -> a -> b
$ Ptr SocketAddressEnumerator
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr SocketAddress)
g_socket_address_enumerator_next_finish Ptr SocketAddressEnumerator
enumerator' Ptr AsyncResult
result_'
Text -> Ptr SocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "socketAddressEnumeratorNextFinish" Ptr SocketAddress
result
SocketAddress
result' <- ((ManagedPtr SocketAddress -> SocketAddress)
-> Ptr SocketAddress -> IO SocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketAddress -> SocketAddress
Gio.SocketAddress.SocketAddress) Ptr SocketAddress
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
enumerator
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketAddressEnumeratorNextFinishMethodInfo
instance (signature ~ (b -> m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocketAddressEnumerator a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo SocketAddressEnumeratorNextFinishMethodInfo a signature where
overloadedMethod = socketAddressEnumeratorNextFinish
#endif