{-# LINE 2 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) Widget Zooms
--
-- 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.Zooms (
-- * Details
-- | 'ImageView' uses a discrete amount of zoom factors for determining which zoom to set. Using these
-- functions, it is possible to retrieve information and manipulate a zoom factor.

-- * Methods
   zoomsGetZoomIn,
   zoomsGetZoomOut,
   zoomsGetMinZoom,
   zoomsGetMaxZoom,
   zoomsClampZoom,
) where

import Control.Monad (liftM)

import System.Glib.Attributes
import System.Glib.FFI
import System.Glib.UTFString


{-# LINE 46 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}

-- | Returns the zoom factor that is one step larger than the supplied zoom factor.
zoomsGetZoomIn :: Double -- ^ @zoom@ A zoom factor.
               -> IO Double -- ^ returns a zoom factor that is one step larger than the supplied one
zoomsGetZoomIn zoom =
  liftM realToFrac $
  gtk_zooms_get_zoom_in
{-# LINE 53 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}
    (realToFrac zoom)

-- | Returns the zoom factor that is one step smaller than the supplied zoom factor.
zoomsGetZoomOut :: Double -- ^ @zoom@ a zoom factor
                -> IO Double -- ^ returns a zoom factor that is one step smaller than the supplied one.
zoomsGetZoomOut zoom =
  liftM realToFrac $
  gtk_zooms_get_zoom_out
{-# LINE 61 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}
    (realToFrac zoom)

-- | Returns the minimum allowed zoom factor.
zoomsGetMinZoom :: IO Double -- ^ returns The minimal zoom factor.
zoomsGetMinZoom =
  liftM realToFrac $
  gtk_zooms_get_min_zoom
{-# LINE 68 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}

-- | Returns the maximum allowed zoom factor.
zoomsGetMaxZoom :: IO Double -- ^ returns The maximal zoom factor.
zoomsGetMaxZoom =
  liftM realToFrac $
  gtk_zooms_get_max_zoom
{-# LINE 74 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}

-- | Returns the zoom factor clamped to the minumum and maximum allowed value.
zoomsClampZoom :: Double -- ^ @zoom@ A zoom factor
               -> IO Double -- ^ returns The zoom factor clamped to the interval [min, max].
zoomsClampZoom zoom =
  liftM realToFrac $
  gtk_zooms_clamp_zoom
{-# LINE 81 "./Graphics/UI/Gtk/ImageView/Zooms.chs" #-}
    (realToFrac zoom)

foreign import ccall safe "gtk_zooms_get_zoom_in"
  gtk_zooms_get_zoom_in :: (CDouble -> (IO CDouble))

foreign import ccall safe "gtk_zooms_get_zoom_out"
  gtk_zooms_get_zoom_out :: (CDouble -> (IO CDouble))

foreign import ccall safe "gtk_zooms_get_min_zoom"
  gtk_zooms_get_min_zoom :: (IO CDouble)

foreign import ccall safe "gtk_zooms_get_max_zoom"
  gtk_zooms_get_max_zoom :: (IO CDouble)

foreign import ccall safe "gtk_zooms_clamp_zoom"
  gtk_zooms_clamp_zoom :: (CDouble -> (IO CDouble))