Re: [Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread Joel Koerwer

Thanks for the link. So many variations on a theme:
   n-vars to a list : Oleg's solution for polyvariadic functions
   list + n-adic function -> value : This thread
   list of (n_i)-adic functions + argument -> list of (n_i-1)-adic
functions : The link you gave.

The first two had very similar answers, and I have a feeling the third
could be answered with yet another application of the same idea.

As I see it, the answer given in that link amounts to wrapping the
function so that it will fit in a homogeneous list. The user still has
to wrap their functions with multiple 'cook's.

Joel

On 10/5/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

This came up a while ago (but with a list of functions of
different arities, all being fed one argument).  I found
Scott Turner's pure Haskell 98 solution very illuminating:


http://www.haskell.org/pipermail/haskell-cafe/2000-November/001332.html

Regards,
Tom


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread tpledger
Joel Koerwer wrote:
> Let's say I want to evaluate a function of type
> (a->a->...->a->a), taking the arguments from a
> list. If know the function ahead of time, I can
> simply wrap it:
>
> foo a b c d = ...
> wrapFoo (a:b:c:d:_) = foo a b c d
>
> But, as an exercise, I challenged myself to write
> a function, multApply :: (a->a->...->a->a) -> [a]
> -> a, that automatically does the wrapping for any
> such function.

This came up a while ago (but with a list of functions of
different arities, all being fed one argument).  I found
Scott Turner's pure Haskell 98 solution very illuminating:

   
http://www.haskell.org/pipermail/haskell-cafe/2000-November/001332.html

Regards,
Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread Joel Koerwer

Thanks!

Don pointed me to Oleg's page too. I *was* (90%) convinced that this
is fundamentally different, but it sure looks similar. Kind of an
inside-out polyvariadic function. Any given f only takes n args, but
myApply doesn't know the value of n. In fact, a polyvariadic f would
cause an infinite loop. At least a stack overflow.

Always nice to know you're in good company though.

Cheers,
Joel

On 10/4/06, David House <[EMAIL PROTECTED]> wrote:

Nice work! I haven't tried it out, but you seem to have on the right
trick here: typeclass hackery. An interesting related exercise to
develop a similar function using Template Haskell [1]. Also of note
might be Oleg's writings on true polyvariadic functions [2].

[1]: http://haskell.org/th
[2]: http://okmij.org/ftp/Haskell/types.html#polyvar-fn

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread David House

On 04/10/06, Joel Koerwer <[EMAIL PROTECTED]> wrote:

I'm posting my solution in hopes to learn from your comments. This
solution uses fundeps, multi-parameter classes, and overlapping
instances. Note that I don't actually understand these things! :)


Nice work! I haven't tried it out, but you seem to have on the right
trick here: typeclass hackery. An interesting related exercise to
develop a similar function using Template Haskell [1]. Also of note
might be Oleg's writings on true polyvariadic functions [2].

[1]: http://haskell.org/th
[2]: http://okmij.org/ftp/Haskell/types.html#polyvar-fn

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mission: To take args from a list... generally

2006-10-04 Thread Joel Koerwer

Haskellers,

Let's say I want to evaluate a function of type (a->a->...->a->a),
taking the arguments from a list. If know the function ahead of time,
I can simply wrap it:

foo a b c d = ...
wrapFoo (a:b:c:d:_) = foo a b c d

But, as an exercise, I challenged myself to write a function,
multApply :: (a->a->...->a->a) -> [a] -> a, that automatically does
the wrapping for any such function.

On #haskell Don Stewart suggested I look at printf, but I've yet to
put much thought into whether that method will work here.

I'm posting my solution in hopes to learn from your comments. This
solution uses fundeps, multi-parameter classes, and overlapping
instances. Note that I don't actually understand these things! :)

 MultApply.hs --
{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}

module MultApply where

class MultApply func arg | func -> arg where
   multApply :: func -> [arg] -> arg

instance MultApply (a->a) a where
   multApply f (x:xs) = f x
   multApply f _  = error "MultApply: one too few args"

instance MultApply cascade a => MultApply (a -> cascade) a where
   multApply f (x:xs) = multApply (f x) xs
   multApply f _  = error "MultApply: n too few args"


-- some random examples
oneArg = multApply sqrt [25..]
twoArg = multApply (+) [1..]
fiveArg = multApply (\a b c d e -> sqrt ((a+b)^2+(d-e)^2)-5*c) [13..]

---End File 

Results in ghci:

*MultApply> oneArg
5.0
*MultApply> fiveArg
-47.981487827787404

To compose your own examples in ghci, you'll need
-fallow-overlapping-instances on the command line.

Cheers,
Joel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe