{-# LINE 2 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
-- -*-haskell-*-
-----------------------------------------------------------------------------
-- Module : Graphics.UI.Gtk.WebKit.CacheModel
-- Author : Andy Stewart
-- Copyright : (c) 2010 Andy Stewart <lazycat.manatee@gmail.com>
--
-- 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)
--
-- Object used to communicate with the application when downloading
-----------------------------------------------------------------------------

module Graphics.UI.Gtk.WebKit.CacheModel (

-- * Enums
   CacheModel (..),

-- * Methods
  getCacheModel,
  setCacheModel,

) where

import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GError
import Graphics.UI.Gtk.Gdk.Events

import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
{-# LINE 49 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
import Graphics.UI.Gtk.WebKit.Signals
{-# LINE 50 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
import Graphics.UI.Gtk.WebKit.Internal
{-# LINE 51 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
import System.Glib.GObject
{-# LINE 52 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
import Graphics.UI.Gtk.General.Selection ( TargetList )
import Graphics.UI.Gtk.MenuComboToolbar.Menu
{-# LINE 54 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}
import Graphics.UI.Gtk.General.Enums
{-# LINE 55 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}


{-# LINE 57 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}


------------------
-- Enums

data CacheModel = CacheModelDocumentViewer
                | CacheModelWebBrowser
                
instance Enum CacheModel where
  fromEnum CacheModelDocumentViewer = 1
  fromEnum CacheModelWebBrowser = 2

  toEnum 1 = CacheModelDocumentViewer
  toEnum 2 = CacheModelWebBrowser
  toEnum unmatched = error ("CacheModel.toEnum: Cannot match " ++ show unmatched)

  succ CacheModelDocumentViewer = CacheModelWebBrowser
  succ _ = undefined

  pred CacheModelWebBrowser = CacheModelDocumentViewer
  pred _ = undefined

  enumFromTo x y | fromEnum x == fromEnum y = [ y ]
                 | otherwise = x : enumFromTo (succ x) y
  enumFrom x = enumFromTo x CacheModelWebBrowser
  enumFromThen _ _ =     error "Enum CacheModel: enumFromThen not implemented"
  enumFromThenTo _ _ _ =     error "Enum CacheModel: enumFromThenTo not implemented"

{-# LINE 63 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}

------------------
-- Methods
-- | Returns the current cache model. For more information about this value check the documentation of
-- the function 'setCacheModel'.
--
-- * Since 1.1.18
getCacheModel :: IO CacheModel
getCacheModel =
  liftM (toEnum . fromIntegral) $
  webkit_get_cache_model
{-# LINE 74 "./Graphics/UI/Gtk/WebKit/CacheModel.chs" #-}

-- | Specifies a usage model for WebViews, which WebKit will use to determine its caching behavior. All
-- web views follow the cache model. This cache model determines the RAM and disk space to use for
-- caching previously viewed content .
--
-- Research indicates that users tend to browse within clusters of documents that hold resources in
-- common, and to revisit previously visited documents. WebKit and the frameworks below it include
-- built-in caches that take advantage of these patterns, substantially improving document load speed
-- in browsing situations. The WebKit cache model controls the behaviors of all of these caches,
-- including various WebCore caches.
--
-- Browsers can improve document load speed substantially by specifying
-- WebkitCacheModelWebBrowser. Applications without a browsing interface can reduce memory usage
-- substantially by specifying WebkitCacheModelDocumentViewer. Default value is
-- WebkitCacheModelWebBrowser.
--
-- * Since 1.1.18
setCacheModel :: CacheModel -> IO ()
setCacheModel model =
  webkit_set_cache_model ((fromIntegral . fromEnum) model)

foreign import ccall safe "webkit_get_cache_model"
  webkit_get_cache_model :: (IO CInt)

foreign import ccall safe "webkit_set_cache_model"
  webkit_set_cache_model :: (CInt -> (IO ()))