3

I'm writing a bunch of different sorts and do this for lists and for arrays also. One thing that bothers me is that I can write a polymorphic sorting function for lists like

bubblesort :: (Ord a) => [a] -> [a]

but I when I try to do the same for UArrays:

alterUArray :: (Ix i, Ord e) => 
               (STUArray s i e -> ST s ()) -> UArray i e -> UArray i e
alterUArray alter ua = runST $ do
    mua <- thaw ua :: ST s1 (STUArray s1 i e)
    alter mua
    freeze mua

it fails with long error messages from GHC (a version with UArray Int Int works well). I tried to specify {-# LANGUAGE ScopedTypeVariables #-}, but this does not remove ambiguity of types i e in the thaw call. An error message without type of thaw : http://hpaste.org/84910.

What do I need to write a polymorhic UArray operation? Are there some fundamentional limitations? Are there compiler extensions which allow to do such things?

Dmytro Sirenko
  • 5,003
  • 21
  • 26

3 Answers3

3

There are two problems. First, as dave4420 pointed out, runST needs the alter function to be polymorphic in the state s.

Fixing that, however, makes it impossible to solve the second problem, that you need an MArray instance for thaw (and freeze). You would need a constraint

alterUArray :: (Ix i, Ord e, IArray UArray e, forall s. MArray (STUArray s) e (ST s)) => ...

to get it to work, since runST is the one to choose s. But you can't specify such a constraint.

If you give a specific element type (Int, Double, ...), it works since there is an

instance MArray (STUArray s) Int (ST s) where ...

so the demands of thaw and freeze are satisfied no matter what s is chosen by runST (and the constraint need not be stated).

It also works if you choose boxed arrays instead of unboxed ones, since there also is an

instance MArray (STArray s) e (ST s) where ...

and so there is no constraint on the element type that needs to be stated in the signature of alterUArray. (There is no constraint on the types of list elements, and list elements are boxed, so boxed arrays are the correspondence to lists, not unboxed arrays).

If you can bear getting your hands dirty, you can circumvent the problem by replacing ST s by IO,

alterUArray :: (Ix i, Ord e, MArray IOUArray e IO, IArray UArray e) =>
               (IOUArray i e -> IO ()) -> UArray i e -> UArray i e
alterUArray alter ua = unsafePerformIO $ do
    mua <- thaw ua
    alter mua
    freeze mua

only needs FlexibleContexts. This allows to pass a bad alter argument that does nefarious IO stuff, though, and would hide it from the caller. So let us make the use of unsafePerformIO here safe, by forcing a more general type on the alter argument:

{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-}

import Data.Array.Unboxed
import Data.Array.IO
import System.IO.Unsafe

alterUArray :: forall i e. (Ix i, Ord e, IArray UArray e, MArray IOUArray e IO) =>
               (forall m u. MArray u e m => u i e -> m ()) -> UArray i e -> UArray i e
alterUArray alter ua = unsafePerformIO $ do
    mua <- thaw ua :: IO (IOUArray i e)
    alter mua
    freeze mua

Now we have given alter a type that makes it impossible to do nefarious IO without itself using unsafePerformIO, so the use of unsafePerformIO here doesn't introduce additional insecurity - at the expense of more needed extensions.

(Note: while using thaw to get a copy of the original array is necessary, there is no need for an additional copy when freezing, that could be unsafeFreeze without a problem.)

Community
  • 1
  • 1
Daniel Fischer
  • 181,706
  • 17
  • 308
  • 431
1

I was bothered by this kind of problems as well. Now I believe it is impossible to write such polymorphic function.

We can write

alterArray :: (Ix i, IArray b e, IArray a e, MArray a2 e m) => 
              (a2 i e -> m a1) -> a i e -> m (b i e)
alterArray alter ua = do
    mua <- thaw ua 
    alter mua
    freeze mua

Or

alterUArrayST :: (Ix i, IArray UArray e, MArray (STUArray s) e (ST s)) => 
                 (STUArray s i e -> ST s ()) -> UArray i e -> ST s (UArray i e)
alterUArrayST alter ua = do
    mua <- thaw ua 
    alter mua
    freeze mua

But if we want to get rid of ST, we have to write some type specific versions, e.g.

alterUArrayInt :: (forall s. STUArray s Int Int -> ST s ()) -> UArray Int Int -> UArray Int Int
alterUArrayInt alter ua = runST $ do
    mua <- thaw ua 
    alter mua
    freeze mua

alterUArrayFloat :: (forall s. STUArray s Int Float -> ST s ()) -> UArray Int Float -> UArray Int Float
alterUArrayFloat alter ua = runST $ do
    mua <- thaw ua 
    alter mua
    freeze mua

If MArray had an instance MArray (STUArray s) e (ST s), I think we could write such polymorphic function. Unforunately, MArray doesn't have no such instance.

yairchu gave another workaround for this kind of problems in https://stackoverflow.com/a/2244281/779412.

Community
  • 1
  • 1
nymk
  • 3,323
  • 3
  • 34
  • 36
0

Change the type declaration to

alterUArray :: (Ix i, Ord e) => 
               (forall s. STUArray s i e -> ST s ()) -> UArray i e -> UArray i e

and get rid of the type annotation from thaw ua.

You'll need to enable the RankNTypes extension (or Rank2Types, though that's deprecated) (but don't you need to do that anyway to use runST? I forget).

Explanation: your original type declaration is equivalent to

alterUArray :: (Ix i, Ord e) => 
               forall s. (STUArray s i e -> ST s ()) -> UArray i e -> UArray i e

Which means that alterUArray's caller gets to choose what s is. My changed type insists instead that alterUArray gets to choose itself what s is. Your code then defers the choice of s to runST; its type insists that it gets to make the choice.

dave4420
  • 46,404
  • 6
  • 118
  • 152
  • I tried to specify more context by changing type signature to `(Ix i, Ord e, MArray (STUArray s) e (ST s)) => (forall s1. STUArray s1 i e -> ST s1 ()) -> UArray i e -> UArray i e `, does not work either. – Dmytro Sirenko Mar 31 '13 at 09:53
  • Cale on #haskell IRC suggested this: `alterUArrayST :: forall i e s. (Ix i, IArray UArray e, MArray (STUArray s) e (ST s)) => (STUArray s i e -> ST s ()) -> UArray i e -> ST s (UArray i e)` – Dmytro Sirenko Mar 31 '13 at 10:14
  • @EarlGray Did Cale's answer fix it for you? If not, which modules are you importing? – dave4420 Mar 31 '13 at 10:56
  • Yes, it compiles with `RankNTypes, FlexibleContexts, ScopedTypeVariables`, but (as he cautioned) application of this function to others is still a lot of type-matching work. – Dmytro Sirenko Mar 31 '13 at 11:30