{-# 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.SocketControlMessage.SocketControlMessage' is a special-purpose utility message that
-- can be sent to or received from a t'GI.Gio.Objects.Socket.Socket'. These types of
-- messages are often called \"ancillary data\".
-- 
-- The message can represent some sort of special instruction to or
-- information from the socket or can represent a special kind of
-- transfer to the peer (for example, sending a file descriptor over
-- a UNIX socket).
-- 
-- These messages are sent with 'GI.Gio.Objects.Socket.socketSendMessage' and received
-- with 'GI.Gio.Objects.Socket.socketReceiveMessage'.
-- 
-- To extend the set of control message that can be sent, subclass this
-- class and override the get_size, get_level, get_type and serialize
-- methods.
-- 
-- To extend the set of control messages that can be received, subclass
-- this class and implement the deserialize method. Also, make sure your
-- class is registered with the GType typesystem before calling
-- 'GI.Gio.Objects.Socket.socketReceiveMessage' to read such a message.
-- 
-- /Since: 2.22/

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

module GI.Gio.Objects.SocketControlMessage
    ( 

-- * Exported types
    SocketControlMessage(..)                ,
    IsSocketControlMessage                  ,
    toSocketControlMessage                  ,
    noSocketControlMessage                  ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSocketControlMessageMethod       ,
#endif


-- ** deserialize #method:deserialize#

    socketControlMessageDeserialize         ,


-- ** getLevel #method:getLevel#

#if defined(ENABLE_OVERLOADING)
    SocketControlMessageGetLevelMethodInfo  ,
#endif
    socketControlMessageGetLevel            ,


-- ** getMsgType #method:getMsgType#

#if defined(ENABLE_OVERLOADING)
    SocketControlMessageGetMsgTypeMethodInfo,
#endif
    socketControlMessageGetMsgType          ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    SocketControlMessageGetSizeMethodInfo   ,
#endif
    socketControlMessageGetSize             ,


-- ** serialize #method:serialize#

#if defined(ENABLE_OVERLOADING)
    SocketControlMessageSerializeMethodInfo ,
#endif
    socketControlMessageSerialize           ,




    ) 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 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 qualified GI.GObject.Objects.Object as GObject.Object

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

instance GObject SocketControlMessage where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_socket_control_message_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `SocketControlMessage`.
noSocketControlMessage :: Maybe SocketControlMessage
noSocketControlMessage :: Maybe SocketControlMessage
noSocketControlMessage = Maybe SocketControlMessage
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketControlMessageMethod (t :: Symbol) (o :: *) :: * where
    ResolveSocketControlMessageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketControlMessageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketControlMessageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketControlMessageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketControlMessageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketControlMessageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketControlMessageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketControlMessageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketControlMessageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketControlMessageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketControlMessageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketControlMessageMethod "serialize" o = SocketControlMessageSerializeMethodInfo
    ResolveSocketControlMessageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketControlMessageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketControlMessageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketControlMessageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketControlMessageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketControlMessageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketControlMessageMethod "getLevel" o = SocketControlMessageGetLevelMethodInfo
    ResolveSocketControlMessageMethod "getMsgType" o = SocketControlMessageGetMsgTypeMethodInfo
    ResolveSocketControlMessageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketControlMessageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketControlMessageMethod "getSize" o = SocketControlMessageGetSizeMethodInfo
    ResolveSocketControlMessageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketControlMessageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketControlMessageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketControlMessageMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSocketControlMessageMethod t SocketControlMessage, O.MethodInfo info SocketControlMessage p) => OL.IsLabel t (SocketControlMessage -> 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 SocketControlMessage
type instance O.AttributeList SocketControlMessage = SocketControlMessageAttributeList
type SocketControlMessageAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SocketControlMessage = SocketControlMessageSignalList
type SocketControlMessageSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "g_socket_control_message_get_level" g_socket_control_message_get_level :: 
    Ptr SocketControlMessage ->             -- message : TInterface (Name {namespace = "Gio", name = "SocketControlMessage"})
    IO Int32

-- | Returns the \"level\" (i.e. the originating protocol) of the control message.
-- This is often SOL_SOCKET.
-- 
-- /Since: 2.22/
socketControlMessageGetLevel ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketControlMessage a) =>
    a
    -- ^ /@message@/: a t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage'
    -> m Int32
    -- ^ __Returns:__ an integer describing the level
socketControlMessageGetLevel :: a -> m Int32
socketControlMessageGetLevel message :: a
message = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketControlMessage
message' <- a -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Int32
result <- Ptr SocketControlMessage -> IO Int32
g_socket_control_message_get_level Ptr SocketControlMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SocketControlMessageGetLevelMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocketControlMessage a) => O.MethodInfo SocketControlMessageGetLevelMethodInfo a signature where
    overloadedMethod = socketControlMessageGetLevel

#endif

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

foreign import ccall "g_socket_control_message_get_msg_type" g_socket_control_message_get_msg_type :: 
    Ptr SocketControlMessage ->             -- message : TInterface (Name {namespace = "Gio", name = "SocketControlMessage"})
    IO Int32

-- | Returns the protocol specific type of the control message.
-- For instance, for UNIX fd passing this would be SCM_RIGHTS.
-- 
-- /Since: 2.22/
socketControlMessageGetMsgType ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketControlMessage a) =>
    a
    -- ^ /@message@/: a t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage'
    -> m Int32
    -- ^ __Returns:__ an integer describing the type of control message
socketControlMessageGetMsgType :: a -> m Int32
socketControlMessageGetMsgType message :: a
message = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketControlMessage
message' <- a -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Int32
result <- Ptr SocketControlMessage -> IO Int32
g_socket_control_message_get_msg_type Ptr SocketControlMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SocketControlMessageGetMsgTypeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocketControlMessage a) => O.MethodInfo SocketControlMessageGetMsgTypeMethodInfo a signature where
    overloadedMethod = socketControlMessageGetMsgType

#endif

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

foreign import ccall "g_socket_control_message_get_size" g_socket_control_message_get_size :: 
    Ptr SocketControlMessage ->             -- message : TInterface (Name {namespace = "Gio", name = "SocketControlMessage"})
    IO Word64

-- | Returns the space required for the control message, not including
-- headers or alignment.
-- 
-- /Since: 2.22/
socketControlMessageGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketControlMessage a) =>
    a
    -- ^ /@message@/: a t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage'
    -> m Word64
    -- ^ __Returns:__ The number of bytes required.
socketControlMessageGetSize :: a -> m Word64
socketControlMessageGetSize message :: a
message = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr SocketControlMessage
message' <- a -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Word64
result <- Ptr SocketControlMessage -> IO Word64
g_socket_control_message_get_size Ptr SocketControlMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data SocketControlMessageGetSizeMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsSocketControlMessage a) => O.MethodInfo SocketControlMessageGetSizeMethodInfo a signature where
    overloadedMethod = socketControlMessageGetSize

#endif

-- method SocketControlMessage::serialize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SocketControlMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketControlMessage"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A buffer to write data to"
--                 , 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_control_message_serialize" g_socket_control_message_serialize :: 
    Ptr SocketControlMessage ->             -- message : TInterface (Name {namespace = "Gio", name = "SocketControlMessage"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | Converts the data in the message to bytes placed in the
-- message.
-- 
-- /@data@/ is guaranteed to have enough space to fit the size
-- returned by 'GI.Gio.Objects.SocketControlMessage.socketControlMessageGetSize' on this
-- object.
-- 
-- /Since: 2.22/
socketControlMessageSerialize ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocketControlMessage a) =>
    a
    -- ^ /@message@/: a t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage'
    -> Ptr ()
    -- ^ /@data@/: A buffer to write data to
    -> m ()
socketControlMessageSerialize :: a -> Ptr () -> m ()
socketControlMessageSerialize message :: a
message data_ :: Ptr ()
data_ = 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 SocketControlMessage
message' <- a -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr SocketControlMessage -> Ptr () -> IO ()
g_socket_control_message_serialize Ptr SocketControlMessage
message' Ptr ()
data_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SocketControlMessageSerializeMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m, IsSocketControlMessage a) => O.MethodInfo SocketControlMessageSerializeMethodInfo a signature where
    overloadedMethod = socketControlMessageSerialize

#endif

-- method SocketControlMessage::deserialize
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "level"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a socket level" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a socket control message type for the given @level"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the size of the data in bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the message data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the size of the data in bytes"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SocketControlMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_control_message_deserialize" g_socket_control_message_deserialize :: 
    Int32 ->                                -- level : TBasicType TInt
    Int32 ->                                -- type : TBasicType TInt
    Word64 ->                               -- size : TBasicType TUInt64
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    IO (Ptr SocketControlMessage)

-- | Tries to deserialize a socket control message of a given
-- /@level@/ and /@type@/. This will ask all known (to GType) subclasses
-- of t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage' if they can understand this kind
-- of message and if so deserialize it into a t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage'.
-- 
-- If there is no implementation for this kind of control message, 'P.Nothing'
-- will be returned.
-- 
-- /Since: 2.22/
socketControlMessageDeserialize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@level@/: a socket level
    -> Int32
    -- ^ /@type@/: a socket control message type for the given /@level@/
    -> ByteString
    -- ^ /@data@/: pointer to the message data
    -> m SocketControlMessage
    -- ^ __Returns:__ the deserialized message or 'P.Nothing'
socketControlMessageDeserialize :: Int32 -> Int32 -> ByteString -> m SocketControlMessage
socketControlMessageDeserialize level :: Int32
level type_ :: Int32
type_ data_ :: ByteString
data_ = IO SocketControlMessage -> m SocketControlMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketControlMessage -> m SocketControlMessage)
-> IO SocketControlMessage -> m SocketControlMessage
forall a b. (a -> b) -> a -> b
$ do
    let size :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    Ptr SocketControlMessage
result <- Int32
-> Int32 -> Word64 -> Ptr Word8 -> IO (Ptr SocketControlMessage)
g_socket_control_message_deserialize Int32
level Int32
type_ Word64
size Ptr Word8
data_'
    Text -> Ptr SocketControlMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "socketControlMessageDeserialize" Ptr SocketControlMessage
result
    SocketControlMessage
result' <- ((ManagedPtr SocketControlMessage -> SocketControlMessage)
-> Ptr SocketControlMessage -> IO SocketControlMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketControlMessage -> SocketControlMessage
SocketControlMessage) Ptr SocketControlMessage
result
    Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
    SocketControlMessage -> IO SocketControlMessage
forall (m :: * -> *) a. Monad m => a -> m a
return SocketControlMessage
result'

#if defined(ENABLE_OVERLOADING)
#endif