[Haskell-cafe] Trying to use more than one array in runSTUArray

Daniel Fischer daniel.is.fischer at googlemail.com
Thu Mar 15 20:07:02 CET 2012


On Thursday 15 March 2012, 19:53:56, Daniel Fischer wrote:
> On Thursday 15 March 2012, 19:27:18, Juan Miguel Vilar wrote:
> > Hello, café:

> 
> > However, when I write
> > 
> > test2 n = runSTUArray $ do
> > 
> >               let createArray v n = newArray (1, n) (v::Int)
> 
> Here you create a local binding for createArray that gets a monomorphic
> type, that type is the fixed by the returning of b to
> 
> createArray :: Int -> Integer -> ST s (STUArray s Integer Int)
> 
> you can make that fail too with enabling {-# LANGUAGE NoMonoLocalBinds
> #-}

Hmm, what compiler version are you using? When I actually tried to compile 
that, it failed with

    No instance for (MArray a0 Int (ST s))

without language extensions. After enabling MonoLocalBinds, however, it 
compiled with 6.12.3, 7.0.2, 7.0.4, 7.2.1 and 7.2.2, but 7.4.1 still 
refused to compile it.

> 
> >               a <- createArray 2 n
> >               b <- createArray 0 n
> >               forM_ [1..n] $ \i -> do
> >               
> >                 v <- readArray a i
> >                 writeArray b i (v+1)
> >               
> >               return b
> > 
> > everything is fine although I expected the two versions to be
> > equivalent.




More information about the Haskell-Cafe mailing list