Newbie: Applying Unknown Number Arguments to A Partial Function

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? Deech

You can't do this in Haskell, if you try to type the function
carefully, you'll know the reason.
Shiqi
On 5/18/06, Aditya Siram
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?
Deech
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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?
Deech
You can't do that, but there are other tricks that do work: http://okmij.org/ftp/Haskell/types.html which describes "Functions with the variable number of (variously typed) arguments" and "Genuine keyword arguments" -- Chris

Chris, the subject states clearly that Aditya is a Newbie, and is most likely just trying to define the function "map". So I think pointing to a bunch of advanced type magic tricks is not really helpful. Aditya, you say you want the function applyArgument to take a function and a list and apply the function to all elements of that list. The result of "applyArgument" is a list, with the results of applying the function to each element. So you want the type of "applyArgument" to be: applyArgument :: (a->b) -> [a] -> [b] There are a numbers of errors in your code. applyArgument f (arg) = f arg The variable "f" is the first parameter of "applyArgument", and has type (a -> b) The variable "arg" is the second parameter of "applyArgument", and has type [a] . You try to apply "f" to a list which is not ok. Most likely you meant "[arg]", which is a singleton list, instead of "(arg)", which is the same as just "arg" Furthermore "applyArgument" returns a list of result. The function "f" only yields a "b", instead of a list "[b]" The following does work: applyArgument f [arg] = [f arg] In your second line: applyArgument f (arg:args) = applyArgument (f arg) args you use a list pattern "(arg:args)", which is good. The variable "arg" is the head of the list, and the variable "args" is the tail of the list. So "arg" has type "a", and "args" has type "[a]" . The application "(f arg)" has type "b". Because the function "applyArgument" expects a function as first argument and not a "b", so this is wrong. I guess you can find out by your self how to fix this. There are a number of very good tutorials for beginners on http://haskell.org . Finally your function won't work for empty lists, it is only defined for singleton lists and longer lists. You can fix this by replacing the definition for singleton lists with a definition for the empty list. The pattern for empty list is simply "[]". Good luck, Arthur On 19-mei-06, at 10:10, Chris Kuklewicz wrote:
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?
Deech
You can't do that, but there are other tricks that do work:
http://okmij.org/ftp/Haskell/types.html
which describes "Functions with the variable number of (variously typed) arguments" and "Genuine keyword arguments"
-- Chris _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

My apologies to Chris, I think I misinterpreted Aditya's description. Thanks to David House for telling me. I thought he was describing a function such as map instead of "polyvaric functions", which would have been more likely for a "newbie" :-) So to answer Aditya's question, whether you can do this in Haskell. The short answer is "no". You cannot do this in plain Haskell. However using various extensions to Haskell, you can indeed use the smart "tricks" as Chris pointed out: http://okmij.org/ftp/Haskell/types.html Cheers, Arthur On 19-mei-06, at 11:24, Arthur Baars wrote:
Chris, the subject states clearly that Aditya is a Newbie, and is most likely just trying to define the function "map". So I think pointing to a bunch of advanced type magic tricks is not really helpful.
Aditya, you say you want the function applyArgument to take a function and a list and apply the function to all elements of that list. The result of "applyArgument" is a list, with the results of applying the function to each element.
So you want the type of "applyArgument" to be: applyArgument :: (a->b) -> [a] -> [b]
There are a numbers of errors in your code. applyArgument f (arg) = f arg The variable "f" is the first parameter of "applyArgument", and has type (a -> b) The variable "arg" is the second parameter of "applyArgument", and has type [a] . You try to apply "f" to a list which is not ok. Most likely you meant "[arg]", which is a singleton list, instead of "(arg)", which is the same as just "arg" Furthermore "applyArgument" returns a list of result. The function "f" only yields a "b", instead of a list "[b]"
The following does work: applyArgument f [arg] = [f arg]
In your second line: applyArgument f (arg:args) = applyArgument (f arg) args you use a list pattern "(arg:args)", which is good. The variable "arg" is the head of the list, and the variable "args" is the tail of the list. So "arg" has type "a", and "args" has type "[a]" . The application "(f arg)" has type "b". Because the function "applyArgument" expects a function as first argument and not a "b", so this is wrong. I guess you can find out by your self how to fix this. There are a number of very good tutorials for beginners on http://haskell.org .
Finally your function won't work for empty lists, it is only defined for singleton lists and longer lists. You can fix this by replacing the definition for singleton lists with a definition for the empty list. The pattern for empty list is simply "[]".
Good luck,
Arthur
On 19-mei-06, at 10:10, Chris Kuklewicz wrote:
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?
Deech
You can't do that, but there are other tricks that do work:
http://okmij.org/ftp/Haskell/types.html
which describes "Functions with the variable number of (variously typed) arguments" and "Genuine keyword arguments"
-- Chris _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello, You can do it -- but it may not be very useful in its current form. The primary problem is, "What is the type of 'f'?"
applyArgument f [arg] = f arg -- NOTE: I changed (arg) to [arg] applyArgument f (arg:args) = applyArgument (f arg) args
Looking at the second line, it seems that f is a function that takes a value and returns a function that takes a value and returns a function that takes a value, etc. Something like: f :: a -> (a -> (a -> (a -> ...))) This is called an 'infinite type' and is not allowed in haskell (or ocaml by default) because it allows you to introduce type errors that the compiler can not catch: http://groups.google.com/group/comp.lang.functional/browse_thread/thread/364... If you introduce a wrapper type, you can make the type checker happy: newtype F a = F { unF :: a -> F a } applyArgument :: F a -> [a] -> F a applyArgument (F f) [arg] = f arg applyArgument (F f) (arg:args) = applyArgument (f arg) args Of course, your final result is still something of type 'F a' -- so it is probably not very useful -- because all you can do is apply it more more things of type a and get more things of type 'F a'. One option would be to modify the function to return a result and a continuation: newtype F a = F { unF :: a -> (a, F a) } applyArgument :: F a -> [a] -> a applyArgument (F f) [arg] = fst (f arg) applyArgument (F f) (arg:args) = applyArgument (snd (f arg)) args Then you define a function like this (a simple sum function in this case): f :: (Num a) => a -> (a, F a) f a' = (a', F $ \a -> f (a + a')) example usage: *Main> applyArgument (snd (f 0)) [1,2,3] 6 Here is another variation that allows for 0 or more arguments instead of 1 or more: newtype F a = F { unF :: (a, a -> F a) } applyArgument :: F a -> [a] -> a applyArgument (F (result, _)) [] = result applyArgument (F (_ , f)) (arg:args) = applyArgument (f arg) args f :: (Num a) => a -> F a f a' = F (a', \a -> f (a + a')) j. At Fri, 19 May 2006 02:25:31 +0000, 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?
Deech
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On May 19, 2006, at 2:49 PM, Jeremy Shaw wrote:
Hello,
You can do it -- but it may not be very useful in its current form. The primary problem is, "What is the type of 'f'?"
applyArgument f [arg] = f arg -- NOTE: I changed (arg) to [arg] applyArgument f (arg:args) = applyArgument (f arg) args
Looking at the second line, it seems that f is a function that takes a value and returns a function that takes a value and returns a function that takes a value, etc. Something like:
f :: a -> (a -> (a -> (a -> ...)))
This is called an 'infinite type' and is not allowed in haskell (or ocaml by default) because it allows you to introduce type errors that the compiler can not catch:
http://groups.google.com/group/comp.lang.functional/browse_thread/ thread/3646ef7e64124301/2a3a33bfd23a7184
If you introduce a wrapper type, you can make the type checker happy:
newtype F a = F { unF :: a -> F a }
applyArgument :: F a -> [a] -> F a applyArgument (F f) [arg] = f arg applyArgument (F f) (arg:args) = applyArgument (f arg) args
Of course, your final result is still something of type 'F a' -- so it is probably not very useful -- because all you can do is apply it more more things of type a and get more things of type 'F a'.
One option would be to modify the function to return a result and a continuation:
newtype F a = F { unF :: a -> (a, F a) }
applyArgument :: F a -> [a] -> a applyArgument (F f) [arg] = fst (f arg) applyArgument (F f) (arg:args) = applyArgument (snd (f arg)) args
Then you define a function like this (a simple sum function in this case):
f :: (Num a) => a -> (a, F a) f a' = (a', F $ \a -> f (a + a'))
example usage:
*Main> applyArgument (snd (f 0)) [1,2,3] 6
This seems like it is just an ugly way to spell 'foldl'. Is there something fundamentally different about this approach, besides the slightly odd typing? I understand its relation to the OP, but I'm just curious now...
Here is another variation that allows for 0 or more arguments instead of 1 or more:
newtype F a = F { unF :: (a, a -> F a) }
applyArgument :: F a -> [a] -> a applyArgument (F (result, _)) [] = result applyArgument (F (_ , f)) (arg:args) = applyArgument (f arg) args
f :: (Num a) => a -> F a f a' = F (a', \a -> f (a + a'))
j.
At Fri, 19 May 2006 02:25:31 +0000, 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?
Deech
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

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

Greg Buchholz wrote:
instance Apply a b c => Apply (a->b) b (a,c) where
Whoops, instead of that, I think I meant... instance Apply (b->c) c d => Apply (a->b->c) (b->c) (a,d) where ...where we strip off one layer of types, because of the recursion. Of course, that still doesn't work though. Greg Buchholz

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? OK, here's a program that is similar to your applyArgument. Instead of the arguments in a list, it stores them in a nested tuple, so that we can have different types of arguments. You'll have to use the "-98" option when using Hugs. Also, it doesn't seem to interact well with type inference, so I had to provide type signatures for the function "f" and some of the parts of "args". Anyone know of a better way to define Apply so we could eliminate these type signatures?
{-# OPTIONS -fglasgow-exts #-}
class Apply x y z | x y -> z where apply :: x -> y -> z
instance Apply (a->b) a b where apply f x = f x
instance Apply b as c => Apply (a->b) (a,as) c where apply f (x,xs) = apply (f x) xs
f :: Int -> Double -> String -> Bool -> Int f x y z True = x + floor y * length z f x y z False= x * floor y + length z
args = (1::Int,(3.1415::Double,("flub",True)))
main = print $ apply f args
participants (8)
-
Aditya Siram
-
Arthur Baars
-
Chris Kuklewicz
-
Greg Buchholz
-
Greg Buchholz
-
Jeremy Shaw
-
Robert Dockins
-
Shiqi Cao