{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.FileMonitor
(
FileMonitor(..) ,
IsFileMonitor ,
toFileMonitor ,
noFileMonitor ,
#if defined(ENABLE_OVERLOADING)
ResolveFileMonitorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FileMonitorCancelMethodInfo ,
#endif
fileMonitorCancel ,
#if defined(ENABLE_OVERLOADING)
FileMonitorEmitEventMethodInfo ,
#endif
fileMonitorEmitEvent ,
#if defined(ENABLE_OVERLOADING)
FileMonitorIsCancelledMethodInfo ,
#endif
fileMonitorIsCancelled ,
#if defined(ENABLE_OVERLOADING)
FileMonitorSetRateLimitMethodInfo ,
#endif
fileMonitorSetRateLimit ,
#if defined(ENABLE_OVERLOADING)
FileMonitorCancelledPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
fileMonitorCancelled ,
#endif
getFileMonitorCancelled ,
#if defined(ENABLE_OVERLOADING)
FileMonitorRateLimitPropertyInfo ,
#endif
constructFileMonitorRateLimit ,
#if defined(ENABLE_OVERLOADING)
fileMonitorRateLimit ,
#endif
getFileMonitorRateLimit ,
setFileMonitorRateLimit ,
C_FileMonitorChangedCallback ,
FileMonitorChangedCallback ,
#if defined(ENABLE_OVERLOADING)
FileMonitorChangedSignalInfo ,
#endif
afterFileMonitorChanged ,
genClosure_FileMonitorChanged ,
mk_FileMonitorChangedCallback ,
noFileMonitorChangedCallback ,
onFileMonitorChanged ,
wrap_FileMonitorChangedCallback ,
) 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.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 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.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.File as Gio.File
newtype FileMonitor = FileMonitor (ManagedPtr FileMonitor)
deriving (FileMonitor -> FileMonitor -> Bool
(FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> Bool) -> Eq FileMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileMonitor -> FileMonitor -> Bool
$c/= :: FileMonitor -> FileMonitor -> Bool
== :: FileMonitor -> FileMonitor -> Bool
$c== :: FileMonitor -> FileMonitor -> Bool
Eq)
foreign import ccall "g_file_monitor_get_type"
c_g_file_monitor_get_type :: IO GType
instance GObject FileMonitor where
gobjectType :: IO GType
gobjectType = IO GType
c_g_file_monitor_get_type
instance B.GValue.IsGValue FileMonitor where
toGValue :: FileMonitor -> IO GValue
toGValue o :: FileMonitor
o = do
GType
gtype <- IO GType
c_g_file_monitor_get_type
FileMonitor -> (Ptr FileMonitor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileMonitor
o (GType
-> (GValue -> Ptr FileMonitor -> IO ())
-> Ptr FileMonitor
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FileMonitor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO FileMonitor
fromGValue gv :: GValue
gv = do
Ptr FileMonitor
ptr <- GValue -> IO (Ptr FileMonitor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FileMonitor)
(ManagedPtr FileMonitor -> FileMonitor)
-> Ptr FileMonitor -> IO FileMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileMonitor -> FileMonitor
FileMonitor Ptr FileMonitor
ptr
class (GObject o, O.IsDescendantOf FileMonitor o) => IsFileMonitor o
instance (GObject o, O.IsDescendantOf FileMonitor o) => IsFileMonitor o
instance O.HasParentTypes FileMonitor
type instance O.ParentTypes FileMonitor = '[GObject.Object.Object]
toFileMonitor :: (MonadIO m, IsFileMonitor o) => o -> m FileMonitor
toFileMonitor :: o -> m FileMonitor
toFileMonitor = IO FileMonitor -> m FileMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileMonitor -> m FileMonitor)
-> (o -> IO FileMonitor) -> o -> m FileMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileMonitor -> FileMonitor) -> o -> IO FileMonitor
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr FileMonitor -> FileMonitor
FileMonitor
noFileMonitor :: Maybe FileMonitor
noFileMonitor :: Maybe FileMonitor
noFileMonitor = Maybe FileMonitor
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveFileMonitorMethod (t :: Symbol) (o :: *) :: * where
ResolveFileMonitorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFileMonitorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFileMonitorMethod "cancel" o = FileMonitorCancelMethodInfo
ResolveFileMonitorMethod "emitEvent" o = FileMonitorEmitEventMethodInfo
ResolveFileMonitorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFileMonitorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFileMonitorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFileMonitorMethod "isCancelled" o = FileMonitorIsCancelledMethodInfo
ResolveFileMonitorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFileMonitorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFileMonitorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFileMonitorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFileMonitorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFileMonitorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFileMonitorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFileMonitorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFileMonitorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFileMonitorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFileMonitorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFileMonitorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFileMonitorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFileMonitorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFileMonitorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFileMonitorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFileMonitorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFileMonitorMethod "setRateLimit" o = FileMonitorSetRateLimitMethodInfo
ResolveFileMonitorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFileMonitorMethod t FileMonitor, O.MethodInfo info FileMonitor p) => OL.IsLabel t (FileMonitor -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type FileMonitorChangedCallback =
Gio.File.File
-> Maybe Gio.File.File
-> Gio.Enums.FileMonitorEvent
-> IO ()
noFileMonitorChangedCallback :: Maybe FileMonitorChangedCallback
noFileMonitorChangedCallback :: Maybe FileMonitorChangedCallback
noFileMonitorChangedCallback = Maybe FileMonitorChangedCallback
forall a. Maybe a
Nothing
type C_FileMonitorChangedCallback =
Ptr () ->
Ptr Gio.File.File ->
Ptr Gio.File.File ->
CUInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileMonitorChangedCallback :: C_FileMonitorChangedCallback -> IO (FunPtr C_FileMonitorChangedCallback)
genClosure_FileMonitorChanged :: MonadIO m => FileMonitorChangedCallback -> m (GClosure C_FileMonitorChangedCallback)
genClosure_FileMonitorChanged :: FileMonitorChangedCallback
-> m (GClosure C_FileMonitorChangedCallback)
genClosure_FileMonitorChanged cb :: FileMonitorChangedCallback
cb = IO (GClosure C_FileMonitorChangedCallback)
-> m (GClosure C_FileMonitorChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FileMonitorChangedCallback)
-> m (GClosure C_FileMonitorChangedCallback))
-> IO (GClosure C_FileMonitorChangedCallback)
-> m (GClosure C_FileMonitorChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FileMonitorChangedCallback
cb' = FileMonitorChangedCallback -> C_FileMonitorChangedCallback
wrap_FileMonitorChangedCallback FileMonitorChangedCallback
cb
C_FileMonitorChangedCallback
-> IO (FunPtr C_FileMonitorChangedCallback)
mk_FileMonitorChangedCallback C_FileMonitorChangedCallback
cb' IO (FunPtr C_FileMonitorChangedCallback)
-> (FunPtr C_FileMonitorChangedCallback
-> IO (GClosure C_FileMonitorChangedCallback))
-> IO (GClosure C_FileMonitorChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FileMonitorChangedCallback
-> IO (GClosure C_FileMonitorChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FileMonitorChangedCallback ::
FileMonitorChangedCallback ->
C_FileMonitorChangedCallback
wrap_FileMonitorChangedCallback :: FileMonitorChangedCallback -> C_FileMonitorChangedCallback
wrap_FileMonitorChangedCallback _cb :: FileMonitorChangedCallback
_cb _ file :: Ptr File
file otherFile :: Ptr File
otherFile eventType :: CUInt
eventType _ = 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 (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 (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 eventType' :: FileMonitorEvent
eventType' = (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
eventType
FileMonitorChangedCallback
_cb File
file' Maybe File
maybeOtherFile FileMonitorEvent
eventType'
onFileMonitorChanged :: (IsFileMonitor a, MonadIO m) => a -> FileMonitorChangedCallback -> m SignalHandlerId
onFileMonitorChanged :: a -> FileMonitorChangedCallback -> m SignalHandlerId
onFileMonitorChanged obj :: a
obj cb :: FileMonitorChangedCallback
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_FileMonitorChangedCallback
cb' = FileMonitorChangedCallback -> C_FileMonitorChangedCallback
wrap_FileMonitorChangedCallback FileMonitorChangedCallback
cb
FunPtr C_FileMonitorChangedCallback
cb'' <- C_FileMonitorChangedCallback
-> IO (FunPtr C_FileMonitorChangedCallback)
mk_FileMonitorChangedCallback C_FileMonitorChangedCallback
cb'
a
-> Text
-> FunPtr C_FileMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_FileMonitorChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileMonitorChanged :: (IsFileMonitor a, MonadIO m) => a -> FileMonitorChangedCallback -> m SignalHandlerId
afterFileMonitorChanged :: a -> FileMonitorChangedCallback -> m SignalHandlerId
afterFileMonitorChanged obj :: a
obj cb :: FileMonitorChangedCallback
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_FileMonitorChangedCallback
cb' = FileMonitorChangedCallback -> C_FileMonitorChangedCallback
wrap_FileMonitorChangedCallback FileMonitorChangedCallback
cb
FunPtr C_FileMonitorChangedCallback
cb'' <- C_FileMonitorChangedCallback
-> IO (FunPtr C_FileMonitorChangedCallback)
mk_FileMonitorChangedCallback C_FileMonitorChangedCallback
cb'
a
-> Text
-> FunPtr C_FileMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_FileMonitorChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileMonitorChangedSignalInfo
instance SignalInfo FileMonitorChangedSignalInfo where
type HaskellCallbackType FileMonitorChangedSignalInfo = FileMonitorChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileMonitorChangedCallback cb
cb'' <- mk_FileMonitorChangedCallback cb'
connectSignalFunPtr obj "changed" cb'' connectMode detail
#endif
getFileMonitorCancelled :: (MonadIO m, IsFileMonitor o) => o -> m Bool
getFileMonitorCancelled :: o -> m Bool
getFileMonitorCancelled obj :: 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 "cancelled"
#if defined(ENABLE_OVERLOADING)
data FileMonitorCancelledPropertyInfo
instance AttrInfo FileMonitorCancelledPropertyInfo where
type AttrAllowedOps FileMonitorCancelledPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint FileMonitorCancelledPropertyInfo = IsFileMonitor
type AttrSetTypeConstraint FileMonitorCancelledPropertyInfo = (~) ()
type AttrTransferTypeConstraint FileMonitorCancelledPropertyInfo = (~) ()
type AttrTransferType FileMonitorCancelledPropertyInfo = ()
type AttrGetType FileMonitorCancelledPropertyInfo = Bool
type AttrLabel FileMonitorCancelledPropertyInfo = "cancelled"
type AttrOrigin FileMonitorCancelledPropertyInfo = FileMonitor
attrGet = getFileMonitorCancelled
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getFileMonitorRateLimit :: (MonadIO m, IsFileMonitor o) => o -> m Int32
getFileMonitorRateLimit :: o -> m Int32
getFileMonitorRateLimit obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "rate-limit"
setFileMonitorRateLimit :: (MonadIO m, IsFileMonitor o) => o -> Int32 -> m ()
setFileMonitorRateLimit :: o -> Int32 -> m ()
setFileMonitorRateLimit obj :: o
obj val :: Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "rate-limit" Int32
val
constructFileMonitorRateLimit :: (IsFileMonitor o) => Int32 -> IO (GValueConstruct o)
constructFileMonitorRateLimit :: Int32 -> IO (GValueConstruct o)
constructFileMonitorRateLimit val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "rate-limit" Int32
val
#if defined(ENABLE_OVERLOADING)
data FileMonitorRateLimitPropertyInfo
instance AttrInfo FileMonitorRateLimitPropertyInfo where
type AttrAllowedOps FileMonitorRateLimitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FileMonitorRateLimitPropertyInfo = IsFileMonitor
type AttrSetTypeConstraint FileMonitorRateLimitPropertyInfo = (~) Int32
type AttrTransferTypeConstraint FileMonitorRateLimitPropertyInfo = (~) Int32
type AttrTransferType FileMonitorRateLimitPropertyInfo = Int32
type AttrGetType FileMonitorRateLimitPropertyInfo = Int32
type AttrLabel FileMonitorRateLimitPropertyInfo = "rate-limit"
type AttrOrigin FileMonitorRateLimitPropertyInfo = FileMonitor
attrGet = getFileMonitorRateLimit
attrSet = setFileMonitorRateLimit
attrTransfer _ v = do
return v
attrConstruct = constructFileMonitorRateLimit
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileMonitor
type instance O.AttributeList FileMonitor = FileMonitorAttributeList
type FileMonitorAttributeList = ('[ '("cancelled", FileMonitorCancelledPropertyInfo), '("rateLimit", FileMonitorRateLimitPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
fileMonitorCancelled :: AttrLabelProxy "cancelled"
fileMonitorCancelled = AttrLabelProxy
fileMonitorRateLimit :: AttrLabelProxy "rateLimit"
fileMonitorRateLimit = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileMonitor = FileMonitorSignalList
type FileMonitorSignalList = ('[ '("changed", FileMonitorChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_file_monitor_cancel" g_file_monitor_cancel ::
Ptr FileMonitor ->
IO CInt
fileMonitorCancel ::
(B.CallStack.HasCallStack, MonadIO m, IsFileMonitor a) =>
a
-> m Bool
fileMonitorCancel :: a -> m Bool
fileMonitorCancel monitor :: 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 FileMonitor
monitor' <- a -> IO (Ptr FileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
CInt
result <- Ptr FileMonitor -> IO CInt
g_file_monitor_cancel Ptr FileMonitor
monitor'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 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 FileMonitorCancelMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileMonitor a) => O.MethodInfo FileMonitorCancelMethodInfo a signature where
overloadedMethod = fileMonitorCancel
#endif
foreign import ccall "g_file_monitor_emit_event" g_file_monitor_emit_event ::
Ptr FileMonitor ->
Ptr Gio.File.File ->
Ptr Gio.File.File ->
CUInt ->
IO ()
fileMonitorEmitEvent ::
(B.CallStack.HasCallStack, MonadIO m, IsFileMonitor a, Gio.File.IsFile b, Gio.File.IsFile c) =>
a
-> b
-> c
-> Gio.Enums.FileMonitorEvent
-> m ()
fileMonitorEmitEvent :: a -> b -> c -> FileMonitorEvent -> m ()
fileMonitorEmitEvent monitor :: a
monitor child :: b
child otherFile :: c
otherFile eventType :: FileMonitorEvent
eventType = 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 FileMonitor
monitor' <- a -> IO (Ptr FileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
Ptr File
child' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
Ptr File
otherFile' <- c -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
otherFile
let eventType' :: CUInt
eventType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileMonitorEvent -> Int) -> FileMonitorEvent -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileMonitorEvent -> Int
forall a. Enum a => a -> Int
fromEnum) FileMonitorEvent
eventType
Ptr FileMonitor -> Ptr File -> Ptr File -> CUInt -> IO ()
g_file_monitor_emit_event Ptr FileMonitor
monitor' Ptr File
child' Ptr File
otherFile' CUInt
eventType'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
otherFile
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileMonitorEmitEventMethodInfo
instance (signature ~ (b -> c -> Gio.Enums.FileMonitorEvent -> m ()), MonadIO m, IsFileMonitor a, Gio.File.IsFile b, Gio.File.IsFile c) => O.MethodInfo FileMonitorEmitEventMethodInfo a signature where
overloadedMethod = fileMonitorEmitEvent
#endif
foreign import ccall "g_file_monitor_is_cancelled" g_file_monitor_is_cancelled ::
Ptr FileMonitor ->
IO CInt
fileMonitorIsCancelled ::
(B.CallStack.HasCallStack, MonadIO m, IsFileMonitor a) =>
a
-> m Bool
fileMonitorIsCancelled :: a -> m Bool
fileMonitorIsCancelled monitor :: 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 FileMonitor
monitor' <- a -> IO (Ptr FileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
CInt
result <- Ptr FileMonitor -> IO CInt
g_file_monitor_is_cancelled Ptr FileMonitor
monitor'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 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 FileMonitorIsCancelledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileMonitor a) => O.MethodInfo FileMonitorIsCancelledMethodInfo a signature where
overloadedMethod = fileMonitorIsCancelled
#endif
foreign import ccall "g_file_monitor_set_rate_limit" g_file_monitor_set_rate_limit ::
Ptr FileMonitor ->
Int32 ->
IO ()
fileMonitorSetRateLimit ::
(B.CallStack.HasCallStack, MonadIO m, IsFileMonitor a) =>
a
-> Int32
-> m ()
fileMonitorSetRateLimit :: a -> Int32 -> m ()
fileMonitorSetRateLimit monitor :: a
monitor limitMsecs :: Int32
limitMsecs = 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 FileMonitor
monitor' <- a -> IO (Ptr FileMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
Ptr FileMonitor -> Int32 -> IO ()
g_file_monitor_set_rate_limit Ptr FileMonitor
monitor' Int32
limitMsecs
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileMonitorSetRateLimitMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsFileMonitor a) => O.MethodInfo FileMonitorSetRateLimitMethodInfo a signature where
overloadedMethod = fileMonitorSetRateLimit
#endif