----------------------------------------------------------------------------- -- | -- Module : Control.Concurrent.TBox.Internal.Class -- Copyright : Peter Robinson 2009 -- License : LGPL -- -- Maintainer : Peter Robinson -- Stability : experimental -- Portability : non-portable (requires STM) -- -- The type class 'TBox'. -- -- ----------------------------------------------------------------------------- module Control.Concurrent.TBox.Internal.Class where import Control.Concurrent.AdvSTM import Prelude hiding(readIO) -------------------------------------------------------------------------------- -- | An instance of 'TBox' is a (Adv)STM variable that might contain a value of -- some type 'a'. In contrast to a plain 'TVar (Maybe a)', a -- 'TBox' has IO hooks that are executed transparently on writes and reads, -- which makes it particularly suitable for implementing a persistent and thread-safe storage. -- The type variable 'k' can be used to provide additional storage information, e.g., -- a filepath. -- -- /Important:/ Note that the read/write functions of this type class, i.e., -- 'readIO', 'readSTM', 'writeIO', 'writeSTM', 'clearIO', 'clearSTM' should -- /only/ be used to derive new -- instances and do not serve to modify the state of a 'TBox'. -- The interface defined in module 'TBox.Operations' provides -- operations on 'TBox's that guarantee consistency. -- -- See the module 'Control.Concurrent.TFile' for a sample instance. class TBox t k a where -- | Takes a key and an initial value new :: k -> a -> AdvSTM (t k a) -- | Takes a key and an initial value. Has a default implementation. newIO :: k -> a -> IO (t k a) newIO k a = atomically (new k a) -- | Takes a key and returns an empty 't' newEmpty :: k -> AdvSTM (t k a) -- | Takes a key and returns an empty 't'. Has a default implementation. newEmptyIO :: k -> IO (t k a) newEmptyIO = atomically . newEmpty -- -- | Return the key -- getKey :: t k a -> AdvSTM k -- | Used in 'TBox.write'. writeSTM :: t k a -> a -> AdvSTM () -- | Used in 'TBox.write' during the commit phase. -- Is guaranteed to be executed exactly once /iff/ the transaction commits. writeIO :: t k a -> a -> IO () -- | Used in 'TBox.read' readSTM :: t k a -> AdvSTM (Maybe a) -- | Used in 'TBox.read' when retrying the transaction, which happens when the -- 'TBox' has been marked \"dirty\". -- Note: Might be executed multiple times for the -- same 'TBox' in a single transaction. See 'unsafeRetryWith'. readIO :: t k a -> IO (Maybe a) -- | Used in 'TBox.clear' clearSTM :: t k a -> AdvSTM () -- | Used in 'TBox.clear' during the commit phase. -- Is guaranteed to be executed exactly once /iff/ the transaction commits. clearIO :: t k a -> IO () -- | If 'isDirty' yields 'True', the 'readIO' hook will be -- run on the next read. isDirty :: t k a -> AdvSTM Bool -- | Change the \"dirty\" status of the 'TBox'. setDirty :: t k a -> Bool -> AdvSTM () {- -- TODO: what about modify? modifySTM :: t k a -> (a -> a) -> AdvSTM () modifyIO :: t k a -> (a -> a) -> IO (Maybe a) modifySTM t f = readSTM t >>= writeSTM t . f modifyIO t f = readIO t >>= writeIO t -}