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

Greg Buchholz haskell at sleepingsquirrel.org
Tue May 30 18:15:10 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?

    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 




More information about the Haskell-Cafe mailing list