{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.NetworkAddress.NetworkAddress' provides an easy way to resolve a hostname and
-- then attempt to connect to that host, handling the possibility of
-- multiple IP addresses and multiple address families.
-- 
-- The enumeration results of resolved addresses *may* be cached as long
-- as this object is kept alive which may have unexpected results if
-- alive for too long.
-- 
-- See t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' for an example of using the connectable
-- interface.

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

module GI.Gio.Objects.NetworkAddress
    ( 

-- * Exported types
    NetworkAddress(..)                      ,
    IsNetworkAddress                        ,
    toNetworkAddress                        ,


 -- * 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"), [enumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:enumerate"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [proxyEnumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:proxyEnumerate"), [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.Interfaces.SocketConnectable#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getHostname]("GI.Gio.Objects.NetworkAddress#g:method:getHostname"), [getPort]("GI.Gio.Objects.NetworkAddress#g:method:getPort"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getScheme]("GI.Gio.Objects.NetworkAddress#g:method:getScheme").
-- 
-- ==== 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)
    ResolveNetworkAddressMethod             ,
#endif

-- ** getHostname #method:getHostname#

#if defined(ENABLE_OVERLOADING)
    NetworkAddressGetHostnameMethodInfo     ,
#endif
    networkAddressGetHostname               ,


-- ** getPort #method:getPort#

#if defined(ENABLE_OVERLOADING)
    NetworkAddressGetPortMethodInfo         ,
#endif
    networkAddressGetPort                   ,


-- ** getScheme #method:getScheme#

#if defined(ENABLE_OVERLOADING)
    NetworkAddressGetSchemeMethodInfo       ,
#endif
    networkAddressGetScheme                 ,


-- ** new #method:new#

    networkAddressNew                       ,


-- ** newLoopback #method:newLoopback#

    networkAddressNewLoopback               ,


-- ** parse #method:parse#

    networkAddressParse                     ,


-- ** parseUri #method:parseUri#

    networkAddressParseUri                  ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    NetworkAddressHostnamePropertyInfo      ,
#endif
    constructNetworkAddressHostname         ,
    getNetworkAddressHostname               ,
#if defined(ENABLE_OVERLOADING)
    networkAddressHostname                  ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    NetworkAddressPortPropertyInfo          ,
#endif
    constructNetworkAddressPort             ,
    getNetworkAddressPort                   ,
#if defined(ENABLE_OVERLOADING)
    networkAddressPort                      ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    NetworkAddressSchemePropertyInfo        ,
#endif
    constructNetworkAddressScheme           ,
    getNetworkAddressScheme                 ,
#if defined(ENABLE_OVERLOADING)
    networkAddressScheme                    ,
#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.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.Coerce as Coerce
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.Interfaces.SocketConnectable as Gio.SocketConnectable

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

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

foreign import ccall "g_network_address_get_type"
    c_g_network_address_get_type :: IO B.Types.GType

instance B.Types.TypedObject NetworkAddress where
    glibType :: IO GType
glibType = IO GType
c_g_network_address_get_type

instance B.Types.GObject NetworkAddress

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

instance O.HasParentTypes NetworkAddress
type instance O.ParentTypes NetworkAddress = '[GObject.Object.Object, Gio.SocketConnectable.SocketConnectable]

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

-- | Convert 'NetworkAddress' 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 NetworkAddress) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_network_address_get_type
    gvalueSet_ :: Ptr GValue -> Maybe NetworkAddress -> IO ()
gvalueSet_ Ptr GValue
gv Maybe NetworkAddress
P.Nothing = Ptr GValue -> Ptr NetworkAddress -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr NetworkAddress
forall a. Ptr a
FP.nullPtr :: FP.Ptr NetworkAddress)
    gvalueSet_ Ptr GValue
gv (P.Just NetworkAddress
obj) = NetworkAddress -> (Ptr NetworkAddress -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NetworkAddress
obj (Ptr GValue -> Ptr NetworkAddress -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe NetworkAddress)
gvalueGet_ Ptr GValue
gv = do
        Ptr NetworkAddress
ptr <- Ptr GValue -> IO (Ptr NetworkAddress)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr NetworkAddress)
        if Ptr NetworkAddress
ptr Ptr NetworkAddress -> Ptr NetworkAddress -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NetworkAddress
forall a. Ptr a
FP.nullPtr
        then NetworkAddress -> Maybe NetworkAddress
forall a. a -> Maybe a
P.Just (NetworkAddress -> Maybe NetworkAddress)
-> IO NetworkAddress -> IO (Maybe NetworkAddress)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr NetworkAddress -> NetworkAddress)
-> Ptr NetworkAddress -> IO NetworkAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr NetworkAddress -> NetworkAddress
NetworkAddress Ptr NetworkAddress
ptr
        else Maybe NetworkAddress -> IO (Maybe NetworkAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NetworkAddress
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveNetworkAddressMethod (t :: Symbol) (o :: *) :: * where
    ResolveNetworkAddressMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveNetworkAddressMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveNetworkAddressMethod "enumerate" o = Gio.SocketConnectable.SocketConnectableEnumerateMethodInfo
    ResolveNetworkAddressMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveNetworkAddressMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveNetworkAddressMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveNetworkAddressMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveNetworkAddressMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveNetworkAddressMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveNetworkAddressMethod "proxyEnumerate" o = Gio.SocketConnectable.SocketConnectableProxyEnumerateMethodInfo
    ResolveNetworkAddressMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveNetworkAddressMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveNetworkAddressMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveNetworkAddressMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveNetworkAddressMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveNetworkAddressMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveNetworkAddressMethod "toString" o = Gio.SocketConnectable.SocketConnectableToStringMethodInfo
    ResolveNetworkAddressMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveNetworkAddressMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveNetworkAddressMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveNetworkAddressMethod "getHostname" o = NetworkAddressGetHostnameMethodInfo
    ResolveNetworkAddressMethod "getPort" o = NetworkAddressGetPortMethodInfo
    ResolveNetworkAddressMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveNetworkAddressMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveNetworkAddressMethod "getScheme" o = NetworkAddressGetSchemeMethodInfo
    ResolveNetworkAddressMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveNetworkAddressMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveNetworkAddressMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveNetworkAddressMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveNetworkAddressMethod t NetworkAddress, O.OverloadedMethod info NetworkAddress p) => OL.IsLabel t (NetworkAddress -> 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 ~ ResolveNetworkAddressMethod t NetworkAddress, O.OverloadedMethod info NetworkAddress p, R.HasField t NetworkAddress p) => R.HasField t NetworkAddress p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "hostname"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@hostname@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' networkAddress #hostname
-- @
getNetworkAddressHostname :: (MonadIO m, IsNetworkAddress o) => o -> m T.Text
getNetworkAddressHostname :: forall (m :: * -> *) o.
(MonadIO m, IsNetworkAddress o) =>
o -> m Text
getNetworkAddressHostname o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getNetworkAddressHostname" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"hostname"

-- | Construct a `GValueConstruct` with valid value for the “@hostname@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructNetworkAddressHostname :: (IsNetworkAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkAddressHostname :: forall o (m :: * -> *).
(IsNetworkAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNetworkAddressHostname Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"hostname" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data NetworkAddressHostnamePropertyInfo
instance AttrInfo NetworkAddressHostnamePropertyInfo where
    type AttrAllowedOps NetworkAddressHostnamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint NetworkAddressHostnamePropertyInfo = IsNetworkAddress
    type AttrSetTypeConstraint NetworkAddressHostnamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint NetworkAddressHostnamePropertyInfo = (~) T.Text
    type AttrTransferType NetworkAddressHostnamePropertyInfo = T.Text
    type AttrGetType NetworkAddressHostnamePropertyInfo = T.Text
    type AttrLabel NetworkAddressHostnamePropertyInfo = "hostname"
    type AttrOrigin NetworkAddressHostnamePropertyInfo = NetworkAddress
    attrGet = getNetworkAddressHostname
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructNetworkAddressHostname
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.hostname"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#g:attr:hostname"
        })
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data NetworkAddressPortPropertyInfo
instance AttrInfo NetworkAddressPortPropertyInfo where
    type AttrAllowedOps NetworkAddressPortPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint NetworkAddressPortPropertyInfo = IsNetworkAddress
    type AttrSetTypeConstraint NetworkAddressPortPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint NetworkAddressPortPropertyInfo = (~) Word32
    type AttrTransferType NetworkAddressPortPropertyInfo = Word32
    type AttrGetType NetworkAddressPortPropertyInfo = Word32
    type AttrLabel NetworkAddressPortPropertyInfo = "port"
    type AttrOrigin NetworkAddressPortPropertyInfo = NetworkAddress
    attrGet = getNetworkAddressPort
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructNetworkAddressPort
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.port"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#g:attr:port"
        })
#endif

-- VVV Prop "scheme"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@scheme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' networkAddress #scheme
-- @
getNetworkAddressScheme :: (MonadIO m, IsNetworkAddress o) => o -> m (Maybe T.Text)
getNetworkAddressScheme :: forall (m :: * -> *) o.
(MonadIO m, IsNetworkAddress o) =>
o -> m (Maybe Text)
getNetworkAddressScheme o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"scheme"

-- | Construct a `GValueConstruct` with valid value for the “@scheme@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructNetworkAddressScheme :: (IsNetworkAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkAddressScheme :: forall o (m :: * -> *).
(IsNetworkAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNetworkAddressScheme Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"scheme" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data NetworkAddressSchemePropertyInfo
instance AttrInfo NetworkAddressSchemePropertyInfo where
    type AttrAllowedOps NetworkAddressSchemePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint NetworkAddressSchemePropertyInfo = IsNetworkAddress
    type AttrSetTypeConstraint NetworkAddressSchemePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint NetworkAddressSchemePropertyInfo = (~) T.Text
    type AttrTransferType NetworkAddressSchemePropertyInfo = T.Text
    type AttrGetType NetworkAddressSchemePropertyInfo = (Maybe T.Text)
    type AttrLabel NetworkAddressSchemePropertyInfo = "scheme"
    type AttrOrigin NetworkAddressSchemePropertyInfo = NetworkAddress
    attrGet = getNetworkAddressScheme
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructNetworkAddressScheme
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.scheme"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#g:attr:scheme"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NetworkAddress
type instance O.AttributeList NetworkAddress = NetworkAddressAttributeList
type NetworkAddressAttributeList = ('[ '("hostname", NetworkAddressHostnamePropertyInfo), '("port", NetworkAddressPortPropertyInfo), '("scheme", NetworkAddressSchemePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
networkAddressHostname :: AttrLabelProxy "hostname"
networkAddressHostname = AttrLabelProxy

networkAddressPort :: AttrLabelProxy "port"
networkAddressPort = AttrLabelProxy

networkAddressScheme :: AttrLabelProxy "scheme"
networkAddressScheme = AttrLabelProxy

#endif

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

#endif

-- method NetworkAddress::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "hostname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the hostname" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the port" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "NetworkAddress" })
-- throws : False
-- Skip return : False

foreign import ccall "g_network_address_new" g_network_address_new :: 
    CString ->                              -- hostname : TBasicType TUTF8
    Word16 ->                               -- port : TBasicType TUInt16
    IO (Ptr NetworkAddress)

-- | Creates a new t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' for connecting to the given
-- /@hostname@/ and /@port@/.
-- 
-- Note that depending on the configuration of the machine, a
-- /@hostname@/ of @localhost@ may refer to the IPv4 loopback address
-- only, or to both IPv4 and IPv6; use
-- 'GI.Gio.Objects.NetworkAddress.networkAddressNewLoopback' to create a t'GI.Gio.Objects.NetworkAddress.NetworkAddress' that
-- is guaranteed to resolve to both addresses.
-- 
-- /Since: 2.22/
networkAddressNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@hostname@/: the hostname
    -> Word16
    -- ^ /@port@/: the port
    -> m NetworkAddress
    -- ^ __Returns:__ the new t'GI.Gio.Objects.NetworkAddress.NetworkAddress'
networkAddressNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Word16 -> m NetworkAddress
networkAddressNew Text
hostname Word16
port = IO NetworkAddress -> m NetworkAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkAddress -> m NetworkAddress)
-> IO NetworkAddress -> m NetworkAddress
forall a b. (a -> b) -> a -> b
$ do
    CString
hostname' <- Text -> IO CString
textToCString Text
hostname
    Ptr NetworkAddress
result <- CString -> Word16 -> IO (Ptr NetworkAddress)
g_network_address_new CString
hostname' Word16
port
    Text -> Ptr NetworkAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkAddressNew" Ptr NetworkAddress
result
    NetworkAddress
result' <- ((ManagedPtr NetworkAddress -> NetworkAddress)
-> Ptr NetworkAddress -> IO NetworkAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkAddress -> NetworkAddress
NetworkAddress) Ptr NetworkAddress
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
hostname'
    NetworkAddress -> IO NetworkAddress
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method NetworkAddress::new_loopback
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the port" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "NetworkAddress" })
-- throws : False
-- Skip return : False

foreign import ccall "g_network_address_new_loopback" g_network_address_new_loopback :: 
    Word16 ->                               -- port : TBasicType TUInt16
    IO (Ptr NetworkAddress)

-- | Creates a new t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' for connecting to the local host
-- over a loopback connection to the given /@port@/. This is intended for
-- use in connecting to local services which may be running on IPv4 or
-- IPv6.
-- 
-- The connectable will return IPv4 and IPv6 loopback addresses,
-- regardless of how the host resolves @localhost@. By contrast,
-- 'GI.Gio.Objects.NetworkAddress.networkAddressNew' will often only return an IPv4 address when
-- resolving @localhost@, and an IPv6 address for @localhost6@.
-- 
-- 'GI.Gio.Objects.NetworkAddress.networkAddressGetHostname' will always return @localhost@ for
-- a t'GI.Gio.Objects.NetworkAddress.NetworkAddress' created with this constructor.
-- 
-- /Since: 2.44/
networkAddressNewLoopback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word16
    -- ^ /@port@/: the port
    -> m NetworkAddress
    -- ^ __Returns:__ the new t'GI.Gio.Objects.NetworkAddress.NetworkAddress'
networkAddressNewLoopback :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word16 -> m NetworkAddress
networkAddressNewLoopback Word16
port = IO NetworkAddress -> m NetworkAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkAddress -> m NetworkAddress)
-> IO NetworkAddress -> m NetworkAddress
forall a b. (a -> b) -> a -> b
$ do
    Ptr NetworkAddress
result <- Word16 -> IO (Ptr NetworkAddress)
g_network_address_new_loopback Word16
port
    Text -> Ptr NetworkAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkAddressNewLoopback" Ptr NetworkAddress
result
    NetworkAddress
result' <- ((ManagedPtr NetworkAddress -> NetworkAddress)
-> Ptr NetworkAddress -> IO NetworkAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkAddress -> NetworkAddress
NetworkAddress) Ptr NetworkAddress
result
    NetworkAddress -> IO NetworkAddress
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method NetworkAddress::get_hostname
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "addr"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "NetworkAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNetworkAddress" , 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_network_address_get_hostname" g_network_address_get_hostname :: 
    Ptr NetworkAddress ->                   -- addr : TInterface (Name {namespace = "Gio", name = "NetworkAddress"})
    IO CString

-- | Gets /@addr@/\'s hostname. This might be either UTF-8 or ASCII-encoded,
-- depending on what /@addr@/ was created with.
-- 
-- /Since: 2.22/
networkAddressGetHostname ::
    (B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
    a
    -- ^ /@addr@/: a t'GI.Gio.Objects.NetworkAddress.NetworkAddress'
    -> m T.Text
    -- ^ __Returns:__ /@addr@/\'s hostname
networkAddressGetHostname :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkAddress a) =>
a -> m Text
networkAddressGetHostname a
addr = 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 NetworkAddress
addr' <- a -> IO (Ptr NetworkAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
addr
    CString
result <- Ptr NetworkAddress -> IO CString
g_network_address_get_hostname Ptr NetworkAddress
addr'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkAddressGetHostname" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
addr
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data NetworkAddressGetHostnameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsNetworkAddress a) => O.OverloadedMethod NetworkAddressGetHostnameMethodInfo a signature where
    overloadedMethod = networkAddressGetHostname

instance O.OverloadedMethodInfo NetworkAddressGetHostnameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.networkAddressGetHostname",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#v:networkAddressGetHostname"
        })


#endif

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

foreign import ccall "g_network_address_get_port" g_network_address_get_port :: 
    Ptr NetworkAddress ->                   -- addr : TInterface (Name {namespace = "Gio", name = "NetworkAddress"})
    IO Word16

-- | Gets /@addr@/\'s port number
-- 
-- /Since: 2.22/
networkAddressGetPort ::
    (B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
    a
    -- ^ /@addr@/: a t'GI.Gio.Objects.NetworkAddress.NetworkAddress'
    -> m Word16
    -- ^ __Returns:__ /@addr@/\'s port (which may be 0)
networkAddressGetPort :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkAddress a) =>
a -> m Word16
networkAddressGetPort a
addr = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr NetworkAddress
addr' <- a -> IO (Ptr NetworkAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
addr
    Word16
result <- Ptr NetworkAddress -> IO Word16
g_network_address_get_port Ptr NetworkAddress
addr'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
addr
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data NetworkAddressGetPortMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsNetworkAddress a) => O.OverloadedMethod NetworkAddressGetPortMethodInfo a signature where
    overloadedMethod = networkAddressGetPort

instance O.OverloadedMethodInfo NetworkAddressGetPortMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.networkAddressGetPort",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#v:networkAddressGetPort"
        })


#endif

-- method NetworkAddress::get_scheme
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "addr"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "NetworkAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNetworkAddress" , 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_network_address_get_scheme" g_network_address_get_scheme :: 
    Ptr NetworkAddress ->                   -- addr : TInterface (Name {namespace = "Gio", name = "NetworkAddress"})
    IO CString

-- | Gets /@addr@/\'s scheme
-- 
-- /Since: 2.26/
networkAddressGetScheme ::
    (B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
    a
    -- ^ /@addr@/: a t'GI.Gio.Objects.NetworkAddress.NetworkAddress'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ /@addr@/\'s scheme ('P.Nothing' if not built from URI)
networkAddressGetScheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkAddress a) =>
a -> m (Maybe Text)
networkAddressGetScheme a
addr = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr NetworkAddress
addr' <- a -> IO (Ptr NetworkAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
addr
    CString
result <- Ptr NetworkAddress -> IO CString
g_network_address_get_scheme Ptr NetworkAddress
addr'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
addr
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data NetworkAddressGetSchemeMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsNetworkAddress a) => O.OverloadedMethod NetworkAddressGetSchemeMethodInfo a signature where
    overloadedMethod = networkAddressGetScheme

instance O.OverloadedMethodInfo NetworkAddressGetSchemeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.NetworkAddress.networkAddressGetScheme",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-NetworkAddress.html#v:networkAddressGetScheme"
        })


#endif

-- method NetworkAddress::parse
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "host_and_port"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the hostname and optionally a port"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "default_port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the default port if not in @host_and_port"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "NetworkAddress" })
-- throws : True
-- Skip return : False

foreign import ccall "g_network_address_parse" g_network_address_parse :: 
    CString ->                              -- host_and_port : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr NetworkAddress)

-- | Creates a new t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' for connecting to the given
-- /@hostname@/ and /@port@/. May fail and return 'P.Nothing' in case
-- parsing /@hostAndPort@/ fails.
-- 
-- /@hostAndPort@/ may be in any of a number of recognised formats; an IPv6
-- address, an IPv4 address, or a domain name (in which case a DNS
-- lookup is performed). Quoting with [] is supported for all address
-- types. A port override may be specified in the usual way with a
-- colon.
-- 
-- If no port is specified in /@hostAndPort@/ then /@defaultPort@/ will be
-- used as the port number to connect to.
-- 
-- In general, /@hostAndPort@/ is expected to be provided by the user
-- (allowing them to give the hostname, and a port override if necessary)
-- and /@defaultPort@/ is expected to be provided by the application.
-- 
-- (The port component of /@hostAndPort@/ can also be specified as a
-- service name rather than as a numeric port, but this functionality
-- is deprecated, because it depends on the contents of \/etc\/services,
-- which is generally quite sparse on platforms other than Linux.)
-- 
-- /Since: 2.22/
networkAddressParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@hostAndPort@/: the hostname and optionally a port
    -> Word16
    -- ^ /@defaultPort@/: the default port if not in /@hostAndPort@/
    -> m NetworkAddress
    -- ^ __Returns:__ the new
    --   t'GI.Gio.Objects.NetworkAddress.NetworkAddress', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
networkAddressParse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Word16 -> m NetworkAddress
networkAddressParse Text
hostAndPort Word16
defaultPort = IO NetworkAddress -> m NetworkAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkAddress -> m NetworkAddress)
-> IO NetworkAddress -> m NetworkAddress
forall a b. (a -> b) -> a -> b
$ do
    CString
hostAndPort' <- Text -> IO CString
textToCString Text
hostAndPort
    IO NetworkAddress -> IO () -> IO NetworkAddress
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr NetworkAddress
result <- (Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
-> IO (Ptr NetworkAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
 -> IO (Ptr NetworkAddress))
-> (Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
-> IO (Ptr NetworkAddress)
forall a b. (a -> b) -> a -> b
$ CString -> Word16 -> Ptr (Ptr GError) -> IO (Ptr NetworkAddress)
g_network_address_parse CString
hostAndPort' Word16
defaultPort
        Text -> Ptr NetworkAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkAddressParse" Ptr NetworkAddress
result
        NetworkAddress
result' <- ((ManagedPtr NetworkAddress -> NetworkAddress)
-> Ptr NetworkAddress -> IO NetworkAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkAddress -> NetworkAddress
NetworkAddress) Ptr NetworkAddress
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
hostAndPort'
        NetworkAddress -> IO NetworkAddress
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkAddress
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
hostAndPort'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method NetworkAddress::parse_uri
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the hostname and optionally a port"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "default_port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The default port if none is found in the URI"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "NetworkAddress" })
-- throws : True
-- Skip return : False

foreign import ccall "g_network_address_parse_uri" g_network_address_parse_uri :: 
    CString ->                              -- uri : TBasicType TUTF8
    Word16 ->                               -- default_port : TBasicType TUInt16
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr NetworkAddress)

-- | Creates a new t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' for connecting to the given
-- /@uri@/. May fail and return 'P.Nothing' in case parsing /@uri@/ fails.
-- 
-- Using this rather than 'GI.Gio.Objects.NetworkAddress.networkAddressNew' or
-- 'GI.Gio.Objects.NetworkAddress.networkAddressParse' allows t'GI.Gio.Objects.SocketClient.SocketClient' to determine
-- when to use application-specific proxy protocols.
-- 
-- /Since: 2.26/
networkAddressParseUri ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@uri@/: the hostname and optionally a port
    -> Word16
    -- ^ /@defaultPort@/: The default port if none is found in the URI
    -> m NetworkAddress
    -- ^ __Returns:__ the new
    --   t'GI.Gio.Objects.NetworkAddress.NetworkAddress', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
networkAddressParseUri :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Word16 -> m NetworkAddress
networkAddressParseUri Text
uri Word16
defaultPort = IO NetworkAddress -> m NetworkAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkAddress -> m NetworkAddress)
-> IO NetworkAddress -> m NetworkAddress
forall a b. (a -> b) -> a -> b
$ do
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO NetworkAddress -> IO () -> IO NetworkAddress
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr NetworkAddress
result <- (Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
-> IO (Ptr NetworkAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
 -> IO (Ptr NetworkAddress))
-> (Ptr (Ptr GError) -> IO (Ptr NetworkAddress))
-> IO (Ptr NetworkAddress)
forall a b. (a -> b) -> a -> b
$ CString -> Word16 -> Ptr (Ptr GError) -> IO (Ptr NetworkAddress)
g_network_address_parse_uri CString
uri' Word16
defaultPort
        Text -> Ptr NetworkAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkAddressParseUri" Ptr NetworkAddress
result
        NetworkAddress
result' <- ((ManagedPtr NetworkAddress -> NetworkAddress)
-> Ptr NetworkAddress -> IO NetworkAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkAddress -> NetworkAddress
NetworkAddress) Ptr NetworkAddress
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        NetworkAddress -> IO NetworkAddress
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkAddress
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
#endif