Getting my mind around UArray -> STUArray conversion

I'm trying to get my mind around how to thaw and then freeze a UArray. Theoretically, what I've written below should be a no-op, but I keep getting typing errors that I can't figure out. GHCI 6.10.3 says: Couldn't match expected type `UArray ix a' against inferred type `ST s (STUArray s ix1 e)' In the first argument of `(>>=)', namely `(unsafeThaw mem :: ST s (STUArray s ix e))' In the expression: (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\ mmem -> unsafeFreeze mmem) In the definition of `wombat': wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\ mmem -> unsafeFreeze mmem) I'm figuring that usafeThaw with the type annotation should have given GHIC enough clue. Any suggestions? -scooter (WOMBAT = Waste Of Money Brains And Time) import Control.Monad; import Control.Monad.ST; import Data.Array.ST; import Data.Array.Unboxed; import Data.Array.MArray; import Data.Word; wombat :: (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\mmem -> unsafeFreeze mmem)

On Friday 19 June 2009 9:43:29 pm Scott Michel wrote:
wombat :: (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\mmem -> unsafeFreeze mmem)
Based on the error message and dealing with this sort of thing before, your problem is that when you say: ":: ST s (STUArray s ix e)" the s, ix and e there aren't the same as they are in the signature of wombat. To make them the same, you need the ScopedTypeVariables extension, and to make wombat's signature: wombat :: forall e ix s. ... where the dots are your current signature. It's possible you'll still have errors, but that will solve the one in your mail. -- Dan

Am Samstag 20 Juni 2009 03:51:08 schrieb Dan Doel:
On Friday 19 June 2009 9:43:29 pm Scott Michel wrote:
wombat :: (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\mmem -> unsafeFreeze mmem)
Based on the error message and dealing with this sort of thing before, your problem is that when you say:
":: ST s (STUArray s ix e)"
the s, ix and e there aren't the same as they are in the signature of wombat. To make them the same, you need the ScopedTypeVariables extension, and to make wombat's signature:
wombat :: forall e ix s. ...
where the dots are your current signature.
It's possible you'll still have errors, but that will solve the one in your mail.
-- Dan
No, only part of it. Another part is unsafeFreeze :: (Ix i, MArray a e m, IArray b e) => a i e -> m (b i e) so unsafeThaw arr >>= unsafeFreeze lives in a monad, here (ST s) and to get the type he wants, he has to wrap it in runST.

Oops, I replied too hastily. What I wrote in my first mail is a problem, as witnessed by the "ix" and "ix1" in the error message. However, it isn't the main error. The main error is that you have a monadic expression, with type something like: ST s (UArray ix e) but the return type of your function is: UArray ix e To make a no-op you need to add a runST, something like: runST (unsafeThaw mem >>= unsafeFreeze) If you need to annotate 'unsafeThaw mem', that's where the ScopedTypeVariables will come in. However, there's also an issue that mentioning 's' in the type of wombat won't work with the runST, which may be a problem with the MArray constraint (and I'm not sure what to do about that off the top of my head; I've not worked with STUArray in a while, so you may be constructing an unresolvable ambiguity). Sorry for the confusion. -- Dan

On Fri, Jun 19, 2009 at 7:08 PM, Dan Doel
Oops, I replied too hastily.
What I wrote in my first mail is a problem, as witnessed by the "ix" and "ix1" in the error message. However, it isn't the main error. The main error is that you have a monadic expression, with type something like:
ST s (UArray ix e)
but the return type of your function is:
UArray ix e
To make a no-op you need to add a runST, something like:
runST (unsafeThaw mem >>= unsafeFreeze)
Actually, I probably wanted runSTUArray. :-) But even then, I can't manage to get wombat to compile correctly. I'm starting to think that MArray is itself a WOMBAT (waste of money, brains and time), for three reasons: a) Overly restrictive Monads in which implementation is supported (i.e., ST and IO) b) The triviality of the examples gives no insight as to how they could be used, other than a create array, do something completely trivial and freeze. c) They are evidently very hard to use in a general sense. Even google-ing for examples just comes up with trivial examples of MArray usage. You might ask why I might need a MArray? I'm investigating the feasibility of building a cycle accurate PPC750 emulator. Memory emulates better as a mutable array. I'd like to be somewhat more general because the various systems with which I deal aren't necessarily 32-bit, sometimes they are 16-bit and sometimes they aren't PPC750 (different systems hooked to a common bus.) Classes with rank-n types looked like a good approach to solving this particular design problem, with a default implementation. I did try out your suggestions and here's what the code looks like now. ---- {-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-} module Wombat where import Control.Monad.ST; import Data.Array.ST; import Data.Array.Unboxed; import Data.Array.MArray; wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = runSTUArray (unsafeThaw mem >>= return) ---- GHCi says: [1 of 1] Compiling Wombat ( wombat.hs, interpreted ) wombat.hs:11:34: Could not deduce (MArray (STUArray s1) e (ST s1)) from the context () arising from a use of `unsafeThaw' at wombat.hs:11:34-47 Possible fix: add (MArray (STUArray s1) e (ST s1)) to the context of the polymorphic type `forall s. ST s (STUArray s ix e)' or add an instance declaration for (MArray (STUArray s1) e (ST s1)) In the first argument of `(>>=)', namely `unsafeThaw mem' In the first argument of `runSTUArray', namely `(unsafeThaw mem >>= return)' In the expression: runSTUArray (unsafeThaw mem >>= return)

scooter.phd:
On Fri, Jun 19, 2009 at 7:08 PM, Dan Doel
wrote: Oops, I replied too hastily.
What I wrote in my first mail is a problem, as witnessed by the "ix" and "ix1" in the error message. However, it isn't the main error. The main error is that you have a monadic expression, with type something like:
ST s (UArray ix e)
but the return type of your function is:
UArray ix e
To make a no-op you need to add a runST, something like:
runST (unsafeThaw mem >>= unsafeFreeze)
Actually, I probably wanted runSTUArray. :-)
But even then, I can't manage to get wombat to compile correctly. I'm starting to think that MArray is itself a WOMBAT (waste of money, brains and time), for three reasons:
a) Overly restrictive Monads in which implementation is supported (i.e., ST and IO) b) The triviality of the examples gives no insight as to how they could be used, other than a create array, do something completely trivial and freeze. c) They are evidently very hard to use in a general sense.
Even google-ing for examples just comes up with trivial examples of MArray usage.
Can you just use STUArrays directly without worrying about MArray overloading? writeArray/readArray on ST is just type safe raw memory access, so should be easy.
wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = runSTUArray (unsafeThaw mem >>= return)
Argh. That type is scary overloaded. -- Don

Hello Scott, Monday, June 22, 2009, 10:23:42 PM, you wrote:
wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) =>> e -> ix -> UArray ix e -> UArray ix e
http://haskell.org/haskellwiki/Library/ArrayRef#Reimplemented_Arrays_library "Unboxed arrays now can be used in polymorphic functions..." -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

This is the best I could come up with.
We let the compiler prove that "s" is irrelevant to the MArray
instance for a particular instance of STUArray, and package up that
knowledge using an existential type. We can then extract the instance
for any type; in particular, the instance for the current state
thread. I think this argues that the class context for MArray is too
constrained.
(I don't really use GADTs here, just pack up the class context, but I
like the GADT syntax for doing this)
-- ryan
{-# LANGUAGE GADTs, RankNTypes, FlexibleContexts, ScopedTypeVariables #-}
module StuTest where
import Control.Monad;
import Control.Monad.ST;
import Data.Array.ST;
import Data.Array.Unboxed;
import Data.Array.MArray;
import Data.Word;
data HasMArray s e where
HasMArray :: MArray (STUArray s) e (ST s) => HasMArray s e
newtype HasUnbox e = HasUnbox (forall s. HasMArray s e)
wombat :: forall s ix e. (IArray UArray e, Ix ix) => HasUnbox e ->
UArray ix e -> ST s (UArray ix e)
wombat (HasUnbox h) arr = case h of
(HasMArray :: HasMArray s e) ->
(unsafeThaw arr :: ST s (STUArray s ix e)) >>= unsafeFreeze
intHasUnbox :: HasUnbox Int
intHasUnbox = HasUnbox HasMArray
test :: (IArray UArray e, Ix ix) => HasUnbox e -> UArray ix e -> UArray ix e
test ctxt mem = runST (wombat ctxt mem)
simpleTest :: Ix ix => UArray ix Int -> UArray ix Int
simpleTest a = runST (wombat (HasUnbox HasMArray) a)
On Fri, Jun 19, 2009 at 6:43 PM, Scott Michel
I'm trying to get my mind around how to thaw and then freeze a UArray. Theoretically, what I've written below should be a no-op, but I keep getting typing errors that I can't figure out. GHCI 6.10.3 says:
Couldn't match expected type `UArray ix a' against inferred type `ST s (STUArray s ix1 e)' In the first argument of `(>>=)', namely `(unsafeThaw mem :: ST s (STUArray s ix e))' In the expression: (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\ mmem -> unsafeFreeze mmem) In the definition of `wombat': wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\ mmem -> unsafeFreeze mmem)
I'm figuring that usafeThaw with the type annotation should have given GHIC enough clue.
Any suggestions?
-scooter (WOMBAT = Waste Of Money Brains And Time)
import Control.Monad; import Control.Monad.ST; import Data.Array.ST; import Data.Array.Unboxed; import Data.Array.MArray; import Data.Word;
wombat :: (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) => e -> ix -> UArray ix e -> UArray ix e wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) >>= (\mmem -> unsafeFreeze mmem) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Bulat Ziganshin
-
Dan Doel
-
Daniel Fischer
-
Don Stewart
-
Ryan Ingram
-
Scott Michel