{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Together with t'GI.Atk.Objects.Plug.Plug', t'GI.Atk.Objects.Socket.Socket' provides the ability to embed
-- accessibles from one process into another in a fashion that is
-- transparent to assistive technologies. t'GI.Atk.Objects.Socket.Socket' works as the
-- container of t'GI.Atk.Objects.Plug.Plug', embedding it using the method
-- 'GI.Atk.Objects.Socket.socketEmbed'. Any accessible contained in the t'GI.Atk.Objects.Plug.Plug' will
-- appear to the assistive technologies as being inside the
-- application that created the t'GI.Atk.Objects.Socket.Socket'.
-- 
-- The communication between a t'GI.Atk.Objects.Socket.Socket' and a t'GI.Atk.Objects.Plug.Plug' is done by
-- the IPC layer of the accessibility framework, normally implemented
-- by the D-Bus based implementation of AT-SPI (at-spi2). If that is
-- the case, at-spi-atk2 is the responsible to implement the abstract
-- methods 'GI.Atk.Objects.Plug.plugGetId' and 'GI.Atk.Objects.Socket.socketEmbed', so an ATK
-- implementor shouldn\'t reimplement them. The process that contains
-- the t'GI.Atk.Objects.Plug.Plug' is responsible to send the ID returned by
-- @/atk_plug_id()/@ to the process that contains the t'GI.Atk.Objects.Socket.Socket', so it
-- could call the method 'GI.Atk.Objects.Socket.socketEmbed' in order to embed it.
-- 
-- For the same reasons, an implementor doesn\'t need to implement
-- 'GI.Atk.Objects.Object.objectGetNAccessibleChildren' and
-- 'GI.Atk.Objects.Object.objectRefAccessibleChild'. All the logic related to those
-- functions will be implemented by the IPC layer.

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

module GI.Atk.Objects.Socket
    ( 

-- * Exported types
    Socket(..)                              ,
    IsSocket                                ,
    toSocket                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSocketMethod                     ,
#endif


-- ** embed #method:embed#

#if defined(ENABLE_OVERLOADING)
    SocketEmbedMethodInfo                   ,
#endif
    socketEmbed                             ,


-- ** isOccupied #method:isOccupied#

#if defined(ENABLE_OVERLOADING)
    SocketIsOccupiedMethodInfo              ,
#endif
    socketIsOccupied                        ,


-- ** new #method:new#

    socketNew                               ,




    ) 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.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 Control.Monad.IO.Class as MIO
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 {-# SOURCE #-} qualified GI.Atk.Interfaces.Component as Atk.Component
import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "atk_socket_get_type"
    c_atk_socket_get_type :: IO B.Types.GType

instance B.Types.TypedObject Socket where
    glibType :: IO GType
glibType = IO GType
c_atk_socket_get_type

instance B.Types.GObject Socket

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

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

instance O.HasParentTypes Socket
type instance O.ParentTypes Socket = '[Atk.Object.Object, GObject.Object.Object, Atk.Component.Component]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketMethod (t :: Symbol) (o :: *) :: * where
    ResolveSocketMethod "addRelationship" o = Atk.Object.ObjectAddRelationshipMethodInfo
    ResolveSocketMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketMethod "contains" o = Atk.Component.ComponentContainsMethodInfo
    ResolveSocketMethod "embed" o = SocketEmbedMethodInfo
    ResolveSocketMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketMethod "grabFocus" o = Atk.Component.ComponentGrabFocusMethodInfo
    ResolveSocketMethod "initialize" o = Atk.Object.ObjectInitializeMethodInfo
    ResolveSocketMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketMethod "isOccupied" o = SocketIsOccupiedMethodInfo
    ResolveSocketMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketMethod "notifyStateChange" o = Atk.Object.ObjectNotifyStateChangeMethodInfo
    ResolveSocketMethod "peekParent" o = Atk.Object.ObjectPeekParentMethodInfo
    ResolveSocketMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketMethod "refAccessibleAtPoint" o = Atk.Component.ComponentRefAccessibleAtPointMethodInfo
    ResolveSocketMethod "refAccessibleChild" o = Atk.Object.ObjectRefAccessibleChildMethodInfo
    ResolveSocketMethod "refRelationSet" o = Atk.Object.ObjectRefRelationSetMethodInfo
    ResolveSocketMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketMethod "refStateSet" o = Atk.Object.ObjectRefStateSetMethodInfo
    ResolveSocketMethod "removeFocusHandler" o = Atk.Component.ComponentRemoveFocusHandlerMethodInfo
    ResolveSocketMethod "removePropertyChangeHandler" o = Atk.Object.ObjectRemovePropertyChangeHandlerMethodInfo
    ResolveSocketMethod "removeRelationship" o = Atk.Object.ObjectRemoveRelationshipMethodInfo
    ResolveSocketMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketMethod "scrollTo" o = Atk.Component.ComponentScrollToMethodInfo
    ResolveSocketMethod "scrollToPoint" o = Atk.Component.ComponentScrollToPointMethodInfo
    ResolveSocketMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketMethod "getAccessibleId" o = Atk.Object.ObjectGetAccessibleIdMethodInfo
    ResolveSocketMethod "getAlpha" o = Atk.Component.ComponentGetAlphaMethodInfo
    ResolveSocketMethod "getAttributes" o = Atk.Object.ObjectGetAttributesMethodInfo
    ResolveSocketMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketMethod "getDescription" o = Atk.Object.ObjectGetDescriptionMethodInfo
    ResolveSocketMethod "getExtents" o = Atk.Component.ComponentGetExtentsMethodInfo
    ResolveSocketMethod "getIndexInParent" o = Atk.Object.ObjectGetIndexInParentMethodInfo
    ResolveSocketMethod "getLayer" o = Atk.Object.ObjectGetLayerMethodInfo
    ResolveSocketMethod "getMdiZorder" o = Atk.Object.ObjectGetMdiZorderMethodInfo
    ResolveSocketMethod "getNAccessibleChildren" o = Atk.Object.ObjectGetNAccessibleChildrenMethodInfo
    ResolveSocketMethod "getName" o = Atk.Object.ObjectGetNameMethodInfo
    ResolveSocketMethod "getObjectLocale" o = Atk.Object.ObjectGetObjectLocaleMethodInfo
    ResolveSocketMethod "getParent" o = Atk.Object.ObjectGetParentMethodInfo
    ResolveSocketMethod "getPosition" o = Atk.Component.ComponentGetPositionMethodInfo
    ResolveSocketMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketMethod "getRole" o = Atk.Object.ObjectGetRoleMethodInfo
    ResolveSocketMethod "getSize" o = Atk.Component.ComponentGetSizeMethodInfo
    ResolveSocketMethod "setAccessibleId" o = Atk.Object.ObjectSetAccessibleIdMethodInfo
    ResolveSocketMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketMethod "setDescription" o = Atk.Object.ObjectSetDescriptionMethodInfo
    ResolveSocketMethod "setExtents" o = Atk.Component.ComponentSetExtentsMethodInfo
    ResolveSocketMethod "setName" o = Atk.Object.ObjectSetNameMethodInfo
    ResolveSocketMethod "setParent" o = Atk.Object.ObjectSetParentMethodInfo
    ResolveSocketMethod "setPosition" o = Atk.Component.ComponentSetPositionMethodInfo
    ResolveSocketMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketMethod "setRole" o = Atk.Object.ObjectSetRoleMethodInfo
    ResolveSocketMethod "setSize" o = Atk.Component.ComponentSetSizeMethodInfo
    ResolveSocketMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSocketMethod t Socket, O.MethodInfo info Socket p) => OL.IsLabel t (Socket -> 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 Socket
type instance O.AttributeList Socket = SocketAttributeList
type SocketAttributeList = ('[ '("accessibleComponentLayer", Atk.Object.ObjectAccessibleComponentLayerPropertyInfo), '("accessibleComponentMdiZorder", Atk.Object.ObjectAccessibleComponentMdiZorderPropertyInfo), '("accessibleDescription", Atk.Object.ObjectAccessibleDescriptionPropertyInfo), '("accessibleHypertextNlinks", Atk.Object.ObjectAccessibleHypertextNlinksPropertyInfo), '("accessibleName", Atk.Object.ObjectAccessibleNamePropertyInfo), '("accessibleParent", Atk.Object.ObjectAccessibleParentPropertyInfo), '("accessibleRole", Atk.Object.ObjectAccessibleRolePropertyInfo), '("accessibleTableCaption", Atk.Object.ObjectAccessibleTableCaptionPropertyInfo), '("accessibleTableCaptionObject", Atk.Object.ObjectAccessibleTableCaptionObjectPropertyInfo), '("accessibleTableColumnDescription", Atk.Object.ObjectAccessibleTableColumnDescriptionPropertyInfo), '("accessibleTableColumnHeader", Atk.Object.ObjectAccessibleTableColumnHeaderPropertyInfo), '("accessibleTableRowDescription", Atk.Object.ObjectAccessibleTableRowDescriptionPropertyInfo), '("accessibleTableRowHeader", Atk.Object.ObjectAccessibleTableRowHeaderPropertyInfo), '("accessibleTableSummary", Atk.Object.ObjectAccessibleTableSummaryPropertyInfo), '("accessibleValue", Atk.Object.ObjectAccessibleValuePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Socket = SocketSignalList
type SocketSignalList = ('[ '("activeDescendantChanged", Atk.Object.ObjectActiveDescendantChangedSignalInfo), '("boundsChanged", Atk.Component.ComponentBoundsChangedSignalInfo), '("childrenChanged", Atk.Object.ObjectChildrenChangedSignalInfo), '("focusEvent", Atk.Object.ObjectFocusEventSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("propertyChange", Atk.Object.ObjectPropertyChangeSignalInfo), '("stateChange", Atk.Object.ObjectStateChangeSignalInfo), '("visibleDataChanged", Atk.Object.ObjectVisibleDataChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Socket::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Socket" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_socket_new" atk_socket_new :: 
    IO (Ptr Socket)

-- | Creates a new t'GI.Atk.Objects.Socket.Socket'.
socketNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Socket
    -- ^ __Returns:__ the newly created t'GI.Atk.Objects.Socket.Socket' instance
socketNew :: m Socket
socketNew  = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
    Ptr Socket
result <- IO (Ptr Socket)
atk_socket_new
    Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketNew" Ptr Socket
result
    Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Socket -> Socket
Socket) Ptr Socket
result
    Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Socket::embed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "obj"
--           , argType = TInterface Name { namespace = "Atk" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plug_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the ID of an #AtkPlug"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_socket_embed" atk_socket_embed :: 
    Ptr Socket ->                           -- obj : TInterface (Name {namespace = "Atk", name = "Socket"})
    CString ->                              -- plug_id : TBasicType TUTF8
    IO ()

-- | Embeds the children of an t'GI.Atk.Objects.Plug.Plug' as the children of the
-- t'GI.Atk.Objects.Socket.Socket'. The plug may be in the same process or in a different
-- process.
-- 
-- The class item used by this function should be filled in by the IPC
-- layer (usually at-spi2-atk). The implementor of the AtkSocket
-- should call this function and pass the id for the plug as returned
-- by 'GI.Atk.Objects.Plug.plugGetId'.  It is the responsibility of the application
-- to pass the plug id on to the process implementing the t'GI.Atk.Objects.Socket.Socket'
-- as needed.
-- 
-- /Since: 1.30/
socketEmbed ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@obj@/: an t'GI.Atk.Objects.Socket.Socket'
    -> T.Text
    -- ^ /@plugId@/: the ID of an t'GI.Atk.Objects.Plug.Plug'
    -> m ()
socketEmbed :: a -> Text -> m ()
socketEmbed a
obj Text
plugId = 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 Socket
obj' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
    CString
plugId' <- Text -> IO CString
textToCString Text
plugId
    Ptr Socket -> CString -> IO ()
atk_socket_embed Ptr Socket
obj' CString
plugId'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
plugId'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SocketEmbedMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketEmbedMethodInfo a signature where
    overloadedMethod = socketEmbed

#endif

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

foreign import ccall "atk_socket_is_occupied" atk_socket_is_occupied :: 
    Ptr Socket ->                           -- obj : TInterface (Name {namespace = "Atk", name = "Socket"})
    IO CInt

-- | Determines whether or not the socket has an embedded plug.
-- 
-- /Since: 1.30/
socketIsOccupied ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@obj@/: an t'GI.Atk.Objects.Socket.Socket'
    -> m Bool
    -- ^ __Returns:__ TRUE if a plug is embedded in the socket
socketIsOccupied :: a -> m Bool
socketIsOccupied a
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Socket
obj' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
    CInt
result <- Ptr Socket -> IO CInt
atk_socket_is_occupied Ptr Socket
obj'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SocketIsOccupiedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketIsOccupiedMethodInfo a signature where
    overloadedMethod = socketIsOccupied

#endif