{-# 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.InetAddress.InetAddress' represents an IPv4 or IPv6 internet address. Use
-- 'GI.Gio.Objects.Resolver.resolverLookupByName' or 'GI.Gio.Objects.Resolver.resolverLookupByNameAsync' to
-- look up the t'GI.Gio.Objects.InetAddress.InetAddress' for a hostname. Use
-- 'GI.Gio.Objects.Resolver.resolverLookupByAddress' or
-- 'GI.Gio.Objects.Resolver.resolverLookupByAddressAsync' to look up the hostname for a
-- t'GI.Gio.Objects.InetAddress.InetAddress'.
-- 
-- To actually connect to a remote host, you will need a
-- t'GI.Gio.Objects.InetSocketAddress.InetSocketAddress' (which includes a t'GI.Gio.Objects.InetAddress.InetAddress' as well as a
-- port number).

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

module GI.Gio.Objects.InetAddress
    ( 

-- * Exported types
    InetAddress(..)                         ,
    IsInetAddress                           ,
    toInetAddress                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveInetAddressMethod                ,
#endif


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    InetAddressEqualMethodInfo              ,
#endif
    inetAddressEqual                        ,


-- ** getFamily #method:getFamily#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetFamilyMethodInfo          ,
#endif
    inetAddressGetFamily                    ,


-- ** getIsAny #method:getIsAny#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsAnyMethodInfo           ,
#endif
    inetAddressGetIsAny                     ,


-- ** getIsLinkLocal #method:getIsLinkLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsLinkLocalMethodInfo     ,
#endif
    inetAddressGetIsLinkLocal               ,


-- ** getIsLoopback #method:getIsLoopback#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsLoopbackMethodInfo      ,
#endif
    inetAddressGetIsLoopback                ,


-- ** getIsMcGlobal #method:getIsMcGlobal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMcGlobalMethodInfo      ,
#endif
    inetAddressGetIsMcGlobal                ,


-- ** getIsMcLinkLocal #method:getIsMcLinkLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMcLinkLocalMethodInfo   ,
#endif
    inetAddressGetIsMcLinkLocal             ,


-- ** getIsMcNodeLocal #method:getIsMcNodeLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMcNodeLocalMethodInfo   ,
#endif
    inetAddressGetIsMcNodeLocal             ,


-- ** getIsMcOrgLocal #method:getIsMcOrgLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMcOrgLocalMethodInfo    ,
#endif
    inetAddressGetIsMcOrgLocal              ,


-- ** getIsMcSiteLocal #method:getIsMcSiteLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMcSiteLocalMethodInfo   ,
#endif
    inetAddressGetIsMcSiteLocal             ,


-- ** getIsMulticast #method:getIsMulticast#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsMulticastMethodInfo     ,
#endif
    inetAddressGetIsMulticast               ,


-- ** getIsSiteLocal #method:getIsSiteLocal#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetIsSiteLocalMethodInfo     ,
#endif
    inetAddressGetIsSiteLocal               ,


-- ** getNativeSize #method:getNativeSize#

#if defined(ENABLE_OVERLOADING)
    InetAddressGetNativeSizeMethodInfo      ,
#endif
    inetAddressGetNativeSize                ,


-- ** newAny #method:newAny#

    inetAddressNewAny                       ,


-- ** newFromBytes #method:newFromBytes#

    inetAddressNewFromBytes                 ,


-- ** newFromString #method:newFromString#

    inetAddressNewFromString                ,


-- ** newLoopback #method:newLoopback#

    inetAddressNewLoopback                  ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    InetAddressToStringMethodInfo           ,
#endif
    inetAddressToString                     ,




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

#if defined(ENABLE_OVERLOADING)
    InetAddressBytesPropertyInfo            ,
#endif
    constructInetAddressBytes               ,
    getInetAddressBytes                     ,
#if defined(ENABLE_OVERLOADING)
    inetAddressBytes                        ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    InetAddressFamilyPropertyInfo           ,
#endif
    constructInetAddressFamily              ,
    getInetAddressFamily                    ,
#if defined(ENABLE_OVERLOADING)
    inetAddressFamily                       ,
#endif


-- ** isAny #attr:isAny#
-- | Whether this is the \"any\" address for its family.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsAny'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsAnyPropertyInfo            ,
#endif
    getInetAddressIsAny                     ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsAny                        ,
#endif


-- ** isLinkLocal #attr:isLinkLocal#
-- | Whether this is a link-local address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsLinkLocal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsLinkLocalPropertyInfo      ,
#endif
    getInetAddressIsLinkLocal               ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsLinkLocal                  ,
#endif


-- ** isLoopback #attr:isLoopback#
-- | Whether this is the loopback address for its family.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsLoopback'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsLoopbackPropertyInfo       ,
#endif
    getInetAddressIsLoopback                ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsLoopback                   ,
#endif


-- ** isMcGlobal #attr:isMcGlobal#
-- | Whether this is a global multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMcGlobal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMcGlobalPropertyInfo       ,
#endif
    getInetAddressIsMcGlobal                ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMcGlobal                   ,
#endif


-- ** isMcLinkLocal #attr:isMcLinkLocal#
-- | Whether this is a link-local multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMcLinkLocal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMcLinkLocalPropertyInfo    ,
#endif
    getInetAddressIsMcLinkLocal             ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMcLinkLocal                ,
#endif


-- ** isMcNodeLocal #attr:isMcNodeLocal#
-- | Whether this is a node-local multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMcNodeLocal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMcNodeLocalPropertyInfo    ,
#endif
    getInetAddressIsMcNodeLocal             ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMcNodeLocal                ,
#endif


-- ** isMcOrgLocal #attr:isMcOrgLocal#
-- | Whether this is an organization-local multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMcOrgLocal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMcOrgLocalPropertyInfo     ,
#endif
    getInetAddressIsMcOrgLocal              ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMcOrgLocal                 ,
#endif


-- ** isMcSiteLocal #attr:isMcSiteLocal#
-- | Whether this is a site-local multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMcSiteLocal'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMcSiteLocalPropertyInfo    ,
#endif
    getInetAddressIsMcSiteLocal             ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMcSiteLocal                ,
#endif


-- ** isMulticast #attr:isMulticast#
-- | Whether this is a multicast address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsMulticast'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsMulticastPropertyInfo      ,
#endif
    getInetAddressIsMulticast               ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsMulticast                  ,
#endif


-- ** isSiteLocal #attr:isSiteLocal#
-- | Whether this is a site-local address.
-- See 'GI.Gio.Objects.InetAddress.inetAddressGetIsLoopback'.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    InetAddressIsSiteLocalPropertyInfo      ,
#endif
    getInetAddressIsSiteLocal               ,
#if defined(ENABLE_OVERLOADING)
    inetAddressIsSiteLocal                  ,
#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

-- | Memory-managed wrapper type.
newtype InetAddress = InetAddress (SP.ManagedPtr InetAddress)
    deriving (InetAddress -> InetAddress -> Bool
(InetAddress -> InetAddress -> Bool)
-> (InetAddress -> InetAddress -> Bool) -> Eq InetAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InetAddress -> InetAddress -> Bool
$c/= :: InetAddress -> InetAddress -> Bool
== :: InetAddress -> InetAddress -> Bool
$c== :: InetAddress -> InetAddress -> Bool
Eq)

instance SP.ManagedPtrNewtype InetAddress where
    toManagedPtr :: InetAddress -> ManagedPtr InetAddress
toManagedPtr (InetAddress ManagedPtr InetAddress
p) = ManagedPtr InetAddress
p

foreign import ccall "g_inet_address_get_type"
    c_g_inet_address_get_type :: IO B.Types.GType

instance B.Types.TypedObject InetAddress where
    glibType :: IO GType
glibType = IO GType
c_g_inet_address_get_type

instance B.Types.GObject InetAddress

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

-- | Type class for types which can be safely cast to `InetAddress`, for instance with `toInetAddress`.
class (SP.GObject o, O.IsDescendantOf InetAddress o) => IsInetAddress o
instance (SP.GObject o, O.IsDescendantOf InetAddress o) => IsInetAddress o

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveInetAddressMethod (t :: Symbol) (o :: *) :: * where
    ResolveInetAddressMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveInetAddressMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveInetAddressMethod "equal" o = InetAddressEqualMethodInfo
    ResolveInetAddressMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveInetAddressMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveInetAddressMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveInetAddressMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveInetAddressMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveInetAddressMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveInetAddressMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveInetAddressMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveInetAddressMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveInetAddressMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveInetAddressMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveInetAddressMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveInetAddressMethod "toString" o = InetAddressToStringMethodInfo
    ResolveInetAddressMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveInetAddressMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveInetAddressMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveInetAddressMethod "getFamily" o = InetAddressGetFamilyMethodInfo
    ResolveInetAddressMethod "getIsAny" o = InetAddressGetIsAnyMethodInfo
    ResolveInetAddressMethod "getIsLinkLocal" o = InetAddressGetIsLinkLocalMethodInfo
    ResolveInetAddressMethod "getIsLoopback" o = InetAddressGetIsLoopbackMethodInfo
    ResolveInetAddressMethod "getIsMcGlobal" o = InetAddressGetIsMcGlobalMethodInfo
    ResolveInetAddressMethod "getIsMcLinkLocal" o = InetAddressGetIsMcLinkLocalMethodInfo
    ResolveInetAddressMethod "getIsMcNodeLocal" o = InetAddressGetIsMcNodeLocalMethodInfo
    ResolveInetAddressMethod "getIsMcOrgLocal" o = InetAddressGetIsMcOrgLocalMethodInfo
    ResolveInetAddressMethod "getIsMcSiteLocal" o = InetAddressGetIsMcSiteLocalMethodInfo
    ResolveInetAddressMethod "getIsMulticast" o = InetAddressGetIsMulticastMethodInfo
    ResolveInetAddressMethod "getIsSiteLocal" o = InetAddressGetIsSiteLocalMethodInfo
    ResolveInetAddressMethod "getNativeSize" o = InetAddressGetNativeSizeMethodInfo
    ResolveInetAddressMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveInetAddressMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveInetAddressMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveInetAddressMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveInetAddressMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveInetAddressMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveInetAddressMethod t InetAddress, O.MethodInfo info InetAddress p) => OL.IsLabel t (InetAddress -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "bytes"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@bytes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #bytes
-- @
getInetAddressBytes :: (MonadIO m, IsInetAddress o) => o -> m (Ptr ())
getInetAddressBytes :: o -> m (Ptr ())
getInetAddressBytes o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj String
"bytes"

-- | Construct a `GValueConstruct` with valid value for the “@bytes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInetAddressBytes :: (IsInetAddress o, MIO.MonadIO m) => Ptr () -> m (GValueConstruct o)
constructInetAddressBytes :: Ptr () -> m (GValueConstruct o)
constructInetAddressBytes Ptr ()
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 -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr String
"bytes" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data InetAddressBytesPropertyInfo
instance AttrInfo InetAddressBytesPropertyInfo where
    type AttrAllowedOps InetAddressBytesPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint InetAddressBytesPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressBytesPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint InetAddressBytesPropertyInfo = (~) (Ptr ())
    type AttrTransferType InetAddressBytesPropertyInfo = Ptr ()
    type AttrGetType InetAddressBytesPropertyInfo = (Ptr ())
    type AttrLabel InetAddressBytesPropertyInfo = "bytes"
    type AttrOrigin InetAddressBytesPropertyInfo = InetAddress
    attrGet = getInetAddressBytes
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructInetAddressBytes
    attrClear = undefined
#endif

-- VVV Prop "family"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketFamily"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- 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' inetAddress #family
-- @
getInetAddressFamily :: (MonadIO m, IsInetAddress o) => o -> m Gio.Enums.SocketFamily
getInetAddressFamily :: o -> m SocketFamily
getInetAddressFamily 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"

-- | Construct a `GValueConstruct` with valid value for the “@family@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInetAddressFamily :: (IsInetAddress o, MIO.MonadIO m) => Gio.Enums.SocketFamily -> m (GValueConstruct o)
constructInetAddressFamily :: SocketFamily -> m (GValueConstruct o)
constructInetAddressFamily SocketFamily
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 -> SocketFamily -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"family" SocketFamily
val

#if defined(ENABLE_OVERLOADING)
data InetAddressFamilyPropertyInfo
instance AttrInfo InetAddressFamilyPropertyInfo where
    type AttrAllowedOps InetAddressFamilyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint InetAddressFamilyPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressFamilyPropertyInfo = (~) Gio.Enums.SocketFamily
    type AttrTransferTypeConstraint InetAddressFamilyPropertyInfo = (~) Gio.Enums.SocketFamily
    type AttrTransferType InetAddressFamilyPropertyInfo = Gio.Enums.SocketFamily
    type AttrGetType InetAddressFamilyPropertyInfo = Gio.Enums.SocketFamily
    type AttrLabel InetAddressFamilyPropertyInfo = "family"
    type AttrOrigin InetAddressFamilyPropertyInfo = InetAddress
    attrGet = getInetAddressFamily
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructInetAddressFamily
    attrClear = undefined
#endif

-- VVV Prop "is-any"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-any@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isAny
-- @
getInetAddressIsAny :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsAny :: o -> m Bool
getInetAddressIsAny 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
"is-any"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsAnyPropertyInfo
instance AttrInfo InetAddressIsAnyPropertyInfo where
    type AttrAllowedOps InetAddressIsAnyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsAnyPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsAnyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsAnyPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsAnyPropertyInfo = ()
    type AttrGetType InetAddressIsAnyPropertyInfo = Bool
    type AttrLabel InetAddressIsAnyPropertyInfo = "is-any"
    type AttrOrigin InetAddressIsAnyPropertyInfo = InetAddress
    attrGet = getInetAddressIsAny
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-link-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-link-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isLinkLocal
-- @
getInetAddressIsLinkLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsLinkLocal :: o -> m Bool
getInetAddressIsLinkLocal 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
"is-link-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsLinkLocalPropertyInfo
instance AttrInfo InetAddressIsLinkLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsLinkLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsLinkLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsLinkLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsLinkLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsLinkLocalPropertyInfo = ()
    type AttrGetType InetAddressIsLinkLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsLinkLocalPropertyInfo = "is-link-local"
    type AttrOrigin InetAddressIsLinkLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsLinkLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-loopback"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-loopback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isLoopback
-- @
getInetAddressIsLoopback :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsLoopback :: o -> m Bool
getInetAddressIsLoopback 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
"is-loopback"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsLoopbackPropertyInfo
instance AttrInfo InetAddressIsLoopbackPropertyInfo where
    type AttrAllowedOps InetAddressIsLoopbackPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsLoopbackPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsLoopbackPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsLoopbackPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsLoopbackPropertyInfo = ()
    type AttrGetType InetAddressIsLoopbackPropertyInfo = Bool
    type AttrLabel InetAddressIsLoopbackPropertyInfo = "is-loopback"
    type AttrOrigin InetAddressIsLoopbackPropertyInfo = InetAddress
    attrGet = getInetAddressIsLoopback
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-mc-global"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-mc-global@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMcGlobal
-- @
getInetAddressIsMcGlobal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMcGlobal :: o -> m Bool
getInetAddressIsMcGlobal 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
"is-mc-global"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMcGlobalPropertyInfo
instance AttrInfo InetAddressIsMcGlobalPropertyInfo where
    type AttrAllowedOps InetAddressIsMcGlobalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMcGlobalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMcGlobalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMcGlobalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMcGlobalPropertyInfo = ()
    type AttrGetType InetAddressIsMcGlobalPropertyInfo = Bool
    type AttrLabel InetAddressIsMcGlobalPropertyInfo = "is-mc-global"
    type AttrOrigin InetAddressIsMcGlobalPropertyInfo = InetAddress
    attrGet = getInetAddressIsMcGlobal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-mc-link-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-mc-link-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMcLinkLocal
-- @
getInetAddressIsMcLinkLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMcLinkLocal :: o -> m Bool
getInetAddressIsMcLinkLocal 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
"is-mc-link-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMcLinkLocalPropertyInfo
instance AttrInfo InetAddressIsMcLinkLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsMcLinkLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMcLinkLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMcLinkLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMcLinkLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMcLinkLocalPropertyInfo = ()
    type AttrGetType InetAddressIsMcLinkLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsMcLinkLocalPropertyInfo = "is-mc-link-local"
    type AttrOrigin InetAddressIsMcLinkLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsMcLinkLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-mc-node-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-mc-node-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMcNodeLocal
-- @
getInetAddressIsMcNodeLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMcNodeLocal :: o -> m Bool
getInetAddressIsMcNodeLocal 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
"is-mc-node-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMcNodeLocalPropertyInfo
instance AttrInfo InetAddressIsMcNodeLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsMcNodeLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMcNodeLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMcNodeLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMcNodeLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMcNodeLocalPropertyInfo = ()
    type AttrGetType InetAddressIsMcNodeLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsMcNodeLocalPropertyInfo = "is-mc-node-local"
    type AttrOrigin InetAddressIsMcNodeLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsMcNodeLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-mc-org-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-mc-org-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMcOrgLocal
-- @
getInetAddressIsMcOrgLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMcOrgLocal :: o -> m Bool
getInetAddressIsMcOrgLocal 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
"is-mc-org-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMcOrgLocalPropertyInfo
instance AttrInfo InetAddressIsMcOrgLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsMcOrgLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMcOrgLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMcOrgLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMcOrgLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMcOrgLocalPropertyInfo = ()
    type AttrGetType InetAddressIsMcOrgLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsMcOrgLocalPropertyInfo = "is-mc-org-local"
    type AttrOrigin InetAddressIsMcOrgLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsMcOrgLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-mc-site-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-mc-site-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMcSiteLocal
-- @
getInetAddressIsMcSiteLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMcSiteLocal :: o -> m Bool
getInetAddressIsMcSiteLocal 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
"is-mc-site-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMcSiteLocalPropertyInfo
instance AttrInfo InetAddressIsMcSiteLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsMcSiteLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMcSiteLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMcSiteLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMcSiteLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMcSiteLocalPropertyInfo = ()
    type AttrGetType InetAddressIsMcSiteLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsMcSiteLocalPropertyInfo = "is-mc-site-local"
    type AttrOrigin InetAddressIsMcSiteLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsMcSiteLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-multicast"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-multicast@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isMulticast
-- @
getInetAddressIsMulticast :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsMulticast :: o -> m Bool
getInetAddressIsMulticast 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
"is-multicast"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsMulticastPropertyInfo
instance AttrInfo InetAddressIsMulticastPropertyInfo where
    type AttrAllowedOps InetAddressIsMulticastPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsMulticastPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsMulticastPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsMulticastPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsMulticastPropertyInfo = ()
    type AttrGetType InetAddressIsMulticastPropertyInfo = Bool
    type AttrLabel InetAddressIsMulticastPropertyInfo = "is-multicast"
    type AttrOrigin InetAddressIsMulticastPropertyInfo = InetAddress
    attrGet = getInetAddressIsMulticast
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "is-site-local"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@is-site-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inetAddress #isSiteLocal
-- @
getInetAddressIsSiteLocal :: (MonadIO m, IsInetAddress o) => o -> m Bool
getInetAddressIsSiteLocal :: o -> m Bool
getInetAddressIsSiteLocal 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
"is-site-local"

#if defined(ENABLE_OVERLOADING)
data InetAddressIsSiteLocalPropertyInfo
instance AttrInfo InetAddressIsSiteLocalPropertyInfo where
    type AttrAllowedOps InetAddressIsSiteLocalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint InetAddressIsSiteLocalPropertyInfo = IsInetAddress
    type AttrSetTypeConstraint InetAddressIsSiteLocalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint InetAddressIsSiteLocalPropertyInfo = (~) ()
    type AttrTransferType InetAddressIsSiteLocalPropertyInfo = ()
    type AttrGetType InetAddressIsSiteLocalPropertyInfo = Bool
    type AttrLabel InetAddressIsSiteLocalPropertyInfo = "is-site-local"
    type AttrOrigin InetAddressIsSiteLocalPropertyInfo = InetAddress
    attrGet = getInetAddressIsSiteLocal
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList InetAddress
type instance O.AttributeList InetAddress = InetAddressAttributeList
type InetAddressAttributeList = ('[ '("bytes", InetAddressBytesPropertyInfo), '("family", InetAddressFamilyPropertyInfo), '("isAny", InetAddressIsAnyPropertyInfo), '("isLinkLocal", InetAddressIsLinkLocalPropertyInfo), '("isLoopback", InetAddressIsLoopbackPropertyInfo), '("isMcGlobal", InetAddressIsMcGlobalPropertyInfo), '("isMcLinkLocal", InetAddressIsMcLinkLocalPropertyInfo), '("isMcNodeLocal", InetAddressIsMcNodeLocalPropertyInfo), '("isMcOrgLocal", InetAddressIsMcOrgLocalPropertyInfo), '("isMcSiteLocal", InetAddressIsMcSiteLocalPropertyInfo), '("isMulticast", InetAddressIsMulticastPropertyInfo), '("isSiteLocal", InetAddressIsSiteLocalPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
inetAddressBytes :: AttrLabelProxy "bytes"
inetAddressBytes = AttrLabelProxy

inetAddressFamily :: AttrLabelProxy "family"
inetAddressFamily = AttrLabelProxy

inetAddressIsAny :: AttrLabelProxy "isAny"
inetAddressIsAny = AttrLabelProxy

inetAddressIsLinkLocal :: AttrLabelProxy "isLinkLocal"
inetAddressIsLinkLocal = AttrLabelProxy

inetAddressIsLoopback :: AttrLabelProxy "isLoopback"
inetAddressIsLoopback = AttrLabelProxy

inetAddressIsMcGlobal :: AttrLabelProxy "isMcGlobal"
inetAddressIsMcGlobal = AttrLabelProxy

inetAddressIsMcLinkLocal :: AttrLabelProxy "isMcLinkLocal"
inetAddressIsMcLinkLocal = AttrLabelProxy

inetAddressIsMcNodeLocal :: AttrLabelProxy "isMcNodeLocal"
inetAddressIsMcNodeLocal = AttrLabelProxy

inetAddressIsMcOrgLocal :: AttrLabelProxy "isMcOrgLocal"
inetAddressIsMcOrgLocal = AttrLabelProxy

inetAddressIsMcSiteLocal :: AttrLabelProxy "isMcSiteLocal"
inetAddressIsMcSiteLocal = AttrLabelProxy

inetAddressIsMulticast :: AttrLabelProxy "isMulticast"
inetAddressIsMulticast = AttrLabelProxy

inetAddressIsSiteLocal :: AttrLabelProxy "isSiteLocal"
inetAddressIsSiteLocal = AttrLabelProxy

#endif

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

#endif

-- method InetAddress::new_any
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "family"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketFamily" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the address family" , 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_new_any" g_inet_address_new_any :: 
    CUInt ->                                -- family : TInterface (Name {namespace = "Gio", name = "SocketFamily"})
    IO (Ptr InetAddress)

-- | Creates a t'GI.Gio.Objects.InetAddress.InetAddress' for the \"any\" address (unassigned\/\"don\'t
-- care\") for /@family@/.
-- 
-- /Since: 2.22/
inetAddressNewAny ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gio.Enums.SocketFamily
    -- ^ /@family@/: the address family
    -> m InetAddress
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddress.InetAddress' corresponding to the \"any\" address
    -- for /@family@/.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
inetAddressNewAny :: SocketFamily -> m InetAddress
inetAddressNewAny SocketFamily
family = 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
    let family' :: CUInt
family' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SocketFamily -> Int) -> SocketFamily -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketFamily -> Int
forall a. Enum a => a -> Int
fromEnum) SocketFamily
family
    Ptr InetAddress
result <- CUInt -> IO (Ptr InetAddress)
g_inet_address_new_any CUInt
family'
    Text -> Ptr InetAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressNewAny" 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
wrapObject ManagedPtr InetAddress -> InetAddress
InetAddress) Ptr InetAddress
result
    InetAddress -> IO InetAddress
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method InetAddress::new_from_bytes
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "raw address data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "family"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketFamily" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the address family of @bytes"
--                 , 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_new_from_bytes" g_inet_address_new_from_bytes :: 
    Ptr Word8 ->                            -- bytes : TCArray False (-1) (-1) (TBasicType TUInt8)
    CUInt ->                                -- family : TInterface (Name {namespace = "Gio", name = "SocketFamily"})
    IO (Ptr InetAddress)

-- | Creates a new t'GI.Gio.Objects.InetAddress.InetAddress' from the given /@family@/ and /@bytes@/.
-- /@bytes@/ should be 4 bytes for 'GI.Gio.Enums.SocketFamilyIpv4' and 16 bytes for
-- 'GI.Gio.Enums.SocketFamilyIpv6'.
-- 
-- /Since: 2.22/
inetAddressNewFromBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Ptr Word8
    -- ^ /@bytes@/: raw address data
    -> Gio.Enums.SocketFamily
    -- ^ /@family@/: the address family of /@bytes@/
    -> m InetAddress
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddress.InetAddress' corresponding to /@family@/ and /@bytes@/.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
inetAddressNewFromBytes :: Ptr Word8 -> SocketFamily -> m InetAddress
inetAddressNewFromBytes Ptr Word8
bytes SocketFamily
family = 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
    let family' :: CUInt
family' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SocketFamily -> Int) -> SocketFamily -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketFamily -> Int
forall a. Enum a => a -> Int
fromEnum) SocketFamily
family
    Ptr InetAddress
result <- Ptr Word8 -> CUInt -> IO (Ptr InetAddress)
g_inet_address_new_from_bytes Ptr Word8
bytes CUInt
family'
    Text -> Ptr InetAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressNewFromBytes" 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
wrapObject ManagedPtr InetAddress -> InetAddress
InetAddress) Ptr InetAddress
result
    InetAddress -> IO InetAddress
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method InetAddress::new_from_string
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string representation of an IP address"
--                 , 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_new_from_string" g_inet_address_new_from_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO (Ptr InetAddress)

-- | Parses /@string@/ as an IP address and creates a new t'GI.Gio.Objects.InetAddress.InetAddress'.
-- 
-- /Since: 2.22/
inetAddressNewFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@string@/: a string representation of an IP address
    -> m InetAddress
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddress.InetAddress' corresponding to /@string@/, or 'P.Nothing' if
    -- /@string@/ could not be parsed.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
inetAddressNewFromString :: Text -> m InetAddress
inetAddressNewFromString Text
string = 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
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr InetAddress
result <- CString -> IO (Ptr InetAddress)
g_inet_address_new_from_string CString
string'
    Text -> Ptr InetAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressNewFromString" 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
wrapObject ManagedPtr InetAddress -> InetAddress
InetAddress) Ptr InetAddress
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    InetAddress -> IO InetAddress
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method InetAddress::new_loopback
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "family"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketFamily" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the address family" , 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_new_loopback" g_inet_address_new_loopback :: 
    CUInt ->                                -- family : TInterface (Name {namespace = "Gio", name = "SocketFamily"})
    IO (Ptr InetAddress)

-- | Creates a t'GI.Gio.Objects.InetAddress.InetAddress' for the loopback address for /@family@/.
-- 
-- /Since: 2.22/
inetAddressNewLoopback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gio.Enums.SocketFamily
    -- ^ /@family@/: the address family
    -> m InetAddress
    -- ^ __Returns:__ a new t'GI.Gio.Objects.InetAddress.InetAddress' corresponding to the loopback address
    -- for /@family@/.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
inetAddressNewLoopback :: SocketFamily -> m InetAddress
inetAddressNewLoopback SocketFamily
family = 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
    let family' :: CUInt
family' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SocketFamily -> Int) -> SocketFamily -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketFamily -> Int
forall a. Enum a => a -> Int
fromEnum) SocketFamily
family
    Ptr InetAddress
result <- CUInt -> IO (Ptr InetAddress)
g_inet_address_new_loopback CUInt
family'
    Text -> Ptr InetAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressNewLoopback" 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
wrapObject ManagedPtr InetAddress -> InetAddress
InetAddress) Ptr InetAddress
result
    InetAddress -> IO InetAddress
forall (m :: * -> *) a. Monad m => a -> m a
return InetAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method InetAddress::equal
-- method type : OrdinaryMethod
-- Args: [ 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
--           }
--       , Arg
--           { argCName = "other_address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Another #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_equal" g_inet_address_equal :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    Ptr InetAddress ->                      -- other_address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Checks if two t'GI.Gio.Objects.InetAddress.InetAddress' instances are equal, e.g. the same address.
-- 
-- /Since: 2.30/
inetAddressEqual ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a, IsInetAddress b) =>
    a
    -- ^ /@address@/: A t'GI.Gio.Objects.InetAddress.InetAddress'.
    -> b
    -- ^ /@otherAddress@/: Another t'GI.Gio.Objects.InetAddress.InetAddress'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ and /@otherAddress@/ are equal, 'P.False' otherwise.
inetAddressEqual :: a -> b -> m Bool
inetAddressEqual a
address b
otherAddress = 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    Ptr InetAddress
otherAddress' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
otherAddress
    CInt
result <- Ptr InetAddress -> Ptr InetAddress -> IO CInt
g_inet_address_equal Ptr InetAddress
address' Ptr InetAddress
otherAddress'
    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
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
otherAddress
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressEqualMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsInetAddress a, IsInetAddress b) => O.MethodInfo InetAddressEqualMethodInfo a signature where
    overloadedMethod = inetAddressEqual

#endif

-- method InetAddress::get_family
-- method type : OrdinaryMethod
-- Args: [ 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
--               (TInterface Name { namespace = "Gio" , name = "SocketFamily" })
-- throws : False
-- Skip return : False

foreign import ccall "g_inet_address_get_family" g_inet_address_get_family :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CUInt

-- | Gets /@address@/\'s family
-- 
-- /Since: 2.22/
inetAddressGetFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Gio.Enums.SocketFamily
    -- ^ __Returns:__ /@address@/\'s family
inetAddressGetFamily :: a -> m SocketFamily
inetAddressGetFamily a
address = IO SocketFamily -> m SocketFamily
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketFamily -> m SocketFamily)
-> IO SocketFamily -> m SocketFamily
forall a b. (a -> b) -> a -> b
$ do
    Ptr InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CUInt
result <- Ptr InetAddress -> IO CUInt
g_inet_address_get_family Ptr InetAddress
address'
    let result' :: SocketFamily
result' = (Int -> SocketFamily
forall a. Enum a => Int -> a
toEnum (Int -> SocketFamily) -> (CUInt -> Int) -> CUInt -> SocketFamily
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
address
    SocketFamily -> IO SocketFamily
forall (m :: * -> *) a. Monad m => a -> m a
return SocketFamily
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetFamilyMethodInfo
instance (signature ~ (m Gio.Enums.SocketFamily), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetFamilyMethodInfo a signature where
    overloadedMethod = inetAddressGetFamily

#endif

-- method InetAddress::get_is_any
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_any" g_inet_address_get_is_any :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is the \"any\" address for its family.
-- 
-- /Since: 2.22/
inetAddressGetIsAny ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is the \"any\" address for its family.
inetAddressGetIsAny :: a -> m Bool
inetAddressGetIsAny 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_any 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsAnyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsAnyMethodInfo a signature where
    overloadedMethod = inetAddressGetIsAny

#endif

-- method InetAddress::get_is_link_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_link_local" g_inet_address_get_is_link_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a link-local address (that is, if it
-- identifies a host on a local network that is not connected to the
-- Internet).
-- 
-- /Since: 2.22/
inetAddressGetIsLinkLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a link-local address.
inetAddressGetIsLinkLocal :: a -> m Bool
inetAddressGetIsLinkLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_link_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsLinkLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsLinkLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsLinkLocal

#endif

-- method InetAddress::get_is_loopback
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_loopback" g_inet_address_get_is_loopback :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is the loopback address for its family.
-- 
-- /Since: 2.22/
inetAddressGetIsLoopback ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is the loopback address for its family.
inetAddressGetIsLoopback :: a -> m Bool
inetAddressGetIsLoopback 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_loopback 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsLoopbackMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsLoopbackMethodInfo a signature where
    overloadedMethod = inetAddressGetIsLoopback

#endif

-- method InetAddress::get_is_mc_global
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_mc_global" g_inet_address_get_is_mc_global :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a global multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMcGlobal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a global multicast address.
inetAddressGetIsMcGlobal :: a -> m Bool
inetAddressGetIsMcGlobal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_mc_global 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMcGlobalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMcGlobalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMcGlobal

#endif

-- method InetAddress::get_is_mc_link_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_mc_link_local" g_inet_address_get_is_mc_link_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a link-local multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMcLinkLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a link-local multicast address.
inetAddressGetIsMcLinkLocal :: a -> m Bool
inetAddressGetIsMcLinkLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_mc_link_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMcLinkLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMcLinkLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMcLinkLocal

#endif

-- method InetAddress::get_is_mc_node_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_mc_node_local" g_inet_address_get_is_mc_node_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a node-local multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMcNodeLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a node-local multicast address.
inetAddressGetIsMcNodeLocal :: a -> m Bool
inetAddressGetIsMcNodeLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_mc_node_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMcNodeLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMcNodeLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMcNodeLocal

#endif

-- method InetAddress::get_is_mc_org_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_mc_org_local" g_inet_address_get_is_mc_org_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is an organization-local multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMcOrgLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is an organization-local multicast address.
inetAddressGetIsMcOrgLocal :: a -> m Bool
inetAddressGetIsMcOrgLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_mc_org_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMcOrgLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMcOrgLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMcOrgLocal

#endif

-- method InetAddress::get_is_mc_site_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_mc_site_local" g_inet_address_get_is_mc_site_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a site-local multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMcSiteLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a site-local multicast address.
inetAddressGetIsMcSiteLocal :: a -> m Bool
inetAddressGetIsMcSiteLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_mc_site_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMcSiteLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMcSiteLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMcSiteLocal

#endif

-- method InetAddress::get_is_multicast
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_multicast" g_inet_address_get_is_multicast :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a multicast address.
-- 
-- /Since: 2.22/
inetAddressGetIsMulticast ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a multicast address.
inetAddressGetIsMulticast :: a -> m Bool
inetAddressGetIsMulticast 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_multicast 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsMulticastMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsMulticastMethodInfo a signature where
    overloadedMethod = inetAddressGetIsMulticast

#endif

-- method InetAddress::get_is_site_local
-- method type : OrdinaryMethod
-- Args: [ 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_get_is_site_local" g_inet_address_get_is_site_local :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CInt

-- | Tests whether /@address@/ is a site-local address such as 10.0.0.1
-- (that is, the address identifies a host on a local network that can
-- not be reached directly from the Internet, but which may have
-- outgoing Internet connectivity via a NAT or firewall).
-- 
-- /Since: 2.22/
inetAddressGetIsSiteLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@address@/ is a site-local address.
inetAddressGetIsSiteLocal :: a -> m Bool
inetAddressGetIsSiteLocal 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CInt
result <- Ptr InetAddress -> IO CInt
g_inet_address_get_is_site_local 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
address
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressGetIsSiteLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetIsSiteLocalMethodInfo a signature where
    overloadedMethod = inetAddressGetIsSiteLocal

#endif

-- method InetAddress::get_native_size
-- method type : OrdinaryMethod
-- Args: [ 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 TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_inet_address_get_native_size" g_inet_address_get_native_size :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO Word64

-- | Gets the size of the native raw binary address for /@address@/. This
-- is the size of the data that you get from @/g_inet_address_to_bytes()/@.
-- 
-- /Since: 2.22/
inetAddressGetNativeSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m Word64
    -- ^ __Returns:__ the number of bytes used for the native version of /@address@/.
inetAddressGetNativeSize :: a -> m Word64
inetAddressGetNativeSize 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    Word64
result <- Ptr InetAddress -> IO Word64
g_inet_address_get_native_size Ptr InetAddress
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 InetAddressGetNativeSizeMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressGetNativeSizeMethodInfo a signature where
    overloadedMethod = inetAddressGetNativeSize

#endif

-- method InetAddress::to_string
-- method type : OrdinaryMethod
-- Args: [ 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_inet_address_to_string" g_inet_address_to_string :: 
    Ptr InetAddress ->                      -- address : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    IO CString

-- | Converts /@address@/ to string form.
-- 
-- /Since: 2.22/
inetAddressToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsInetAddress a) =>
    a
    -- ^ /@address@/: a t'GI.Gio.Objects.InetAddress.InetAddress'
    -> m T.Text
    -- ^ __Returns:__ a representation of /@address@/ as a string, which should be
    -- freed after use.
inetAddressToString :: a -> m Text
inetAddressToString 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 InetAddress
address' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
address
    CString
result <- Ptr InetAddress -> IO CString
g_inet_address_to_string Ptr InetAddress
address'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inetAddressToString" 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
address
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data InetAddressToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsInetAddress a) => O.MethodInfo InetAddressToStringMethodInfo a signature where
    overloadedMethod = inetAddressToString

#endif