-----------------------------------------------------------------------------
-- |
-- Module      :  Data.CacheStructure
-- Copyright   :  Peter Robinson 2009
-- License     :  LGPL
--
-- Maintainer  :  Peter Robinson <thaldyron@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable (requires STM)
--
-- A type class for implementing different caching policies (e.g. LRU, LFU,... ).
-- Should be imported qualified.
-----------------------------------------------------------------------------

module Data.CacheStructure( CacheStructure(..), CacheException(..) )
where
import Control.Exception 
import Data.Typeable

data CacheException = CacheException String
                      deriving (Show,Eq,Typeable)

instance Exception CacheException

-- | A type class for implementing a caching policy (e.g. LRU)
class CacheStructure c a where
  -- | A new element is added to the cache or an already existing element
  -- was accessed.
  hit    :: a -> c a -> c a
  -- | Returns the \"last\" element w.r.t. the caching policy.
  last   :: c a -> a
  -- | Removes and returns the \"last\" element w.r.t. the caching policy.
  pop    :: c a -> (c a,a)
  -- | Creates an empty cache structure.
  empty  :: c a
  -- | Checks for emptyness. 
  null   :: c a -> Bool
  -- | Transforms the cache structure to a list.
  toList :: c a -> [a]
  -- | An element is deleted.
  delete :: a -> c a -> c a
  -- | Checks if an element is in the cache structure.
  member :: a -> c a -> Bool
  -- | Returns the size. Should be /O(1)/.
  size   :: c a -> Int
  -- | Runs 'pop' a number of times. Has a default implementation. 
  popMany :: Int -> c a -> (c a,[a])
  popMany = popMany' []
            where
                popMany' del 0 cs = (cs,del) 
                popMany' del i cs 
                  | i < 0     = throw $ CacheException "Invalid size for cache structure!"
                  | otherwise = let (cs',a) = pop cs
                                in  popMany' (a:del) (i-1) cs'