
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/* <\ * (__ */\ <

On Mon, Jun 23, 2008 at 3:26 AM, Xiao-Yong Jin
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 you want to give a type signature for 'go', you need a GHC extension called ScopeTypeVariables (IIRC). The problem is that the 'b' in the signature of mapVecToMat is not the same b as the one in 'go'. With this extension, you can put those variables into scope for the body of the definition using explicit 'forall' quantifiers: mapVecToMat :: forall a b. (Element a, Element b) => (a -> Vector b) -> Vector a -> Matrix b -- rest as before But the Element b constraint is redundant in the signature of 'go', since that constraint is already in place by the above signature. As far as I can tell, giving an explicit signature for 'go' is not possible without this extension. Luke

On Mon, Jun 23, 2008 at 5:58 AM, Luke Palmer
On Mon, Jun 23, 2008 at 3:26 AM, Xiao-Yong Jin
wrote: 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 you want to give a type signature for 'go', you need a GHC extension called ScopeTypeVariables (IIRC).
I was indeed correct on the name of this extension, but it would be no help to you to know this since I made a typo :-) The extension is called ScopedTypeVaraibles. You probably already know that this can be enabled with: {-# LANGUAGE ScopedTypeVariables #-} Luke

"Luke Palmer"
On Mon, Jun 23, 2008 at 5:58 AM, Luke Palmer
wrote: On Mon, Jun 23, 2008 at 3:26 AM, Xiao-Yong Jin
wrote: 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 you want to give a type signature for 'go', you need a GHC extension called ScopeTypeVariables (IIRC).
I was indeed correct on the name of this extension, but it would be no help to you to know this since I made a typo :-)
The extension is called ScopedTypeVaraibles.
You probably already know that this can be enabled with:
{-# LANGUAGE ScopedTypeVariables #-}
Luke
Thanks for the explanation. I guess it's just easier for me not to give any type signature to `go', since ghc should do the type inference quite nicely and reliably. X-Y -- c/* __o/* <\ * (__ */\ <

To answer the question in the subject:
From "Simple unification-based type inference for GADTs", Peyton-Jones, et al. ICFP 2006. http://research.microsoft.com/users/simonpj/papers/gadt/
"Instead of "user-specified type", we use the briefer term rigid
type to describe a type that is completely specified, in some
direct fashion, by a programmer-supplied type annotation."
So a rigid type is any type specified by a programmer type signature.
All other types are "wobbly".
Does anyone know what is going to change about the terminology with
the new "boxy types" paper?
http://research.microsoft.com/users/simonpj/papers/boxy/
-- ryan
-- ryan
On Sun, Jun 22, 2008 at 8:26 PM, Xiao-Yong Jin
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/* <\ * (__ */\ < _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram wrote:
To answer the question in the subject:
From "Simple unification-based type inference for GADTs", Peyton-Jones, et al. ICFP 2006. http://research.microsoft.com/users/simonpj/papers/gadt/
"Instead of "user-specified type", we use the briefer term rigid type to describe a type that is completely specified, in some direct fashion, by a programmer-supplied type annotation."
So a rigid type is any type specified by a programmer type signature. All other types are "wobbly".
Wow. Such a short and clear explanation. I have been wondering for some time what exactly this 'rigid' means... Please somebody who understands stuff like that better than me put it on some wiki page. It's obviously a FAQ. BTW, do we have a FAQ page? I think we should have one. Cheers Ben (a little behind on cafe, catching up...)

On Tue, 8 Jul 2008, Ben Franksen wrote:
Wow. Such a short and clear explanation. I have been wondering for some time what exactly this 'rigid' means... Please somebody who understands stuff like that better than me put it on some wiki page. It's obviously a FAQ.
BTW, do we have a FAQ page? I think we should have one.
participants (5)
-
Ben Franksen
-
Henning Thielemann
-
Luke Palmer
-
Ryan Ingram
-
Xiao-Yong Jin