[Haskell-cafe] What is a rigid type variable?

Xiao-Yong Jin xj2106 at columbia.edu
Sun Jun 22 23:26:58 EDT 2008


Hi all,

I'm writing a short function as follows, but I'm not able to
find a suitable type signature for `go'.  It uses
Numeric.LinearAlgebra from hmatrix.


-- | Map each element in a vector to vectors and thus form a matrix
-- | row by row
mapVecToMat :: (Element a, Element b) =>
               (a -> Vector b) -> Vector a -> Matrix b
mapVecToMat f v = fromRows $ go (d - 1) []
    where
      d = dim v
      go :: Element b => Int -> [Vector b] -> [Vector b]
      go 0 vs = f (v @> 0) : vs
      go !j !vs = go (j - 1) (f (v @> j) : vs)


If I give the type signature to go as this, I got the
following error

    Couldn't match expected type `b1' against inferred type `b'
      `b1' is a rigid type variable bound by
           the type signature for `go' at test.hs:36:20
      `b' is a rigid type variable bound by
          the type signature for `mapVecToMat' at test.hs:31:35
      Expected type: Vector b1
      Inferred type: Vector b
    In the first argument of `(:)', namely `f (v @> 0)'
    In the expression: f (v @> 0) : vs

So what is this rigid type variable all about and what is
correct type of the function `go'?

Thanks in advance,
X-Y
-- 
    c/*    __o/*
    <\     * (__
    */\      <


More information about the Haskell-Cafe mailing list