[Haskell-cafe] Re: rigid variables

Rodney D Price rodprice at raytheon.com
Thu Jul 20 18:26:31 EDT 2006


Thanks for the responses.  The semantics of check as described the
"Data Invariants" paper on STM are really close to what I am looking
for.  Unfortunately, that work is not in GHC yet, so I'm attempting my
own poor substitute (below).  I have a store that is to be accessed by
other threads, and I want to throw an error under certain conditions.
(The names below are borrowed from the "Scheme in 48 Hours"
tutorial.)  In reality I'm looking for an inconsistent store, but for
simplicity's sake I've just put in a standard read operation below.
Is there an easier way?

Thanks,

-Rod


--
module Store where

import Control.Monad.Error
import Control.Concurrent.STM

data StoreError = DoesNotExist String
                 | Default String

instance Error StoreError where
     noMsg  = Default "Store error"
     strMsg = Default

type ThrowsError = Either StoreError

type IOThrowsError = ErrorT StoreError IO

type Store a = TVar [ (String, TVar a) ]


-- read from the store
getSTM :: String -> Store a -> STM (ThrowsError a)
getSTM name store = do
     st <- readTVar store
     case lookup name st of
         Nothing -> return (Left $ DoesNotExist name)
         Just rd -> readTVar rd >>= return . Right

get :: String -> Store a -> IOThrowsError a
get name store = do
     d <- liftIO $ atomically $ getSTM name store
     case d of
         Left err -> throwError err
         Right d' -> return d'



More information about the Haskell-Cafe mailing list