[Haskell-cafe] How to convert a list to a vector encoding its
length in its type?
Miguel Mitrofanov
miguelimo38 at yandex.ru
Fri Aug 21 08:02:34 EDT 2009
>> {-# LANGUAGE UndecidableInstances #-}
Ouch!
Don't worry, it's just me not liking UndecidableInstances.
> So instead of passing the parameters as a list I want to pass them as
> arguments:
>
>> \x p1 p2 p3 -> p1*x^2 + p2*x + p3
Why not use tuples?
\x (p1, p2, p3) -> p1 * x^2 + p2 * x + p3
Or a special list-like data type
data a :* b = ($*) a b
func :: Double -> (Double :* Double :* Double) -> Double
func x (p1 $* p2 $* p3) = p1 * x^2 + p2 * x + p3
More information about the Haskell-Cafe
mailing list