[Haskell-cafe] Newbie: Applying Unknown Number Arguments to A Partial Function

Greg Buchholz greg at sleepingsquirrel.org
Fri May 19 17:19:25 EDT 2006


Aditya Siram wrote:
] I am trying to write a function 'applyArguments' which takes a function and 
] a list and recursively uses element each in the list as an argument to the 
] function. I want to do this for any function taking any number of arguments.
] 
] applyArgument f (arg) = f arg
] applyArgument f (arg:args) = applyArgument (f arg) args
] 
] This has failed in Hugs, so my question is: Can I conceptually do this? If 
] so, what is the type signature of this function?

    It seems like it should be doable, but I'm not enough of a Haskell
wizard to figure it out.  But here is my thought process, FWIW.  First
off, since you want it to work for *any* function, we know that it can't
use lists, since in Haskell all list elements have to have the same
type.  Nested tuples, like (1,("foo",(3.14,Nil))) can have elements of
arbitrary types, so that's a possibility for the container storing the
function's arguments.  Next we'll note that the return type of
"applyArgument" can be different depending on the input argument types.
For example, lets invent a function and some possible argument
"lists"...

    foo x y z = x + y + z
    one = (1,Nil)
    two = (1,(2,Nil))
    three = (1,(2,(3,Nil)))

...so the type of "applyArgument foo three" would be Integer, while the
type of "applyArgument foo two" would be Integer->Integer, and the type
of "applyArgument foo one" would be Integer->Integer->Integer.  But
Haskell doesn't allow a single function to different types.  What we can
do though, is define an infinite family of functions which have
different types, but share the same name.  That is the purpose of type
classes.  Here's a fun example that I like...

    instance Num a => Num [a] where
        (+) = zipWith (+)

...that little snippet says that whenever we have a list of type "a"
(the [a]), where a is also in the class Num, then we can add two of
those lists together.  So now something like "[1,2,3]+[4,5,6]" is legal.
But that also happens to be a recursive definition since a list like
[1,2,3] is now also in class Num.  So things like...

    [[1,2,3],[4,5,6]] + [[7,8,9],[0,1,2]]
    [[[[[[1,2,3]]]]]] + [[[[[[4,5,6]]]]]]

...will also work.  Now here is where I run into trouble.  The code
below is what I think you should be able to do to define "applyArgument"
(shortened to "app"), but it doesn't quite work, failing with a type
error...

  Illegal instance declaration for `Apply (a -> b) b (a, c)'
      (the instance types do not agree with the functional dependencies of the class)
  In the instance declaration for `Apply (a -> b) b (a, c)'

...Maybe someone can chime in to correct me, or point out the flaw in my
thinking.

> {-# OPTIONS -fglasgow-exts #-} 
> data Nil = Nil  -- A type to terminate our nested tuples
> 
> class Apply a b c | b->c where
>     app :: (a->b) -> (a,c) -> b
>     
> -- base case: ran out of arguments, so stop recursion
> instance Apply a b Nil where
>     app f (x,Nil)  = f x
>     
> -- recursive case: If types a, b, and c are member of the 
> --  class Apply, then the types (a->b), b, and (a,c) are
> --  also a member, so keep going...
> instance Apply a b c => Apply (a->b) b (a,c) where
>     app f (x,rest) = app (f x) rest
> 
> g w x y z = w*x + y*z
> args = (1,(2,(3,(4,Nil))))
> 
> main = print $ app g args 


Greg Buchholz



More information about the Haskell-Cafe mailing list