{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.NetworkAddress
(
NetworkAddress(..) ,
IsNetworkAddress ,
toNetworkAddress ,
#if defined(ENABLE_OVERLOADING)
ResolveNetworkAddressMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkAddressGetHostnameMethodInfo ,
#endif
networkAddressGetHostname ,
#if defined(ENABLE_OVERLOADING)
NetworkAddressGetPortMethodInfo ,
#endif
networkAddressGetPort ,
#if defined(ENABLE_OVERLOADING)
NetworkAddressGetSchemeMethodInfo ,
#endif
networkAddressGetScheme ,
networkAddressNew ,
networkAddressNewLoopback ,
networkAddressParse ,
networkAddressParseUri ,
#if defined(ENABLE_OVERLOADING)
NetworkAddressHostnamePropertyInfo ,
#endif
constructNetworkAddressHostname ,
getNetworkAddressHostname ,
#if defined(ENABLE_OVERLOADING)
networkAddressHostname ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkAddressPortPropertyInfo ,
#endif
constructNetworkAddressPort ,
getNetworkAddressPort ,
#if defined(ENABLE_OVERLOADING)
networkAddressPort ,
#endif
#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
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
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]
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
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
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"
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
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"
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
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"
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
foreign import ccall "g_network_address_new" g_network_address_new ::
CString ->
Word16 ->
IO (Ptr NetworkAddress)
networkAddressNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Word16
-> m 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
foreign import ccall "g_network_address_new_loopback" g_network_address_new_loopback ::
Word16 ->
IO (Ptr NetworkAddress)
networkAddressNewLoopback ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word16
-> m 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
foreign import ccall "g_network_address_get_hostname" g_network_address_get_hostname ::
Ptr NetworkAddress ->
IO CString
networkAddressGetHostname ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
a
-> m T.Text
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
foreign import ccall "g_network_address_get_port" g_network_address_get_port ::
Ptr NetworkAddress ->
IO Word16
networkAddressGetPort ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
a
-> m Word16
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
foreign import ccall "g_network_address_get_scheme" g_network_address_get_scheme ::
Ptr NetworkAddress ->
IO CString
networkAddressGetScheme ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkAddress a) =>
a
-> m (Maybe T.Text)
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
foreign import ccall "g_network_address_parse" g_network_address_parse ::
CString ->
Word16 ->
Ptr (Ptr GError) ->
IO (Ptr NetworkAddress)
networkAddressParse ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Word16
-> m NetworkAddress
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
foreign import ccall "g_network_address_parse_uri" g_network_address_parse_uri ::
CString ->
Word16 ->
Ptr (Ptr GError) ->
IO (Ptr NetworkAddress)
networkAddressParseUri ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Word16
-> m NetworkAddress
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