[Haskell-cafe] repa Shape help

briand at aracnet.com briand at aracnet.com
Mon May 9 07:31:24 CEST 2011


Howdy,

as usual, the haskell type system complete defeats me in the simplest of applications:

import Data.Array.Repa as A
import Data.Array.Repa.Index
import Data.Array.Repa.Shape as AS

main = do
  let x = A.fromList (AS.shapeOfList [2, 2]) ([1.0, 2.0, 3.0, 4.0]::[Double])
  putStrLn $ show x

test_repa.hs:10:13:
    Ambiguous type variable `sh' in the constraint:
      `Shape sh' arising from a use of `show' at test_repa.hs:10:13-18
    Probable fix: add a type signature that fixes these type variable(s)
Failed, modules loaded: none.

After much staring at the type signatures I finally figured out that adding a type annotation to x of :

  :: Array DIM2 Double

would fix the problem, but I'm not completely clear as to why.

after all fromList is typed:

(Shape sh, Elt a) => sh -> [a] -> Array sh a

Since it knows [a] is [Double] and sh must be - well I'm not really clear on what sh is supposed to be.  therein lies my problem.  Although it does seem that sh can be darn near anything, which is probably why it was ambiguous.

At one point I had tried something like (2 :. 2) and got a whole host of errors for that too, except that DIM2 is defined in exactly that way, so it's not at all obvious why that didn't work.

I was hoping someone could clarify on what's going on.


Thanks,

Brian




More information about the Haskell-Cafe mailing list