{-# LINE 2 "./System/GIO/File/FileMonitor.chs" #-}
-- GIMP Toolkit (GTK) Binding for Haskell: binding to gio -*-haskell-*-
--
-- Author : Andy Stewart
-- Created: 30-Apirl-2010
--
-- Copyright (c) 2010 Andy Stewart
--
-- This library is free software: you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public License
-- as published by the Free Software Foundation, either version 3 of
-- the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this program. If not, see
-- <http:
--
-- GIO, the C library which this Haskell library depends on, is
-- available under LGPL Version 2. The documentation included with
-- this library is based on the original GIO documentation.
--
-- | Maintainer : gtk2hs-devel@lists.sourceforge.net
-- Stability : alpha
-- Portability : portable (depends on GHC)
module System.GIO.File.FileMonitor (
-- * Details
--
-- | Monitors a file or directory for changes.
--
-- To obtain a 'FileMonitor' for a file or directory, use 'fileMonitor', or
-- 'fileMonitorDirectory' .
--
-- To get informed about changes to the file or directory you are monitoring, connect to the "changed"
-- signal. The signal will be emitted in the thread-default main context of the thread that the monitor
-- was created in (though if the global default main context is blocked, this may cause notifications
-- to be blocked even if the thread-default context is still running).

-- * Types
   FileMonitor(..),
   FileMonitorClass,

-- * Enums
   FileMonitorEvent(..),

-- * Methods
    fileMonitorCancel,
    fileMonitorIsCancelled,

-- * Attributes
    fileMonitorCancelled,
    fileMonitorRateLimit,

-- * Signals
    fileMonitorChanged,
    ) where

import Control.Monad
import System.GIO.Enums
import System.Glib.Attributes
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GObject
import System.Glib.Properties
import System.Glib.Signals
import System.Glib.UTFString
import System.GIO.Signals
{-# LINE 73 "./System/GIO/File/FileMonitor.chs" #-}
import System.GIO.Types
{-# LINE 74 "./System/GIO/File/FileMonitor.chs" #-}

--------------------
-- Methods
-- | Cancels a file monitor.
fileMonitorCancel :: FileMonitorClass monitor => monitor
                  -> IO Bool -- ^ returns 'True' if monitor was cancelled.
fileMonitorCancel :: forall monitor. FileMonitorClass monitor => monitor -> IO Bool
fileMonitorCancel monitor
monitor =
  (CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$ (\(FileMonitor ForeignPtr FileMonitor
arg1) -> ForeignPtr FileMonitor -> (Ptr FileMonitor -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr FileMonitor
arg1 ((Ptr FileMonitor -> IO CInt) -> IO CInt)
-> (Ptr FileMonitor -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr FileMonitor
argPtr1 ->Ptr FileMonitor -> IO CInt
g_file_monitor_cancel Ptr FileMonitor
argPtr1) (monitor -> FileMonitor
forall o. FileMonitorClass o => o -> FileMonitor
toFileMonitor monitor
monitor)

-- | Returns whether the monitor is canceled.
fileMonitorIsCancelled :: FileMonitorClass monitor => monitor
                       -> IO Bool -- ^ returns 'True' if monitor is canceled. 'False' otherwise.
fileMonitorIsCancelled :: forall monitor. FileMonitorClass monitor => monitor -> IO Bool
fileMonitorIsCancelled monitor
monitor =
  (CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$ (\(FileMonitor ForeignPtr FileMonitor
arg1) -> ForeignPtr FileMonitor -> (Ptr FileMonitor -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr FileMonitor
arg1 ((Ptr FileMonitor -> IO CInt) -> IO CInt)
-> (Ptr FileMonitor -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr FileMonitor
argPtr1 ->Ptr FileMonitor -> IO CInt
g_file_monitor_is_cancelled Ptr FileMonitor
argPtr1) (monitor -> FileMonitor
forall o. FileMonitorClass o => o -> FileMonitor
toFileMonitor monitor
monitor)

--------------------
-- Attributes
-- | Whether the monitor has been cancelled.
--
-- Default value: 'False'
fileMonitorCancelled :: FileMonitorClass monitor => ReadAttr monitor Bool
fileMonitorCancelled :: forall monitor. FileMonitorClass monitor => ReadAttr monitor Bool
fileMonitorCancelled = String -> ReadAttr monitor Bool
forall gobj. GObjectClass gobj => String -> ReadAttr gobj Bool
readAttrFromBoolProperty String
"cancelled"

-- | The limit of the monitor to watch for changes, in milliseconds.
--
-- Allowed values: >= 0
--
-- Default value: 800
fileMonitorRateLimit :: FileMonitorClass monitor => Attr monitor Int
fileMonitorRateLimit :: forall monitor. FileMonitorClass monitor => Attr monitor Int
fileMonitorRateLimit = String -> Attr monitor Int
forall gobj. GObjectClass gobj => String -> Attr gobj Int
newAttrFromIntProperty String
"rate-limit"

--------------------
-- Signals
fileMonitorChanged :: FileMonitorClass monitor => Signal monitor (Maybe File -> Maybe File -> FileMonitorEvent -> IO ())
fileMonitorChanged :: forall monitor.
FileMonitorClass monitor =>
Signal
  monitor (Maybe File -> Maybe File -> FileMonitorEvent -> IO ())
fileMonitorChanged = (Bool
 -> monitor
 -> (Maybe File -> Maybe File -> FileMonitorEvent -> IO ())
 -> IO (ConnectId monitor))
-> Signal
     monitor (Maybe File -> Maybe File -> FileMonitorEvent -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (String
-> Bool
-> monitor
-> (Maybe File -> Maybe File -> FileMonitorEvent -> IO ())
-> IO (ConnectId monitor)
forall a' b' c obj.
(GObjectClass a', GObjectClass b', Enum c, GObjectClass obj) =>
String
-> Bool
-> obj
-> (Maybe a' -> Maybe b' -> c -> IO ())
-> IO (ConnectId obj)
connect_MOBJECT_MOBJECT_ENUM__NONE String
"changed")

foreign import ccall safe "g_file_monitor_cancel"
  g_file_monitor_cancel :: ((Ptr FileMonitor) -> (IO CInt))

foreign import ccall safe "g_file_monitor_is_cancelled"
  g_file_monitor_is_cancelled :: ((Ptr FileMonitor) -> (IO CInt))