Typesafe MRef with a regular monad

Ken Shan ken@digitas.harvard.edu
Mon, 23 Jun 2003 22:21:02 -0400


Keith Wansbrough <Keith.Wansbrough@cl.cam.ac.uk> wrote in article <E19PLTP-0002fT-00@wisbech.cl.cam.ac.uk> in gmane.comp.lang.haskell.general:
>   module TypedFM where
>        data FM k     -- Abstract; finite map indexed bykeys of type k
>        data Key k a  -- Abstract; a key of type k, indexing a value of type a
> 
>        empty :: FM k
>        insert :: Ord k => FM k -> k -> a -> (FM k, Key k a)
>        lookup :: Ord k => FM k -> Key k a -> Maybe a
>        update :: Ord k => FM k -> Key k a -> a -> FM k
> 
> If updating gives you a new key, then you might as well just store the
> value in the key.  Instead, you keep the same key; and so you'd better
> remain type-compatible.

Discussing this with Oleg, I realized that this signature is not sound.

    (fm1, key)      = insert empty 42 undefined
    value_in        = 1 :: Int
    fm2             = update fm1 key value_in
    Just value_out  = lookup fm2 key :: Char

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
* "Harry Potter is a sexist neo-conservative autocrat."
  -- Pierre Bruno, Liberation (cf. ISBN 1-85984-666-1)
* Return junk mail in the postage-paid response envelope included.
* Insert spanners randomly in unjust capitalist machines.