using Typeable with STRefs

Hi, I'm having a problem using Typeable with STRefs. Basically, I want to store STRefs (among other things) in a universal type. STRef is an instance of Typeable2, which means that STRef s a is Typeable if s and a are both Typeable. The problem is that the state type s is opaque and I can see no way to make it Typeable (other than making it RealWorld, and I don't want to use IO for this). If this is the case, then AFAICT there is no point in having STRefs be instances of Typeable2. Am I missing something? Here's the code I'd like to write: import Data.Typeable import Data.STRef import Control.Monad.ST data Value = forall a . Typeable a => V a deriving Typeable getValue :: Typeable a => Value -> Maybe a getValue (V v) = cast v -- I need the Typeable s constraint for the code to compile, but I'd rather leave it out. test :: Typeable s => ST s Integer test = do ref <- newSTRef (10 :: Integer) let refVal = V ref case getValue refVal of Nothing -> error "BAD" Just r -> readSTRef r -- This doesn't compile, because s is not Typeable. test2 :: Integer test2 = runST test Thanks in advance, Mike

Having the state be an instance of Typeable breaks the purity
guarantees of runST; a reference could escape runST:
let v = runST (V `liftM` newSTRef 0)
in runST (readSTRef $ fromJust $ getValue v)
Keep in mind that the state actually used by runST is "RealWorld";
runST is just a pretty name for unsafePerformIO. So the state types
are actually the same, and the cast would succeed.
-- ryan
On Mon, Mar 16, 2009 at 5:48 PM, Michael Vanier
Hi,
I'm having a problem using Typeable with STRefs. Basically, I want to store STRefs (among other things) in a universal type. STRef is an instance of Typeable2, which means that STRef s a is Typeable if s and a are both Typeable. The problem is that the state type s is opaque and I can see no way to make it Typeable (other than making it RealWorld, and I don't want to use IO for this). If this is the case, then AFAICT there is no point in having STRefs be instances of Typeable2. Am I missing something?
Here's the code I'd like to write:
import Data.Typeable import Data.STRef import Control.Monad.ST
data Value = forall a . Typeable a => V a deriving Typeable
getValue :: Typeable a => Value -> Maybe a getValue (V v) = cast v
-- I need the Typeable s constraint for the code to compile, but I'd rather leave it out. test :: Typeable s => ST s Integer test = do ref <- newSTRef (10 :: Integer) let refVal = V ref case getValue refVal of Nothing -> error "BAD" Just r -> readSTRef r
-- This doesn't compile, because s is not Typeable. test2 :: Integer test2 = runST test
Thanks in advance,
Mike
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan, So, if I understand you correctly, my only option is to use an IORef instead of an STRef? What I'm trying to do is implement a mutable box type as part of a dynamically-typed language I'm implementing in Haskell (which is mainly an exercise to improve my Haskell programming; mission accomplished). It bothers me that I have to use an IORef for this, since I don't see what this has to do with I/O. Similarly, if I wanted to have a mutable array type, I couldn't use STArray; I'd have to use IOArray. Or, I suppose I could define a richer Value type that had extra constructors for stateful types. Mike Ryan Ingram wrote:
Having the state be an instance of Typeable breaks the purity guarantees of runST; a reference could escape runST:
let v = runST (V `liftM` newSTRef 0) in runST (readSTRef $ fromJust $ getValue v)
Keep in mind that the state actually used by runST is "RealWorld"; runST is just a pretty name for unsafePerformIO. So the state types are actually the same, and the cast would succeed.
-- ryan
On Mon, Mar 16, 2009 at 5:48 PM, Michael Vanier
wrote: Hi,
I'm having a problem using Typeable with STRefs. Basically, I want to store STRefs (among other things) in a universal type. STRef is an instance of Typeable2, which means that STRef s a is Typeable if s and a are both Typeable. The problem is that the state type s is opaque and I can see no way to make it Typeable (other than making it RealWorld, and I don't want to use IO for this). If this is the case, then AFAICT there is no point in having STRefs be instances of Typeable2. Am I missing something?
Here's the code I'd like to write:
import Data.Typeable import Data.STRef import Control.Monad.ST
data Value = forall a . Typeable a => V a deriving Typeable
getValue :: Typeable a => Value -> Maybe a getValue (V v) = cast v
-- I need the Typeable s constraint for the code to compile, but I'd rather leave it out. test :: Typeable s => ST s Integer test = do ref <- newSTRef (10 :: Integer) let refVal = V ref case getValue refVal of Nothing -> error "BAD" Just r -> readSTRef r
-- This doesn't compile, because s is not Typeable. test2 :: Integer test2 = runST test
Thanks in advance,
Mike
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Mar 16, 2009 at 8:08 PM, Michael Vanier
Ryan,
So, if I understand you correctly, my only option is to use an IORef instead of an STRef? What I'm trying to do is implement a mutable box type as part of a dynamically-typed language I'm implementing in Haskell (which is mainly an exercise to improve my Haskell programming; mission accomplished). It bothers me that I have to use an IORef for this, since I don't see what this has to do with I/O. Similarly, if I wanted to have a mutable array type, I couldn't use STArray; I'd have to use IOArray. Or, I suppose I could define a richer Value type that had extra constructors for stateful types.
Why not: data Value = forall a . Typeable a => V a type STValue s = STRef Value Then you have a dynamic, mutable box. Also, even if the language you're interpretting is dynamicaly typed, it doesn't mean that you need to use Haskell Dynamics. It should be enough to do something like: data Value = VInt Integer | VStr String | VChar Char and then: -- | Similar to Prelude.Head primOpHead :: Value -> Value primOpHead (VStr xs) = VChar $ head xs primOpHead _ = error "Type Mismatch!" I'm sure other people can point you to much better ways to do this - the point is that you don't need Dynamics to implement a dynamic language. Antoine
participants (3)
-
Antoine Latter
-
Michael Vanier
-
Ryan Ingram