{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.UnixSocketAddress
(
UnixSocketAddress(..) ,
IsUnixSocketAddress ,
toUnixSocketAddress ,
#if defined(ENABLE_OVERLOADING)
ResolveUnixSocketAddressMethod ,
#endif
unixSocketAddressAbstractNamesSupported ,
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressGetAddressTypeMethodInfo,
#endif
unixSocketAddressGetAddressType ,
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressGetIsAbstractMethodInfo,
#endif
unixSocketAddressGetIsAbstract ,
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressGetPathMethodInfo ,
#endif
unixSocketAddressGetPath ,
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressGetPathLenMethodInfo ,
#endif
unixSocketAddressGetPathLen ,
unixSocketAddressNew ,
unixSocketAddressNewAbstract ,
unixSocketAddressNewWithType ,
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressAbstractPropertyInfo ,
#endif
constructUnixSocketAddressAbstract ,
getUnixSocketAddressAbstract ,
#if defined(ENABLE_OVERLOADING)
unixSocketAddressAbstract ,
#endif
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressAddressTypePropertyInfo,
#endif
constructUnixSocketAddressAddressType ,
getUnixSocketAddressAddressType ,
#if defined(ENABLE_OVERLOADING)
unixSocketAddressAddressType ,
#endif
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressPathPropertyInfo ,
#endif
constructUnixSocketAddressPath ,
getUnixSocketAddressPath ,
#if defined(ENABLE_OVERLOADING)
unixSocketAddressPath ,
#endif
#if defined(ENABLE_OVERLOADING)
UnixSocketAddressPathAsArrayPropertyInfo,
#endif
constructUnixSocketAddressPathAsArray ,
getUnixSocketAddressPathAsArray ,
#if defined(ENABLE_OVERLOADING)
unixSocketAddressPathAsArray ,
#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
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
newtype UnixSocketAddress = UnixSocketAddress (SP.ManagedPtr UnixSocketAddress)
deriving (UnixSocketAddress -> UnixSocketAddress -> Bool
(UnixSocketAddress -> UnixSocketAddress -> Bool)
-> (UnixSocketAddress -> UnixSocketAddress -> Bool)
-> Eq UnixSocketAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnixSocketAddress -> UnixSocketAddress -> Bool
$c/= :: UnixSocketAddress -> UnixSocketAddress -> Bool
== :: UnixSocketAddress -> UnixSocketAddress -> Bool
$c== :: UnixSocketAddress -> UnixSocketAddress -> Bool
Eq)
instance SP.ManagedPtrNewtype UnixSocketAddress where
toManagedPtr :: UnixSocketAddress -> ManagedPtr UnixSocketAddress
toManagedPtr (UnixSocketAddress ManagedPtr UnixSocketAddress
p) = ManagedPtr UnixSocketAddress
p
foreign import ccall "g_unix_socket_address_get_type"
c_g_unix_socket_address_get_type :: IO B.Types.GType
instance B.Types.TypedObject UnixSocketAddress where
glibType :: IO GType
glibType = IO GType
c_g_unix_socket_address_get_type
instance B.Types.GObject UnixSocketAddress
instance B.GValue.IsGValue UnixSocketAddress where
toGValue :: UnixSocketAddress -> IO GValue
toGValue UnixSocketAddress
o = do
GType
gtype <- IO GType
c_g_unix_socket_address_get_type
UnixSocketAddress
-> (Ptr UnixSocketAddress -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr UnixSocketAddress
o (GType
-> (GValue -> Ptr UnixSocketAddress -> IO ())
-> Ptr UnixSocketAddress
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr UnixSocketAddress -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO UnixSocketAddress
fromGValue GValue
gv = do
Ptr UnixSocketAddress
ptr <- GValue -> IO (Ptr UnixSocketAddress)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr UnixSocketAddress)
(ManagedPtr UnixSocketAddress -> UnixSocketAddress)
-> Ptr UnixSocketAddress -> IO UnixSocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr UnixSocketAddress -> UnixSocketAddress
UnixSocketAddress Ptr UnixSocketAddress
ptr
class (SP.GObject o, O.IsDescendantOf UnixSocketAddress o) => IsUnixSocketAddress o
instance (SP.GObject o, O.IsDescendantOf UnixSocketAddress o) => IsUnixSocketAddress o
instance O.HasParentTypes UnixSocketAddress
type instance O.ParentTypes UnixSocketAddress = '[Gio.SocketAddress.SocketAddress, GObject.Object.Object, Gio.SocketConnectable.SocketConnectable]
toUnixSocketAddress :: (MonadIO m, IsUnixSocketAddress o) => o -> m UnixSocketAddress
toUnixSocketAddress :: o -> m UnixSocketAddress
toUnixSocketAddress = IO UnixSocketAddress -> m UnixSocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddress -> m UnixSocketAddress)
-> (o -> IO UnixSocketAddress) -> o -> m UnixSocketAddress
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr UnixSocketAddress -> UnixSocketAddress)
-> o -> IO UnixSocketAddress
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr UnixSocketAddress -> UnixSocketAddress
UnixSocketAddress
#if defined(ENABLE_OVERLOADING)
type family ResolveUnixSocketAddressMethod (t :: Symbol) (o :: *) :: * where
ResolveUnixSocketAddressMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveUnixSocketAddressMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveUnixSocketAddressMethod "enumerate" o = Gio.SocketConnectable.SocketConnectableEnumerateMethodInfo
ResolveUnixSocketAddressMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveUnixSocketAddressMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveUnixSocketAddressMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveUnixSocketAddressMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveUnixSocketAddressMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveUnixSocketAddressMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveUnixSocketAddressMethod "proxyEnumerate" o = Gio.SocketConnectable.SocketConnectableProxyEnumerateMethodInfo
ResolveUnixSocketAddressMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveUnixSocketAddressMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveUnixSocketAddressMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveUnixSocketAddressMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveUnixSocketAddressMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveUnixSocketAddressMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveUnixSocketAddressMethod "toNative" o = Gio.SocketAddress.SocketAddressToNativeMethodInfo
ResolveUnixSocketAddressMethod "toString" o = Gio.SocketConnectable.SocketConnectableToStringMethodInfo
ResolveUnixSocketAddressMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveUnixSocketAddressMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveUnixSocketAddressMethod "getAddressType" o = UnixSocketAddressGetAddressTypeMethodInfo
ResolveUnixSocketAddressMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveUnixSocketAddressMethod "getFamily" o = Gio.SocketAddress.SocketAddressGetFamilyMethodInfo
ResolveUnixSocketAddressMethod "getIsAbstract" o = UnixSocketAddressGetIsAbstractMethodInfo
ResolveUnixSocketAddressMethod "getNativeSize" o = Gio.SocketAddress.SocketAddressGetNativeSizeMethodInfo
ResolveUnixSocketAddressMethod "getPath" o = UnixSocketAddressGetPathMethodInfo
ResolveUnixSocketAddressMethod "getPathLen" o = UnixSocketAddressGetPathLenMethodInfo
ResolveUnixSocketAddressMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveUnixSocketAddressMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveUnixSocketAddressMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveUnixSocketAddressMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveUnixSocketAddressMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveUnixSocketAddressMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveUnixSocketAddressMethod t UnixSocketAddress, O.MethodInfo info UnixSocketAddress p) => OL.IsLabel t (UnixSocketAddress -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getUnixSocketAddressAbstract :: (MonadIO m, IsUnixSocketAddress o) => o -> m Bool
getUnixSocketAddressAbstract :: o -> m Bool
getUnixSocketAddressAbstract 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 String
"abstract"
constructUnixSocketAddressAbstract :: (IsUnixSocketAddress o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructUnixSocketAddressAbstract :: Bool -> m (GValueConstruct o)
constructUnixSocketAddressAbstract Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"abstract" Bool
val
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressAbstractPropertyInfo
instance AttrInfo UnixSocketAddressAbstractPropertyInfo where
type AttrAllowedOps UnixSocketAddressAbstractPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint UnixSocketAddressAbstractPropertyInfo = IsUnixSocketAddress
type AttrSetTypeConstraint UnixSocketAddressAbstractPropertyInfo = (~) Bool
type AttrTransferTypeConstraint UnixSocketAddressAbstractPropertyInfo = (~) Bool
type AttrTransferType UnixSocketAddressAbstractPropertyInfo = Bool
type AttrGetType UnixSocketAddressAbstractPropertyInfo = Bool
type AttrLabel UnixSocketAddressAbstractPropertyInfo = "abstract"
type AttrOrigin UnixSocketAddressAbstractPropertyInfo = UnixSocketAddress
attrGet = getUnixSocketAddressAbstract
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructUnixSocketAddressAbstract
attrClear = undefined
#endif
getUnixSocketAddressAddressType :: (MonadIO m, IsUnixSocketAddress o) => o -> m Gio.Enums.UnixSocketAddressType
getUnixSocketAddressAddressType :: o -> m UnixSocketAddressType
getUnixSocketAddressAddressType o
obj = IO UnixSocketAddressType -> m UnixSocketAddressType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddressType -> m UnixSocketAddressType)
-> IO UnixSocketAddressType -> m UnixSocketAddressType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO UnixSocketAddressType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"address-type"
constructUnixSocketAddressAddressType :: (IsUnixSocketAddress o, MIO.MonadIO m) => Gio.Enums.UnixSocketAddressType -> m (GValueConstruct o)
constructUnixSocketAddressAddressType :: UnixSocketAddressType -> m (GValueConstruct o)
constructUnixSocketAddressAddressType UnixSocketAddressType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> UnixSocketAddressType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"address-type" UnixSocketAddressType
val
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressAddressTypePropertyInfo
instance AttrInfo UnixSocketAddressAddressTypePropertyInfo where
type AttrAllowedOps UnixSocketAddressAddressTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint UnixSocketAddressAddressTypePropertyInfo = IsUnixSocketAddress
type AttrSetTypeConstraint UnixSocketAddressAddressTypePropertyInfo = (~) Gio.Enums.UnixSocketAddressType
type AttrTransferTypeConstraint UnixSocketAddressAddressTypePropertyInfo = (~) Gio.Enums.UnixSocketAddressType
type AttrTransferType UnixSocketAddressAddressTypePropertyInfo = Gio.Enums.UnixSocketAddressType
type AttrGetType UnixSocketAddressAddressTypePropertyInfo = Gio.Enums.UnixSocketAddressType
type AttrLabel UnixSocketAddressAddressTypePropertyInfo = "address-type"
type AttrOrigin UnixSocketAddressAddressTypePropertyInfo = UnixSocketAddress
attrGet = getUnixSocketAddressAddressType
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructUnixSocketAddressAddressType
attrClear = undefined
#endif
getUnixSocketAddressPath :: (MonadIO m, IsUnixSocketAddress o) => o -> m T.Text
getUnixSocketAddressPath :: o -> m Text
getUnixSocketAddressPath o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getUnixSocketAddressPath" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"path"
constructUnixSocketAddressPath :: (IsUnixSocketAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructUnixSocketAddressPath :: Text -> m (GValueConstruct o)
constructUnixSocketAddressPath Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressPathPropertyInfo
instance AttrInfo UnixSocketAddressPathPropertyInfo where
type AttrAllowedOps UnixSocketAddressPathPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint UnixSocketAddressPathPropertyInfo = IsUnixSocketAddress
type AttrSetTypeConstraint UnixSocketAddressPathPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint UnixSocketAddressPathPropertyInfo = (~) T.Text
type AttrTransferType UnixSocketAddressPathPropertyInfo = T.Text
type AttrGetType UnixSocketAddressPathPropertyInfo = T.Text
type AttrLabel UnixSocketAddressPathPropertyInfo = "path"
type AttrOrigin UnixSocketAddressPathPropertyInfo = UnixSocketAddress
attrGet = getUnixSocketAddressPath
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructUnixSocketAddressPath
attrClear = undefined
#endif
getUnixSocketAddressPathAsArray :: (MonadIO m, IsUnixSocketAddress o) => o -> m (Maybe ByteString)
getUnixSocketAddressPathAsArray :: o -> m (Maybe ByteString)
getUnixSocketAddressPathAsArray o
obj = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe ByteString)
forall a. GObject a => a -> String -> IO (Maybe ByteString)
B.Properties.getObjectPropertyByteArray o
obj String
"path-as-array"
constructUnixSocketAddressPathAsArray :: (IsUnixSocketAddress o, MIO.MonadIO m) => ByteString -> m (GValueConstruct o)
constructUnixSocketAddressPathAsArray :: ByteString -> m (GValueConstruct o)
constructUnixSocketAddressPathAsArray ByteString
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe ByteString -> IO (GValueConstruct o)
forall o. String -> Maybe ByteString -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyByteArray String
"path-as-array" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
P.Just ByteString
val)
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressPathAsArrayPropertyInfo
instance AttrInfo UnixSocketAddressPathAsArrayPropertyInfo where
type AttrAllowedOps UnixSocketAddressPathAsArrayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint UnixSocketAddressPathAsArrayPropertyInfo = IsUnixSocketAddress
type AttrSetTypeConstraint UnixSocketAddressPathAsArrayPropertyInfo = (~) ByteString
type AttrTransferTypeConstraint UnixSocketAddressPathAsArrayPropertyInfo = (~) ByteString
type AttrTransferType UnixSocketAddressPathAsArrayPropertyInfo = ByteString
type AttrGetType UnixSocketAddressPathAsArrayPropertyInfo = (Maybe ByteString)
type AttrLabel UnixSocketAddressPathAsArrayPropertyInfo = "path-as-array"
type AttrOrigin UnixSocketAddressPathAsArrayPropertyInfo = UnixSocketAddress
attrGet = getUnixSocketAddressPathAsArray
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructUnixSocketAddressPathAsArray
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UnixSocketAddress
type instance O.AttributeList UnixSocketAddress = UnixSocketAddressAttributeList
type UnixSocketAddressAttributeList = ('[ '("abstract", UnixSocketAddressAbstractPropertyInfo), '("addressType", UnixSocketAddressAddressTypePropertyInfo), '("family", Gio.SocketAddress.SocketAddressFamilyPropertyInfo), '("path", UnixSocketAddressPathPropertyInfo), '("pathAsArray", UnixSocketAddressPathAsArrayPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
unixSocketAddressAbstract :: AttrLabelProxy "abstract"
unixSocketAddressAbstract = AttrLabelProxy
unixSocketAddressAddressType :: AttrLabelProxy "addressType"
unixSocketAddressAddressType = AttrLabelProxy
unixSocketAddressPath :: AttrLabelProxy "path"
unixSocketAddressPath = AttrLabelProxy
unixSocketAddressPathAsArray :: AttrLabelProxy "pathAsArray"
unixSocketAddressPathAsArray = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList UnixSocketAddress = UnixSocketAddressSignalList
type UnixSocketAddressSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_unix_socket_address_new" g_unix_socket_address_new ::
CString ->
IO (Ptr UnixSocketAddress)
unixSocketAddressNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m UnixSocketAddress
unixSocketAddressNew :: Text -> m UnixSocketAddress
unixSocketAddressNew Text
path = IO UnixSocketAddress -> m UnixSocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddress -> m UnixSocketAddress)
-> IO UnixSocketAddress -> m UnixSocketAddress
forall a b. (a -> b) -> a -> b
$ do
CString
path' <- Text -> IO CString
textToCString Text
path
Ptr UnixSocketAddress
result <- CString -> IO (Ptr UnixSocketAddress)
g_unix_socket_address_new CString
path'
Text -> Ptr UnixSocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"unixSocketAddressNew" Ptr UnixSocketAddress
result
UnixSocketAddress
result' <- ((ManagedPtr UnixSocketAddress -> UnixSocketAddress)
-> Ptr UnixSocketAddress -> IO UnixSocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixSocketAddress -> UnixSocketAddress
UnixSocketAddress) Ptr UnixSocketAddress
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
UnixSocketAddress -> IO UnixSocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return UnixSocketAddress
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_unix_socket_address_new_abstract" g_unix_socket_address_new_abstract ::
Ptr Int8 ->
Int32 ->
IO (Ptr UnixSocketAddress)
{-# DEPRECATED unixSocketAddressNewAbstract ["Use 'GI.Gio.Objects.UnixSocketAddress.unixSocketAddressNewWithType'."] #-}
unixSocketAddressNewAbstract ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Int8]
-> m UnixSocketAddress
unixSocketAddressNewAbstract :: [Int8] -> m UnixSocketAddress
unixSocketAddressNewAbstract [Int8]
path = IO UnixSocketAddress -> m UnixSocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddress -> m UnixSocketAddress)
-> IO UnixSocketAddress -> m UnixSocketAddress
forall a b. (a -> b) -> a -> b
$ do
let pathLen :: Int32
pathLen = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Int8] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Int8]
path
Ptr Int8
path' <- [Int8] -> IO (Ptr Int8)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int8]
path
Ptr UnixSocketAddress
result <- Ptr Int8 -> Int32 -> IO (Ptr UnixSocketAddress)
g_unix_socket_address_new_abstract Ptr Int8
path' Int32
pathLen
Text -> Ptr UnixSocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"unixSocketAddressNewAbstract" Ptr UnixSocketAddress
result
UnixSocketAddress
result' <- ((ManagedPtr UnixSocketAddress -> UnixSocketAddress)
-> Ptr UnixSocketAddress -> IO UnixSocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixSocketAddress -> UnixSocketAddress
UnixSocketAddress) Ptr UnixSocketAddress
result
Ptr Int8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int8
path'
UnixSocketAddress -> IO UnixSocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return UnixSocketAddress
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_unix_socket_address_new_with_type" g_unix_socket_address_new_with_type ::
Ptr Int8 ->
Int32 ->
CUInt ->
IO (Ptr UnixSocketAddress)
unixSocketAddressNewWithType ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Int8]
-> Gio.Enums.UnixSocketAddressType
-> m UnixSocketAddress
unixSocketAddressNewWithType :: [Int8] -> UnixSocketAddressType -> m UnixSocketAddress
unixSocketAddressNewWithType [Int8]
path UnixSocketAddressType
type_ = IO UnixSocketAddress -> m UnixSocketAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddress -> m UnixSocketAddress)
-> IO UnixSocketAddress -> m UnixSocketAddress
forall a b. (a -> b) -> a -> b
$ do
let pathLen :: Int32
pathLen = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Int8] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Int8]
path
Ptr Int8
path' <- [Int8] -> IO (Ptr Int8)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int8]
path
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (UnixSocketAddressType -> Int) -> UnixSocketAddressType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnixSocketAddressType -> Int
forall a. Enum a => a -> Int
fromEnum) UnixSocketAddressType
type_
Ptr UnixSocketAddress
result <- Ptr Int8 -> Int32 -> CUInt -> IO (Ptr UnixSocketAddress)
g_unix_socket_address_new_with_type Ptr Int8
path' Int32
pathLen CUInt
type_'
Text -> Ptr UnixSocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"unixSocketAddressNewWithType" Ptr UnixSocketAddress
result
UnixSocketAddress
result' <- ((ManagedPtr UnixSocketAddress -> UnixSocketAddress)
-> Ptr UnixSocketAddress -> IO UnixSocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixSocketAddress -> UnixSocketAddress
UnixSocketAddress) Ptr UnixSocketAddress
result
Ptr Int8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int8
path'
UnixSocketAddress -> IO UnixSocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return UnixSocketAddress
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_unix_socket_address_get_address_type" g_unix_socket_address_get_address_type ::
Ptr UnixSocketAddress ->
IO CUInt
unixSocketAddressGetAddressType ::
(B.CallStack.HasCallStack, MonadIO m, IsUnixSocketAddress a) =>
a
-> m Gio.Enums.UnixSocketAddressType
unixSocketAddressGetAddressType :: a -> m UnixSocketAddressType
unixSocketAddressGetAddressType a
address = IO UnixSocketAddressType -> m UnixSocketAddressType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixSocketAddressType -> m UnixSocketAddressType)
-> IO UnixSocketAddressType -> m UnixSocketAddressType
forall a b. (a -> b) -> a -> b
$ do
Ptr UnixSocketAddress
address' <- a -> IO (Ptr UnixSocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
CUInt
result <- Ptr UnixSocketAddress -> IO CUInt
g_unix_socket_address_get_address_type Ptr UnixSocketAddress
address'
let result' :: UnixSocketAddressType
result' = (Int -> UnixSocketAddressType
forall a. Enum a => Int -> a
toEnum (Int -> UnixSocketAddressType)
-> (CUInt -> Int) -> CUInt -> UnixSocketAddressType
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
UnixSocketAddressType -> IO UnixSocketAddressType
forall (m :: * -> *) a. Monad m => a -> m a
return UnixSocketAddressType
result'
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressGetAddressTypeMethodInfo
instance (signature ~ (m Gio.Enums.UnixSocketAddressType), MonadIO m, IsUnixSocketAddress a) => O.MethodInfo UnixSocketAddressGetAddressTypeMethodInfo a signature where
overloadedMethod = unixSocketAddressGetAddressType
#endif
foreign import ccall "g_unix_socket_address_get_is_abstract" g_unix_socket_address_get_is_abstract ::
Ptr UnixSocketAddress ->
IO CInt
{-# DEPRECATED unixSocketAddressGetIsAbstract ["Use 'GI.Gio.Objects.UnixSocketAddress.unixSocketAddressGetAddressType'"] #-}
unixSocketAddressGetIsAbstract ::
(B.CallStack.HasCallStack, MonadIO m, IsUnixSocketAddress a) =>
a
-> m Bool
unixSocketAddressGetIsAbstract :: a -> m Bool
unixSocketAddressGetIsAbstract a
address = 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 UnixSocketAddress
address' <- a -> IO (Ptr UnixSocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
CInt
result <- Ptr UnixSocketAddress -> IO CInt
g_unix_socket_address_get_is_abstract Ptr UnixSocketAddress
address'
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
address
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressGetIsAbstractMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsUnixSocketAddress a) => O.MethodInfo UnixSocketAddressGetIsAbstractMethodInfo a signature where
overloadedMethod = unixSocketAddressGetIsAbstract
#endif
foreign import ccall "g_unix_socket_address_get_path" g_unix_socket_address_get_path ::
Ptr UnixSocketAddress ->
IO CString
unixSocketAddressGetPath ::
(B.CallStack.HasCallStack, MonadIO m, IsUnixSocketAddress a) =>
a
-> m T.Text
unixSocketAddressGetPath :: a -> m Text
unixSocketAddressGetPath a
address = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr UnixSocketAddress
address' <- a -> IO (Ptr UnixSocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
CString
result <- Ptr UnixSocketAddress -> IO CString
g_unix_socket_address_get_path Ptr UnixSocketAddress
address'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"unixSocketAddressGetPath" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressGetPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsUnixSocketAddress a) => O.MethodInfo UnixSocketAddressGetPathMethodInfo a signature where
overloadedMethod = unixSocketAddressGetPath
#endif
foreign import ccall "g_unix_socket_address_get_path_len" g_unix_socket_address_get_path_len ::
Ptr UnixSocketAddress ->
IO Word64
unixSocketAddressGetPathLen ::
(B.CallStack.HasCallStack, MonadIO m, IsUnixSocketAddress a) =>
a
-> m Word64
unixSocketAddressGetPathLen :: a -> m Word64
unixSocketAddressGetPathLen a
address = 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 UnixSocketAddress
address' <- a -> IO (Ptr UnixSocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
Word64
result <- Ptr UnixSocketAddress -> IO Word64
g_unix_socket_address_get_path_len Ptr UnixSocketAddress
address'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data UnixSocketAddressGetPathLenMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsUnixSocketAddress a) => O.MethodInfo UnixSocketAddressGetPathLenMethodInfo a signature where
overloadedMethod = unixSocketAddressGetPathLen
#endif
foreign import ccall "g_unix_socket_address_abstract_names_supported" g_unix_socket_address_abstract_names_supported ::
IO CInt
unixSocketAddressAbstractNamesSupported ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Bool
unixSocketAddressAbstractNamesSupported :: m Bool
unixSocketAddressAbstractNamesSupported = 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
CInt
result <- IO CInt
g_unix_socket_address_abstract_names_supported
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif