{-# LINE 2 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) Widget IImageTool
--
-- Author : Andy Stewart
--
-- Created: 19 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 : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
module Graphics.UI.Gtk.ImageView.IImageTool (
-- * Details
-- | 'IImageTool' is an interface that defines how 'ImageView' interacts with objects that acts as
-- tools. 'ImageView' delegates many of its most important tasks (such as drawing) to its tool which
-- carries out all the hard work. The 'ImageView' package comes with two tools; 'ImageToolDragger'
-- and 'ImageToolSelector', but by implementing your own tool it is possible to extend 'ImageView' to
-- do stuff its author (thats me) didn't imagine.
--
-- 'ImageView' uses 'ImageToolDragger' by default, as that tool is he most generally useful
-- one. However, it is trivial to make it use another tool.

-- * Types
   IImageTool,
   IImageToolClass,

-- * Methods
   iimageToolPixbufChanged,
) where

import Control.Monad (liftM)
import Data.Maybe (fromMaybe)

import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.ImageView.Enums
import Graphics.UI.Gtk.Abstract.Widget (Rectangle(..))
import System.Glib.Attributes
import System.Glib.FFI
import System.Glib.UTFString

import Graphics.UI.Gtk.ImageView.Signals
{-# LINE 56 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}
import Graphics.UI.Gtk.ImageView.Types
{-# LINE 57 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}
import System.Glib.Properties
{-# LINE 58 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}


{-# LINE 60 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}

-- | Indiate to the tool that either a part of, or the whole pixbuf that the image view shows has
-- changed. This method is called by the view whenever its pixbuf or its tool changes. That is, when
-- any of the following methods are used:
--
-- * 'imageViewSetPixbuf'
--
-- If the @resetFit@ parameter is 'True', it means that a new pixbuf has been loaded into the view. rect
-- is a rectangle in image space coordinates that indicates which rectangular region of the pixbufs
-- pixels that is modified. If rect is 'Nothing', then all of the pixbuf has changed. See also
-- 'pixbufChanged'.
iimageToolPixbufChanged :: IImageToolClass tool => tool
                        -> Bool -- ^ @resetFit@ whether the view is resetting its fit mode or not
                        -> Maybe Rectangle -- ^ @rect@ rectangle containing the changed area or 'Nothing'
                        -> IO ()
iimageToolPixbufChanged tool resetFit rect =
  maybeWith with rect $ \rectPtr ->
  (\(IImageTool arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_iimage_tool_pixbuf_changed argPtr1 arg2 arg3)
{-# LINE 78 "./Graphics/UI/Gtk/ImageView/IImageTool.chs" #-}
    (toIImageTool tool)
    (fromBool resetFit)
    (castPtr rectPtr)

foreign import ccall safe "gtk_iimage_tool_pixbuf_changed"
  gtk_iimage_tool_pixbuf_changed :: ((Ptr IImageTool) -> (CInt -> ((Ptr ()) -> (IO ()))))