[Haskell] I try to thaw an array of unboxed arrays to the IO monad

Simon Marlow simonmar at microsoft.com
Wed Jan 5 11:43:49 EST 2005


On 03 January 2005 23:53, Andreas Marth wrote:

> So I tried the following:
> 
>> import Data.Array.Base (thaw,freeze)
>> import Data.Array.Unboxed as UA (UArray,listArray)
>> import Data.Array.IArray as IA (Array,listArray)
> 
>> main :: IO ()
>> main = do let sL = [1,4,6,3,2,5]
>>   dim = length sL
>>   help :: [FlatVector]
>>   help = [listFlatVector (1,s) [0|i<-[1..s]]|s<-sL]   tmp :: Vector
>>   FlatVector tmp = listVector (1,dim) help
>>  v <- thaw tmp
>>  -- lots of stuff
>> --  res <- freeze v
>>  return ()
> 
>> type FlatVector  = UArray Int Double
> 
>> listFlatVector :: (Int,Int) -> [Double] -> FlatVector
>> listFlatVector = UA.listArray
> 
>> type Vector a = Array Int a
> 
>> listVector :: (Int,Int) -> [a] -> Vector a
>> listVector = IA.listArray
> 
...
> And this one in GHC:
> 
> mini-thaw.hs:12:
>     No instance for (Data.Array.Base.MArray b FlatVector IO)
>       arising from use of `thaw' at mini-thaw.hs:12
>     In a 'do' expression: v <- thaw tmp
>     In the definition of `main':
>         main = do
>                  let sL = [1, 4, 6, 3, 2, 5]
>                      dim = length sL
>                      help :: [FlatVector]
>                      help = [... | s <- ...]
>                      tmp :: Vector FlatVector
>                      tmp = listVector (1, dim) help
>                  v <- thaw tmp
>                  return ()

This is because thaw is overloaded, with type:

*Main> :t thaw
thaw :: forall e i b m a.
        (MArray b e m, IArray a e, Ix i) =>
        a i e -> m (b i e)

nice type, eh?  :-)  It means, basically, that thaw converts an
immutable array type 'a' of elements 'e' into a mutable array type 'b',
in monad 'm'.  This works to convert between any pair of 'a' and 'b'
array types as long as they have appropriate instances of IArray and
MArray, respectively.

The error above is telling you that there's no instance for 'MArray b
FlatVector IO' - this is because you haven't specified the array type
'b' into which thaw should convert the array.  The error message is a
bit misleading; it's really an ambiguity rather than a missing instance
(I don't know whether it could be reasonably improved, though).

Easily fixed by adding an appropriate type signature, for example:

    let _ = v :: IOArray Int FlatVector

after 'v <- thaw tmp' will do the trick.

BTW, don't import Data.Array.Base, use Data.Array.MArray instead.

Cheers,
	Simon


More information about the Haskell mailing list