{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.NetworkMonitor
(
NetworkMonitor(..) ,
IsNetworkMonitor ,
toNetworkMonitor ,
#if defined(ENABLE_OVERLOADING)
ResolveNetworkMonitorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkMonitorCanReachMethodInfo ,
#endif
networkMonitorCanReach ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorCanReachAsyncMethodInfo ,
#endif
networkMonitorCanReachAsync ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorCanReachFinishMethodInfo ,
#endif
networkMonitorCanReachFinish ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorGetConnectivityMethodInfo ,
#endif
networkMonitorGetConnectivity ,
networkMonitorGetDefault ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorGetNetworkAvailableMethodInfo,
#endif
networkMonitorGetNetworkAvailable ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorGetNetworkMeteredMethodInfo,
#endif
networkMonitorGetNetworkMetered ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorConnectivityPropertyInfo ,
#endif
getNetworkMonitorConnectivity ,
#if defined(ENABLE_OVERLOADING)
networkMonitorConnectivity ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkMonitorNetworkAvailablePropertyInfo,
#endif
getNetworkMonitorNetworkAvailable ,
#if defined(ENABLE_OVERLOADING)
networkMonitorNetworkAvailable ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkMonitorNetworkMeteredPropertyInfo,
#endif
getNetworkMonitorNetworkMetered ,
#if defined(ENABLE_OVERLOADING)
networkMonitorNetworkMetered ,
#endif
C_NetworkMonitorNetworkChangedCallback ,
NetworkMonitorNetworkChangedCallback ,
#if defined(ENABLE_OVERLOADING)
NetworkMonitorNetworkChangedSignalInfo ,
#endif
afterNetworkMonitorNetworkChanged ,
genClosure_NetworkMonitorNetworkChanged ,
mk_NetworkMonitorNetworkChangedCallback ,
noNetworkMonitorNetworkChangedCallback ,
onNetworkMonitorNetworkChanged ,
wrap_NetworkMonitorNetworkChangedCallback,
) 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 qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
newtype NetworkMonitor = NetworkMonitor (SP.ManagedPtr NetworkMonitor)
deriving (NetworkMonitor -> NetworkMonitor -> Bool
(NetworkMonitor -> NetworkMonitor -> Bool)
-> (NetworkMonitor -> NetworkMonitor -> Bool) -> Eq NetworkMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkMonitor -> NetworkMonitor -> Bool
$c/= :: NetworkMonitor -> NetworkMonitor -> Bool
== :: NetworkMonitor -> NetworkMonitor -> Bool
$c== :: NetworkMonitor -> NetworkMonitor -> Bool
Eq)
instance SP.ManagedPtrNewtype NetworkMonitor where
toManagedPtr :: NetworkMonitor -> ManagedPtr NetworkMonitor
toManagedPtr (NetworkMonitor ManagedPtr NetworkMonitor
p) = ManagedPtr NetworkMonitor
p
foreign import ccall "g_network_monitor_get_type"
c_g_network_monitor_get_type :: IO B.Types.GType
instance B.Types.TypedObject NetworkMonitor where
glibType :: IO GType
glibType = IO GType
c_g_network_monitor_get_type
instance B.Types.GObject NetworkMonitor
instance B.GValue.IsGValue NetworkMonitor where
toGValue :: NetworkMonitor -> IO GValue
toGValue NetworkMonitor
o = do
GType
gtype <- IO GType
c_g_network_monitor_get_type
NetworkMonitor -> (Ptr NetworkMonitor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NetworkMonitor
o (GType
-> (GValue -> Ptr NetworkMonitor -> IO ())
-> Ptr NetworkMonitor
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr NetworkMonitor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO NetworkMonitor
fromGValue GValue
gv = do
Ptr NetworkMonitor
ptr <- GValue -> IO (Ptr NetworkMonitor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr NetworkMonitor)
(ManagedPtr NetworkMonitor -> NetworkMonitor)
-> Ptr NetworkMonitor -> IO NetworkMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr NetworkMonitor -> NetworkMonitor
NetworkMonitor Ptr NetworkMonitor
ptr
class (SP.GObject o, O.IsDescendantOf NetworkMonitor o) => IsNetworkMonitor o
instance (SP.GObject o, O.IsDescendantOf NetworkMonitor o) => IsNetworkMonitor o
instance O.HasParentTypes NetworkMonitor
type instance O.ParentTypes NetworkMonitor = '[Gio.Initable.Initable, GObject.Object.Object]
toNetworkMonitor :: (MonadIO m, IsNetworkMonitor o) => o -> m NetworkMonitor
toNetworkMonitor :: o -> m NetworkMonitor
toNetworkMonitor = IO NetworkMonitor -> m NetworkMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkMonitor -> m NetworkMonitor)
-> (o -> IO NetworkMonitor) -> o -> m NetworkMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr NetworkMonitor -> NetworkMonitor)
-> o -> IO NetworkMonitor
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr NetworkMonitor -> NetworkMonitor
NetworkMonitor
getNetworkMonitorConnectivity :: (MonadIO m, IsNetworkMonitor o) => o -> m Gio.Enums.NetworkConnectivity
getNetworkMonitorConnectivity :: o -> m NetworkConnectivity
getNetworkMonitorConnectivity o
obj = IO NetworkConnectivity -> m NetworkConnectivity
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkConnectivity -> m NetworkConnectivity)
-> IO NetworkConnectivity -> m NetworkConnectivity
forall a b. (a -> b) -> a -> b
$ o -> String -> IO NetworkConnectivity
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"connectivity"
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorConnectivityPropertyInfo
instance AttrInfo NetworkMonitorConnectivityPropertyInfo where
type AttrAllowedOps NetworkMonitorConnectivityPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint NetworkMonitorConnectivityPropertyInfo = IsNetworkMonitor
type AttrSetTypeConstraint NetworkMonitorConnectivityPropertyInfo = (~) ()
type AttrTransferTypeConstraint NetworkMonitorConnectivityPropertyInfo = (~) ()
type AttrTransferType NetworkMonitorConnectivityPropertyInfo = ()
type AttrGetType NetworkMonitorConnectivityPropertyInfo = Gio.Enums.NetworkConnectivity
type AttrLabel NetworkMonitorConnectivityPropertyInfo = "connectivity"
type AttrOrigin NetworkMonitorConnectivityPropertyInfo = NetworkMonitor
attrGet = getNetworkMonitorConnectivity
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getNetworkMonitorNetworkAvailable :: (MonadIO m, IsNetworkMonitor o) => o -> m Bool
getNetworkMonitorNetworkAvailable :: o -> m Bool
getNetworkMonitorNetworkAvailable o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"network-available"
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorNetworkAvailablePropertyInfo
instance AttrInfo NetworkMonitorNetworkAvailablePropertyInfo where
type AttrAllowedOps NetworkMonitorNetworkAvailablePropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint NetworkMonitorNetworkAvailablePropertyInfo = IsNetworkMonitor
type AttrSetTypeConstraint NetworkMonitorNetworkAvailablePropertyInfo = (~) ()
type AttrTransferTypeConstraint NetworkMonitorNetworkAvailablePropertyInfo = (~) ()
type AttrTransferType NetworkMonitorNetworkAvailablePropertyInfo = ()
type AttrGetType NetworkMonitorNetworkAvailablePropertyInfo = Bool
type AttrLabel NetworkMonitorNetworkAvailablePropertyInfo = "network-available"
type AttrOrigin NetworkMonitorNetworkAvailablePropertyInfo = NetworkMonitor
attrGet = getNetworkMonitorNetworkAvailable
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getNetworkMonitorNetworkMetered :: (MonadIO m, IsNetworkMonitor o) => o -> m Bool
getNetworkMonitorNetworkMetered :: o -> m Bool
getNetworkMonitorNetworkMetered o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"network-metered"
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorNetworkMeteredPropertyInfo
instance AttrInfo NetworkMonitorNetworkMeteredPropertyInfo where
type AttrAllowedOps NetworkMonitorNetworkMeteredPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint NetworkMonitorNetworkMeteredPropertyInfo = IsNetworkMonitor
type AttrSetTypeConstraint NetworkMonitorNetworkMeteredPropertyInfo = (~) ()
type AttrTransferTypeConstraint NetworkMonitorNetworkMeteredPropertyInfo = (~) ()
type AttrTransferType NetworkMonitorNetworkMeteredPropertyInfo = ()
type AttrGetType NetworkMonitorNetworkMeteredPropertyInfo = Bool
type AttrLabel NetworkMonitorNetworkMeteredPropertyInfo = "network-metered"
type AttrOrigin NetworkMonitorNetworkMeteredPropertyInfo = NetworkMonitor
attrGet = getNetworkMonitorNetworkMetered
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NetworkMonitor
type instance O.AttributeList NetworkMonitor = NetworkMonitorAttributeList
type NetworkMonitorAttributeList = ('[ '("connectivity", NetworkMonitorConnectivityPropertyInfo), '("networkAvailable", NetworkMonitorNetworkAvailablePropertyInfo), '("networkMetered", NetworkMonitorNetworkMeteredPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
networkMonitorConnectivity :: AttrLabelProxy "connectivity"
networkMonitorConnectivity = AttrLabelProxy
networkMonitorNetworkAvailable :: AttrLabelProxy "networkAvailable"
networkMonitorNetworkAvailable = AttrLabelProxy
networkMonitorNetworkMetered :: AttrLabelProxy "networkMetered"
networkMonitorNetworkMetered = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveNetworkMonitorMethod (t :: Symbol) (o :: *) :: * where
ResolveNetworkMonitorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveNetworkMonitorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveNetworkMonitorMethod "canReach" o = NetworkMonitorCanReachMethodInfo
ResolveNetworkMonitorMethod "canReachAsync" o = NetworkMonitorCanReachAsyncMethodInfo
ResolveNetworkMonitorMethod "canReachFinish" o = NetworkMonitorCanReachFinishMethodInfo
ResolveNetworkMonitorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveNetworkMonitorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveNetworkMonitorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveNetworkMonitorMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveNetworkMonitorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveNetworkMonitorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveNetworkMonitorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveNetworkMonitorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveNetworkMonitorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveNetworkMonitorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveNetworkMonitorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveNetworkMonitorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveNetworkMonitorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveNetworkMonitorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveNetworkMonitorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveNetworkMonitorMethod "getConnectivity" o = NetworkMonitorGetConnectivityMethodInfo
ResolveNetworkMonitorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveNetworkMonitorMethod "getNetworkAvailable" o = NetworkMonitorGetNetworkAvailableMethodInfo
ResolveNetworkMonitorMethod "getNetworkMetered" o = NetworkMonitorGetNetworkMeteredMethodInfo
ResolveNetworkMonitorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveNetworkMonitorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveNetworkMonitorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveNetworkMonitorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveNetworkMonitorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveNetworkMonitorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveNetworkMonitorMethod t NetworkMonitor, O.MethodInfo info NetworkMonitor p) => OL.IsLabel t (NetworkMonitor -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_network_monitor_can_reach" g_network_monitor_can_reach ::
Ptr NetworkMonitor ->
Ptr Gio.SocketConnectable.SocketConnectable ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
networkMonitorCanReach ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a, Gio.SocketConnectable.IsSocketConnectable b, Gio.Cancellable.IsCancellable c) =>
a
-> b
-> Maybe (c)
-> m ()
networkMonitorCanReach :: a -> b -> Maybe c -> m ()
networkMonitorCanReach a
monitor b
connectable Maybe c
cancellable = 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 NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
Ptr SocketConnectable
connectable' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connectable
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr NetworkMonitor
-> Ptr SocketConnectable
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
g_network_monitor_can_reach Ptr NetworkMonitor
monitor' Ptr SocketConnectable
connectable' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connectable
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorCanReachMethodInfo
instance (signature ~ (b -> Maybe (c) -> m ()), MonadIO m, IsNetworkMonitor a, Gio.SocketConnectable.IsSocketConnectable b, Gio.Cancellable.IsCancellable c) => O.MethodInfo NetworkMonitorCanReachMethodInfo a signature where
overloadedMethod = networkMonitorCanReach
#endif
foreign import ccall "g_network_monitor_can_reach_async" g_network_monitor_can_reach_async ::
Ptr NetworkMonitor ->
Ptr Gio.SocketConnectable.SocketConnectable ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
networkMonitorCanReachAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a, Gio.SocketConnectable.IsSocketConnectable b, Gio.Cancellable.IsCancellable c) =>
a
-> b
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
networkMonitorCanReachAsync :: a -> b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
networkMonitorCanReachAsync a
monitor b
connectable Maybe c
cancellable Maybe AsyncReadyCallback
callback = 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 NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
Ptr SocketConnectable
connectable' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connectable
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr NetworkMonitor
-> Ptr SocketConnectable
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_network_monitor_can_reach_async Ptr NetworkMonitor
monitor' Ptr SocketConnectable
connectable' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connectable
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorCanReachAsyncMethodInfo
instance (signature ~ (b -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsNetworkMonitor a, Gio.SocketConnectable.IsSocketConnectable b, Gio.Cancellable.IsCancellable c) => O.MethodInfo NetworkMonitorCanReachAsyncMethodInfo a signature where
overloadedMethod = networkMonitorCanReachAsync
#endif
foreign import ccall "g_network_monitor_can_reach_finish" g_network_monitor_can_reach_finish ::
Ptr NetworkMonitor ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
networkMonitorCanReachFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
networkMonitorCanReachFinish :: a -> b -> m ()
networkMonitorCanReachFinish a
monitor b
result_ = 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 NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr NetworkMonitor
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_network_monitor_can_reach_finish Ptr NetworkMonitor
monitor' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorCanReachFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsNetworkMonitor a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo NetworkMonitorCanReachFinishMethodInfo a signature where
overloadedMethod = networkMonitorCanReachFinish
#endif
foreign import ccall "g_network_monitor_get_connectivity" g_network_monitor_get_connectivity ::
Ptr NetworkMonitor ->
IO CUInt
networkMonitorGetConnectivity ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a) =>
a
-> m Gio.Enums.NetworkConnectivity
networkMonitorGetConnectivity :: a -> m NetworkConnectivity
networkMonitorGetConnectivity a
monitor = IO NetworkConnectivity -> m NetworkConnectivity
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkConnectivity -> m NetworkConnectivity)
-> IO NetworkConnectivity -> m NetworkConnectivity
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
CUInt
result <- Ptr NetworkMonitor -> IO CUInt
g_network_monitor_get_connectivity Ptr NetworkMonitor
monitor'
let result' :: NetworkConnectivity
result' = (Int -> NetworkConnectivity
forall a. Enum a => Int -> a
toEnum (Int -> NetworkConnectivity)
-> (CUInt -> Int) -> CUInt -> NetworkConnectivity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
NetworkConnectivity -> IO NetworkConnectivity
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkConnectivity
result'
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorGetConnectivityMethodInfo
instance (signature ~ (m Gio.Enums.NetworkConnectivity), MonadIO m, IsNetworkMonitor a) => O.MethodInfo NetworkMonitorGetConnectivityMethodInfo a signature where
overloadedMethod = networkMonitorGetConnectivity
#endif
foreign import ccall "g_network_monitor_get_network_available" g_network_monitor_get_network_available ::
Ptr NetworkMonitor ->
IO CInt
networkMonitorGetNetworkAvailable ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a) =>
a
-> m Bool
networkMonitorGetNetworkAvailable :: a -> m Bool
networkMonitorGetNetworkAvailable a
monitor = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
CInt
result <- Ptr NetworkMonitor -> IO CInt
g_network_monitor_get_network_available Ptr NetworkMonitor
monitor'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorGetNetworkAvailableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNetworkMonitor a) => O.MethodInfo NetworkMonitorGetNetworkAvailableMethodInfo a signature where
overloadedMethod = networkMonitorGetNetworkAvailable
#endif
foreign import ccall "g_network_monitor_get_network_metered" g_network_monitor_get_network_metered ::
Ptr NetworkMonitor ->
IO CInt
networkMonitorGetNetworkMetered ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkMonitor a) =>
a
-> m Bool
networkMonitorGetNetworkMetered :: a -> m Bool
networkMonitorGetNetworkMetered a
monitor = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkMonitor
monitor' <- a -> IO (Ptr NetworkMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
CInt
result <- Ptr NetworkMonitor -> IO CInt
g_network_monitor_get_network_metered Ptr NetworkMonitor
monitor'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorGetNetworkMeteredMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNetworkMonitor a) => O.MethodInfo NetworkMonitorGetNetworkMeteredMethodInfo a signature where
overloadedMethod = networkMonitorGetNetworkMetered
#endif
foreign import ccall "g_network_monitor_get_default" g_network_monitor_get_default ::
IO (Ptr NetworkMonitor)
networkMonitorGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m NetworkMonitor
networkMonitorGetDefault :: m NetworkMonitor
networkMonitorGetDefault = IO NetworkMonitor -> m NetworkMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkMonitor -> m NetworkMonitor)
-> IO NetworkMonitor -> m NetworkMonitor
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkMonitor
result <- IO (Ptr NetworkMonitor)
g_network_monitor_get_default
Text -> Ptr NetworkMonitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkMonitorGetDefault" Ptr NetworkMonitor
result
NetworkMonitor
result' <- ((ManagedPtr NetworkMonitor -> NetworkMonitor)
-> Ptr NetworkMonitor -> IO NetworkMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr NetworkMonitor -> NetworkMonitor
NetworkMonitor) Ptr NetworkMonitor
result
NetworkMonitor -> IO NetworkMonitor
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkMonitor
result'
#if defined(ENABLE_OVERLOADING)
#endif
type NetworkMonitorNetworkChangedCallback =
Bool
-> IO ()
noNetworkMonitorNetworkChangedCallback :: Maybe NetworkMonitorNetworkChangedCallback
noNetworkMonitorNetworkChangedCallback :: Maybe NetworkMonitorNetworkChangedCallback
noNetworkMonitorNetworkChangedCallback = Maybe NetworkMonitorNetworkChangedCallback
forall a. Maybe a
Nothing
type C_NetworkMonitorNetworkChangedCallback =
Ptr () ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_NetworkMonitorNetworkChangedCallback :: C_NetworkMonitorNetworkChangedCallback -> IO (FunPtr C_NetworkMonitorNetworkChangedCallback)
genClosure_NetworkMonitorNetworkChanged :: MonadIO m => NetworkMonitorNetworkChangedCallback -> m (GClosure C_NetworkMonitorNetworkChangedCallback)
genClosure_NetworkMonitorNetworkChanged :: NetworkMonitorNetworkChangedCallback
-> m (GClosure C_NetworkMonitorNetworkChangedCallback)
genClosure_NetworkMonitorNetworkChanged NetworkMonitorNetworkChangedCallback
cb = IO (GClosure C_NetworkMonitorNetworkChangedCallback)
-> m (GClosure C_NetworkMonitorNetworkChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_NetworkMonitorNetworkChangedCallback)
-> m (GClosure C_NetworkMonitorNetworkChangedCallback))
-> IO (GClosure C_NetworkMonitorNetworkChangedCallback)
-> m (GClosure C_NetworkMonitorNetworkChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_NetworkMonitorNetworkChangedCallback
cb' = NetworkMonitorNetworkChangedCallback
-> C_NetworkMonitorNetworkChangedCallback
wrap_NetworkMonitorNetworkChangedCallback NetworkMonitorNetworkChangedCallback
cb
C_NetworkMonitorNetworkChangedCallback
-> IO (FunPtr C_NetworkMonitorNetworkChangedCallback)
mk_NetworkMonitorNetworkChangedCallback C_NetworkMonitorNetworkChangedCallback
cb' IO (FunPtr C_NetworkMonitorNetworkChangedCallback)
-> (FunPtr C_NetworkMonitorNetworkChangedCallback
-> IO (GClosure C_NetworkMonitorNetworkChangedCallback))
-> IO (GClosure C_NetworkMonitorNetworkChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_NetworkMonitorNetworkChangedCallback
-> IO (GClosure C_NetworkMonitorNetworkChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_NetworkMonitorNetworkChangedCallback ::
NetworkMonitorNetworkChangedCallback ->
C_NetworkMonitorNetworkChangedCallback
wrap_NetworkMonitorNetworkChangedCallback :: NetworkMonitorNetworkChangedCallback
-> C_NetworkMonitorNetworkChangedCallback
wrap_NetworkMonitorNetworkChangedCallback NetworkMonitorNetworkChangedCallback
_cb Ptr ()
_ CInt
networkAvailable Ptr ()
_ = do
let networkAvailable' :: Bool
networkAvailable' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
networkAvailable
NetworkMonitorNetworkChangedCallback
_cb Bool
networkAvailable'
onNetworkMonitorNetworkChanged :: (IsNetworkMonitor a, MonadIO m) => a -> NetworkMonitorNetworkChangedCallback -> m SignalHandlerId
onNetworkMonitorNetworkChanged :: a -> NetworkMonitorNetworkChangedCallback -> m SignalHandlerId
onNetworkMonitorNetworkChanged a
obj NetworkMonitorNetworkChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_NetworkMonitorNetworkChangedCallback
cb' = NetworkMonitorNetworkChangedCallback
-> C_NetworkMonitorNetworkChangedCallback
wrap_NetworkMonitorNetworkChangedCallback NetworkMonitorNetworkChangedCallback
cb
FunPtr C_NetworkMonitorNetworkChangedCallback
cb'' <- C_NetworkMonitorNetworkChangedCallback
-> IO (FunPtr C_NetworkMonitorNetworkChangedCallback)
mk_NetworkMonitorNetworkChangedCallback C_NetworkMonitorNetworkChangedCallback
cb'
a
-> Text
-> FunPtr C_NetworkMonitorNetworkChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"network-changed" FunPtr C_NetworkMonitorNetworkChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterNetworkMonitorNetworkChanged :: (IsNetworkMonitor a, MonadIO m) => a -> NetworkMonitorNetworkChangedCallback -> m SignalHandlerId
afterNetworkMonitorNetworkChanged :: a -> NetworkMonitorNetworkChangedCallback -> m SignalHandlerId
afterNetworkMonitorNetworkChanged a
obj NetworkMonitorNetworkChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_NetworkMonitorNetworkChangedCallback
cb' = NetworkMonitorNetworkChangedCallback
-> C_NetworkMonitorNetworkChangedCallback
wrap_NetworkMonitorNetworkChangedCallback NetworkMonitorNetworkChangedCallback
cb
FunPtr C_NetworkMonitorNetworkChangedCallback
cb'' <- C_NetworkMonitorNetworkChangedCallback
-> IO (FunPtr C_NetworkMonitorNetworkChangedCallback)
mk_NetworkMonitorNetworkChangedCallback C_NetworkMonitorNetworkChangedCallback
cb'
a
-> Text
-> FunPtr C_NetworkMonitorNetworkChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"network-changed" FunPtr C_NetworkMonitorNetworkChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data NetworkMonitorNetworkChangedSignalInfo
instance SignalInfo NetworkMonitorNetworkChangedSignalInfo where
type HaskellCallbackType NetworkMonitorNetworkChangedSignalInfo = NetworkMonitorNetworkChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_NetworkMonitorNetworkChangedCallback cb
cb'' <- mk_NetworkMonitorNetworkChangedCallback cb'
connectSignalFunPtr obj "network-changed" cb'' connectMode detail
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList NetworkMonitor = NetworkMonitorSignalList
type NetworkMonitorSignalList = ('[ '("networkChanged", NetworkMonitorNetworkChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif