{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.RecursiveFileMonitor
(
RecursiveFileMonitor(..) ,
IsRecursiveFileMonitor ,
toRecursiveFileMonitor ,
#if defined(ENABLE_OVERLOADING)
ResolveRecursiveFileMonitorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorCancelMethodInfo ,
#endif
recursiveFileMonitorCancel ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorGetRootMethodInfo ,
#endif
recursiveFileMonitorGetRoot ,
recursiveFileMonitorNew ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorSetIgnoreFuncMethodInfo,
#endif
recursiveFileMonitorSetIgnoreFunc ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorStartAsyncMethodInfo,
#endif
recursiveFileMonitorStartAsync ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorStartFinishMethodInfo,
#endif
recursiveFileMonitorStartFinish ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorRootPropertyInfo ,
#endif
constructRecursiveFileMonitorRoot ,
getRecursiveFileMonitorRoot ,
#if defined(ENABLE_OVERLOADING)
recursiveFileMonitorRoot ,
#endif
RecursiveFileMonitorChangedCallback ,
#if defined(ENABLE_OVERLOADING)
RecursiveFileMonitorChangedSignalInfo ,
#endif
afterRecursiveFileMonitorChanged ,
onRecursiveFileMonitorChanged ,
) 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.GHashTable as B.GHT
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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Dazzle.Callbacks as Dazzle.Callbacks
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Enums as Gio.Enums
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
#else
import qualified GI.Dazzle.Callbacks as Dazzle.Callbacks
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Enums as Gio.Enums
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
#endif
newtype RecursiveFileMonitor = RecursiveFileMonitor (SP.ManagedPtr RecursiveFileMonitor)
deriving (RecursiveFileMonitor -> RecursiveFileMonitor -> Bool
(RecursiveFileMonitor -> RecursiveFileMonitor -> Bool)
-> (RecursiveFileMonitor -> RecursiveFileMonitor -> Bool)
-> Eq RecursiveFileMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecursiveFileMonitor -> RecursiveFileMonitor -> Bool
== :: RecursiveFileMonitor -> RecursiveFileMonitor -> Bool
$c/= :: RecursiveFileMonitor -> RecursiveFileMonitor -> Bool
/= :: RecursiveFileMonitor -> RecursiveFileMonitor -> Bool
Eq)
instance SP.ManagedPtrNewtype RecursiveFileMonitor where
toManagedPtr :: RecursiveFileMonitor -> ManagedPtr RecursiveFileMonitor
toManagedPtr (RecursiveFileMonitor ManagedPtr RecursiveFileMonitor
p) = ManagedPtr RecursiveFileMonitor
p
foreign import ccall "dzl_recursive_file_monitor_get_type"
c_dzl_recursive_file_monitor_get_type :: IO B.Types.GType
instance B.Types.TypedObject RecursiveFileMonitor where
glibType :: IO GType
glibType = IO GType
c_dzl_recursive_file_monitor_get_type
instance B.Types.GObject RecursiveFileMonitor
class (SP.GObject o, O.IsDescendantOf RecursiveFileMonitor o) => IsRecursiveFileMonitor o
instance (SP.GObject o, O.IsDescendantOf RecursiveFileMonitor o) => IsRecursiveFileMonitor o
instance O.HasParentTypes RecursiveFileMonitor
type instance O.ParentTypes RecursiveFileMonitor = '[GObject.Object.Object]
toRecursiveFileMonitor :: (MIO.MonadIO m, IsRecursiveFileMonitor o) => o -> m RecursiveFileMonitor
toRecursiveFileMonitor :: forall (m :: * -> *) o.
(MonadIO m, IsRecursiveFileMonitor o) =>
o -> m RecursiveFileMonitor
toRecursiveFileMonitor = IO RecursiveFileMonitor -> m RecursiveFileMonitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO RecursiveFileMonitor -> m RecursiveFileMonitor)
-> (o -> IO RecursiveFileMonitor) -> o -> m RecursiveFileMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor)
-> o -> IO RecursiveFileMonitor
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor
RecursiveFileMonitor
instance B.GValue.IsGValue (Maybe RecursiveFileMonitor) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_recursive_file_monitor_get_type
gvalueSet_ :: Ptr GValue -> Maybe RecursiveFileMonitor -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RecursiveFileMonitor
P.Nothing = Ptr GValue -> Ptr RecursiveFileMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr RecursiveFileMonitor
forall a. Ptr a
FP.nullPtr :: FP.Ptr RecursiveFileMonitor)
gvalueSet_ Ptr GValue
gv (P.Just RecursiveFileMonitor
obj) = RecursiveFileMonitor
-> (Ptr RecursiveFileMonitor -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RecursiveFileMonitor
obj (Ptr GValue -> Ptr RecursiveFileMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe RecursiveFileMonitor)
gvalueGet_ Ptr GValue
gv = do
Ptr RecursiveFileMonitor
ptr <- Ptr GValue -> IO (Ptr RecursiveFileMonitor)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr RecursiveFileMonitor)
if Ptr RecursiveFileMonitor
ptr Ptr RecursiveFileMonitor -> Ptr RecursiveFileMonitor -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr RecursiveFileMonitor
forall a. Ptr a
FP.nullPtr
then RecursiveFileMonitor -> Maybe RecursiveFileMonitor
forall a. a -> Maybe a
P.Just (RecursiveFileMonitor -> Maybe RecursiveFileMonitor)
-> IO RecursiveFileMonitor -> IO (Maybe RecursiveFileMonitor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor)
-> Ptr RecursiveFileMonitor -> IO RecursiveFileMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor
RecursiveFileMonitor Ptr RecursiveFileMonitor
ptr
else Maybe RecursiveFileMonitor -> IO (Maybe RecursiveFileMonitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RecursiveFileMonitor
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveRecursiveFileMonitorMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveRecursiveFileMonitorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRecursiveFileMonitorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRecursiveFileMonitorMethod "cancel" o = RecursiveFileMonitorCancelMethodInfo
ResolveRecursiveFileMonitorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRecursiveFileMonitorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRecursiveFileMonitorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRecursiveFileMonitorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRecursiveFileMonitorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRecursiveFileMonitorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRecursiveFileMonitorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRecursiveFileMonitorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRecursiveFileMonitorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRecursiveFileMonitorMethod "startAsync" o = RecursiveFileMonitorStartAsyncMethodInfo
ResolveRecursiveFileMonitorMethod "startFinish" o = RecursiveFileMonitorStartFinishMethodInfo
ResolveRecursiveFileMonitorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRecursiveFileMonitorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRecursiveFileMonitorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRecursiveFileMonitorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRecursiveFileMonitorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRecursiveFileMonitorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRecursiveFileMonitorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRecursiveFileMonitorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRecursiveFileMonitorMethod "getRoot" o = RecursiveFileMonitorGetRootMethodInfo
ResolveRecursiveFileMonitorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRecursiveFileMonitorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRecursiveFileMonitorMethod "setIgnoreFunc" o = RecursiveFileMonitorSetIgnoreFuncMethodInfo
ResolveRecursiveFileMonitorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRecursiveFileMonitorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRecursiveFileMonitorMethod t RecursiveFileMonitor, O.OverloadedMethod info RecursiveFileMonitor p) => OL.IsLabel t (RecursiveFileMonitor -> 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 ~ ResolveRecursiveFileMonitorMethod t RecursiveFileMonitor, O.OverloadedMethod info RecursiveFileMonitor p, R.HasField t RecursiveFileMonitor p) => R.HasField t RecursiveFileMonitor p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRecursiveFileMonitorMethod t RecursiveFileMonitor, O.OverloadedMethodInfo info RecursiveFileMonitor) => OL.IsLabel t (O.MethodProxy info RecursiveFileMonitor) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type RecursiveFileMonitorChangedCallback =
Gio.File.File
-> Maybe Gio.File.File
-> Gio.Enums.FileMonitorEvent
-> IO ()
type C_RecursiveFileMonitorChangedCallback =
Ptr RecursiveFileMonitor ->
Ptr Gio.File.File ->
Ptr Gio.File.File ->
CUInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_RecursiveFileMonitorChangedCallback :: C_RecursiveFileMonitorChangedCallback -> IO (FunPtr C_RecursiveFileMonitorChangedCallback)
wrap_RecursiveFileMonitorChangedCallback ::
GObject a => (a -> RecursiveFileMonitorChangedCallback) ->
C_RecursiveFileMonitorChangedCallback
wrap_RecursiveFileMonitorChangedCallback :: forall a.
GObject a =>
(a -> RecursiveFileMonitorChangedCallback)
-> C_RecursiveFileMonitorChangedCallback
wrap_RecursiveFileMonitorChangedCallback a -> RecursiveFileMonitorChangedCallback
gi'cb Ptr RecursiveFileMonitor
gi'selfPtr Ptr File
file Ptr File
otherFile CUInt
event Ptr ()
_ = do
File
file' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
file
Maybe File
maybeOtherFile <-
if Ptr File
otherFile Ptr File -> Ptr File -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr File
forall a. Ptr a
nullPtr
then Maybe File -> IO (Maybe File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe File
forall a. Maybe a
Nothing
else do
File
otherFile' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
otherFile
Maybe File -> IO (Maybe File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe File -> IO (Maybe File)) -> Maybe File -> IO (Maybe File)
forall a b. (a -> b) -> a -> b
$ File -> Maybe File
forall a. a -> Maybe a
Just File
otherFile'
let event' :: FileMonitorEvent
event' = (Int -> FileMonitorEvent
forall a. Enum a => Int -> a
toEnum (Int -> FileMonitorEvent)
-> (CUInt -> Int) -> CUInt -> FileMonitorEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
event
Ptr RecursiveFileMonitor
-> (RecursiveFileMonitor -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr RecursiveFileMonitor
gi'selfPtr ((RecursiveFileMonitor -> IO ()) -> IO ())
-> (RecursiveFileMonitor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RecursiveFileMonitor
gi'self -> a -> RecursiveFileMonitorChangedCallback
gi'cb (RecursiveFileMonitor -> a
forall a b. Coercible a b => a -> b
Coerce.coerce RecursiveFileMonitor
gi'self) File
file' Maybe File
maybeOtherFile FileMonitorEvent
event'
onRecursiveFileMonitorChanged :: (IsRecursiveFileMonitor a, MonadIO m) => a -> ((?self :: a) => RecursiveFileMonitorChangedCallback) -> m SignalHandlerId
onRecursiveFileMonitorChanged :: forall a (m :: * -> *).
(IsRecursiveFileMonitor a, MonadIO m) =>
a
-> ((?self::a) => RecursiveFileMonitorChangedCallback)
-> m SignalHandlerId
onRecursiveFileMonitorChanged a
obj (?self::a) => RecursiveFileMonitorChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> RecursiveFileMonitorChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RecursiveFileMonitorChangedCallback
RecursiveFileMonitorChangedCallback
cb
let wrapped' :: C_RecursiveFileMonitorChangedCallback
wrapped' = (a -> RecursiveFileMonitorChangedCallback)
-> C_RecursiveFileMonitorChangedCallback
forall a.
GObject a =>
(a -> RecursiveFileMonitorChangedCallback)
-> C_RecursiveFileMonitorChangedCallback
wrap_RecursiveFileMonitorChangedCallback a -> RecursiveFileMonitorChangedCallback
wrapped
FunPtr C_RecursiveFileMonitorChangedCallback
wrapped'' <- C_RecursiveFileMonitorChangedCallback
-> IO (FunPtr C_RecursiveFileMonitorChangedCallback)
mk_RecursiveFileMonitorChangedCallback C_RecursiveFileMonitorChangedCallback
wrapped'
a
-> Text
-> FunPtr C_RecursiveFileMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_RecursiveFileMonitorChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterRecursiveFileMonitorChanged :: (IsRecursiveFileMonitor a, MonadIO m) => a -> ((?self :: a) => RecursiveFileMonitorChangedCallback) -> m SignalHandlerId
afterRecursiveFileMonitorChanged :: forall a (m :: * -> *).
(IsRecursiveFileMonitor a, MonadIO m) =>
a
-> ((?self::a) => RecursiveFileMonitorChangedCallback)
-> m SignalHandlerId
afterRecursiveFileMonitorChanged a
obj (?self::a) => RecursiveFileMonitorChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> RecursiveFileMonitorChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RecursiveFileMonitorChangedCallback
RecursiveFileMonitorChangedCallback
cb
let wrapped' :: C_RecursiveFileMonitorChangedCallback
wrapped' = (a -> RecursiveFileMonitorChangedCallback)
-> C_RecursiveFileMonitorChangedCallback
forall a.
GObject a =>
(a -> RecursiveFileMonitorChangedCallback)
-> C_RecursiveFileMonitorChangedCallback
wrap_RecursiveFileMonitorChangedCallback a -> RecursiveFileMonitorChangedCallback
wrapped
FunPtr C_RecursiveFileMonitorChangedCallback
wrapped'' <- C_RecursiveFileMonitorChangedCallback
-> IO (FunPtr C_RecursiveFileMonitorChangedCallback)
mk_RecursiveFileMonitorChangedCallback C_RecursiveFileMonitorChangedCallback
wrapped'
a
-> Text
-> FunPtr C_RecursiveFileMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_RecursiveFileMonitorChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorChangedSignalInfo
instance SignalInfo RecursiveFileMonitorChangedSignalInfo where
type HaskellCallbackType RecursiveFileMonitorChangedSignalInfo = RecursiveFileMonitorChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_RecursiveFileMonitorChangedCallback cb
cb'' <- mk_RecursiveFileMonitorChangedCallback cb'
connectSignalFunPtr obj "changed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor::changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#g:signal:changed"})
#endif
getRecursiveFileMonitorRoot :: (MonadIO m, IsRecursiveFileMonitor o) => o -> m Gio.File.File
getRecursiveFileMonitorRoot :: forall (m :: * -> *) o.
(MonadIO m, IsRecursiveFileMonitor o) =>
o -> m File
getRecursiveFileMonitorRoot o
obj = IO File -> m File
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe File) -> IO File
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getRecursiveFileMonitorRoot" (IO (Maybe File) -> IO File) -> IO (Maybe File) -> IO File
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"root" ManagedPtr File -> File
Gio.File.File
constructRecursiveFileMonitorRoot :: (IsRecursiveFileMonitor o, MIO.MonadIO m, Gio.File.IsFile a) => a -> m (GValueConstruct o)
constructRecursiveFileMonitorRoot :: forall o (m :: * -> *) a.
(IsRecursiveFileMonitor o, MonadIO m, IsFile a) =>
a -> m (GValueConstruct o)
constructRecursiveFileMonitorRoot a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"root" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorRootPropertyInfo
instance AttrInfo RecursiveFileMonitorRootPropertyInfo where
type AttrAllowedOps RecursiveFileMonitorRootPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint RecursiveFileMonitorRootPropertyInfo = IsRecursiveFileMonitor
type AttrSetTypeConstraint RecursiveFileMonitorRootPropertyInfo = Gio.File.IsFile
type AttrTransferTypeConstraint RecursiveFileMonitorRootPropertyInfo = Gio.File.IsFile
type AttrTransferType RecursiveFileMonitorRootPropertyInfo = Gio.File.File
type AttrGetType RecursiveFileMonitorRootPropertyInfo = Gio.File.File
type AttrLabel RecursiveFileMonitorRootPropertyInfo = "root"
type AttrOrigin RecursiveFileMonitorRootPropertyInfo = RecursiveFileMonitor
attrGet = getRecursiveFileMonitorRoot
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.File.File v
attrConstruct = constructRecursiveFileMonitorRoot
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.root"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#g:attr:root"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RecursiveFileMonitor
type instance O.AttributeList RecursiveFileMonitor = RecursiveFileMonitorAttributeList
type RecursiveFileMonitorAttributeList = ('[ '("root", RecursiveFileMonitorRootPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
recursiveFileMonitorRoot :: AttrLabelProxy "root"
recursiveFileMonitorRoot = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList RecursiveFileMonitor = RecursiveFileMonitorSignalList
type RecursiveFileMonitorSignalList = ('[ '("changed", RecursiveFileMonitorChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_recursive_file_monitor_new" dzl_recursive_file_monitor_new ::
Ptr Gio.File.File ->
IO (Ptr RecursiveFileMonitor)
recursiveFileMonitorNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
a
-> m RecursiveFileMonitor
recursiveFileMonitorNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFile a) =>
a -> m RecursiveFileMonitor
recursiveFileMonitorNew a
root = IO RecursiveFileMonitor -> m RecursiveFileMonitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RecursiveFileMonitor -> m RecursiveFileMonitor)
-> IO RecursiveFileMonitor -> m RecursiveFileMonitor
forall a b. (a -> b) -> a -> b
$ do
Ptr File
root' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
root
Ptr RecursiveFileMonitor
result <- Ptr File -> IO (Ptr RecursiveFileMonitor)
dzl_recursive_file_monitor_new Ptr File
root'
Text -> Ptr RecursiveFileMonitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recursiveFileMonitorNew" Ptr RecursiveFileMonitor
result
RecursiveFileMonitor
result' <- ((ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor)
-> Ptr RecursiveFileMonitor -> IO RecursiveFileMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr RecursiveFileMonitor -> RecursiveFileMonitor
RecursiveFileMonitor) Ptr RecursiveFileMonitor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
root
RecursiveFileMonitor -> IO RecursiveFileMonitor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RecursiveFileMonitor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_recursive_file_monitor_cancel" dzl_recursive_file_monitor_cancel ::
Ptr RecursiveFileMonitor ->
IO ()
recursiveFileMonitorCancel ::
(B.CallStack.HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a
-> m ()
recursiveFileMonitorCancel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a -> m ()
recursiveFileMonitorCancel a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr RecursiveFileMonitor
self' <- a -> IO (Ptr RecursiveFileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr RecursiveFileMonitor -> IO ()
dzl_recursive_file_monitor_cancel Ptr RecursiveFileMonitor
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorCancelMethodInfo
instance (signature ~ (m ()), MonadIO m, IsRecursiveFileMonitor a) => O.OverloadedMethod RecursiveFileMonitorCancelMethodInfo a signature where
overloadedMethod = recursiveFileMonitorCancel
instance O.OverloadedMethodInfo RecursiveFileMonitorCancelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.recursiveFileMonitorCancel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#v:recursiveFileMonitorCancel"
})
#endif
foreign import ccall "dzl_recursive_file_monitor_get_root" dzl_recursive_file_monitor_get_root ::
Ptr RecursiveFileMonitor ->
IO (Ptr Gio.File.File)
recursiveFileMonitorGetRoot ::
(B.CallStack.HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a
-> m Gio.File.File
recursiveFileMonitorGetRoot :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a -> m File
recursiveFileMonitorGetRoot a
self = IO File -> m File
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
Ptr RecursiveFileMonitor
self' <- a -> IO (Ptr RecursiveFileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr File
result <- Ptr RecursiveFileMonitor -> IO (Ptr File)
dzl_recursive_file_monitor_get_root Ptr RecursiveFileMonitor
self'
Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recursiveFileMonitorGetRoot" Ptr File
result
File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorGetRootMethodInfo
instance (signature ~ (m Gio.File.File), MonadIO m, IsRecursiveFileMonitor a) => O.OverloadedMethod RecursiveFileMonitorGetRootMethodInfo a signature where
overloadedMethod = recursiveFileMonitorGetRoot
instance O.OverloadedMethodInfo RecursiveFileMonitorGetRootMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.recursiveFileMonitorGetRoot",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#v:recursiveFileMonitorGetRoot"
})
#endif
foreign import ccall "dzl_recursive_file_monitor_set_ignore_func" dzl_recursive_file_monitor_set_ignore_func ::
Ptr RecursiveFileMonitor ->
FunPtr Dazzle.Callbacks.C_RecursiveIgnoreFunc ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
recursiveFileMonitorSetIgnoreFunc ::
(B.CallStack.HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a
-> Dazzle.Callbacks.RecursiveIgnoreFunc
-> m ()
recursiveFileMonitorSetIgnoreFunc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRecursiveFileMonitor a) =>
a -> RecursiveIgnoreFunc -> m ()
recursiveFileMonitorSetIgnoreFunc a
self RecursiveIgnoreFunc
ignoreFunc = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr RecursiveFileMonitor
self' <- a -> IO (Ptr RecursiveFileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
FunPtr C_RecursiveIgnoreFunc
ignoreFunc' <- C_RecursiveIgnoreFunc -> IO (FunPtr C_RecursiveIgnoreFunc)
Dazzle.Callbacks.mk_RecursiveIgnoreFunc (Maybe (Ptr (FunPtr C_RecursiveIgnoreFunc))
-> RecursiveIgnoreFunc_WithClosures -> C_RecursiveIgnoreFunc
Dazzle.Callbacks.wrap_RecursiveIgnoreFunc Maybe (Ptr (FunPtr C_RecursiveIgnoreFunc))
forall a. Maybe a
Nothing (RecursiveIgnoreFunc -> RecursiveIgnoreFunc_WithClosures
Dazzle.Callbacks.drop_closures_RecursiveIgnoreFunc RecursiveIgnoreFunc
ignoreFunc))
let ignoreFuncData :: Ptr ()
ignoreFuncData = FunPtr C_RecursiveIgnoreFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_RecursiveIgnoreFunc
ignoreFunc'
let ignoreFuncDataDestroy :: FunPtr (Ptr a -> IO ())
ignoreFuncDataDestroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
Ptr RecursiveFileMonitor
-> FunPtr C_RecursiveIgnoreFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
dzl_recursive_file_monitor_set_ignore_func Ptr RecursiveFileMonitor
self' FunPtr C_RecursiveIgnoreFunc
ignoreFunc' Ptr ()
ignoreFuncData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
ignoreFuncDataDestroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorSetIgnoreFuncMethodInfo
instance (signature ~ (Dazzle.Callbacks.RecursiveIgnoreFunc -> m ()), MonadIO m, IsRecursiveFileMonitor a) => O.OverloadedMethod RecursiveFileMonitorSetIgnoreFuncMethodInfo a signature where
overloadedMethod = recursiveFileMonitorSetIgnoreFunc
instance O.OverloadedMethodInfo RecursiveFileMonitorSetIgnoreFuncMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.recursiveFileMonitorSetIgnoreFunc",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#v:recursiveFileMonitorSetIgnoreFunc"
})
#endif
foreign import ccall "dzl_recursive_file_monitor_start_async" dzl_recursive_file_monitor_start_async ::
Ptr RecursiveFileMonitor ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
recursiveFileMonitorStartAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsRecursiveFileMonitor a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
recursiveFileMonitorStartAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRecursiveFileMonitor a,
IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
recursiveFileMonitorStartAsync a
self Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr RecursiveFileMonitor
self' <- a -> IO (Ptr RecursiveFileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 RecursiveFileMonitor
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
dzl_recursive_file_monitor_start_async Ptr RecursiveFileMonitor
self' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorStartAsyncMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsRecursiveFileMonitor a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod RecursiveFileMonitorStartAsyncMethodInfo a signature where
overloadedMethod = recursiveFileMonitorStartAsync
instance O.OverloadedMethodInfo RecursiveFileMonitorStartAsyncMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.recursiveFileMonitorStartAsync",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#v:recursiveFileMonitorStartAsync"
})
#endif
foreign import ccall "dzl_recursive_file_monitor_start_finish" dzl_recursive_file_monitor_start_finish ::
Ptr RecursiveFileMonitor ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
recursiveFileMonitorStartFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsRecursiveFileMonitor a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
recursiveFileMonitorStartFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRecursiveFileMonitor a,
IsAsyncResult b) =>
a -> b -> m ()
recursiveFileMonitorStartFinish a
self b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr RecursiveFileMonitor
self' <- a -> IO (Ptr RecursiveFileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
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 RecursiveFileMonitor
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
dzl_recursive_file_monitor_start_finish Ptr RecursiveFileMonitor
self' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data RecursiveFileMonitorStartFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsRecursiveFileMonitor a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod RecursiveFileMonitorStartFinishMethodInfo a signature where
overloadedMethod = recursiveFileMonitorStartFinish
instance O.OverloadedMethodInfo RecursiveFileMonitorStartFinishMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.RecursiveFileMonitor.recursiveFileMonitorStartFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-RecursiveFileMonitor.html#v:recursiveFileMonitorStartFinish"
})
#endif