diffing dir...
Mon Aug 16 14:39:05 EDT 2010 Andy Stewart <laz...@gm...>
* Add new module Graphics.UI.Gtk.Display.Spinner
Ignore-this: 2e82291368e55411e0445e1e5c6aaf09
{
hunk ./gtk/Graphics/UI/Gtk.chs 81
+ module Graphics.UI.Gtk.Display.Spinner,
hunk ./gtk/Graphics/UI/Gtk.chs 270
+import Graphics.UI.Gtk.Display.Spinner
addfile ./gtk/Graphics/UI/Gtk/Display/Spinner.chs
hunk ./gtk/Graphics/UI/Gtk/Display/Spinner.chs 1
+{-# LANGUAGE CPP #-}
+-- -*-haskell-*-
+-- GIMP Toolkit (GTK) Widget Spinner
+--
+-- Author : Andy Stewart
+--
+-- Created: 17 Aug 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 : gtk...@li...
+-- Stability : provisional
+-- Portability : portable (depends on GHC)
+--
+-- Report messages of minor importance to the user
+--
+module Graphics.UI.Gtk.Display.Spinner (
+#if GTK_CHECK_VERSION(2,20,0)
+-- * Detail
+-- [_$_]
+-- | A 'Spinner' widget displays an icon-size spinning animation. It is often used as an alternative to
+-- a 'ProgressBar' for displaying indefinite activity, instead of actual progress.
+-- [_$_]
+-- To start the animation, use 'spinnerStart'.
hunk ./gtk/Graphics/UI/Gtk/Display/Spinner.chs 37
+-- * Types
+ Spinner,
+ SpinnerClass,
+
+-- * Constructors
+ spinnerNew,
+
+-- * Methods
+ spinnerStart,
+ spinnerStop,
+ [_$_]
+-- * Attributes [_$_]
+ spinnerActive,
+#endif
+) where
+
+import Control.Monad (liftM)
+
+import System.Glib.FFI
+import System.Glib.UTFString
+import System.Glib.Attributes
+import System.Glib.Properties
+import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
+{#import Graphics.UI.Gtk.Types#}
+{#import Graphics.UI.Gtk.Signals#}
+
+{# context lib="gtk" prefix="gtk" #}
+
+#if GTK_CHECK_VERSION(2,20,0)
+--------------------
+-- Constructors
+
+-- | Returns a new spinner widget. Not yet started.
+spinnerNew :: IO Spinner
+spinnerNew = [_$_]
+ makeNewObject mkSpinner $
+ liftM (castPtr :: Ptr Widget -> Ptr Spinner) $
+ {# call unsafe spinner_new #}
+
+--------------------
+-- Methods
+
+-- | Starts the animation of the spinner.
+spinnerStart :: SpinnerClass spinner => spinner -> IO ()
+spinnerStart spinner =
+ {#call spinner_start #}
+ (toSpinner spinner)
+
+-- | Stops the animation of the spinner.
+spinnerStop :: SpinnerClass spinner => spinner -> IO ()
+spinnerStop spinner =
+ {#call spinner_stop #}
+ (toSpinner spinner)
+
+--------------------
+-- Attributes
+
+-- | Whether the spinner is active.
+-- [_$_]
+-- Default value: 'False'
+spinnerActive :: SpinnerClass spinner => Attr spinner Bool
+spinnerActive = newAttrFromBoolProperty "active"
+#endif
hunk ./gtk/gtk.cabal 166
+ Graphics.UI.Gtk.Display.Spinner
hunk ./gtk/hierarchy.list 147
+ GtkSpinner if gtk-2.20
}
|