{-# LINE 2 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
-- -*-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
-- @


-- * Types
  RecentManager,
  RecentManagerClass,
  castToRecentManager,
  toRecentManager,

-- * Constructors
  recentManagerNew,

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

-- * Attributes
  recentManagerFilename,
  recentManagerLimit,
  recentManagerSize,

-- * Signals
  recentManagerChanged,

  ) where

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.GObject (Quark, quarkFromString)
import System.Glib.GError (GErrorDomain, GErrorClass(..), propagateGError, checkGError)
import Graphics.UI.Gtk.Recent.RecentInfo (RecentInfo, mkRecentInfo)
import Graphics.UI.Gtk.Types
{-# LINE 103 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
import Graphics.UI.Gtk.Signals
{-# LINE 104 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}


{-# LINE 106 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}



--------------------
-- 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 $
  gtk_recent_manager_new
{-# LINE 123 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}

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

-- | Gets a unique instance of 'RecentManager'.
--
-- * Available since Gtk+ version 2.10
--
recentManagerGetDefault :: IO RecentManager -- ^ returns A unique 'RecentManager'.
recentManagerGetDefault =
  makeNewGObject mkRecentManager $
  gtk_recent_manager_get_default
{-# LINE 135 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}

-- | 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 => 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 ->
  (\(RecentManager arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_add_item argPtr1 arg2)
{-# LINE 157 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
    (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 => 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 ->
                       (\(RecentManager arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_remove_item argPtr1 arg2 arg3)
{-# LINE 176 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
                            (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 => self
 -> String -- ^ @uri@ - a URI
 -> IO RecentInfo -- ^ returns a 'RecentInfo'
                          -- structure containing information about the
                          -- resource pointed by @uri@, or {@((void *)0)@, 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 <- (\(RecentManager arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_lookup_item argPtr1 arg2 arg3)
{-# LINE 200 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
           (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 => self
 -> String -- ^ @uri@ - a URI
 -> IO Bool -- ^ returns @True@ if the resource was found, @False@ otherwise.
recentManagerHasItem self uri =
  liftM toBool $
  withUTFString uri $ \uriPtr ->
  (\(RecentManager arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_has_item argPtr1 arg2)
{-# LINE 218 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
    (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 => 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 ->
                    (\(RecentManager arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_move_item argPtr1 arg2 arg3 arg4)
{-# LINE 239 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
                         (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 <- (\(RecentManager arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_get_items argPtr1)
{-# LINE 255 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
            (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 ->
  (\(RecentManager arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_manager_purge_items argPtr1 arg2)
{-# LINE 271 "./Graphics/UI/Gtk/Recent/RecentManager.chs" #-}
    (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 => 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")

foreign import ccall safe "gtk_recent_manager_new"
  gtk_recent_manager_new :: (IO (Ptr RecentManager))

foreign import ccall safe "gtk_recent_manager_get_default"
  gtk_recent_manager_get_default :: (IO (Ptr RecentManager))

foreign import ccall safe "gtk_recent_manager_add_item"
  gtk_recent_manager_add_item :: ((Ptr RecentManager) -> ((Ptr CChar) -> (IO CInt)))

foreign import ccall safe "gtk_recent_manager_remove_item"
  gtk_recent_manager_remove_item :: ((Ptr RecentManager) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))

foreign import ccall unsafe "gtk_recent_manager_lookup_item"
  gtk_recent_manager_lookup_item :: ((Ptr RecentManager) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr RecentInfo)))))

foreign import ccall safe "gtk_recent_manager_has_item"
  gtk_recent_manager_has_item :: ((Ptr RecentManager) -> ((Ptr CChar) -> (IO CInt)))

foreign import ccall safe "gtk_recent_manager_move_item"
  gtk_recent_manager_move_item :: ((Ptr RecentManager) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt)))))

foreign import ccall safe "gtk_recent_manager_get_items"
  gtk_recent_manager_get_items :: ((Ptr RecentManager) -> (IO (Ptr ())))

foreign import ccall safe "gtk_recent_manager_purge_items"
  gtk_recent_manager_purge_items :: ((Ptr RecentManager) -> ((Ptr (Ptr ())) -> (IO CInt)))