File: RecentManager.chs

package info (click to toggle)
haskell-gtk 0.15.7-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 3,964 kB
  • sloc: haskell: 3,346; ansic: 826; makefile: 161
file content (320 lines) | stat: -rw-r--r-- 10,248 bytes parent folder | download | duplicates (8)
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
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Widget RecentManager
--
--  Author : Andy Stewart
--
--  Created: 27 Mar 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 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)
--
-- Managing Recently Used Files
--
-- * Module available since Gtk+ version 2.10
--
-- TODO:
--      GtkRecentData
--      gtk_recent_manager_add_full
--
module Graphics.UI.Gtk.Recent.RecentManager (

-- * Detail
--
-- | 'RecentManager' provides a facility for adding, removing and looking up
-- recently used files. Each recently used file is identified by its URI, and
-- has meta-data associated to it, like the names and command lines of the
-- applications that have registered it, the number of time each application
-- has registered the same file, the mime type of the file and whether the file
-- should be displayed only by the applications that have registered it.
--
-- The 'RecentManager' acts like a database of all the recently used files.
-- You can create new 'RecentManager' objects, but it is more efficient to use
-- the standard recent manager for the 'Screen' so that informations about the
-- recently used files is shared with other people using them. In case the
-- default screen is being used, adding a new recently used file is as simple
-- as:
--
-- Recently used files are supported since Gtk+ 2.10.

-- * Class Hierarchy
--
-- |
-- @
-- |  'GObject'
-- |   +----RecentManager
-- @

#if GTK_CHECK_VERSION(2,10,0)
-- * Types
  RecentManager,
  RecentManagerClass,
  castToRecentManager,
  toRecentManager,

-- * Constructors
  recentManagerNew,

-- * Methods
  recentManagerGetDefault,
  recentManagerAddItem,
  recentManagerRemoveItem,
  recentManagerLookupItem,
  recentManagerHasItem,
  recentManagerMoveItem,
  recentManagerGetItems,
  recentManagerPurgeItems,

-- * Attributes
  recentManagerFilename,
  recentManagerLimit,
  recentManagerSize,

-- * Signals
  recentManagerChanged,
#endif
  ) where

#if GTK_CHECK_VERSION(2,10,0)

import Control.Monad    (liftM)

import System.Glib.FFI
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GList
import System.Glib.UTFString
import System.Glib.GError   (propagateGError, checkGError)
{#import Graphics.UI.Gtk.Recent.RecentInfo#} (RecentInfo, mkRecentInfo)
{#import Graphics.UI.Gtk.Types#}
{#import Graphics.UI.Gtk.Signals#}

{# context lib="gtk" prefix="gtk" #}

--------------------
-- Constructors

-- | Creates a new recent manager object. Recent manager objects are used to
-- handle the list of recently used resources. A 'RecentManager' object
-- monitors the recently used resources list, and emits the \"changed\" signal
-- each time something inside the list changes.
--
-- * Available since Gtk+ version 2.10
--
recentManagerNew :: IO RecentManager
recentManagerNew =
  wrapNewGObject mkRecentManager $
  {# call gtk_recent_manager_new #}

--------------------
-- Methods

-- | Gets a unique instance of 'RecentManager'.
--
-- * Available since Gtk+ version 2.10
--
recentManagerGetDefault :: IO RecentManager -- ^ returns A unique 'RecentManager'.
recentManagerGetDefault =
  makeNewGObject mkRecentManager $
  {# call gtk_recent_manager_get_default #}

-- | Adds a new resource, pointed by @uri@, into the recently used resources
-- list.
--
-- This function automatically retrieves some of the needed metadata and
-- setting other metadata to common default values; it then feeds the data to
-- 'recentManagerAddFull'.
--
-- See 'recentManagerAddFull' if you want to explicitly define the metadata
-- for the resource pointed by @uri@.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerAddItem :: (RecentManagerClass self, GlibString string) => self
 -> string  -- ^ @uri@ - a valid URI
 -> IO Bool -- ^ returns @True@ if the new item was successfully added to the
            -- recently used resources list
recentManagerAddItem self uri =
  liftM toBool $
  withUTFString uri $ \uriPtr ->
  {# call gtk_recent_manager_add_item #}
    (toRecentManager self)
    uriPtr

-- | Removes a resource pointed by @uri@ from the recently used resources list
-- handled by a recent manager.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerRemoveItem :: (RecentManagerClass self, GlibString string) => self
 -> string  -- ^ @uri@ - the URI of the item you wish to remove
 -> IO Bool -- ^ returns @True@ if the item pointed by @uri@ has been
            -- successfully removed by the recently used resources list, and
            -- @False@ otherwise.
recentManagerRemoveItem self uri =
      checkGError (\errorPtr ->
                       liftM toBool $
                       withUTFString uri $ \uriPtr ->
                       {# call gtk_recent_manager_remove_item #}
                            (toRecentManager self)
                            uriPtr
                            errorPtr)
                  (\_ -> return False)

-- | Searches for a URI inside the recently used resources list, and returns a
-- structure containing informations about the resource like its MIME type, or
-- its display name.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerLookupItem :: (RecentManagerClass self, GlibString string) => self
 -> string                -- ^ @uri@ - a URI
 -> IO RecentInfo -- ^ returns a 'RecentInfo'
                          -- structure containing information about the
                          -- resource pointed by @uri@, or {@NULL@, FIXME: this
                          -- should probably be converted to a Maybe data type}
                          -- if the URI was not registered in the recently used
                          -- resources list.
recentManagerLookupItem self uri =
  propagateGError $ \errorPtr ->
  withUTFString uri $ \uriPtr -> do
  result <- {# call unsafe gtk_recent_manager_lookup_item #}
           (toRecentManager self)
           uriPtr
           errorPtr
  mkRecentInfo result

-- | Checks whether there is a recently used resource registered with @uri@
-- inside the recent manager.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerHasItem :: (RecentManagerClass self, GlibString string) => self
 -> string  -- ^ @uri@ - a URI
 -> IO Bool -- ^ returns @True@ if the resource was found, @False@ otherwise.
recentManagerHasItem self uri =
  liftM toBool $
  withUTFString uri $ \uriPtr ->
  {# call gtk_recent_manager_has_item #}
    (toRecentManager self)
    uriPtr

-- | Changes the location of a recently used resource from @uri@ to @newUri@.
--
-- Please note that this function will not affect the resource pointed by
-- the URIs, but only the URI used in the recently used resources list.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerMoveItem :: (RecentManagerClass self, GlibString string) => self
 -> string  -- ^ @uri@ - the URI of a recently used resource
 -> string  -- ^ @newUri@ - the new URI of the recently used resource to remove the item pointed by @uri@ in the list
 -> IO Bool -- ^ returns @True@ on success.
recentManagerMoveItem self uri newUri =
  checkGError ( \errorPtr ->
                    liftM toBool $
                    withUTFString newUri $ \newUriPtr ->
                    withUTFString uri $ \uriPtr ->
                    {# call gtk_recent_manager_move_item #}
                         (toRecentManager self)
                         uriPtr
                         newUriPtr
                         errorPtr)
              (\_ -> return False)

-- | Gets the list of recently used resources.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerGetItems :: RecentManagerClass self => self
 -> IO [RecentInfo]                        -- ^ returns a list of newly allocated
                            -- 'RecentInfo' objects.
recentManagerGetItems self = do
  glist <- {# call gtk_recent_manager_get_items #}
            (toRecentManager self)
  list <- fromGList glist
  mapM mkRecentInfo list

-- | Purges every item from the recently used resources list.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerPurgeItems :: RecentManagerClass self => self
 -> IO Int -- ^ returns the number of items that have been removed from the
           -- recently used resources list.
recentManagerPurgeItems self =
  liftM fromIntegral $
  propagateGError $ \errorPtr ->
  {# call gtk_recent_manager_purge_items #}
    (toRecentManager self)
    errorPtr

--------------------
-- Attributes

-- | The full path to the file to be used to store and read the recently used resources list
--
-- Default value: 'Nothing'
--
-- * Available since Gtk+ version 2.10
--
recentManagerFilename :: (RecentManagerClass self, GlibString string) => ReadAttr self string
recentManagerFilename = readAttrFromStringProperty "filename"

-- | The maximum number of items to be returned by the 'recentManagerGetItems' function.
--
-- Allowed values: >= 'GMaxulong'
--
-- Default value: -1
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerLimit :: RecentManagerClass self => Attr self Int
recentManagerLimit = newAttrFromIntProperty "limit"

-- | The size of the recently used resources list.
--
-- Allowed values: >= 'GMaxulong'
--
-- Default value: 0
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerSize :: RecentManagerClass self => ReadAttr self Int
recentManagerSize = readAttrFromIntProperty "size"

--------------------
-- Signals

-- | Emitted when the current recently used resources manager changes its
-- contents.
--
--
-- * Available since Gtk+ version 2.10
--
recentManagerChanged :: RecentManagerClass self => Signal self (IO ())
recentManagerChanged = Signal (connect_NONE__NONE "changed")
#endif