{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.NetworkService
(
NetworkService(..) ,
IsNetworkService ,
toNetworkService ,
#if defined(ENABLE_OVERLOADING)
ResolveNetworkServiceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkServiceGetDomainMethodInfo ,
#endif
networkServiceGetDomain ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceGetProtocolMethodInfo ,
#endif
networkServiceGetProtocol ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceGetSchemeMethodInfo ,
#endif
networkServiceGetScheme ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceGetServiceMethodInfo ,
#endif
networkServiceGetService ,
networkServiceNew ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceSetSchemeMethodInfo ,
#endif
networkServiceSetScheme ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceDomainPropertyInfo ,
#endif
constructNetworkServiceDomain ,
getNetworkServiceDomain ,
#if defined(ENABLE_OVERLOADING)
networkServiceDomain ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkServiceProtocolPropertyInfo ,
#endif
constructNetworkServiceProtocol ,
getNetworkServiceProtocol ,
#if defined(ENABLE_OVERLOADING)
networkServiceProtocol ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkServiceSchemePropertyInfo ,
#endif
constructNetworkServiceScheme ,
getNetworkServiceScheme ,
#if defined(ENABLE_OVERLOADING)
networkServiceScheme ,
#endif
setNetworkServiceScheme ,
#if defined(ENABLE_OVERLOADING)
NetworkServiceServicePropertyInfo ,
#endif
constructNetworkServiceService ,
getNetworkServiceService ,
#if defined(ENABLE_OVERLOADING)
networkServiceService ,
#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.Interfaces.SocketConnectable as Gio.SocketConnectable
newtype NetworkService = NetworkService (SP.ManagedPtr NetworkService)
deriving (NetworkService -> NetworkService -> Bool
(NetworkService -> NetworkService -> Bool)
-> (NetworkService -> NetworkService -> Bool) -> Eq NetworkService
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkService -> NetworkService -> Bool
$c/= :: NetworkService -> NetworkService -> Bool
== :: NetworkService -> NetworkService -> Bool
$c== :: NetworkService -> NetworkService -> Bool
Eq)
instance SP.ManagedPtrNewtype NetworkService where
toManagedPtr :: NetworkService -> ManagedPtr NetworkService
toManagedPtr (NetworkService ManagedPtr NetworkService
p) = ManagedPtr NetworkService
p
foreign import ccall "g_network_service_get_type"
c_g_network_service_get_type :: IO B.Types.GType
instance B.Types.TypedObject NetworkService where
glibType :: IO GType
glibType = IO GType
c_g_network_service_get_type
instance B.Types.GObject NetworkService
instance B.GValue.IsGValue NetworkService where
toGValue :: NetworkService -> IO GValue
toGValue NetworkService
o = do
GType
gtype <- IO GType
c_g_network_service_get_type
NetworkService -> (Ptr NetworkService -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NetworkService
o (GType
-> (GValue -> Ptr NetworkService -> IO ())
-> Ptr NetworkService
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr NetworkService -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO NetworkService
fromGValue GValue
gv = do
Ptr NetworkService
ptr <- GValue -> IO (Ptr NetworkService)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr NetworkService)
(ManagedPtr NetworkService -> NetworkService)
-> Ptr NetworkService -> IO NetworkService
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr NetworkService -> NetworkService
NetworkService Ptr NetworkService
ptr
class (SP.GObject o, O.IsDescendantOf NetworkService o) => IsNetworkService o
instance (SP.GObject o, O.IsDescendantOf NetworkService o) => IsNetworkService o
instance O.HasParentTypes NetworkService
type instance O.ParentTypes NetworkService = '[GObject.Object.Object, Gio.SocketConnectable.SocketConnectable]
toNetworkService :: (MonadIO m, IsNetworkService o) => o -> m NetworkService
toNetworkService :: o -> m NetworkService
toNetworkService = IO NetworkService -> m NetworkService
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkService -> m NetworkService)
-> (o -> IO NetworkService) -> o -> m NetworkService
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr NetworkService -> NetworkService)
-> o -> IO NetworkService
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr NetworkService -> NetworkService
NetworkService
#if defined(ENABLE_OVERLOADING)
type family ResolveNetworkServiceMethod (t :: Symbol) (o :: *) :: * where
ResolveNetworkServiceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveNetworkServiceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveNetworkServiceMethod "enumerate" o = Gio.SocketConnectable.SocketConnectableEnumerateMethodInfo
ResolveNetworkServiceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveNetworkServiceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveNetworkServiceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveNetworkServiceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveNetworkServiceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveNetworkServiceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveNetworkServiceMethod "proxyEnumerate" o = Gio.SocketConnectable.SocketConnectableProxyEnumerateMethodInfo
ResolveNetworkServiceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveNetworkServiceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveNetworkServiceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveNetworkServiceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveNetworkServiceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveNetworkServiceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveNetworkServiceMethod "toString" o = Gio.SocketConnectable.SocketConnectableToStringMethodInfo
ResolveNetworkServiceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveNetworkServiceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveNetworkServiceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveNetworkServiceMethod "getDomain" o = NetworkServiceGetDomainMethodInfo
ResolveNetworkServiceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveNetworkServiceMethod "getProtocol" o = NetworkServiceGetProtocolMethodInfo
ResolveNetworkServiceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveNetworkServiceMethod "getScheme" o = NetworkServiceGetSchemeMethodInfo
ResolveNetworkServiceMethod "getService" o = NetworkServiceGetServiceMethodInfo
ResolveNetworkServiceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveNetworkServiceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveNetworkServiceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveNetworkServiceMethod "setScheme" o = NetworkServiceSetSchemeMethodInfo
ResolveNetworkServiceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveNetworkServiceMethod t NetworkService, O.MethodInfo info NetworkService p) => OL.IsLabel t (NetworkService -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getNetworkServiceDomain :: (MonadIO m, IsNetworkService o) => o -> m T.Text
getNetworkServiceDomain :: o -> m Text
getNetworkServiceDomain o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getNetworkServiceDomain" (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
"domain"
constructNetworkServiceDomain :: (IsNetworkService o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkServiceDomain :: Text -> m (GValueConstruct o)
constructNetworkServiceDomain 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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"domain" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data NetworkServiceDomainPropertyInfo
instance AttrInfo NetworkServiceDomainPropertyInfo where
type AttrAllowedOps NetworkServiceDomainPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NetworkServiceDomainPropertyInfo = IsNetworkService
type AttrSetTypeConstraint NetworkServiceDomainPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkServiceDomainPropertyInfo = (~) T.Text
type AttrTransferType NetworkServiceDomainPropertyInfo = T.Text
type AttrGetType NetworkServiceDomainPropertyInfo = T.Text
type AttrLabel NetworkServiceDomainPropertyInfo = "domain"
type AttrOrigin NetworkServiceDomainPropertyInfo = NetworkService
attrGet = getNetworkServiceDomain
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkServiceDomain
attrClear = undefined
#endif
getNetworkServiceProtocol :: (MonadIO m, IsNetworkService o) => o -> m T.Text
getNetworkServiceProtocol :: o -> m Text
getNetworkServiceProtocol o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getNetworkServiceProtocol" (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
"protocol"
constructNetworkServiceProtocol :: (IsNetworkService o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkServiceProtocol :: Text -> m (GValueConstruct o)
constructNetworkServiceProtocol 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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"protocol" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data NetworkServiceProtocolPropertyInfo
instance AttrInfo NetworkServiceProtocolPropertyInfo where
type AttrAllowedOps NetworkServiceProtocolPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NetworkServiceProtocolPropertyInfo = IsNetworkService
type AttrSetTypeConstraint NetworkServiceProtocolPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkServiceProtocolPropertyInfo = (~) T.Text
type AttrTransferType NetworkServiceProtocolPropertyInfo = T.Text
type AttrGetType NetworkServiceProtocolPropertyInfo = T.Text
type AttrLabel NetworkServiceProtocolPropertyInfo = "protocol"
type AttrOrigin NetworkServiceProtocolPropertyInfo = NetworkService
attrGet = getNetworkServiceProtocol
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkServiceProtocol
attrClear = undefined
#endif
getNetworkServiceScheme :: (MonadIO m, IsNetworkService o) => o -> m T.Text
getNetworkServiceScheme :: o -> m Text
getNetworkServiceScheme o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getNetworkServiceScheme" (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
"scheme"
setNetworkServiceScheme :: (MonadIO m, IsNetworkService o) => o -> T.Text -> m ()
setNetworkServiceScheme :: o -> Text -> m ()
setNetworkServiceScheme o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"scheme" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructNetworkServiceScheme :: (IsNetworkService o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkServiceScheme :: Text -> m (GValueConstruct o)
constructNetworkServiceScheme 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
$ 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 NetworkServiceSchemePropertyInfo
instance AttrInfo NetworkServiceSchemePropertyInfo where
type AttrAllowedOps NetworkServiceSchemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint NetworkServiceSchemePropertyInfo = IsNetworkService
type AttrSetTypeConstraint NetworkServiceSchemePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkServiceSchemePropertyInfo = (~) T.Text
type AttrTransferType NetworkServiceSchemePropertyInfo = T.Text
type AttrGetType NetworkServiceSchemePropertyInfo = T.Text
type AttrLabel NetworkServiceSchemePropertyInfo = "scheme"
type AttrOrigin NetworkServiceSchemePropertyInfo = NetworkService
attrGet = getNetworkServiceScheme
attrSet = setNetworkServiceScheme
attrTransfer _ v = do
return v
attrConstruct = constructNetworkServiceScheme
attrClear = undefined
#endif
getNetworkServiceService :: (MonadIO m, IsNetworkService o) => o -> m T.Text
getNetworkServiceService :: o -> m Text
getNetworkServiceService o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getNetworkServiceService" (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
"service"
constructNetworkServiceService :: (IsNetworkService o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkServiceService :: Text -> m (GValueConstruct o)
constructNetworkServiceService 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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"service" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data NetworkServiceServicePropertyInfo
instance AttrInfo NetworkServiceServicePropertyInfo where
type AttrAllowedOps NetworkServiceServicePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NetworkServiceServicePropertyInfo = IsNetworkService
type AttrSetTypeConstraint NetworkServiceServicePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkServiceServicePropertyInfo = (~) T.Text
type AttrTransferType NetworkServiceServicePropertyInfo = T.Text
type AttrGetType NetworkServiceServicePropertyInfo = T.Text
type AttrLabel NetworkServiceServicePropertyInfo = "service"
type AttrOrigin NetworkServiceServicePropertyInfo = NetworkService
attrGet = getNetworkServiceService
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkServiceService
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NetworkService
type instance O.AttributeList NetworkService = NetworkServiceAttributeList
type NetworkServiceAttributeList = ('[ '("domain", NetworkServiceDomainPropertyInfo), '("protocol", NetworkServiceProtocolPropertyInfo), '("scheme", NetworkServiceSchemePropertyInfo), '("service", NetworkServiceServicePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
networkServiceDomain :: AttrLabelProxy "domain"
networkServiceDomain = AttrLabelProxy
networkServiceProtocol :: AttrLabelProxy "protocol"
networkServiceProtocol = AttrLabelProxy
networkServiceScheme :: AttrLabelProxy "scheme"
networkServiceScheme = AttrLabelProxy
networkServiceService :: AttrLabelProxy "service"
networkServiceService = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList NetworkService = NetworkServiceSignalList
type NetworkServiceSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_network_service_new" g_network_service_new ::
CString ->
CString ->
CString ->
IO (Ptr NetworkService)
networkServiceNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> T.Text
-> T.Text
-> m NetworkService
networkServiceNew :: Text -> Text -> Text -> m NetworkService
networkServiceNew Text
service Text
protocol Text
domain = IO NetworkService -> m NetworkService
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkService -> m NetworkService)
-> IO NetworkService -> m NetworkService
forall a b. (a -> b) -> a -> b
$ do
CString
service' <- Text -> IO CString
textToCString Text
service
CString
protocol' <- Text -> IO CString
textToCString Text
protocol
CString
domain' <- Text -> IO CString
textToCString Text
domain
Ptr NetworkService
result <- CString -> CString -> CString -> IO (Ptr NetworkService)
g_network_service_new CString
service' CString
protocol' CString
domain'
Text -> Ptr NetworkService -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkServiceNew" Ptr NetworkService
result
NetworkService
result' <- ((ManagedPtr NetworkService -> NetworkService)
-> Ptr NetworkService -> IO NetworkService
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkService -> NetworkService
NetworkService) Ptr NetworkService
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
service'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
protocol'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
domain'
NetworkService -> IO NetworkService
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkService
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_network_service_get_domain" g_network_service_get_domain ::
Ptr NetworkService ->
IO CString
networkServiceGetDomain ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkService a) =>
a
-> m T.Text
networkServiceGetDomain :: a -> m Text
networkServiceGetDomain a
srv = 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 NetworkService
srv' <- a -> IO (Ptr NetworkService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srv
CString
result <- Ptr NetworkService -> IO CString
g_network_service_get_domain Ptr NetworkService
srv'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkServiceGetDomain" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srv
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data NetworkServiceGetDomainMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsNetworkService a) => O.MethodInfo NetworkServiceGetDomainMethodInfo a signature where
overloadedMethod = networkServiceGetDomain
#endif
foreign import ccall "g_network_service_get_protocol" g_network_service_get_protocol ::
Ptr NetworkService ->
IO CString
networkServiceGetProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkService a) =>
a
-> m T.Text
networkServiceGetProtocol :: a -> m Text
networkServiceGetProtocol a
srv = 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 NetworkService
srv' <- a -> IO (Ptr NetworkService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srv
CString
result <- Ptr NetworkService -> IO CString
g_network_service_get_protocol Ptr NetworkService
srv'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkServiceGetProtocol" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srv
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data NetworkServiceGetProtocolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsNetworkService a) => O.MethodInfo NetworkServiceGetProtocolMethodInfo a signature where
overloadedMethod = networkServiceGetProtocol
#endif
foreign import ccall "g_network_service_get_scheme" g_network_service_get_scheme ::
Ptr NetworkService ->
IO CString
networkServiceGetScheme ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkService a) =>
a
-> m T.Text
networkServiceGetScheme :: a -> m Text
networkServiceGetScheme a
srv = 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 NetworkService
srv' <- a -> IO (Ptr NetworkService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srv
CString
result <- Ptr NetworkService -> IO CString
g_network_service_get_scheme Ptr NetworkService
srv'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkServiceGetScheme" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srv
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data NetworkServiceGetSchemeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsNetworkService a) => O.MethodInfo NetworkServiceGetSchemeMethodInfo a signature where
overloadedMethod = networkServiceGetScheme
#endif
foreign import ccall "g_network_service_get_service" g_network_service_get_service ::
Ptr NetworkService ->
IO CString
networkServiceGetService ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkService a) =>
a
-> m T.Text
networkServiceGetService :: a -> m Text
networkServiceGetService a
srv = 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 NetworkService
srv' <- a -> IO (Ptr NetworkService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srv
CString
result <- Ptr NetworkService -> IO CString
g_network_service_get_service Ptr NetworkService
srv'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkServiceGetService" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srv
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data NetworkServiceGetServiceMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsNetworkService a) => O.MethodInfo NetworkServiceGetServiceMethodInfo a signature where
overloadedMethod = networkServiceGetService
#endif
foreign import ccall "g_network_service_set_scheme" g_network_service_set_scheme ::
Ptr NetworkService ->
CString ->
IO ()
networkServiceSetScheme ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkService a) =>
a
-> T.Text
-> m ()
networkServiceSetScheme :: a -> Text -> m ()
networkServiceSetScheme a
srv Text
scheme = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkService
srv' <- a -> IO (Ptr NetworkService)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srv
CString
scheme' <- Text -> IO CString
textToCString Text
scheme
Ptr NetworkService -> CString -> IO ()
g_network_service_set_scheme Ptr NetworkService
srv' CString
scheme'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srv
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
scheme'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkServiceSetSchemeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNetworkService a) => O.MethodInfo NetworkServiceSetSchemeMethodInfo a signature where
overloadedMethod = networkServiceSetScheme
#endif