{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.InetAddressMask
(
InetAddressMask(..) ,
IsInetAddressMask ,
toInetAddressMask ,
#if defined(ENABLE_OVERLOADING)
ResolveInetAddressMaskMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
InetAddressMaskEqualMethodInfo ,
#endif
inetAddressMaskEqual ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskGetAddressMethodInfo ,
#endif
inetAddressMaskGetAddress ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskGetFamilyMethodInfo ,
#endif
inetAddressMaskGetFamily ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskGetLengthMethodInfo ,
#endif
inetAddressMaskGetLength ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskMatchesMethodInfo ,
#endif
inetAddressMaskMatches ,
inetAddressMaskNew ,
inetAddressMaskNewFromString ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskToStringMethodInfo ,
#endif
inetAddressMaskToString ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskAddressPropertyInfo ,
#endif
clearInetAddressMaskAddress ,
constructInetAddressMaskAddress ,
getInetAddressMaskAddress ,
#if defined(ENABLE_OVERLOADING)
inetAddressMaskAddress ,
#endif
setInetAddressMaskAddress ,
#if defined(ENABLE_OVERLOADING)
InetAddressMaskFamilyPropertyInfo ,
#endif
getInetAddressMaskFamily ,
#if defined(ENABLE_OVERLOADING)
inetAddressMaskFamily ,
#endif
#if defined(ENABLE_OVERLOADING)
InetAddressMaskLengthPropertyInfo ,
#endif
constructInetAddressMaskLength ,
getInetAddressMaskLength ,
#if defined(ENABLE_OVERLOADING)
inetAddressMaskLength ,
#endif
setInetAddressMaskLength ,
) 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.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.InetAddress as Gio.InetAddress
newtype InetAddressMask = InetAddressMask (SP.ManagedPtr InetAddressMask)
deriving (InetAddressMask -> InetAddressMask -> Bool
(InetAddressMask -> InetAddressMask -> Bool)
-> (InetAddressMask -> InetAddressMask -> Bool)
-> Eq InetAddressMask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InetAddressMask -> InetAddressMask -> Bool
$c/= :: InetAddressMask -> InetAddressMask -> Bool
== :: InetAddressMask -> InetAddressMask -> Bool
$c== :: InetAddressMask -> InetAddressMask -> Bool
Eq)
instance SP.ManagedPtrNewtype InetAddressMask where
toManagedPtr :: InetAddressMask -> ManagedPtr InetAddressMask
toManagedPtr (InetAddressMask ManagedPtr InetAddressMask
p) = ManagedPtr InetAddressMask
p
foreign import ccall "g_inet_address_mask_get_type"
c_g_inet_address_mask_get_type :: IO B.Types.GType
instance B.Types.TypedObject InetAddressMask where
glibType :: IO GType
glibType = IO GType
c_g_inet_address_mask_get_type
instance B.Types.GObject InetAddressMask
instance B.GValue.IsGValue InetAddressMask where
toGValue :: InetAddressMask -> IO GValue
toGValue InetAddressMask
o = do
GType
gtype <- IO GType
c_g_inet_address_mask_get_type
InetAddressMask -> (Ptr InetAddressMask -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr InetAddressMask
o (GType
-> (GValue -> Ptr InetAddressMask -> IO ())
-> Ptr InetAddressMask
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr InetAddressMask -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO InetAddressMask
fromGValue GValue
gv = do
Ptr InetAddressMask
ptr <- GValue -> IO (Ptr InetAddressMask)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr InetAddressMask)
(ManagedPtr InetAddressMask -> InetAddressMask)
-> Ptr InetAddressMask -> IO InetAddressMask
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr InetAddressMask -> InetAddressMask
InetAddressMask Ptr InetAddressMask
ptr
class (SP.GObject o, O.IsDescendantOf InetAddressMask o) => IsInetAddressMask o
instance (SP.GObject o, O.IsDescendantOf InetAddressMask o) => IsInetAddressMask o
instance O.HasParentTypes InetAddressMask
type instance O.ParentTypes InetAddressMask = '[GObject.Object.Object, Gio.Initable.Initable]
toInetAddressMask :: (MonadIO m, IsInetAddressMask o) => o -> m InetAddressMask
toInetAddressMask :: o -> m InetAddressMask
toInetAddressMask = IO InetAddressMask -> m InetAddressMask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InetAddressMask -> m InetAddressMask)
-> (o -> IO InetAddressMask) -> o -> m InetAddressMask
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr InetAddressMask -> InetAddressMask)
-> o -> IO InetAddressMask
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr InetAddressMask -> InetAddressMask
InetAddressMask
#if defined(ENABLE_OVERLOADING)
type family ResolveInetAddressMaskMethod (t :: Symbol) (o :: *) :: * where
ResolveInetAddressMaskMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveInetAddressMaskMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveInetAddressMaskMethod "equal" o = InetAddressMaskEqualMethodInfo
ResolveInetAddressMaskMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveInetAddressMaskMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveInetAddressMaskMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveInetAddressMaskMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveInetAddressMaskMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveInetAddressMaskMethod "matches" o = InetAddressMaskMatchesMethodInfo
ResolveInetAddressMaskMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveInetAddressMaskMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveInetAddressMaskMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveInetAddressMaskMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveInetAddressMaskMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveInetAddressMaskMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveInetAddressMaskMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveInetAddressMaskMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveInetAddressMaskMethod "toString" o = InetAddressMaskToStringMethodInfo
ResolveInetAddressMaskMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveInetAddressMaskMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveInetAddressMaskMethod "getAddress" o = InetAddressMaskGetAddressMethodInfo
ResolveInetAddressMaskMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveInetAddressMaskMethod "getFamily" o = InetAddressMaskGetFamilyMethodInfo
ResolveInetAddressMaskMethod "getLength" o = InetAddressMaskGetLengthMethodInfo
ResolveInetAddressMaskMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveInetAddressMaskMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveInetAddressMaskMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveInetAddressMaskMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveInetAddressMaskMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveInetAddressMaskMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveInetAddressMaskMethod t InetAddressMask, O.MethodInfo info InetAddressMask p) => OL.IsLabel t (InetAddressMask -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o) => o -> m Gio.InetAddress.InetAddress
getInetAddressMaskAddress :: o -> m InetAddress
getInetAddressMaskAddress o
obj = IO InetAddress -> m InetAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InetAddress -> m InetAddress)
-> IO InetAddress -> m InetAddress
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe InetAddress) -> IO InetAddress
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getInetAddressMaskAddress" (IO (Maybe InetAddress) -> IO InetAddress)
-> IO (Maybe InetAddress) -> IO InetAddress
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr InetAddress -> InetAddress)
-> IO (Maybe InetAddress)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"address" ManagedPtr InetAddress -> InetAddress
Gio.InetAddress.InetAddress
setInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o, Gio.InetAddress.IsInetAddress a) => o -> a -> m ()
setInetAddressMaskAddress :: o -> a -> m ()
setInetAddressMaskAddress o
obj a
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 -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"address" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructInetAddressMaskAddress :: (IsInetAddressMask o, MIO.MonadIO m, Gio.InetAddress.IsInetAddress a) => a -> m (GValueConstruct o)
constructInetAddressMaskAddress :: a -> m (GValueConstruct o)
constructInetAddressMaskAddress a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"address" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o) => o -> m ()
clearInetAddressMaskAddress :: o -> m ()
clearInetAddressMaskAddress o
obj = 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 -> Maybe InetAddress -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"address" (Maybe InetAddress
forall a. Maybe a
Nothing :: Maybe Gio.InetAddress.InetAddress)
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskAddressPropertyInfo
instance AttrInfo InetAddressMaskAddressPropertyInfo where
type AttrAllowedOps InetAddressMaskAddressPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint InetAddressMaskAddressPropertyInfo = IsInetAddressMask
type AttrSetTypeConstraint InetAddressMaskAddressPropertyInfo = Gio.InetAddress.IsInetAddress
type AttrTransferTypeConstraint InetAddressMaskAddressPropertyInfo = Gio.InetAddress.IsInetAddress
type AttrTransferType InetAddressMaskAddressPropertyInfo = Gio.InetAddress.InetAddress
type AttrGetType InetAddressMaskAddressPropertyInfo = Gio.InetAddress.InetAddress
type AttrLabel InetAddressMaskAddressPropertyInfo = "address"
type AttrOrigin InetAddressMaskAddressPropertyInfo = InetAddressMask
attrGet = getInetAddressMaskAddress
attrSet = setInetAddressMaskAddress
attrTransfer _ v = do
unsafeCastTo Gio.InetAddress.InetAddress v
attrConstruct = constructInetAddressMaskAddress
attrClear = clearInetAddressMaskAddress
#endif
getInetAddressMaskFamily :: (MonadIO m, IsInetAddressMask o) => o -> m Gio.Enums.SocketFamily
getInetAddressMaskFamily :: o -> m SocketFamily
getInetAddressMaskFamily 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 InetAddressMaskFamilyPropertyInfo
instance AttrInfo InetAddressMaskFamilyPropertyInfo where
type AttrAllowedOps InetAddressMaskFamilyPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint InetAddressMaskFamilyPropertyInfo = IsInetAddressMask
type AttrSetTypeConstraint InetAddressMaskFamilyPropertyInfo = (~) ()
type AttrTransferTypeConstraint InetAddressMaskFamilyPropertyInfo = (~) ()
type AttrTransferType InetAddressMaskFamilyPropertyInfo = ()
type AttrGetType InetAddressMaskFamilyPropertyInfo = Gio.Enums.SocketFamily
type AttrLabel InetAddressMaskFamilyPropertyInfo = "family"
type AttrOrigin InetAddressMaskFamilyPropertyInfo = InetAddressMask
attrGet = getInetAddressMaskFamily
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getInetAddressMaskLength :: (MonadIO m, IsInetAddressMask o) => o -> m Word32
getInetAddressMaskLength :: o -> m Word32
getInetAddressMaskLength o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"length"
setInetAddressMaskLength :: (MonadIO m, IsInetAddressMask o) => o -> Word32 -> m ()
setInetAddressMaskLength :: o -> Word32 -> m ()
setInetAddressMaskLength o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"length" Word32
val
constructInetAddressMaskLength :: (IsInetAddressMask o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructInetAddressMaskLength :: Word32 -> m (GValueConstruct o)
constructInetAddressMaskLength Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"length" Word32
val
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskLengthPropertyInfo
instance AttrInfo InetAddressMaskLengthPropertyInfo where
type AttrAllowedOps InetAddressMaskLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint InetAddressMaskLengthPropertyInfo = IsInetAddressMask
type AttrSetTypeConstraint InetAddressMaskLengthPropertyInfo = (~) Word32
type AttrTransferTypeConstraint InetAddressMaskLengthPropertyInfo = (~) Word32
type AttrTransferType InetAddressMaskLengthPropertyInfo = Word32
type AttrGetType InetAddressMaskLengthPropertyInfo = Word32
type AttrLabel InetAddressMaskLengthPropertyInfo = "length"
type AttrOrigin InetAddressMaskLengthPropertyInfo = InetAddressMask
attrGet = getInetAddressMaskLength
attrSet = setInetAddressMaskLength
attrTransfer _ v = do
return v
attrConstruct = constructInetAddressMaskLength
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList InetAddressMask
type instance O.AttributeList InetAddressMask = InetAddressMaskAttributeList
type InetAddressMaskAttributeList = ('[ '("address", InetAddressMaskAddressPropertyInfo), '("family", InetAddressMaskFamilyPropertyInfo), '("length", InetAddressMaskLengthPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
inetAddressMaskAddress :: AttrLabelProxy "address"
inetAddressMaskAddress = AttrLabelProxy
inetAddressMaskFamily :: AttrLabelProxy "family"
inetAddressMaskFamily = AttrLabelProxy
inetAddressMaskLength :: AttrLabelProxy "length"
inetAddressMaskLength = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList InetAddressMask = InetAddressMaskSignalList
type InetAddressMaskSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_inet_address_mask_new" g_inet_address_mask_new ::
Ptr Gio.InetAddress.InetAddress ->
Word32 ->
Ptr (Ptr GError) ->
IO (Ptr InetAddressMask)
inetAddressMaskNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.InetAddress.IsInetAddress a) =>
a
-> Word32
-> m InetAddressMask
inetAddressMaskNew :: a -> Word32 -> m InetAddressMask
inetAddressMaskNew a
addr Word32
length_ = IO InetAddressMask -> m InetAddressMask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InetAddressMask -> m InetAddressMask)
-> IO InetAddressMask -> m InetAddressMask
forall a b. (a -> b) -> a -> b
$ do
Ptr InetAddress
addr' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
addr
IO InetAddressMask -> IO () -> IO InetAddressMask
forall a b. IO a -> IO b -> IO a
onException (do
Ptr InetAddressMask
result <- (Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask))
-> (Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask)
forall a b. (a -> b) -> a -> b
$ Ptr InetAddress
-> Word32 -> Ptr (Ptr GError) -> IO (Ptr InetAddressMask)
g_inet_address_mask_new Ptr InetAddress
addr' Word32
length_
Text -> Ptr InetAddressMask -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressMaskNew" Ptr InetAddressMask
result
InetAddressMask
result' <- ((ManagedPtr InetAddressMask -> InetAddressMask)
-> Ptr InetAddressMask -> IO InetAddressMask
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr InetAddressMask -> InetAddressMask
InetAddressMask) Ptr InetAddressMask
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
addr
InetAddressMask -> IO InetAddressMask
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddressMask
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_inet_address_mask_new_from_string" g_inet_address_mask_new_from_string ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr InetAddressMask)
inetAddressMaskNewFromString ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m InetAddressMask
inetAddressMaskNewFromString :: Text -> m InetAddressMask
inetAddressMaskNewFromString Text
maskString = IO InetAddressMask -> m InetAddressMask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InetAddressMask -> m InetAddressMask)
-> IO InetAddressMask -> m InetAddressMask
forall a b. (a -> b) -> a -> b
$ do
CString
maskString' <- Text -> IO CString
textToCString Text
maskString
IO InetAddressMask -> IO () -> IO InetAddressMask
forall a b. IO a -> IO b -> IO a
onException (do
Ptr InetAddressMask
result <- (Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask))
-> (Ptr (Ptr GError) -> IO (Ptr InetAddressMask))
-> IO (Ptr InetAddressMask)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr InetAddressMask)
g_inet_address_mask_new_from_string CString
maskString'
Text -> Ptr InetAddressMask -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressMaskNewFromString" Ptr InetAddressMask
result
InetAddressMask
result' <- ((ManagedPtr InetAddressMask -> InetAddressMask)
-> Ptr InetAddressMask -> IO InetAddressMask
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr InetAddressMask -> InetAddressMask
InetAddressMask) Ptr InetAddressMask
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maskString'
InetAddressMask -> IO InetAddressMask
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddressMask
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maskString'
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_inet_address_mask_equal" g_inet_address_mask_equal ::
Ptr InetAddressMask ->
Ptr InetAddressMask ->
IO CInt
inetAddressMaskEqual ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a, IsInetAddressMask b) =>
a
-> b
-> m Bool
inetAddressMaskEqual :: a -> b -> m Bool
inetAddressMaskEqual a
mask b
mask2 = 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 InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
Ptr InetAddressMask
mask2' <- b -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
mask2
CInt
result <- Ptr InetAddressMask -> Ptr InetAddressMask -> IO CInt
g_inet_address_mask_equal Ptr InetAddressMask
mask' Ptr InetAddressMask
mask2'
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
mask
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
mask2
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskEqualMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsInetAddressMask a, IsInetAddressMask b) => O.MethodInfo InetAddressMaskEqualMethodInfo a signature where
overloadedMethod = inetAddressMaskEqual
#endif
foreign import ccall "g_inet_address_mask_get_address" g_inet_address_mask_get_address ::
Ptr InetAddressMask ->
IO (Ptr Gio.InetAddress.InetAddress)
inetAddressMaskGetAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
a
-> m Gio.InetAddress.InetAddress
inetAddressMaskGetAddress :: a -> m InetAddress
inetAddressMaskGetAddress a
mask = IO InetAddress -> m InetAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InetAddress -> m InetAddress)
-> IO InetAddress -> m InetAddress
forall a b. (a -> b) -> a -> b
$ do
Ptr InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
Ptr InetAddress
result <- Ptr InetAddressMask -> IO (Ptr InetAddress)
g_inet_address_mask_get_address Ptr InetAddressMask
mask'
Text -> Ptr InetAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressMaskGetAddress" Ptr InetAddress
result
InetAddress
result' <- ((ManagedPtr InetAddress -> InetAddress)
-> Ptr InetAddress -> IO InetAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InetAddress -> InetAddress
Gio.InetAddress.InetAddress) Ptr InetAddress
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mask
InetAddress -> IO InetAddress
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddress
result'
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskGetAddressMethodInfo
instance (signature ~ (m Gio.InetAddress.InetAddress), MonadIO m, IsInetAddressMask a) => O.MethodInfo InetAddressMaskGetAddressMethodInfo a signature where
overloadedMethod = inetAddressMaskGetAddress
#endif
foreign import ccall "g_inet_address_mask_get_family" g_inet_address_mask_get_family ::
Ptr InetAddressMask ->
IO CUInt
inetAddressMaskGetFamily ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
a
-> m Gio.Enums.SocketFamily
inetAddressMaskGetFamily :: a -> m SocketFamily
inetAddressMaskGetFamily a
mask = 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 InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
CUInt
result <- Ptr InetAddressMask -> IO CUInt
g_inet_address_mask_get_family Ptr InetAddressMask
mask'
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
mask
SocketFamily -> IO SocketFamily
forall (m :: * -> *) a. Monad m => a -> m a
return SocketFamily
result'
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskGetFamilyMethodInfo
instance (signature ~ (m Gio.Enums.SocketFamily), MonadIO m, IsInetAddressMask a) => O.MethodInfo InetAddressMaskGetFamilyMethodInfo a signature where
overloadedMethod = inetAddressMaskGetFamily
#endif
foreign import ccall "g_inet_address_mask_get_length" g_inet_address_mask_get_length ::
Ptr InetAddressMask ->
IO Word32
inetAddressMaskGetLength ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
a
-> m Word32
inetAddressMaskGetLength :: a -> m Word32
inetAddressMaskGetLength a
mask = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
Word32
result <- Ptr InetAddressMask -> IO Word32
g_inet_address_mask_get_length Ptr InetAddressMask
mask'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mask
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskGetLengthMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsInetAddressMask a) => O.MethodInfo InetAddressMaskGetLengthMethodInfo a signature where
overloadedMethod = inetAddressMaskGetLength
#endif
foreign import ccall "g_inet_address_mask_matches" g_inet_address_mask_matches ::
Ptr InetAddressMask ->
Ptr Gio.InetAddress.InetAddress ->
IO CInt
inetAddressMaskMatches ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a, Gio.InetAddress.IsInetAddress b) =>
a
-> b
-> m Bool
inetAddressMaskMatches :: a -> b -> m Bool
inetAddressMaskMatches a
mask b
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 InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
Ptr InetAddress
address' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
address
CInt
result <- Ptr InetAddressMask -> Ptr InetAddress -> IO CInt
g_inet_address_mask_matches Ptr InetAddressMask
mask' Ptr InetAddress
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
mask
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
address
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskMatchesMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsInetAddressMask a, Gio.InetAddress.IsInetAddress b) => O.MethodInfo InetAddressMaskMatchesMethodInfo a signature where
overloadedMethod = inetAddressMaskMatches
#endif
foreign import ccall "g_inet_address_mask_to_string" g_inet_address_mask_to_string ::
Ptr InetAddressMask ->
IO CString
inetAddressMaskToString ::
(B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
a
-> m T.Text
inetAddressMaskToString :: a -> m Text
inetAddressMaskToString a
mask = 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 InetAddressMask
mask' <- a -> IO (Ptr InetAddressMask)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mask
CString
result <- Ptr InetAddressMask -> IO CString
g_inet_address_mask_to_string Ptr InetAddressMask
mask'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressMaskToString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mask
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data InetAddressMaskToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsInetAddressMask a) => O.MethodInfo InetAddressMaskToStringMethodInfo a signature where
overloadedMethod = inetAddressMaskToString
#endif