{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.InetAddressMask.InetAddressMask' represents a range of IPv4 or IPv6 addresses
-- described by a base address and a length indicating how many bits
-- of the base address are relevant for matching purposes. These are
-- often given in string form. Eg, \"10.0.0.0\/8\", or \"fe80::\/10\".
-- 
-- /Since: 2.32/

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

module GI.Gio.Objects.InetAddressMask
    ( 

-- * Exported types
    InetAddressMask(..)                     ,
    IsInetAddressMask                       ,
    toInetAddressMask                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [equal]("GI.Gio.Objects.InetAddressMask#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [matches]("GI.Gio.Objects.InetAddressMask#g:method:matches"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Objects.InetAddressMask#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAddress]("GI.Gio.Objects.InetAddressMask#g:method:getAddress"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFamily]("GI.Gio.Objects.InetAddressMask#g:method:getFamily"), [getLength]("GI.Gio.Objects.InetAddressMask#g:method:getLength"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveInetAddressMaskMethod            ,
#endif

-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskEqualMethodInfo          ,
#endif
    inetAddressMaskEqual                    ,


-- ** getAddress #method:getAddress#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskGetAddressMethodInfo     ,
#endif
    inetAddressMaskGetAddress               ,


-- ** getFamily #method:getFamily#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskGetFamilyMethodInfo      ,
#endif
    inetAddressMaskGetFamily                ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskGetLengthMethodInfo      ,
#endif
    inetAddressMaskGetLength                ,


-- ** matches #method:matches#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskMatchesMethodInfo        ,
#endif
    inetAddressMaskMatches                  ,


-- ** new #method:new#

    inetAddressMaskNew                      ,


-- ** newFromString #method:newFromString#

    inetAddressMaskNewFromString            ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskToStringMethodInfo       ,
#endif
    inetAddressMaskToString                 ,




 -- * Properties


-- ** address #attr:address#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskAddressPropertyInfo      ,
#endif
    clearInetAddressMaskAddress             ,
    constructInetAddressMaskAddress         ,
    getInetAddressMaskAddress               ,
#if defined(ENABLE_OVERLOADING)
    inetAddressMaskAddress                  ,
#endif
    setInetAddressMaskAddress               ,


-- ** family #attr:family#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    InetAddressMaskFamilyPropertyInfo       ,
#endif
    getInetAddressMaskFamily                ,
#if defined(ENABLE_OVERLOADING)
    inetAddressMaskFamily                   ,
#endif


-- ** length #attr:length#
-- | /No description available in the introspection data./

#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.GArray as B.GArray
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 GHC.Records as R

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

-- | Memory-managed wrapper type.
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

-- | Type class for types which can be safely cast to `InetAddressMask`, for instance with `toInetAddressMask`.
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]

-- | Cast to `InetAddressMask`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toInetAddressMask :: (MIO.MonadIO m, IsInetAddressMask o) => o -> m InetAddressMask
toInetAddressMask :: forall (m :: * -> *) o.
(MonadIO m, IsInetAddressMask o) =>
o -> m InetAddressMask
toInetAddressMask = IO InetAddressMask -> m InetAddressMask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr InetAddressMask -> InetAddressMask
InetAddressMask

-- | Convert 'InetAddressMask' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe InetAddressMask) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_inet_address_mask_get_type
    gvalueSet_ :: Ptr GValue -> Maybe InetAddressMask -> IO ()
gvalueSet_ Ptr GValue
gv Maybe InetAddressMask
P.Nothing = Ptr GValue -> Ptr InetAddressMask -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr InetAddressMask
forall a. Ptr a
FP.nullPtr :: FP.Ptr InetAddressMask)
    gvalueSet_ Ptr GValue
gv (P.Just InetAddressMask
obj) = InetAddressMask -> (Ptr InetAddressMask -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr InetAddressMask
obj (Ptr GValue -> Ptr InetAddressMask -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe InetAddressMask)
gvalueGet_ Ptr GValue
gv = do
        Ptr InetAddressMask
ptr <- Ptr GValue -> IO (Ptr InetAddressMask)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr InetAddressMask)
        if Ptr InetAddressMask
ptr Ptr InetAddressMask -> Ptr InetAddressMask -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr InetAddressMask
forall a. Ptr a
FP.nullPtr
        then InetAddressMask -> Maybe InetAddressMask
forall a. a -> Maybe a
P.Just (InetAddressMask -> Maybe InetAddressMask)
-> IO InetAddressMask -> IO (Maybe InetAddressMask)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe InetAddressMask -> IO (Maybe InetAddressMask)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe InetAddressMask
forall a. Maybe a
P.Nothing
        
    

#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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveInetAddressMaskMethod t InetAddressMask, O.OverloadedMethod info InetAddressMask p, R.HasField t InetAddressMask p) => R.HasField t InetAddressMask p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveInetAddressMaskMethod t InetAddressMask, O.OverloadedMethodInfo info InetAddressMask) => OL.IsLabel t (O.MethodProxy info InetAddressMask) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "address"
   -- Type: TInterface (Name {namespace = "Gio", name = "InetAddress"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@address@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddressMask #address
-- @
getInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o) => o -> m Gio.InetAddress.InetAddress
getInetAddressMaskAddress :: forall (m :: * -> *) o.
(MonadIO m, IsInetAddressMask o) =>
o -> m InetAddress
getInetAddressMaskAddress o
obj = IO InetAddress -> m InetAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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

-- | Set the value of the “@address@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' inetAddressMask [ #address 'Data.GI.Base.Attributes.:=' value ]
-- @
setInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o, Gio.InetAddress.IsInetAddress a) => o -> a -> m ()
setInetAddressMaskAddress :: forall (m :: * -> *) o a.
(MonadIO m, IsInetAddressMask o, IsInetAddress a) =>
o -> a -> m ()
setInetAddressMaskAddress o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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)

-- | Construct a `GValueConstruct` with valid value for the “@address@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInetAddressMaskAddress :: (IsInetAddressMask o, MIO.MonadIO m, Gio.InetAddress.IsInetAddress a) => a -> m (GValueConstruct o)
constructInetAddressMaskAddress :: forall o (m :: * -> *) a.
(IsInetAddressMask o, MonadIO m, IsInetAddress a) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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)

-- | Set the value of the “@address@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #address
-- @
clearInetAddressMaskAddress :: (MonadIO m, IsInetAddressMask o) => o -> m ()
clearInetAddressMaskAddress :: forall (m :: * -> *) o.
(MonadIO m, IsInetAddressMask o) =>
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

-- VVV Prop "family"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketFamily"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@family@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddressMask #family
-- @
getInetAddressMaskFamily :: (MonadIO m, IsInetAddressMask o) => o -> m Gio.Enums.SocketFamily
getInetAddressMaskFamily :: forall (m :: * -> *) o.
(MonadIO m, IsInetAddressMask o) =>
o -> m SocketFamily
getInetAddressMaskFamily o
obj = IO SocketFamily -> m SocketFamily
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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

-- VVV Prop "length"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@length@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddressMask #length
-- @
getInetAddressMaskLength :: (MonadIO m, IsInetAddressMask o) => o -> m Word32
getInetAddressMaskLength :: forall (m :: * -> *) o.
(MonadIO m, IsInetAddressMask o) =>
o -> m Word32
getInetAddressMaskLength o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

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

-- | Construct a `GValueConstruct` with valid value for the “@length@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInetAddressMaskLength :: (IsInetAddressMask o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructInetAddressMaskLength :: forall o (m :: * -> *).
(IsInetAddressMask o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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

-- method InetAddressMask::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "addr"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GInetAddress" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of bits of @addr to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "InetAddressMask" })
-- throws : True
-- Skip return : False

foreign import ccall "g_inet_address_mask_new" g_inet_address_mask_new :: 
    Ptr Gio.InetAddress.InetAddress ->      -- addr : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    Word32 ->                               -- length : TBasicType TUInt
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr InetAddressMask)

-- | Creates a new t'GI.Gio.Objects.InetAddressMask.InetAddressMask' representing all addresses whose
-- first /@length@/ bits match /@addr@/.
-- 
-- /Since: 2.32/
inetAddressMaskNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InetAddress.IsInetAddress a) =>
    a
    -- ^ /@addr@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> Word32
    -- ^ /@length@/: number of bits of /@addr@/ to use
    -> m InetAddressMask
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddressMask.InetAddressMask', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
inetAddressMaskNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddress a) =>
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

-- method InetAddressMask::new_from_string
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "mask_string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an IP address or address/length string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "InetAddressMask" })
-- throws : True
-- Skip return : False

foreign import ccall "g_inet_address_mask_new_from_string" g_inet_address_mask_new_from_string :: 
    CString ->                              -- mask_string : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr InetAddressMask)

-- | Parses /@maskString@/ as an IP address and (optional) length, and
-- creates a new t'GI.Gio.Objects.InetAddressMask.InetAddressMask'. The length, if present, is
-- delimited by a \"\/\". If it is not present, then the length is
-- assumed to be the full length of the address.
-- 
-- /Since: 2.32/
inetAddressMaskNewFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@maskString@/: an IP address or address\/length string
    -> m InetAddressMask
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddressMask.InetAddressMask' corresponding to /@string@/, or 'P.Nothing'
    -- on error. /(Can throw 'Data.GI.Base.GError.GError')/
inetAddressMaskNewFromString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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

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

foreign import ccall "g_inet_address_mask_equal" g_inet_address_mask_equal :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    Ptr InetAddressMask ->                  -- mask2 : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    IO CInt

-- | Tests if /@mask@/ and /@mask2@/ are the same mask.
-- 
-- /Since: 2.32/
inetAddressMaskEqual ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a, IsInetAddressMask b) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> b
    -- ^ /@mask2@/: another t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> m Bool
    -- ^ __Returns:__ whether /@mask@/ and /@mask2@/ are the same mask
inetAddressMaskEqual :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInetAddressMask a,
 IsInetAddressMask b) =>
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.OverloadedMethod InetAddressMaskEqualMethodInfo a signature where
    overloadedMethod = inetAddressMaskEqual

instance O.OverloadedMethodInfo InetAddressMaskEqualMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskEqual",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskEqual"
        }


#endif

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

foreign import ccall "g_inet_address_mask_get_address" g_inet_address_mask_get_address :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    IO (Ptr Gio.InetAddress.InetAddress)

-- | Gets /@mask@/\'s base address
-- 
-- /Since: 2.32/
inetAddressMaskGetAddress ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> m Gio.InetAddress.InetAddress
    -- ^ __Returns:__ /@mask@/\'s base address
inetAddressMaskGetAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddressMask a) =>
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.OverloadedMethod InetAddressMaskGetAddressMethodInfo a signature where
    overloadedMethod = inetAddressMaskGetAddress

instance O.OverloadedMethodInfo InetAddressMaskGetAddressMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskGetAddress",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskGetAddress"
        }


#endif

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

foreign import ccall "g_inet_address_mask_get_family" g_inet_address_mask_get_family :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    IO CUInt

-- | Gets the t'GI.Gio.Enums.SocketFamily' of /@mask@/\'s address
-- 
-- /Since: 2.32/
inetAddressMaskGetFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> m Gio.Enums.SocketFamily
    -- ^ __Returns:__ the t'GI.Gio.Enums.SocketFamily' of /@mask@/\'s address
inetAddressMaskGetFamily :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddressMask a) =>
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.OverloadedMethod InetAddressMaskGetFamilyMethodInfo a signature where
    overloadedMethod = inetAddressMaskGetFamily

instance O.OverloadedMethodInfo InetAddressMaskGetFamilyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskGetFamily",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskGetFamily"
        }


#endif

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

foreign import ccall "g_inet_address_mask_get_length" g_inet_address_mask_get_length :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    IO Word32

-- | Gets /@mask@/\'s length
-- 
-- /Since: 2.32/
inetAddressMaskGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> m Word32
    -- ^ __Returns:__ /@mask@/\'s length
inetAddressMaskGetLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddressMask a) =>
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.OverloadedMethod InetAddressMaskGetLengthMethodInfo a signature where
    overloadedMethod = inetAddressMaskGetLength

instance O.OverloadedMethodInfo InetAddressMaskGetLengthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskGetLength",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskGetLength"
        }


#endif

-- method InetAddressMask::matches
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mask"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddressMask" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GInetAddressMask"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GInetAddress" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_inet_address_mask_matches" g_inet_address_mask_matches :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    Ptr Gio.InetAddress.InetAddress ->      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests if /@address@/ falls within the range described by /@mask@/.
-- 
-- /Since: 2.32/
inetAddressMaskMatches ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a, Gio.InetAddress.IsInetAddress b) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> b
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ whether /@address@/ falls within the range described by
    -- /@mask@/.
inetAddressMaskMatches :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInetAddressMask a, IsInetAddress b) =>
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.OverloadedMethod InetAddressMaskMatchesMethodInfo a signature where
    overloadedMethod = inetAddressMaskMatches

instance O.OverloadedMethodInfo InetAddressMaskMatchesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskMatches",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskMatches"
        }


#endif

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

foreign import ccall "g_inet_address_mask_to_string" g_inet_address_mask_to_string :: 
    Ptr InetAddressMask ->                  -- mask : TInterface (Name {namespace = "Gio", name = "InetAddressMask"})
    IO CString

-- | Converts /@mask@/ back to its corresponding string form.
-- 
-- /Since: 2.32/
inetAddressMaskToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddressMask a) =>
    a
    -- ^ /@mask@/: a t'GI.Gio.Objects.InetAddressMask.InetAddressMask'
    -> m T.Text
    -- ^ __Returns:__ a string corresponding to /@mask@/.
inetAddressMaskToString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddressMask a) =>
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.OverloadedMethod InetAddressMaskToStringMethodInfo a signature where
    overloadedMethod = inetAddressMaskToString

instance O.OverloadedMethodInfo InetAddressMaskToStringMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.InetAddressMask.inetAddressMaskToString",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-InetAddressMask.html#v:inetAddressMaskToString"
        }


#endif