File: MainLoop.chs

package info (click to toggle)
haskell-glib 0.13.11.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 260 kB
  • sloc: haskell: 321; ansic: 224; makefile: 3
file content (348 lines) | stat: -rw-r--r-- 11,750 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) General
--
--  Author : Axel Simon, Manuel M. T. Chakravarty, Duncan Coutts
--
--  Created: 11 October 2005
--
--  Copyright (C) 2000..2005 Axel Simon, Manuel M. T. Chakravarty, Duncan Coutts
--
--  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)
--
-- main event loop, and events
--
module System.Glib.MainLoop (
  HandlerId,
  timeoutAdd,
  timeoutAddFull,
  timeoutRemove,
  idleAdd,
  idleRemove,
  IOCondition(..),
  inputAdd,
  inputRemove,
  Priority,
  priorityLow,
  priorityDefaultIdle,
  priorityHighIdle,
  priorityDefault,
  priorityHigh,
  MainLoop,
  mainLoopNew,
  mainLoopRun,
  mainLoopQuit,
  mainLoopIsRunning,
  MainContext,
  mainContextNew,
  mainContextDefault,
  mainContextIteration,
  mainContextFindSourceById,
  Source(..),
  sourceAttach,
  sourceSetPriority,
  sourceGetPriority,
  sourceDestroy,
#if GLIB_CHECK_VERSION(2,12,0)
  sourceIsDestroyed
#endif
  ) where

import Control.Monad    (liftM)

import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GObject      (DestroyNotify, destroyFunPtr)

{#context lib="glib" prefix ="g"#}

{#pointer SourceFunc#}

foreign import ccall "wrapper" mkSourceFunc :: (Ptr () -> IO {#type gint#}) -> IO SourceFunc

type HandlerId = {#type guint#}

-- Turn a function into a function pointer and a destructor pointer.
--
makeCallback :: IO {#type gint#} -> IO (SourceFunc, DestroyNotify)
makeCallback fun = do
  funPtr <- mkSourceFunc (const fun)
  return (funPtr, destroyFunPtr)

-- | 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).
--
timeoutAdd :: IO Bool -> Int -> IO HandlerId
timeoutAdd fun msec = timeoutAddFull fun priorityDefault 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).
--
timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId
timeoutAddFull fun pri msec = do
  (funPtr, dPtr) <- makeCallback (liftM fromBool fun)
  {#call unsafe g_timeout_add_full#}
    (fromIntegral pri)
    (fromIntegral msec)
    funPtr
    (castFunPtrToPtr funPtr)
    dPtr

-- | Remove a previously added timeout handler by its 'HandlerId'.
--
timeoutRemove :: HandlerId -> IO ()
timeoutRemove id = {#call source_remove#} id >> return ()

-- | 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.
--
idleAdd :: IO Bool -> Priority -> IO HandlerId
idleAdd fun pri = do
  (funPtr, dPtr) <- makeCallback (liftM fromBool fun)
  {#call unsafe idle_add_full#} (fromIntegral pri) funPtr
    (castFunPtrToPtr funPtr) dPtr

-- | Remove a previously added idle handler by its 'HandlerId'.
--
idleRemove :: HandlerId -> IO ()
idleRemove id = {#call source_remove#} id >> return ()

-- | Flags representing a condition to watch for on a file descriptor.
--
-- [@IOIn@]             There is data to read.
-- [@IOOut@]            Data can be written (without blocking).
-- [@IOPri@]            There is urgent data to read.
-- [@IOErr@]            Error condition.
-- [@IOHup@]            Hung up (the connection has been broken, usually for
--                      pipes and sockets).
-- [@IOInvalid@]        Invalid request. The file descriptor is not open.
--
{# enum IOCondition {
          G_IO_IN   as IOIn,
          G_IO_OUT  as IOOut,
          G_IO_PRI  as IOPri,
          G_IO_ERR  as IOErr,
          G_IO_HUP  as IOHup,
          G_IO_NVAL as IOInvalid
        } deriving (Eq, Bounded) #}
instance Flags IOCondition

{#pointer *IOChannel newtype#}
{#pointer IOFunc#}

foreign import ccall "wrapper" mkIOFunc :: (Ptr IOChannel -> CInt -> Ptr () -> IO {#type gboolean#}) -> IO IOFunc

type FD = Int

-- | Adds the file descriptor into the main event loop with the given priority.
--
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 fd conds pri fun = do
  funPtr <- mkIOFunc (\_ _ _ -> liftM fromBool fun)
  channel <- {#call unsafe g_io_channel_unix_new #} (fromIntegral fd)
  {#call unsafe g_io_add_watch_full#}
    (IOChannel channel)
    (fromIntegral pri)
    ((fromIntegral . fromFlags) conds)
    funPtr
    (castFunPtrToPtr funPtr)
    destroyFunPtr

inputRemove :: HandlerId -> IO ()
inputRemove id = {#call source_remove#} id >> return ()

-- Standard priorities

#define G_PRIORITY_HIGH            -100
#define G_PRIORITY_DEFAULT          0
#define G_PRIORITY_HIGH_IDLE        100
#define G_PRIORITY_DEFAULT_IDLE     200
#define G_PRIORITY_LOW              300

-- | Priorities for installing callbacks.
--
type Priority = Int

priorityHigh :: Int
priorityHigh = G_PRIORITY_HIGH

priorityDefault :: Int
priorityDefault = G_PRIORITY_DEFAULT

priorityHighIdle :: Int
priorityHighIdle = G_PRIORITY_HIGH_IDLE

priorityDefaultIdle :: Int
priorityDefaultIdle = G_PRIORITY_DEFAULT_IDLE

priorityLow :: Int
priorityLow = G_PRIORITY_LOW

-- | A main event loop abstraction.
{# pointer *GMainLoop as MainLoop foreign newtype #}

-- | An opaque datatype representing a set of sources to be handled in
--   a main loop.
{# pointer *GMainContext as MainContext foreign newtype #}

-- | Create a new 'MainLoop'.
mainLoopNew :: Maybe MainContext -- ^ @context@ - the context to use, or 'Nothing' to use the default context
            -> Bool              -- ^ @isRunning@ - 'True' to indicate that the loop is running; 'False' otherwise
            -> IO MainLoop       -- ^ the new 'MainLoop'
mainLoopNew context isRunning =
    do let context' = maybe (MainContext nullForeignPtr) id context
       loopPtr <- {# call main_loop_new #} context' $ fromBool isRunning
       liftM MainLoop $ newForeignPtr loopPtr mainLoopFinalizer
foreign import ccall unsafe "&g_main_loop_unref"
    mainLoopFinalizer :: FunPtr (Ptr MainLoop -> IO ())

-- | Runs a main loop until 'mainLoopQuit' is called on the
--   loop. If this is called for the thread of the loop's
--   'MainContext', it will process events from the loop, otherwise it
--   will simply wait.
mainLoopRun :: MainLoop
            -> IO ()
mainLoopRun loop =
    {# call main_loop_run #} loop

-- | Stops a 'MainLoop' from running. Any calls to mainLoopRun for the
--   loop will return.
mainLoopQuit :: MainLoop
             -> IO ()
mainLoopQuit loop =
    {# call main_loop_quit #} loop

-- | Checks to see if the main loop is currently being run via mainLoopRun.
mainLoopIsRunning :: MainLoop
                  -> IO Bool
mainLoopIsRunning loop =
    liftM toBool $ {# call main_loop_is_running #} loop

-- | Gets a 'MainLoop's context.
mainLoopGetContext :: MainLoop
                   -> MainContext
mainLoopGetContext loop =
    MainContext $ unsafePerformIO $
        {# call main_loop_get_context #} loop >>=
            flip newForeignPtr mainContextFinalizer

foreign import ccall unsafe "&g_main_context_unref"
    mainContextFinalizer :: FunPtr (Ptr MainContext -> IO ())

-- | Creates a new 'MainContext'.
mainContextNew :: IO MainContext
mainContextNew =
    newContextMarshal {# call main_context_new #}

-- | The default 'MainContext'. This is the main context used for main
--   loop functions when a main loop is not explicitly specified.
mainContextDefault :: MainContext
mainContextDefault =
    unsafePerformIO $ newContextMarshal {# call main_context_default #}

newContextMarshal action =
    do ptr <- action
       liftM MainContext $ newForeignPtr ptr mainContextFinalizer

-- | Runs a single iteration for the given main loop. This involves
--   checking to see if any event sources are ready to be processed,
--   then if no events sources are ready and @mayBlock@ is 'True',
--   waiting for a source to become ready, then dispatching the
--   highest priority events sources that are ready. Note that even
--   when @mayBlock@ is 'True', it is still possible for
--   'mainContextIteration' to return 'False', since the the wait
--   may be interrupted for other reasons than an event source
--   becoming ready.
mainContextIteration :: MainContext
                     -> Bool
                     -> IO Bool
mainContextIteration context mayBlock =
    liftM toBool $ {# call main_context_iteration #} context (fromBool mayBlock)

mainContextFindSourceById :: MainContext
                          -> HandlerId
                          -> IO Source
mainContextFindSourceById context id =
    {# call main_context_find_source_by_id #} context (fromIntegral id) >>= newSource . castPtr

{# pointer *GSource as Source foreign newtype #}
newSource :: Ptr Source
          -> IO Source
newSource sourcePtr =
    liftM Source $ newForeignPtr sourcePtr sourceFinalizer
foreign import ccall unsafe "&g_source_unref"
    sourceFinalizer :: FunPtr (Ptr Source -> IO ())

sourceAttach :: Source
             -> MainContext
             -> IO HandlerId
sourceAttach source context =
    liftM fromIntegral $ {# call source_attach #} source context

sourceSetPriority :: Source
                  -> Priority
                  -> IO ()
sourceSetPriority source priority =
    {# call source_set_priority #} source $ fromIntegral priority

sourceGetPriority :: Source
                  -> IO Priority
sourceGetPriority source =
    liftM fromIntegral $ {# call source_get_priority #} source

sourceDestroy :: Source
              -> IO ()
sourceDestroy source =
    {# call source_destroy #} source

#if GLIB_CHECK_VERSION(2,12,0)
sourceIsDestroyed :: Source
                  -> IO Bool
sourceIsDestroyed source =
    liftM toBool $ {# call source_is_destroyed #} source
#endif

sourceRemove :: HandlerId
             -> IO Bool
sourceRemove tag =
    liftM toBool $ {# call source_remove #} $ fromIntegral tag