{-# LINE 2 "./Graphics/UI/Gtk/General/General.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) General
--
-- Author : Axel Simon, Manuel M. T. Chakravarty
--
-- Created: 8 December 1998
--
-- Copyright (C) 2000..2005 Axel Simon, Manuel M. T. Chakravarty
--
-- 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 2.1 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.
--
-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- library initialization, main event loop, and events
--
module Graphics.UI.Gtk.General.General (
-- getDefaultLanguage,
  -- * Initialisation
  initGUI,

  -- ** Support for OS threads
  unsafeInitGUIForThreadedRTS,
  postGUISync,
  postGUIAsync,
  threadsEnter,
  threadsLeave,

  -- * Main event loop
  mainGUI,
  mainQuit,

  -- ** Less commonly used event loop functions
  eventsPending,
  mainLevel,
  mainIteration,
  mainIterationDo,
  mainDoEvent,

  -- ** Call when mainloop is left

  quitAddDestroy,
  quitAdd,
  quitRemove,


  -- * Grab widgets
  grabAdd,
  grabGetCurrent,
  grabRemove,

  -- * Timeout and idle callbacks
  Priority,
  priorityLow,
  priorityDefaultIdle,
  priorityHighIdle,
  priorityDefault,
  priorityHigh,
  timeoutAdd,
  timeoutAddFull,
  timeoutRemove,
  idleAdd,
  idleRemove,
  inputAdd,
  inputRemove,
  IOCondition(..),
  HandlerId,
  FD
  ) where

import Control.Applicative
import Prelude
import System.Environment (getProgName, getArgs)
import Control.Monad (liftM, when)
import Control.Concurrent (rtsSupportsBoundThreads, newEmptyMVar,
                           putMVar, takeMVar)

import System.Glib.FFI
import System.Glib.UTFString
import qualified System.Glib.MainLoop as ML
import System.Glib.MainLoop ( Priority, priorityLow, priorityDefaultIdle,
  priorityHighIdle, priorityDefault, priorityHigh, timeoutRemove, idleRemove,
  inputRemove, IOCondition(..), HandlerId )
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Gdk.EventM (EventM)
import Control.Monad.Reader (ask)
import Control.Monad.Trans (liftIO)
import Graphics.UI.Gtk.Types
{-# LINE 100 "./Graphics/UI/Gtk/General/General.chs" #-}


{-# LINE 102 "./Graphics/UI/Gtk/General/General.chs" #-}

{-
-- | Retreive the current language.
-- * This function returns a String which's pointer can be used later on for
-- comarisions.
--
--getDefaultLanguage :: GlibString string => IO string
--getDefaultLanguage = do
-- strPtr <- {#call unsafe get_default_language#}
-- str <- peekUTFString strPtr
-- destruct strPtr
-- return str
-}

unsafeInitGUIForThreadedRTS :: IO [String]
unsafeInitGUIForThreadedRTS = IO [String]
initGUI

-- We compile this module using -#includ"gtk/wingtk.h" to bypass the win32 abi
-- check however we do not compile users programs with this header so if
-- initGUI was ever inlined in a users program, then that program would not
-- bypass the abi check and would fail on startup. So to stop that we must
-- prevent initGUI from being inlined.
{-# NOINLINE initGUI #-}
-- | Initialize the GUI.
--
-- This must be called before any other function in the Gtk2Hs library.
--
-- This function initializes the GUI toolkit and parses all Gtk
-- specific arguments. The remaining arguments are returned. If the
-- initialization of the toolkit fails for whatever reason, an exception
-- is thrown.
--
-- * Throws: @error \"Cannot initialize GUI.\"@
--
--
-- * If you want to use Gtk2Hs and in a multi-threaded application then it is your obligation
-- to ensure that all calls to Gtk+ happen in a single OS thread.
-- If you want to make calls to Gtk2Hs functions from a Haskell thread other
-- than the one that calls this functions and 'mainGUI' then you will have to
-- \'post\' your GUI actions to the main GUI thread. You can do this using
-- 'postGUISync' or 'postGUIAsync'. See also 'threadsEnter'.
--
initGUI :: IO [String]
initGUI :: IO [String]
initGUI = do
  IO ()
initialise
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
rtsSupportsBoundThreads IO ()
initialiseGThreads
  -- note: initizliseGThreads calls 'threadsEnter'
  String
prog <- IO String
getProgName
  [String]
args <- IO [String]
getArgs
  let allArgs :: [String]
allArgs = (String
progString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)
  (Text -> (CString -> IO [String]) -> IO [String])
-> [Text] -> ([CString] -> IO [String]) -> IO [String]
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany Text -> (CString -> IO [String]) -> IO [String]
forall a. Text -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString ((String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
stringToGlib [String]
allArgs) (([CString] -> IO [String]) -> IO [String])
-> ([CString] -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \[CString]
addrs ->
    [CString] -> (Int -> Ptr CString -> IO [String]) -> IO [String]
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CString]
addrs ((Int -> Ptr CString -> IO [String]) -> IO [String])
-> (Int -> Ptr CString -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Int
argc Ptr CString
argv ->
    Ptr CString -> (Ptr (Ptr CString) -> IO [String]) -> IO [String]
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr CString
argv ((Ptr (Ptr CString) -> IO [String]) -> IO [String])
-> (Ptr (Ptr CString) -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CString)
argvp ->
    Int -> (Ptr Int -> IO [String]) -> IO [String]
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Int
argc ((Ptr Int -> IO [String]) -> IO [String])
-> (Ptr Int -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Ptr Int
argcp -> do
      CInt
res <- Ptr CInt -> Ptr (Ptr CString) -> IO CInt
gtk_init_check (Ptr Int -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr Int
argcp) (Ptr (Ptr CString) -> Ptr (Ptr CString)
forall a b. Ptr a -> Ptr b
castPtr Ptr (Ptr CString)
argvp)
      if (CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
res) then do
        Int
argc'   <- Ptr Int -> IO Int
forall a. Storable a => Ptr a -> IO a
peek Ptr Int
argcp
        Ptr CString
argv'   <- Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CString)
argvp
        CString
_:[CString]
addrs'  <- Int -> Ptr CString -> IO [CString]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
argc' Ptr CString
argv'  -- drop the program name
        (CString -> IO String) -> [CString] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Text -> String
glibToString (Text -> String) -> IO Text -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (IO Text -> IO String)
-> (CString -> IO Text) -> CString -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> IO Text
forall s. GlibString s => CString -> IO s
peekUTFString) [CString]
addrs'
        else String -> IO [String]
forall a. HasCallStack => String -> a
error String
"Cannot initialize GUI."

-- g_thread_init aborts the whole program if it's called more than once so
-- we've got to keep track of whether or not we've called it already. Sigh.
--
foreign import ccall "hsgthread.h gtk2hs_threads_initialise"
  initialiseGThreads :: IO ()

foreign import ccall "hsgthread.h gtk2hs_initialise"
  initialise :: IO ()

-- | Post an action to be run in the main GUI thread.
--
-- The current thread blocks until the action completes and the result is
-- returned.
--
postGUISync :: IO a -> IO a
postGUISync :: forall a. IO a -> IO a
postGUISync IO a
action = do
  MVar a
resultVar <- IO (MVar a)
forall a. IO (MVar a)
newEmptyMVar
  IO Bool -> Int -> IO CUInt
idleAdd (IO a
action IO a -> (a -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MVar a -> a -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar a
resultVar IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Int
priorityDefault
  MVar a -> IO a
forall a. MVar a -> IO a
takeMVar MVar a
resultVar

-- | Post an action to be run in the main GUI thread.
--
-- The current thread continues and does not wait for the result of the
-- action.
--
postGUIAsync :: IO () -> IO ()
postGUIAsync :: IO () -> IO ()
postGUIAsync IO ()
action = do
  IO Bool -> Int -> IO CUInt
idleAdd (IO ()
action IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Int
priorityDefault
  () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Acquire the global Gtk lock.
--
-- * During normal operation, this lock is held by the thread from which all
-- interaction with Gtk is performed. When calling 'mainGUI', the thread will
-- release this global lock before it waits for user interaction. During this
-- time it is, in principle, possible to use a different OS thread (any other
-- Haskell thread that is bound to the Gtk OS thread will be blocked anyway)
-- to interact with Gtk by explicitly acquiring the lock, calling Gtk functions
-- and releasing the lock. However, the Gtk functions that are called from this
-- different thread may not trigger any calls to the OS since this will
-- lead to a crash on Windows (the Win32 API can only be used from a single
-- thread). Since it is very hard to tell which function only interacts on
-- Gtk data structures and which function call actual OS functions, it
-- is best not to use this feature at all. A better way to perform updates
-- in the background is to spawn a Haskell thread and to perform the update
-- to Gtk widgets using 'postGUIAsync' or 'postGUISync'. These will execute
-- their arguments from the main loop, that is, from the OS thread of Gtk,
-- thereby ensuring that any Gtk and OS function can be called.
--
threadsEnter :: IO ()
threadsEnter :: IO ()
threadsEnter =
  IO ()
threadsEnter'_ IO () -> (() -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \()
res ->
  () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 213 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Release the global Gtk lock.
--
-- * The use of this function is not recommended. See 'threadsEnter'.
--
threadsLeave :: IO ()
threadsLeave :: IO ()
threadsLeave =
  IO ()
threadsLeave'_ IO () -> (() -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \()
res ->
  () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 219 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Inquire the number of events pending on the event queue
--
eventsPending :: IO Int
eventsPending :: IO Int
eventsPending = (CInt -> Int) -> IO CInt -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral IO CInt
gtk_events_pending
{-# LINE 224 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Run the Gtk+ main event loop.
--
mainGUI :: IO ()
mainGUI :: IO ()
mainGUI = IO ()
gtk_main
{-# LINE 229 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Inquire the main loop level.
--
-- * Callbacks that take more time to process can call 'mainIteration' to keep
-- the GUI responsive. Each time the main loop is restarted this way, the main
-- loop counter is increased. This function returns this counter.
--
mainLevel :: IO Int
mainLevel :: IO Int
mainLevel = (CUInt -> Int) -> IO CUInt -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> Int
forall a. Enum a => Int -> a
toEnum(Int -> Int) -> (CUInt -> Int) -> CUInt -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.CUInt -> Int
forall a. Enum a => a -> Int
fromEnum) IO CUInt
gtk_main_level
{-# LINE 238 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Exit the main event loop.
--
mainQuit :: IO ()
mainQuit :: IO ()
mainQuit = IO ()
gtk_main_quit
{-# LINE 243 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Process an event, block if necessary.
--
-- * Returns @True@ if 'mainQuit' was called while processing the event.
--
mainIteration :: IO Bool
mainIteration :: IO Bool
mainIteration = (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
gtk_main_iteration
{-# LINE 250 "./Graphics/UI/Gtk/General/General.chs" #-}

-- | Process a single event.
--
-- * Called with @True@, this function behaves as 'mainIteration' in that it
-- waits until an event is available for processing. It will return
-- immediately, if passed @False@.
--
-- * Returns @True@ if the 'mainQuit' was called while processing the event.
--
mainIterationDo :: Bool -> IO Bool
mainIterationDo :: Bool -> IO Bool
mainIterationDo Bool
blocking =
  (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
$ CInt -> IO CInt
gtk_main_iteration_do (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
blocking)

-- | Processes a single GDK event. This is public only to allow filtering of events between GDK and
-- GTK+. You will not usually need to call this function directly.
--
-- While you should not call this function directly, you might want to know how exactly events are
-- handled. So here is what this function does with the event:
--
-- 1. Compress enter\/leave notify events. If the event passed build an enter\/leave pair together with
-- the next event (peeked from GDK) both events are thrown away. This is to avoid a backlog of
-- (de-)highlighting widgets crossed by the pointer.
--
-- 2. Find the widget which got the event. If the widget can't be determined the event is thrown away
-- unless it belongs to a INCR transaction. In that case it is passed to
-- 'selectionIncrEvent'.
--
-- 3. Then the event is passed on a stack so you can query the currently handled event with
-- 'getCurrentEvent'.
--
-- 4. The event is sent to a widget. If a grab is active all events for widgets that are not in the
-- contained in the grab widget are sent to the latter with a few exceptions:
--
-- * Deletion and destruction events are still sent to the event widget for obvious reasons.
--
-- * Events which directly relate to the visual representation of the event widget.
--
-- * Leave events are delivered to the event widget if there was an enter event delivered to it
-- before without the paired leave event.
--
-- * Drag events are not redirected because it is unclear what the semantics of that would be.
--
-- Another point of interest might be that all key events are first passed through the key snooper
-- functions if there are any. Read the description of 'keySnooperInstall' if you need this
-- feature.
--
-- 5. After finishing the delivery the event is popped from the event stack.
mainDoEvent :: EventM t ()
mainDoEvent :: forall t. EventM t ()
mainDoEvent = do
  Ptr t
ptr <- ReaderT (Ptr t) IO (Ptr t)
forall r (m :: * -> *). MonadReader r m => m r
ask
  IO () -> EventM t ()
forall a. IO a -> ReaderT (Ptr t) IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> EventM t ()) -> IO () -> EventM t ()
forall a b. (a -> b) -> a -> b
$ Ptr () -> IO ()
gtk_main_do_event (Ptr t -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr t
ptr)


-- | Trigger destruction of object in case the mainloop at level @mainLevel@ is quit.
--
-- Removed in Gtk3.
quitAddDestroy :: ObjectClass obj
                 => Int -- ^ @mainLevel@ Level of the mainloop which shall trigger the destruction.
                 -> obj -- ^ @object@ Object to be destroyed.
                 -> IO ()
quitAddDestroy :: forall obj. ObjectClass obj => Int -> obj -> IO ()
quitAddDestroy Int
mainLevel obj
obj =
  (\CUInt
arg1 (Object ForeignPtr Object
arg2) -> ForeignPtr Object -> (Ptr Object -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Object
arg2 ((Ptr Object -> IO ()) -> IO ()) -> (Ptr Object -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Object
argPtr2 ->CUInt -> Ptr Object -> IO ()
gtk_quit_add_destroy CUInt
arg1 Ptr Object
argPtr2)
{-# LINE 312 "./Graphics/UI/Gtk/General/General.chs" #-}
     (fromIntegral mainLevel)
     (obj -> Object
forall o. ObjectClass o => o -> Object
toObject obj
obj)

-- | Registers a function to be called when an instance of the mainloop is left.
--
-- Removed in Gtk3.
quitAdd :: Int -- ^ @mainLevel@ Level at which termination the function shall be called. You can pass 0 here to have the function run at the current mainloop.
        -> (IO Bool) -- ^ @function@ The function to call. This should return 'False' to be removed from the list of quit handlers. Otherwise the function might be called again.
        -> IO Int -- ^ returns A handle for this quit handler (you need this for 'quitRemove')
quitAdd :: Int -> IO Bool -> IO Int
quitAdd Int
mainLevel IO Bool
func = do
  GtkFunction
funcPtr <- (Ptr () -> IO CInt) -> IO GtkFunction
mkGtkFunction ((Ptr () -> IO CInt) -> IO GtkFunction)
-> (Ptr () -> IO CInt) -> IO GtkFunction
forall a b. (a -> b) -> a -> b
$ \ Ptr ()
_ ->
    (Bool -> CInt) -> IO Bool -> IO CInt
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Bool -> CInt
forall a. Num a => Bool -> a
fromBool IO Bool
func
  (CUInt -> Int) -> IO CUInt -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CUInt -> IO Int) -> IO CUInt -> IO Int
forall a b. (a -> b) -> a -> b
$
            CUInt -> GtkFunction -> Ptr () -> IO CUInt
gtk_quit_add
{-# LINE 326 "./Graphics/UI/Gtk/General/General.chs" #-}
              (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
mainLevel)
              GtkFunction
funcPtr
              Ptr ()
forall a. Ptr a
nullPtr

type GtkFunction = FunPtr (((Ptr ()) -> (IO CInt)))
{-# LINE 331 "./Graphics/UI/Gtk/General/General.chs" #-}

foreign import ccall "wrapper" mkGtkFunction ::
  (Ptr () -> IO (CInt)) -> IO GtkFunction

-- | Removes a quit handler by its identifier.
--
-- Removed in Gtk3.
quitRemove :: Int -- ^ @quitHandlerId@ Identifier for the handler returned when installing it.
           -> IO ()
quitRemove :: Int -> IO ()
quitRemove Int
quitHandlerId =
  CUInt -> IO ()
gtk_quit_remove (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
quitHandlerId)


-- | add a grab widget
--
grabAdd :: WidgetClass wd => wd -> IO ()
grabAdd :: forall wd. WidgetClass wd => wd -> IO ()
grabAdd = (\(Widget ForeignPtr Widget
arg1) -> ForeignPtr Widget -> (Ptr Widget -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Widget
arg1 ((Ptr Widget -> IO ()) -> IO ()) -> (Ptr Widget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
argPtr1 ->Ptr Widget -> IO ()
gtk_grab_add Ptr Widget
argPtr1) (Widget -> IO ()) -> (wd -> Widget) -> wd -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. wd -> Widget
forall o. WidgetClass o => o -> Widget
toWidget

-- | inquire current grab widget
--
grabGetCurrent :: IO (Maybe Widget)
grabGetCurrent :: IO (Maybe Widget)
grabGetCurrent = do
  Ptr Widget
wPtr <- IO (Ptr Widget)
gtk_grab_get_current
{-# LINE 354 "./Graphics/UI/Gtk/General/General.chs" #-}
  if (wPtr==nullPtr) then return Nothing else
    liftM Just $ makeNewObject mkWidget (return wPtr)

-- | remove a grab widget
--
grabRemove :: WidgetClass w => w -> IO ()
grabRemove :: forall wd. WidgetClass wd => wd -> IO ()
grabRemove = (\(Widget ForeignPtr Widget
arg1) -> ForeignPtr Widget -> (Ptr Widget -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Widget
arg1 ((Ptr Widget -> IO ()) -> IO ()) -> (Ptr Widget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
argPtr1 ->Ptr Widget -> IO ()
gtk_grab_remove Ptr Widget
argPtr1) (Widget -> IO ()) -> (w -> Widget) -> w -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w -> Widget
forall o. WidgetClass o => o -> Widget
toWidget

-- | Sets a function to be called at regular intervals, with the default
-- priority 'priorityDefault'. The function is called repeatedly until it
-- returns @False@, after which point the timeout function will not be called
-- again. The first call to the function will be at the end of the first interval.
--
-- Note that timeout functions may be delayed, due to the processing of other
-- event sources. Thus they should not be relied on for precise timing. After
-- each call to the timeout function, the time of the next timeout is
-- recalculated based on the current time and the given interval (it does not
-- try to 'catch up' time lost in delays).
--
-- This function differs from 'ML.timeoutAdd' in that the action will
-- be executed within the global Gtk+ lock. It is therefore possible to
-- call Gtk+ functions from the action.
--
timeoutAdd :: IO Bool -> Int -> IO HandlerId
timeoutAdd :: IO Bool -> Int -> IO CUInt
timeoutAdd IO Bool
fun Int
msec = IO Bool -> Int -> Int -> IO CUInt
timeoutAddFull IO Bool
fun Int
priorityDefault Int
msec

-- | Sets a function to be called at regular intervals, with the given
-- priority. The function is called repeatedly until it returns @False@, after
-- which point the timeout function will not be called again. The first call
-- to the function will be at the end of the first interval.
--
-- Note that timeout functions may be delayed, due to the processing of other
-- event sources. Thus they should not be relied on for precise timing. After
-- each call to the timeout function, the time of the next timeout is
-- recalculated based on the current time and the given interval (it does not
-- try to 'catch up' time lost in delays).
--
-- This function differs from 'ML.timeoutAddFull' in that the action will
-- be executed within the global Gtk+ lock. It is therefore possible to
-- call Gtk+ functions from the action.
--
timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId
timeoutAddFull :: IO Bool -> Int -> Int -> IO CUInt
timeoutAddFull IO Bool
fun Int
pri Int
msec =
  IO Bool -> Int -> Int -> IO CUInt
ML.timeoutAddFull (IO ()
threadsEnter IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO Bool
fun IO Bool -> (Bool -> IO Bool) -> IO Bool
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
r -> IO ()
threadsLeave IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
r)
                    Int
pri Int
msec

-- | Add a callback that is called whenever the system is idle.
--
-- * A priority can be specified via an integer. This should usually be
-- 'priorityDefaultIdle'.
--
-- * If the function returns @False@ it will be removed.
--
-- This function differs from 'ML.idleAdd' in that the action will
-- be executed within the global Gtk+ lock. It is therefore possible to
-- call Gtk+ functions from the action.
--
idleAdd :: IO Bool -> Priority -> IO HandlerId
idleAdd :: IO Bool -> Int -> IO CUInt
idleAdd IO Bool
fun Int
pri =
  IO Bool -> Int -> IO CUInt
ML.idleAdd (IO ()
threadsEnter IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO Bool
fun IO Bool -> (Bool -> IO Bool) -> IO Bool
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
r -> IO ()
threadsLeave IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
r) Int
pri

type FD = Int

-- | Adds the file descriptor into the main event loop with the given priority.
--
-- This function differs from 'ML.inputAdd' in that the action will
-- be executed within the global Gtk+ lock. It is therefore possible to
-- call Gtk+ functions from the action.
--
inputAdd ::
    FD -- ^ a file descriptor
 -> [IOCondition] -- ^ the condition to watch for
 -> Priority -- ^ the priority of the event source
 -> IO Bool -- ^ the function to call when the condition is satisfied.
                  -- The function should return False if the event source
                  -- should be removed.
 -> IO HandlerId -- ^ the event source id
inputAdd :: Int -> [IOCondition] -> Int -> IO Bool -> IO CUInt
inputAdd Int
fd [IOCondition]
conds Int
pri IO Bool
fun =
  Int -> [IOCondition] -> Int -> IO Bool -> IO CUInt
ML.inputAdd Int
fd [IOCondition]
conds Int
pri (IO ()
threadsEnter IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO Bool
fun IO Bool -> (Bool -> IO Bool) -> IO Bool
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
r -> IO ()
threadsLeave IO () -> IO Bool -> IO Bool
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
r)

foreign import ccall unsafe "gtk_init_check"
  gtk_init_check :: ((Ptr CInt) -> ((Ptr (Ptr (Ptr CChar))) -> (IO CInt)))

foreign import ccall safe "gdk_threads_enter"
  threadsEnter'_ :: (IO ())

foreign import ccall unsafe "gdk_threads_leave"
  threadsLeave'_ :: (IO ())

foreign import ccall safe "gtk_events_pending"
  gtk_events_pending :: (IO CInt)

foreign import ccall safe "gtk_main"
  gtk_main :: (IO ())

foreign import ccall unsafe "gtk_main_level"
  gtk_main_level :: (IO CUInt)

foreign import ccall safe "gtk_main_quit"
  gtk_main_quit :: (IO ())

foreign import ccall safe "gtk_main_iteration"
  gtk_main_iteration :: (IO CInt)

foreign import ccall safe "gtk_main_iteration_do"
  gtk_main_iteration_do :: (CInt -> (IO CInt))

foreign import ccall safe "gtk_main_do_event"
  gtk_main_do_event :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "gtk_quit_add_destroy"
  gtk_quit_add_destroy :: (CUInt -> ((Ptr Object) -> (IO ())))

foreign import ccall safe "gtk_quit_add"
  gtk_quit_add :: (CUInt -> ((FunPtr ((Ptr ()) -> (IO CInt))) -> ((Ptr ()) -> (IO CUInt))))

foreign import ccall safe "gtk_quit_remove"
  gtk_quit_remove :: (CUInt -> (IO ()))

foreign import ccall safe "gtk_grab_add"
  gtk_grab_add :: ((Ptr Widget) -> (IO ()))

foreign import ccall safe "gtk_grab_get_current"
  gtk_grab_get_current :: (IO (Ptr Widget))

foreign import ccall safe "gtk_grab_remove"
  gtk_grab_remove :: ((Ptr Widget) -> (IO ()))