
Hi Stefan I'd have my membership of the one-leg club taken away if I didn't write in and say that,... On 12 Aug 2007, at 04:25, Stefan O'Rear wrote:
On Sun, Aug 12, 2007 at 12:56:31PM +1000, Alexis Hazell wrote:
On Sunday 12 August 2007 05:24, Stefan O'Rear wrote:
Currying makes it MUCH harder to implement varargs functions.
...while I wouldn't disagree,...
That's interesting - why is that the case?
varsum 2 3 -- varsum receives 2, and returns a function, which when -- passed 3, returns 5 varsum 2 3 4 -- varsum receives 2, and returns a function, which when -- passed 3, returns a function that when passed 4 returns -- 9.
...this is one of the more elementary exercises in overloading...
Because of this, the number of arguments must somehow be passed out-of-band;
...the type...
but then the type of the whole function (usually) must depend on the control parameter, requiring dependent types.
...of dependent walk you can mimic by hopping in Haskell.
module VarSum where
class VarSum t where varacc :: Int -> t
varsum :: VarSum t => t varsum = varacc 0
type Z = Int type S = (->) Int
instance VarSum Z where varacc a = a
instance VarSum t => VarSum (S t) where varacc a b = varacc (a + b)
Of course, you have to say stuff like varsum (2 :: Int) (3 :: Int) :: Int to determine the type at which the overloading happens. Or perhaps (varsum :: S (S Z)) 2 3 But there am I, proving your point. In Haskell, this sort of thing is a stunt. I'd much rather it was boring. All the best Conor