File: PixbufAnimation.chs

package info (click to toggle)
haskell-gtk 0.11.0-5
  • links: PTS, VCS
  • area: main
  • in suites: squeeze
  • size: 2,920 kB
  • ctags: 82
  • sloc: haskell: 1,929; ansic: 714; sh: 5; makefile: 3
file content (309 lines) | stat: -rw-r--r-- 13,123 bytes parent folder | download
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
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Pixbuf Animation
--
--  Author : Matthew Arsenault
--
--  Created: 14 November 2009
--
--  Copyright (C) 2009 Matthew Arsenault
--
--  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)
--
module Graphics.UI.Gtk.Gdk.PixbufAnimation (
-- * Class Hierarchy
-- |
-- @
-- |  'GObject'
-- |   +----'PixbufAnimation'
-- |        +----'PixbufSimpleAnim'
-- @

-- * Types
  PixbufAnimation,
  PixbufAnimationClass,
  castToPixbufAnimation, gTypePixbufAnimation,
  toPixbufAnimation,

  PixbufAnimationIter,
  PixbufAnimationIterClass,
  castToPixbufAnimationIter, gTypePixbufAnimationIter,
  toPixbufAnimationIter,

  PixbufSimpleAnim,
  PixbufSimpleAnimClass,
  castToPixbufSimpleAnim, gTypePixbufSimpleAnim,
  toPixbufSimpleAnim,

-- * Constructors
  pixbufAnimationNewFromFile,
#if GTK_CHECK_VERSION(2,8,0)
  pixbufSimpleAnimNew,
#endif

-- * Methods
  pixbufAnimationGetWidth,
  pixbufAnimationGetHeight,
  pixbufAnimationGetIter,
  pixbufAnimationIsStaticImage,
  pixbufAnimationGetStaticImage,
  pixbufAnimationIterAdvance,
  pixbufAnimationIterGetDelayTime,
  pixbufAnimationIterOnCurrentlyLoadingFrame,
  pixbufAnimationIterGetPixbuf,
#if GTK_CHECK_VERSION(2,8,0)
  pixbufSimpleAnimAddFrame,
#endif

#if GTK_CHECK_VERSION(2,18,0)
  pixbufSimpleAnimSetLoop,
  pixbufSimpleAnimGetLoop
#endif
  ) where

import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GDateTime
import System.Glib.GObject
{#import Graphics.UI.Gtk.Types#}
import System.Glib.GError	(GError(..), GErrorClass(..), GErrorDomain,
				propagateGError)
{# import Graphics.UI.Gtk.Gdk.Pixbuf #}

{# context prefix="gdk" #}


--CHECKME: Domain error doc, GFileError ???
-- | Creates a new animation by loading it from a file. The file
--   format is detected automatically. If the file's format does not
--   support multi-frame images, then an animation with a single frame
--   will be created. Possible errors are in the 'PixbufError' and
--   'GFileError' domains.
--
-- Any of several error conditions may occur: the file could not be
-- opened, there was no loader for the file's format, there was not
-- enough memory to allocate the image buffer, or the image file
-- contained invalid data.
--
-- * If an error occurs, the function will throw an exception that can
--   be caught using e.g. 'System.Glib.GError.catchGErrorJust' and one of the
--   error codes in 'PixbufError' or 'GFileError'
--
pixbufAnimationNewFromFile :: FilePath               -- ^ Name of file to load, in the GLib file name encoding
                           -> IO PixbufAnimation     -- ^ A newly-created animation
pixbufAnimationNewFromFile fname =
  constructNewGObject mkPixbufAnimation $
  propagateGError $ \errPtrPtr ->
     withUTFString fname $ \strPtr ->
#if defined (WIN32) && GTK_CHECK_VERSION(2,6,5)
     {#call unsafe pixbuf_animation_new_from_file_utf8#} strPtr errPtrPtr
#else
     {#call unsafe pixbuf_animation_new_from_file#} strPtr errPtrPtr
#endif

-- | Queries the width of the bounding box of a pixbuf animation.
pixbufAnimationGetWidth :: PixbufAnimation -- ^ An animation.
                        -> IO Int          -- ^ Width of the bounding box of the animation.
pixbufAnimationGetWidth self = liftM fromIntegral $ {#call unsafe pixbuf_animation_get_width#} self

-- | Queries the height of the bounding box of a pixbuf animation.
pixbufAnimationGetHeight :: PixbufAnimation  -- ^ An animation.
                         -> IO Int           -- ^ Height of the bounding box of the animation.
pixbufAnimationGetHeight self = liftM fromIntegral $ {#call unsafe pixbuf_animation_get_height#} self


-- | Get an iterator for displaying an animation. The iterator
--   provides the frames that should be displayed at a given time. The
--   start time would normally come from 'gGetCurrentTime', and marks
--   the beginning of animation playback. After creating an iterator,
--   you should immediately display the pixbuf returned by
--   'pixbufAnimationIterGetPixbuf'. Then, you should install a
--   timeout (with 'timeoutAdd') or by some other mechanism ensure
--   that you'll update the image after
--   'pixbufAnimationIterGetDelayTime' milliseconds. Each time the
--   image is updated, you should reinstall the timeout with the new,
--   possibly-changed delay time.
--
-- As a shortcut, if start_time is @Nothing@, the result of
-- 'gGetCurrentTime' will be used automatically.
--
-- To update the image (i.e. possibly change the result of
-- 'pixbufAnimationIterGetPixbuf' to a new frame of the animation),
-- call 'pixbufAnimationIterAdvance'.
--
--  If you're using 'PixbufLoader', in addition to updating the image
--  after the delay time, you should also update it whenever you
--  receive the area_updated signal and
--  'pixbufAnimationIterOnCurrentlyLoadingFrame' returns @True@. In
--  this case, the frame currently being fed into the loader has
--  received new data, so needs to be refreshed. The delay time for a
--  frame may also be modified after an area_updated signal, for
--  example if the delay time for a frame is encoded in the data after
--  the frame itself. So your timeout should be reinstalled after any
--  area_updated signal.
--
-- A delay time of -1 is possible, indicating "infinite."
--
pixbufAnimationGetIter :: PixbufAnimation            -- ^ a 'PixbufAnimation'
                       -> Maybe GTimeVal             -- ^ time when the animation starts playing
                       -> IO PixbufAnimationIter     -- ^ an iterator to move over the animation
pixbufAnimationGetIter self tv = maybeWith with tv $ \stPtr ->
                                 constructNewGObject mkPixbufAnimationIter $
                                   {#call unsafe pixbuf_animation_get_iter#} self (castPtr stPtr)



-- | If you load a file with 'pixbufAnimationNewFromFile' and it turns
--   out to be a plain, unanimated image, then this function will
--   return @True@. Use 'pixbufAnimationGetStaticImage' to retrieve
--   the image.
--
pixbufAnimationIsStaticImage :: PixbufAnimation
                             -> IO Bool          -- ^ TRUE if the "animation" was really just an image
pixbufAnimationIsStaticImage self = liftM toBool $ {#call unsafe pixbuf_animation_is_static_image#} self


-- | If an animation is really just a plain image (has only one
--   frame), this function returns that image. If the animation is an
--   animation, this function returns a reasonable thing to display as
--   a static unanimated image, which might be the first frame, or
--   something more sophisticated. If an animation hasn't loaded any
--   frames yet, this function will return @Nothing@.
--
pixbufAnimationGetStaticImage :: PixbufAnimation
                              -> IO (Maybe Pixbuf) -- ^ unanimated image representing the animation
pixbufAnimationGetStaticImage self =
  maybeNull (constructNewGObject mkPixbuf) $ {#call unsafe pixbuf_animation_get_static_image#} self



-- | Possibly advances an animation to a new frame. Chooses the frame
--   based on the start time passed to 'pixbufAnimationGetIter'.
--
-- current_time would normally come from 'gGetCurrentTime', and must
-- be greater than or equal to the time passed to
-- 'pixbufAnimationGetIter', and must increase or remain unchanged
-- each time 'pixbufAnimationIterGetPixbuf' is called. That is, you
-- can't go backward in time; animations only play forward.
--
--  As a shortcut, pass @Nothing@ for the current time and
-- 'gGetCurrentTime' will be invoked on your behalf. So you only need
-- to explicitly pass current_time if you're doing something odd like
-- playing the animation at double speed.
--
-- If this function returns @False@, there's no need to update the
-- animation display, assuming the display had been rendered prior to
-- advancing; if @True@, you need to call 'animationIterGetPixbuf' and
-- update the display with the new pixbuf.
--
pixbufAnimationIterAdvance :: PixbufAnimationIter  -- ^ A 'PixbufAnimationIter'
                           -> Maybe GTimeVal       -- ^ current time
                           -> IO Bool              -- ^ @True@ if the image may need updating
pixbufAnimationIterAdvance iter currentTime = liftM toBool $ maybeWith with currentTime $ \tvPtr ->
                                                {# call unsafe pixbuf_animation_iter_advance #} iter (castPtr tvPtr)


-- | Gets the number of milliseconds the current pixbuf should be
--   displayed, or -1 if the current pixbuf should be displayed
--   forever. 'timeoutAdd' conveniently takes a timeout in
--   milliseconds, so you can use a timeout to schedule the next
--   update.
--
pixbufAnimationIterGetDelayTime :: PixbufAnimationIter  -- ^ an animation iterator
                                -> IO Int               -- ^ delay time in milliseconds (thousandths of a second)
pixbufAnimationIterGetDelayTime self = liftM fromIntegral $
  {#call unsafe pixbuf_animation_iter_get_delay_time#} self


-- | Used to determine how to respond to the area_updated signal on
--   'PixbufLoader' when loading an animation. area_updated is emitted
--   for an area of the frame currently streaming in to the loader. So
--   if you're on the currently loading frame, you need to redraw the
--   screen for the updated area.
--
pixbufAnimationIterOnCurrentlyLoadingFrame :: PixbufAnimationIter
                                           -> IO Bool              -- ^ @True@ if the frame we're on is partially loaded, or the last frame
pixbufAnimationIterOnCurrentlyLoadingFrame iter = liftM toBool $
  {# call unsafe pixbuf_animation_iter_on_currently_loading_frame #} iter

--CHECKME: referencing, usage of constructNewGObject
-- | Gets the current pixbuf which should be displayed; the pixbuf will
-- be the same size as the animation itself
-- ('pixbufAnimationGetWidth', 'pixbufAnimationGetHeight'). This
-- pixbuf should be displayed for 'pixbufAnimationIterGetDelayTime'
-- milliseconds. The caller of this function does not own a reference
-- to the returned pixbuf; the returned pixbuf will become invalid
-- when the iterator advances to the next frame, which may happen
-- anytime you call 'pixbufAnimationIterAdvance'. Copy the pixbuf to
-- keep it (don't just add a reference), as it may get recycled as you
-- advance the iterator.
--
pixbufAnimationIterGetPixbuf :: PixbufAnimationIter -- ^ an animation iterator
                                -> IO Pixbuf        -- ^ the pixbuf to be displayed
pixbufAnimationIterGetPixbuf iter = constructNewGObject mkPixbuf $
   {# call unsafe pixbuf_animation_iter_get_pixbuf #} iter


#if GTK_CHECK_VERSION(2,8,0)
-- | Creates a new, empty animation.
--
-- * Available since Gtk+ version 2.8
--
pixbufSimpleAnimNew :: Int   -- ^ the width of the animation
                    -> Int   -- ^ the height of the animation
                    -> Float -- ^ the speed of the animation, in frames per second
                    -> IO PixbufSimpleAnim  -- ^ a newly allocated 'PixbufSimpleAnim'
pixbufSimpleAnimNew width height rate = constructNewGObject mkPixbufSimpleAnim $
  {#call unsafe pixbuf_simple_anim_new#} (fromIntegral width) (fromIntegral height) (realToFrac rate)


-- | Adds a new frame to animation. The pixbuf must have the
--   dimensions specified when the animation was constructed.
--
-- * Available since Gtk+ version 2.8
--
pixbufSimpleAnimAddFrame :: PixbufSimpleAnim   -- ^ a 'PixbufSimpleAnim'
                         -> Pixbuf             -- ^ the pixbuf to add
                         -> IO ()
pixbufSimpleAnimAddFrame psa pb = {#call unsafe pixbuf_simple_anim_add_frame#} psa pb

#endif

#if GTK_CHECK_VERSION(2,18,0)

-- | Sets whether animation should loop indefinitely when it reaches
--   the end.
--
-- * Available since Gtk+ version 2.18
--
pixbufSimpleAnimSetLoop :: PixbufSimpleAnim  -- ^ a 'PixbufSimpleAnim'
                           -> Bool           -- ^ whether to loop the animation
                           -> IO ()
pixbufSimpleAnimSetLoop animation loop = {#call unsafe pixbuf_simple_anim_set_loop#} animation (fromBool loop)


-- | Gets whether animation should loop indefinitely when it reaches
--   the end.
--
-- * Available since Gtk+ version 2.18
--
pixbufSimpleAnimGetLoop :: PixbufSimpleAnim  -- ^ a 'PixbufSimpleAnim'
                           -> IO Bool        -- ^ @True@ if the animation loops forever, @False@ otherwise
pixbufSimpleAnimGetLoop animation = liftM toBool $ {#call unsafe pixbuf_simple_anim_get_loop#} animation

#endif