
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)