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

Xiao-Yong Jin xj2106 at columbia.edu
Mon Jun 23 09:31:59 EDT 2008


"Luke Palmer" <lrpalmer at gmail.com> writes:

> On Mon, Jun 23, 2008 at 5:58 AM, Luke Palmer <lrpalmer at gmail.com> wrote:
>> On Mon, Jun 23, 2008 at 3:26 AM, Xiao-Yong Jin <xj2106 at columbia.edu> 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/*
    <\     * (__
    */\      <


More information about the Haskell-Cafe mailing list