
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!)

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
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

Ryan Ingram wrote:
Congratulations, you're halfway to reinventing ST! :)
Except that, AFAIK, ST doesn't provide the "hey you can store anything and retrieve it later" trick. ;-) I did however wonder if there wasn't some way I could use an extra phantom type to somehow "tag" which thread a key was generated in... but I couldn't figure out how to make it work.
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!
Ah, I see. It sounds so easy when you already know how... :-) BTW, does anybody know how rank-N types are different from existential types?

What ST doesn't provide is a delete operation, otherwise it the rest
(but in a safe way).
On Thu, Dec 11, 2008 at 9:04 PM, Tillmann Rendel
Andrew Coppin wrote:
Except that, AFAIK, ST doesn't provide the "hey you can store anything and retrieve it later" trick. ;-)
I would say that Data.STRef does exactly that.
Tillmann _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Tillmann Rendel wrote:
Andrew Coppin wrote:
Except that, AFAIK, ST doesn't provide the "hey you can store anything and retrieve it later" trick. ;-)
I would say that Data.STRef does exactly that.
That's true - but you can't transport those from place to play. (By design.) The reason I went to all the bother of implementing this strange monad is that I actually want several different monads that I can secretly transport keys between...and I couldn't figure out how to make STRef do that.

On Thu, Dec 11, 2008 at 2:05 PM, Andrew Coppin
Tillmann Rendel wrote:
Andrew Coppin wrote:
Except that, AFAIK, ST doesn't provide the "hey you can store anything and retrieve it later" trick. ;-)
I would say that Data.STRef does exactly that.
That's true - but you can't transport those from place to play. (By design.)
If you could guarantee that the ID of a key is globally unique, even through different invocations of the monad (using eg. unsafePerformIO newUnique), then you could ensure type safety and allow transport of keys between different monads. However, if you did this, then your library would not be referentially transparent. Can you see how? Luke

2008/12/11 Luke Palmer
If you could guarantee that the ID of a key is globally unique, even through different invocations of the monad (using eg. unsafePerformIO newUnique), then you could ensure type safety and allow transport of keys between different monads.
Well, for type-safety you don't need the entire ID of the key; you just need a globally unique type tag. This is, of course, what Data.Typeable provides. But you can also roll your own using Uniques: newtype TKey a = TKey Unique deriving Eq newTKey :: IO (TKey a) newTKey = fmap TKey newUnique castTKey :: TKey a -> TKey b -> Maybe (a -> b) castTKey (TKey u1) (TKey u2) | u1 == u2 = Just unsafeCoerce | otherwise = Nothing data Key a = Key Int (TKey a) deriving (Eq, Ord) data StoredValue = forall a. Stored (TKey a) a type StorageMap = IntMap StoredValue You then split up the program; one part generates TKeys for the types in IO; then you can use those throughout the pure rest of the program to index the types: newKey :: TKey a -> Storage (Key a) newKey ta = do ik <- getNextFreeInt return $ Key ik ta -- using MaybeT: -- newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) } -- with the appropriate Monad instance readKey :: Key a -> Storage (Maybe a) readKey (Key i t) = runMaybeT $ do Stored tx x <- MaybeT $ lookupMap i f <- MaybeT $ return (castTKey tx t) return (f x) -- exercises for the reader lookupMap :: Int -> Storage StoredValue getNextFreeInt :: Storage Int writeKey :: a -> Key a -> Storage () If you're willing to be *slightly* non-referentially transparent, you can generate the type keys at global scope: intTKey :: TKey Int intTKey = unsafePerformIO newTKey {-# NOINLINE intTKey #-} (There have been many arguments about "top level IO actions"; I don't want to get into that here!) -- ryan

On Thu, Dec 11, 2008 at 1:48 PM, Andrew Coppin
BTW, does anybody know how rank-N types are different from existential types?
You mean the Haskell extensions?
ExistentialQuantification lets you define types such as,
data SomeNum = forall a. Num a => SomeNum a
RankNTypes lets you nest foralls arbitrarily deep in type signatures,
callCC :: ((forall b. a -> m b) -> m a) -> m a -- this is rank-3
RankNTypes implies ExistentialQuantification (among others).
--
Dave Menendez

David Menendez wrote:
On Thu, Dec 11, 2008 at 1:48 PM, Andrew Coppin
wrote: BTW, does anybody know how rank-N types are different from existential types?
You mean the Haskell extensions?
ExistentialQuantification lets you define types such as,
data SomeNum = forall a. Num a => SomeNum a
RankNTypes lets you nest foralls arbitrarily deep in type signatures,
callCC :: ((forall b. a -> m b) -> m a) -> m a -- this is rank-3
RankNTypes implies ExistentialQuantification (among others).
So how is foo :: ((forall b. a -> m b) -> m a) -> m a different from bar :: forall b. ((a -> m b) -> m a) -> m a then?

Am Sonntag, 14. Dezember 2008 00:00 schrieb Andrew Coppin:
David Menendez wrote:
On Thu, Dec 11, 2008 at 1:48 PM, Andrew Coppin
wrote: BTW, does anybody know how rank-N types are different from existential types?
You mean the Haskell extensions?
ExistentialQuantification lets you define types such as,
data SomeNum = forall a. Num a => SomeNum a
RankNTypes lets you nest foralls arbitrarily deep in type signatures,
callCC :: ((forall b. a -> m b) -> m a) -> m a -- this is rank-3
RankNTypes implies ExistentialQuantification (among others).
So how is
foo :: ((forall b. a -> m b) -> m a) -> m a
Here, the argument of foo's argument must be a polymorphic function, capable of returning an (m b) whatever b is.
different from
bar :: forall b. ((a -> m b) -> m a) -> m a
Here, the argument of bar's argument can have any monomorphic type (a -> m b)
then?

On Sat, Dec 13, 2008 at 3:00 PM, Andrew Coppin
So how is foo :: ((forall b. a -> m b) -> m a) -> m a different from bar :: forall b. ((a -> m b) -> m a) -> m a
Lets use a simpler example:
foo :: (forall a. a -> a) -> (Int, String) bar :: forall a. (a -> a) -> (Int, String)
-- this compiles foo f = (f 1, f "hello")
-- this does not compile -- bar f = (f 1, f "hello")
-- but this does bar f = (1, "hello")
The difference is that the *caller* of bar chooses how to instantiate a, whereas the caller of foo must pass in a polymorphic function that foo can instantiate at whatever type it wants... even multiple different types!
ident x = x plus1 x = x + 1 :: Int
-- legal useFoo = foo ident -- not legal, not polymorphic -- useFoo = foo plus1
-- legal useBar = bar ident -- also legal, instantiate "a" in the type of "bar" with "Int" useBar2 = bar plus1
-- ryan

On Sat, Dec 13, 2008 at 6:00 PM, Andrew Coppin
David Menendez wrote:
On Thu, Dec 11, 2008 at 1:48 PM, Andrew Coppin
wrote: BTW, does anybody know how rank-N types are different from existential types?
You mean the Haskell extensions?
ExistentialQuantification lets you define types such as,
data SomeNum = forall a. Num a => SomeNum a
RankNTypes lets you nest foralls arbitrarily deep in type signatures,
callCC :: ((forall b. a -> m b) -> m a) -> m a -- this is rank-3
RankNTypes implies ExistentialQuantification (among others).
So how is
foo :: ((forall b. a -> m b) -> m a) -> m a
different from
bar :: forall b. ((a -> m b) -> m a) -> m a
then?
Daniel Fischer already gave the short answer, I'll try explaining why
someone might *want* a rank-3 signature for callCC. It involves a
continuation monad, but hopefully nothing headache-inducing.
The type for callCC in Control.Monad.Cont.Class is,
callCC :: forall m a b. (MonadCont m) => ((a -> m b) -> m b) -> m b
You can use callCC to do very complicated things, but you can also use
it as a simple short-cut escape, like the way "return" works in C.
foo = callCC (\exit -> do
...
x <- if something
then return 'a'
else exit False
...
return True)
The type of exit is Bool -> m Char, which is fine in this example, but
it means that we can only use exit to escape from computations that
are producing characters. For example, we cannot write,
bar = callCC (\exit -> do
...
x <- if something then return 'a' else exit False
y <- if something then return 42 else exit False
...
return True)
Because exit would need to have the type Bool -> m Char the first time
and Bool -> m Int the second time. But, if callCC had a rank-3 type,
callCC :: forall m a. (MonadCont m) => ((forall b. a -> m b) -> m a) -> m a
then exit would have the type "forall b. Bool -> m b", and bar would
compile just fine.
--
Dave Menendez

Andrew Coppin wrote:
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?
I did exactly that in my Yogurt project[1]. It felt dirty but in a good way, mostly because the interface was exactly what I needed. :-)
...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
I've worried about this but I couldn't find a good code example of when this goes wrong. Can you? Without using any of the unsafeXxx functions, of course. Maybe I should build my monad on top of the ST monad if that makes things safer. Martijn. [1] http://hackage.haskell.org/packages/archive/Yogurt/0.2/doc/html/Network-Yogu...

On Fri, Dec 12, 2008 at 2:48 AM, Martijn van Steenbergen
I've worried about this but I couldn't find a good code example of when this goes wrong. Can you? Without using any of the unsafeXxx functions, of course.
Maybe I should build my monad on top of the ST monad if that makes things safer.
[1] http://hackage.haskell.org/packages/archive/Yogurt/0.2/doc/html/Network-Yogu...
Here's a simple example: runMud :: Mud a -> a runMud = flip evalState emptyMud main = do let v = runMud (mkVar "hello") let crash = runMud $ do v2 <- mkVar True -- v2 :: Var Bool res <- readVar v -- v :: Var String return res print crash -- boom! Both v2 and v are the same variable index (0), but different types. Since there's nothing preventing the variable from escaping from the first "runMud", we can import it into the second one where it fails. The key is that both use the same "initial state", so you have lost the uniqueness of variables. ST is safer, although you can make these systems just as safe with the phantom "state" type like ST does. It's also faster; variables turn directly into pointer references, instead of traversing an IntMap. But it gets kind of annoying writing all the extra "s" on your type signatures. -- ryan

Ryan Ingram wrote:
Here's a simple example:
runMud :: Mud a -> a runMud = flip evalState emptyMud
main = do let v = runMud (mkVar "hello") let crash = runMud $ do v2 <- mkVar True -- v2 :: Var Bool res <- readVar v -- v :: Var String return res print crash -- boom!
Both v2 and v are the same variable index (0), but different types. Since there's nothing preventing the variable from escaping from the first "runMud", we can import it into the second one where it fails. The key is that both use the same "initial state", so you have lost the uniqueness of variables.
Ah, yes, of course, thank you. :-) I was trying to break it from within the monad. Martijn.
participants (8)
-
Andrew Coppin
-
Daniel Fischer
-
David Menendez
-
Lennart Augustsson
-
Luke Palmer
-
Martijn van Steenbergen
-
Ryan Ingram
-
Tillmann Rendel