Congratulations, you're halfway to reinventing ST! :) Here's the "trick" [1]:
> data Storage s x > ... > data Key s v > ... Now add the extra "s" parameter to all the functions that use Storage & Key. > run :: (forall s. Storage s x) -> x Now you can't save keys between sessions; the type "s" isn't allowed to escape the "forall" on the left of the function arrow! For reference, here's a complete implementation of ST: > {-# LANGUAGE GeneralizedNewtypeDeriving, Rank2Types #-} > module ST where > import Data.IORef > import System.IO.Unsafe (unsafePerformIO) > > newtype ST s a = ST (IO a) deriving Monad > newtype STRef s a = STRef (IORef a) deriving Eq > -- magic is in the rank 2 type here, it makes the unsafePerformIO safe! > runST :: (forall s. ST s a) -> a > runST (ST m) = unsafePerformIO m > newSTRef a = ST (fmap STRef $ newIORef a) > readSTRef (STRef v) = ST (readIORef v) > writeSTRef (STRef v) a = ST (writeIORef v a) [1] "Lazy Functional State Threads", Launchbury & Peyton Jones, PLDI 1994 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.50.3299 On Thu, Dec 11, 2008 at 10:26 AM, Andrew Coppin <andrewcop...@btinternet.com> wrote: > Yesterday I wrote something slightly unusual: > > > module Storage where > > data Storage x > instance Monad Storage > run :: Storage x -> x > > data Key v > instance Eq (Key v) > instance Ord (Key v) > > new_key :: v -> Storage (Key v) > set_key :: Key v -> v -> Storage () > get_key :: Key v -> Storage (Maybe v) > delete_key :: Key v -> Storage () > > > In other words, you can store a value (of arbitrary type) under a unique > key. The monad chooses what key for you, and tells you the key so you can > look up or alter the value again later. Under the covers, it uses Data.Map > to store stuff. I used some trickery with existential quantification and > unsafeCoerce (!!) to make it work. Notice the sneaky phantom type in the > key, telling the type system what type to coerce the value back to when you > read it. Neat, eh? > > ...until I realised that somebody that somebody could generate a key in one > run and then try to use it in another run. o_O > > Oops! > > But hey, until then it was working quite well. And completely pure; no IO > anywhere. > > Ah well, just thought I'd share... > > (You could of course do away with the monad, but then you'd be able to > manipulate the dictionary directly, and key uniqueness would be even more > fragile!) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe