
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