{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gio.Objects.SocketService.SocketService' is an object that represents a service that
-- is provided to the network or over local sockets.  When a new
-- connection is made to the service the [incoming]("GI.Gio.Objects.SocketService#signal:incoming")
-- signal is emitted.
-- 
-- A t'GI.Gio.Objects.SocketService.SocketService' is a subclass of t'GI.Gio.Objects.SocketListener.SocketListener' and you need
-- to add the addresses you want to accept connections on with the
-- t'GI.Gio.Objects.SocketListener.SocketListener' APIs.
-- 
-- There are two options for implementing a network service based on
-- t'GI.Gio.Objects.SocketService.SocketService'. The first is to create the service using
-- 'GI.Gio.Objects.SocketService.socketServiceNew' and to connect to the [incoming]("GI.Gio.Objects.SocketService#signal:incoming")
-- signal. The second is to subclass t'GI.Gio.Objects.SocketService.SocketService' and override the
-- default signal handler implementation.
-- 
-- In either case, the handler must immediately return, or else it
-- will block additional incoming connections from being serviced.
-- If you are interested in writing connection handlers that contain
-- blocking code then see t'GI.Gio.Objects.ThreadedSocketService.ThreadedSocketService'.
-- 
-- The socket service runs on the main loop of the
-- [thread-default context][g-main-context-push-thread-default-context]
-- of the thread it is created in, and is not
-- threadsafe in general. However, the calls to start and stop the
-- service are thread-safe so these can be used from threads that
-- handle incoming clients.
-- 
-- /Since: 2.22/

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

module GI.Gio.Objects.SocketService
    ( 

-- * Exported types
    SocketService(..)                       ,
    IsSocketService                         ,
    toSocketService                         ,
    noSocketService                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSocketServiceMethod              ,
#endif


-- ** isActive #method:isActive#

#if defined(ENABLE_OVERLOADING)
    SocketServiceIsActiveMethodInfo         ,
#endif
    socketServiceIsActive                   ,


-- ** new #method:new#

    socketServiceNew                        ,


-- ** start #method:start#

#if defined(ENABLE_OVERLOADING)
    SocketServiceStartMethodInfo            ,
#endif
    socketServiceStart                      ,


-- ** stop #method:stop#

#if defined(ENABLE_OVERLOADING)
    SocketServiceStopMethodInfo             ,
#endif
    socketServiceStop                       ,




 -- * Properties
-- ** active #attr:active#
-- | Whether the service is currently accepting connections.
-- 
-- /Since: 2.46/

#if defined(ENABLE_OVERLOADING)
    SocketServiceActivePropertyInfo         ,
#endif
    constructSocketServiceActive            ,
    getSocketServiceActive                  ,
    setSocketServiceActive                  ,
#if defined(ENABLE_OVERLOADING)
    socketServiceActive                     ,
#endif




 -- * Signals
-- ** incoming #signal:incoming#

    C_SocketServiceIncomingCallback         ,
    SocketServiceIncomingCallback           ,
#if defined(ENABLE_OVERLOADING)
    SocketServiceIncomingSignalInfo         ,
#endif
    afterSocketServiceIncoming              ,
    genClosure_SocketServiceIncoming        ,
    mk_SocketServiceIncomingCallback        ,
    noSocketServiceIncomingCallback         ,
    onSocketServiceIncoming                 ,
    wrap_SocketServiceIncomingCallback      ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

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

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

instance GObject SocketService where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_socket_service_get_type
    

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

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

instance O.HasParentTypes SocketService
type instance O.ParentTypes SocketService = '[Gio.SocketListener.SocketListener, GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `SocketService`.
noSocketService :: Maybe SocketService
noSocketService :: Maybe SocketService
noSocketService = Maybe SocketService
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketServiceMethod (t :: Symbol) (o :: *) :: * where
    ResolveSocketServiceMethod "accept" o = Gio.SocketListener.SocketListenerAcceptMethodInfo
    ResolveSocketServiceMethod "acceptAsync" o = Gio.SocketListener.SocketListenerAcceptAsyncMethodInfo
    ResolveSocketServiceMethod "acceptFinish" o = Gio.SocketListener.SocketListenerAcceptFinishMethodInfo
    ResolveSocketServiceMethod "acceptSocket" o = Gio.SocketListener.SocketListenerAcceptSocketMethodInfo
    ResolveSocketServiceMethod "acceptSocketAsync" o = Gio.SocketListener.SocketListenerAcceptSocketAsyncMethodInfo
    ResolveSocketServiceMethod "acceptSocketFinish" o = Gio.SocketListener.SocketListenerAcceptSocketFinishMethodInfo
    ResolveSocketServiceMethod "addAddress" o = Gio.SocketListener.SocketListenerAddAddressMethodInfo
    ResolveSocketServiceMethod "addAnyInetPort" o = Gio.SocketListener.SocketListenerAddAnyInetPortMethodInfo
    ResolveSocketServiceMethod "addInetPort" o = Gio.SocketListener.SocketListenerAddInetPortMethodInfo
    ResolveSocketServiceMethod "addSocket" o = Gio.SocketListener.SocketListenerAddSocketMethodInfo
    ResolveSocketServiceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketServiceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketServiceMethod "close" o = Gio.SocketListener.SocketListenerCloseMethodInfo
    ResolveSocketServiceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketServiceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketServiceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketServiceMethod "isActive" o = SocketServiceIsActiveMethodInfo
    ResolveSocketServiceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketServiceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketServiceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketServiceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketServiceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketServiceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketServiceMethod "start" o = SocketServiceStartMethodInfo
    ResolveSocketServiceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketServiceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketServiceMethod "stop" o = SocketServiceStopMethodInfo
    ResolveSocketServiceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketServiceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketServiceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketServiceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketServiceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketServiceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketServiceMethod "setBacklog" o = Gio.SocketListener.SocketListenerSetBacklogMethodInfo
    ResolveSocketServiceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketServiceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketServiceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketServiceMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal SocketService::incoming
-- | The [incoming](#signal:incoming) signal is emitted when a new incoming connection
-- to /@service@/ needs to be handled. The handler must initiate the
-- handling of /@connection@/, but may not block; in essence,
-- asynchronous operations must be used.
-- 
-- /@connection@/ will be unreffed once the signal handler returns,
-- so you need to ref it yourself if you are planning to use it.
-- 
-- /Since: 2.22/
type SocketServiceIncomingCallback =
    Gio.SocketConnection.SocketConnection
    -- ^ /@connection@/: a new t'GI.Gio.Objects.SocketConnection.SocketConnection' object
    -> Maybe GObject.Object.Object
    -- ^ /@sourceObject@/: the source_object passed to
    --     'GI.Gio.Objects.SocketListener.socketListenerAddAddress'
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to stop other handlers from being called

-- | A convenience synonym for @`Nothing` :: `Maybe` `SocketServiceIncomingCallback`@.
noSocketServiceIncomingCallback :: Maybe SocketServiceIncomingCallback
noSocketServiceIncomingCallback :: Maybe SocketServiceIncomingCallback
noSocketServiceIncomingCallback = Maybe SocketServiceIncomingCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SocketServiceIncomingCallback =
    Ptr () ->                               -- object
    Ptr Gio.SocketConnection.SocketConnection ->
    Ptr GObject.Object.Object ->
    Ptr () ->                               -- user_data
    IO CInt

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

-- | Wrap the callback into a `GClosure`.
genClosure_SocketServiceIncoming :: MonadIO m => SocketServiceIncomingCallback -> m (GClosure C_SocketServiceIncomingCallback)
genClosure_SocketServiceIncoming :: SocketServiceIncomingCallback
-> m (GClosure C_SocketServiceIncomingCallback)
genClosure_SocketServiceIncoming cb :: SocketServiceIncomingCallback
cb = IO (GClosure C_SocketServiceIncomingCallback)
-> m (GClosure C_SocketServiceIncomingCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SocketServiceIncomingCallback)
 -> m (GClosure C_SocketServiceIncomingCallback))
-> IO (GClosure C_SocketServiceIncomingCallback)
-> m (GClosure C_SocketServiceIncomingCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SocketServiceIncomingCallback
cb' = SocketServiceIncomingCallback -> C_SocketServiceIncomingCallback
wrap_SocketServiceIncomingCallback SocketServiceIncomingCallback
cb
    C_SocketServiceIncomingCallback
-> IO (FunPtr C_SocketServiceIncomingCallback)
mk_SocketServiceIncomingCallback C_SocketServiceIncomingCallback
cb' IO (FunPtr C_SocketServiceIncomingCallback)
-> (FunPtr C_SocketServiceIncomingCallback
    -> IO (GClosure C_SocketServiceIncomingCallback))
-> IO (GClosure C_SocketServiceIncomingCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SocketServiceIncomingCallback
-> IO (GClosure C_SocketServiceIncomingCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SocketServiceIncomingCallback` into a `C_SocketServiceIncomingCallback`.
wrap_SocketServiceIncomingCallback ::
    SocketServiceIncomingCallback ->
    C_SocketServiceIncomingCallback
wrap_SocketServiceIncomingCallback :: SocketServiceIncomingCallback -> C_SocketServiceIncomingCallback
wrap_SocketServiceIncomingCallback _cb :: SocketServiceIncomingCallback
_cb _ connection :: Ptr SocketConnection
connection sourceObject :: Ptr Object
sourceObject _ = do
    SocketConnection
connection' <- ((ManagedPtr SocketConnection -> SocketConnection)
-> Ptr SocketConnection -> IO SocketConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SocketConnection -> SocketConnection
Gio.SocketConnection.SocketConnection) Ptr SocketConnection
connection
    Maybe Object
maybeSourceObject <-
        if Ptr Object
sourceObject Ptr Object -> Ptr Object -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Object
forall a. Ptr a
nullPtr
        then Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
forall a. Maybe a
Nothing
        else do
            Object
sourceObject' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
sourceObject
            Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Object -> IO (Maybe Object))
-> Maybe Object -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ Object -> Maybe Object
forall a. a -> Maybe a
Just Object
sourceObject'
    Bool
result <- SocketServiceIncomingCallback
_cb  SocketConnection
connection' Maybe Object
maybeSourceObject
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [incoming](#signal:incoming) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' socketService #incoming callback
-- @
-- 
-- 
onSocketServiceIncoming :: (IsSocketService a, MonadIO m) => a -> SocketServiceIncomingCallback -> m SignalHandlerId
onSocketServiceIncoming :: a -> SocketServiceIncomingCallback -> m SignalHandlerId
onSocketServiceIncoming obj :: a
obj cb :: SocketServiceIncomingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SocketServiceIncomingCallback
cb' = SocketServiceIncomingCallback -> C_SocketServiceIncomingCallback
wrap_SocketServiceIncomingCallback SocketServiceIncomingCallback
cb
    FunPtr C_SocketServiceIncomingCallback
cb'' <- C_SocketServiceIncomingCallback
-> IO (FunPtr C_SocketServiceIncomingCallback)
mk_SocketServiceIncomingCallback C_SocketServiceIncomingCallback
cb'
    a
-> Text
-> FunPtr C_SocketServiceIncomingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "incoming" FunPtr C_SocketServiceIncomingCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [incoming](#signal:incoming) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' socketService #incoming callback
-- @
-- 
-- 
afterSocketServiceIncoming :: (IsSocketService a, MonadIO m) => a -> SocketServiceIncomingCallback -> m SignalHandlerId
afterSocketServiceIncoming :: a -> SocketServiceIncomingCallback -> m SignalHandlerId
afterSocketServiceIncoming obj :: a
obj cb :: SocketServiceIncomingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SocketServiceIncomingCallback
cb' = SocketServiceIncomingCallback -> C_SocketServiceIncomingCallback
wrap_SocketServiceIncomingCallback SocketServiceIncomingCallback
cb
    FunPtr C_SocketServiceIncomingCallback
cb'' <- C_SocketServiceIncomingCallback
-> IO (FunPtr C_SocketServiceIncomingCallback)
mk_SocketServiceIncomingCallback C_SocketServiceIncomingCallback
cb'
    a
-> Text
-> FunPtr C_SocketServiceIncomingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "incoming" FunPtr C_SocketServiceIncomingCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SocketServiceIncomingSignalInfo
instance SignalInfo SocketServiceIncomingSignalInfo where
    type HaskellCallbackType SocketServiceIncomingSignalInfo = SocketServiceIncomingCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SocketServiceIncomingCallback cb
        cb'' <- mk_SocketServiceIncomingCallback cb'
        connectSignalFunPtr obj "incoming" cb'' connectMode detail

#endif

-- VVV Prop "active"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@active@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socketService #active
-- @
getSocketServiceActive :: (MonadIO m, IsSocketService o) => o -> m Bool
getSocketServiceActive :: o -> m Bool
getSocketServiceActive obj :: o
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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "active"

-- | Set the value of the “@active@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socketService [ #active 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketServiceActive :: (MonadIO m, IsSocketService o) => o -> Bool -> m ()
setSocketServiceActive :: o -> Bool -> m ()
setSocketServiceActive obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "active" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@active@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketServiceActive :: (IsSocketService o) => Bool -> IO (GValueConstruct o)
constructSocketServiceActive :: Bool -> IO (GValueConstruct o)
constructSocketServiceActive val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "active" Bool
val

#if defined(ENABLE_OVERLOADING)
data SocketServiceActivePropertyInfo
instance AttrInfo SocketServiceActivePropertyInfo where
    type AttrAllowedOps SocketServiceActivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketServiceActivePropertyInfo = IsSocketService
    type AttrSetTypeConstraint SocketServiceActivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SocketServiceActivePropertyInfo = (~) Bool
    type AttrTransferType SocketServiceActivePropertyInfo = Bool
    type AttrGetType SocketServiceActivePropertyInfo = Bool
    type AttrLabel SocketServiceActivePropertyInfo = "active"
    type AttrOrigin SocketServiceActivePropertyInfo = SocketService
    attrGet = getSocketServiceActive
    attrSet = setSocketServiceActive
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketServiceActive
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SocketService
type instance O.AttributeList SocketService = SocketServiceAttributeList
type SocketServiceAttributeList = ('[ '("active", SocketServiceActivePropertyInfo), '("listenBacklog", Gio.SocketListener.SocketListenerListenBacklogPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
socketServiceActive :: AttrLabelProxy "active"
socketServiceActive = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SocketService = SocketServiceSignalList
type SocketServiceSignalList = ('[ '("event", Gio.SocketListener.SocketListenerEventSignalInfo), '("incoming", SocketServiceIncomingSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "g_socket_service_new" g_socket_service_new :: 
    IO (Ptr SocketService)

-- | Creates a new t'GI.Gio.Objects.SocketService.SocketService' with no sockets to listen for.
-- New listeners can be added with e.g. 'GI.Gio.Objects.SocketListener.socketListenerAddAddress'
-- or 'GI.Gio.Objects.SocketListener.socketListenerAddInetPort'.
-- 
-- New services are created active, there is no need to call
-- 'GI.Gio.Objects.SocketService.socketServiceStart', unless 'GI.Gio.Objects.SocketService.socketServiceStop' has been
-- called before.
-- 
-- /Since: 2.22/
socketServiceNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SocketService
    -- ^ __Returns:__ a new t'GI.Gio.Objects.SocketService.SocketService'.
socketServiceNew :: m SocketService
socketServiceNew  = IO SocketService -> m SocketService
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketService -> m SocketService)
-> IO SocketService -> m SocketService
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketService
result <- IO (Ptr SocketService)
g_socket_service_new
    Text -> Ptr SocketService -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "socketServiceNew" Ptr SocketService
result
    SocketService
result' <- ((ManagedPtr SocketService -> SocketService)
-> Ptr SocketService -> IO SocketService
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketService -> SocketService
SocketService) Ptr SocketService
result
    SocketService -> IO SocketService
forall (m :: * -> *) a. Monad m => a -> m a
return SocketService
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SocketService::is_active
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketService" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketService" , 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 "g_socket_service_is_active" g_socket_service_is_active :: 
    Ptr SocketService ->                    -- service : TInterface (Name {namespace = "Gio", name = "SocketService"})
    IO CInt

-- | Check whether the service is active or not. An active
-- service will accept new clients that connect, while
-- a non-active service will let connecting clients queue
-- up until the service is started.
-- 
-- /Since: 2.22/
socketServiceIsActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketService a) =>
    a
    -- ^ /@service@/: a t'GI.Gio.Objects.SocketService.SocketService'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the service is active, 'P.False' otherwise
socketServiceIsActive :: a -> m Bool
socketServiceIsActive service :: a
service = 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 SocketService
service' <- a -> IO (Ptr SocketService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    CInt
result <- Ptr SocketService -> IO CInt
g_socket_service_is_active Ptr SocketService
service'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SocketServiceIsActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocketService a) => O.MethodInfo SocketServiceIsActiveMethodInfo a signature where
    overloadedMethod = socketServiceIsActive

#endif

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

foreign import ccall "g_socket_service_start" g_socket_service_start :: 
    Ptr SocketService ->                    -- service : TInterface (Name {namespace = "Gio", name = "SocketService"})
    IO ()

-- | Restarts the service, i.e. start accepting connections
-- from the added sockets when the mainloop runs. This only needs
-- to be called after the service has been stopped from
-- 'GI.Gio.Objects.SocketService.socketServiceStop'.
-- 
-- This call is thread-safe, so it may be called from a thread
-- handling an incoming client request.
-- 
-- /Since: 2.22/
socketServiceStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketService a) =>
    a
    -- ^ /@service@/: a t'GI.Gio.Objects.SocketService.SocketService'
    -> m ()
socketServiceStart :: a -> m ()
socketServiceStart service :: a
service = 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 SocketService
service' <- a -> IO (Ptr SocketService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    Ptr SocketService -> IO ()
g_socket_service_start Ptr SocketService
service'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SocketServiceStartMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocketService a) => O.MethodInfo SocketServiceStartMethodInfo a signature where
    overloadedMethod = socketServiceStart

#endif

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

foreign import ccall "g_socket_service_stop" g_socket_service_stop :: 
    Ptr SocketService ->                    -- service : TInterface (Name {namespace = "Gio", name = "SocketService"})
    IO ()

-- | Stops the service, i.e. stops accepting connections
-- from the added sockets when the mainloop runs.
-- 
-- This call is thread-safe, so it may be called from a thread
-- handling an incoming client request.
-- 
-- Note that this only stops accepting new connections; it does not
-- close the listening sockets, and you can call
-- 'GI.Gio.Objects.SocketService.socketServiceStart' again later to begin listening again. To
-- close the listening sockets, call 'GI.Gio.Objects.SocketListener.socketListenerClose'. (This
-- will happen automatically when the t'GI.Gio.Objects.SocketService.SocketService' is finalized.)
-- 
-- This must be called before calling 'GI.Gio.Objects.SocketListener.socketListenerClose' as
-- the socket service will start accepting connections immediately
-- when a new socket is added.
-- 
-- /Since: 2.22/
socketServiceStop ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketService a) =>
    a
    -- ^ /@service@/: a t'GI.Gio.Objects.SocketService.SocketService'
    -> m ()
socketServiceStop :: a -> m ()
socketServiceStop service :: a
service = 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 SocketService
service' <- a -> IO (Ptr SocketService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    Ptr SocketService -> IO ()
g_socket_service_stop Ptr SocketService
service'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SocketServiceStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocketService a) => O.MethodInfo SocketServiceStopMethodInfo a signature where
    overloadedMethod = socketServiceStop

#endif