{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.SocketAddress
(
SocketAddress(..) ,
IsSocketAddress ,
toSocketAddress ,
#if defined(ENABLE_OVERLOADING)
ResolveSocketAddressMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketAddressGetFamilyMethodInfo ,
#endif
socketAddressGetFamily ,
#if defined(ENABLE_OVERLOADING)
SocketAddressGetNativeSizeMethodInfo ,
#endif
socketAddressGetNativeSize ,
socketAddressNewFromNative ,
#if defined(ENABLE_OVERLOADING)
SocketAddressToNativeMethodInfo ,
#endif
socketAddressToNative ,
#if defined(ENABLE_OVERLOADING)
SocketAddressFamilyPropertyInfo ,
#endif
getSocketAddressFamily ,
#if defined(ENABLE_OVERLOADING)
socketAddressFamily ,
#endif
) 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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
newtype SocketAddress = SocketAddress (SP.ManagedPtr SocketAddress)
deriving (SocketAddress -> SocketAddress -> Bool
(SocketAddress -> SocketAddress -> Bool)
-> (SocketAddress -> SocketAddress -> Bool) -> Eq SocketAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketAddress -> SocketAddress -> Bool
$c/= :: SocketAddress -> SocketAddress -> Bool
== :: SocketAddress -> SocketAddress -> Bool
$c== :: SocketAddress -> SocketAddress -> Bool
Eq)
instance SP.ManagedPtrNewtype SocketAddress where
toManagedPtr :: SocketAddress -> ManagedPtr SocketAddress
toManagedPtr (SocketAddress ManagedPtr SocketAddress
p) = ManagedPtr SocketAddress
p
foreign import ccall "g_socket_address_get_type"
c_g_socket_address_get_type :: IO B.Types.GType
instance B.Types.TypedObject SocketAddress where
glibType :: IO GType
glibType = IO GType
c_g_socket_address_get_type
instance B.Types.GObject SocketAddress
instance B.GValue.IsGValue SocketAddress where
toGValue :: SocketAddress -> IO GValue
toGValue SocketAddress
o = do
GType
gtype <- IO GType
c_g_socket_address_get_type
SocketAddress -> (Ptr SocketAddress -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SocketAddress
o (GType
-> (GValue -> Ptr SocketAddress -> IO ())
-> Ptr SocketAddress
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SocketAddress -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO SocketAddress
fromGValue GValue
gv = do
Ptr SocketAddress
ptr <- GValue -> IO (Ptr SocketAddress)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SocketAddress)
(ManagedPtr SocketAddress -> SocketAddress)
-> Ptr SocketAddress -> IO SocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SocketAddress -> SocketAddress
SocketAddress Ptr SocketAddress
ptr
class (SP.GObject o, O.IsDescendantOf SocketAddress o) => IsSocketAddress o
instance (SP.GObject o, O.IsDescendantOf SocketAddress o) => IsSocketAddress o
instance O.HasParentTypes SocketAddress
type instance O.ParentTypes SocketAddress = '[GObject.Object.Object, Gio.SocketConnectable.SocketConnectable]
toSocketAddress :: (MonadIO m, IsSocketAddress o) => o -> m SocketAddress
toSocketAddress :: o -> m SocketAddress
toSocketAddress = IO SocketAddress -> m SocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddress -> m SocketAddress)
-> (o -> IO SocketAddress) -> o -> m SocketAddress
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SocketAddress -> SocketAddress)
-> o -> IO SocketAddress
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr SocketAddress -> SocketAddress
SocketAddress
#if defined(ENABLE_OVERLOADING)
type family ResolveSocketAddressMethod (t :: Symbol) (o :: *) :: * where
ResolveSocketAddressMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSocketAddressMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSocketAddressMethod "enumerate" o = Gio.SocketConnectable.SocketConnectableEnumerateMethodInfo
ResolveSocketAddressMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSocketAddressMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSocketAddressMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSocketAddressMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSocketAddressMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSocketAddressMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSocketAddressMethod "proxyEnumerate" o = Gio.SocketConnectable.SocketConnectableProxyEnumerateMethodInfo
ResolveSocketAddressMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSocketAddressMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSocketAddressMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSocketAddressMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSocketAddressMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSocketAddressMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSocketAddressMethod "toNative" o = SocketAddressToNativeMethodInfo
ResolveSocketAddressMethod "toString" o = Gio.SocketConnectable.SocketConnectableToStringMethodInfo
ResolveSocketAddressMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSocketAddressMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSocketAddressMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSocketAddressMethod "getFamily" o = SocketAddressGetFamilyMethodInfo
ResolveSocketAddressMethod "getNativeSize" o = SocketAddressGetNativeSizeMethodInfo
ResolveSocketAddressMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSocketAddressMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSocketAddressMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSocketAddressMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSocketAddressMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSocketAddressMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSocketAddressMethod t SocketAddress, O.MethodInfo info SocketAddress p) => OL.IsLabel t (SocketAddress -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getSocketAddressFamily :: (MonadIO m, IsSocketAddress o) => o -> m Gio.Enums.SocketFamily
getSocketAddressFamily :: o -> m SocketFamily
getSocketAddressFamily o
obj = IO SocketFamily -> m SocketFamily
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketFamily -> m SocketFamily)
-> IO SocketFamily -> m SocketFamily
forall a b. (a -> b) -> a -> b
$ o -> String -> IO SocketFamily
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"family"
#if defined(ENABLE_OVERLOADING)
data SocketAddressFamilyPropertyInfo
instance AttrInfo SocketAddressFamilyPropertyInfo where
type AttrAllowedOps SocketAddressFamilyPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint SocketAddressFamilyPropertyInfo = IsSocketAddress
type AttrSetTypeConstraint SocketAddressFamilyPropertyInfo = (~) ()
type AttrTransferTypeConstraint SocketAddressFamilyPropertyInfo = (~) ()
type AttrTransferType SocketAddressFamilyPropertyInfo = ()
type AttrGetType SocketAddressFamilyPropertyInfo = Gio.Enums.SocketFamily
type AttrLabel SocketAddressFamilyPropertyInfo = "family"
type AttrOrigin SocketAddressFamilyPropertyInfo = SocketAddress
attrGet = getSocketAddressFamily
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SocketAddress
type instance O.AttributeList SocketAddress = SocketAddressAttributeList
type SocketAddressAttributeList = ('[ '("family", SocketAddressFamilyPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
socketAddressFamily :: AttrLabelProxy "family"
socketAddressFamily = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SocketAddress = SocketAddressSignalList
type SocketAddressSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_socket_address_new_from_native" g_socket_address_new_from_native ::
Ptr () ->
Word64 ->
IO (Ptr SocketAddress)
socketAddressNewFromNative ::
(B.CallStack.HasCallStack, MonadIO m) =>
Ptr ()
-> Word64
-> m SocketAddress
socketAddressNewFromNative :: Ptr () -> Word64 -> m SocketAddress
socketAddressNewFromNative Ptr ()
native Word64
len = 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 SocketAddress
result <- Ptr () -> Word64 -> IO (Ptr SocketAddress)
g_socket_address_new_from_native Ptr ()
native Word64
len
Text -> Ptr SocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketAddressNewFromNative" 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
SocketAddress) Ptr SocketAddress
result
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_socket_address_get_family" g_socket_address_get_family ::
Ptr SocketAddress ->
IO CUInt
socketAddressGetFamily ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddress a) =>
a
-> m Gio.Enums.SocketFamily
socketAddressGetFamily :: a -> m SocketFamily
socketAddressGetFamily a
address = IO SocketFamily -> m SocketFamily
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketFamily -> m SocketFamily)
-> IO SocketFamily -> m SocketFamily
forall a b. (a -> b) -> a -> b
$ do
Ptr SocketAddress
address' <- a -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
CUInt
result <- Ptr SocketAddress -> IO CUInt
g_socket_address_get_family Ptr SocketAddress
address'
let result' :: SocketFamily
result' = (Int -> SocketFamily
forall a. Enum a => Int -> a
toEnum (Int -> SocketFamily) -> (CUInt -> Int) -> CUInt -> SocketFamily
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
SocketFamily -> IO SocketFamily
forall (m :: * -> *) a. Monad m => a -> m a
return SocketFamily
result'
#if defined(ENABLE_OVERLOADING)
data SocketAddressGetFamilyMethodInfo
instance (signature ~ (m Gio.Enums.SocketFamily), MonadIO m, IsSocketAddress a) => O.MethodInfo SocketAddressGetFamilyMethodInfo a signature where
overloadedMethod = socketAddressGetFamily
#endif
foreign import ccall "g_socket_address_get_native_size" g_socket_address_get_native_size ::
Ptr SocketAddress ->
IO Int64
socketAddressGetNativeSize ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddress a) =>
a
-> m Int64
socketAddressGetNativeSize :: a -> m Int64
socketAddressGetNativeSize a
address = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
Ptr SocketAddress
address' <- a -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
Int64
result <- Ptr SocketAddress -> IO Int64
g_socket_address_get_native_size Ptr SocketAddress
address'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
#if defined(ENABLE_OVERLOADING)
data SocketAddressGetNativeSizeMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsSocketAddress a) => O.MethodInfo SocketAddressGetNativeSizeMethodInfo a signature where
overloadedMethod = socketAddressGetNativeSize
#endif
foreign import ccall "g_socket_address_to_native" g_socket_address_to_native ::
Ptr SocketAddress ->
Ptr () ->
Word64 ->
Ptr (Ptr GError) ->
IO CInt
socketAddressToNative ::
(B.CallStack.HasCallStack, MonadIO m, IsSocketAddress a) =>
a
-> Ptr ()
-> Word64
-> m ()
socketAddressToNative :: a -> Ptr () -> Word64 -> m ()
socketAddressToNative a
address Ptr ()
dest Word64
destlen = 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 SocketAddress
address' <- a -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr SocketAddress
-> Ptr () -> Word64 -> Ptr (Ptr GError) -> IO CInt
g_socket_address_to_native Ptr SocketAddress
address' Ptr ()
dest Word64
destlen
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketAddressToNativeMethodInfo
instance (signature ~ (Ptr () -> Word64 -> m ()), MonadIO m, IsSocketAddress a) => O.MethodInfo SocketAddressToNativeMethodInfo a signature where
overloadedMethod = socketAddressToNative
#endif