Typesafe MRef with a regular monad
Ralf Hinze
ralf@informatik.uni-bonn.de
Fri, 6 Jun 2003 16:26:16 +0200
Am Freitag, 6. Juni 2003 16:09 schrieb Simon Peyton-Jones:
> You can't overwrite an entry with a value of a different type, because
> the keys are typed! Any more than you can overwrite an IORef with a
> value of a different type.
> S
Why is that? Ok, here is my second implementation. It uses the
Dynamic module from our HW2002 paper. A key is a pair consisting
of the actual key and a type representation.
> module TypedFM
> where
> import Prelude hiding (lookup)
> import qualified Prelude
> import Dynamics
> data FM k = FM [(k, Dynamic)]
> data Key k a = Key k (Type a)
> empty :: FM k
> empty = FM []
> insert :: (Typable a) => FM k -> k -> a -> (FM k, Key k a)
> insert (FM bs) k a = (FM ((k, Dyn rep a) : bs), Key k rep)
> lookup :: (Eq k) => FM k -> Key k a -> Maybe a
> lookup (FM bs) (Key k rep) = case Prelude.lookup k bs of
> Nothing -> Nothing
> Just dy -> cast dy rep
> update :: (Typable b) => FM k -> Key k a -> b -> (FM k, Key k b)
> update (FM bs) (Key k _) b = (FM ((k, Dyn rep b) : bs), Key k rep)
Does this fit the bill?
Cheers, Ralf