wawa
wawa

Reputation: 5084

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.

Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?

Example:

module Foo where
    import Data.List

    foo :: Int -> Int -> Int -> Int
    foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])

Upvotes: 4

Views: 1687

Answers (2)

Ignat Insarov
Ignat Insarov

Reputation: 4832

With all respect, I would disagree with @leftaroundabout's answer above. Something being unusual is not a reason to shun it as unworthy.

It is correct that you would not be able to define a polymorphic variadic list constructor without type annotations. However, we're not usually dealing with Haskell 98, where type annotations were never required. With Dependent Haskell just around the corner, some familiarity with non-trivial type annotations is becoming vital.

So, let's take a shot at this, disregarding worthiness considerations.


One way to define a function that does not seem to admit a single type is to make it a method of a suitably constructed class. Many a trick involving type classes were devised by cunning Haskellers, starting at least as early as 15 years ago. Even if we don't understand their type wizardry in all its depth, we may still try our hand with a similar approach.

Let us first try to obtain a method for summing any number of Integers. That means repeatedly applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do it:

class Eval a where
    eval :: Integer -> a

instance (Eval a) => Eval (Integer -> a) where
    eval i = \y -> eval (i + y)

instance Eval Integer where
    eval i = i

And this is the extract from repl:

λ eval 1 2 3 :: Integer
6

Notice that we can't do without explicit type annotation, because the very idea of our approach is that an expression eval x1 ... xn may either be a function that waits for yet another argument, or a final value.

One generalization now is to actually make a list of values. The science tells us that we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to a list, then sum it and obtain the same result as above.

Here's how we can go about turning arguments of our method to a list:

class Eval a where
    eval2 :: [Integer] -> Integer -> a

instance (Eval a) => Eval (Integer -> a) where
    eval2 is i = \j -> eval2 (i:is) j

instance Eval [Integer] where
    eval2 is i = i:is

This is how it would work:

λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]

Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two different things: a (possibly empty) list of values and the next value to put in. Notice how it's similar to the usual foldr:

λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]

The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit tricky, as we have to make Eval a 2-parameter type class:

class Eval a i where
    eval2 :: [i] -> i -> a

instance (Eval a i) => Eval (i -> a) i where
    eval2 is i = \j -> eval2 (i:is) j

instance Eval [i] i where
    eval2 is i = i:is

It works as the previous with Integers, but it can also carry any other type, even a function:

(I'm sorry for the messy example. I had to show a function somehow.)

λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]

So far so good: we can convert any number of arguments into a list. However, it will be hard to compose this function with the one that would do useful work with the resulting list, because composition only admits unary functions − with some trickery, binary ones, but in no way the variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:

class Ap a i r where
    apply :: ([i] -> r) -> [i] -> i -> a
    apply', ($...) :: ([i] -> r) -> i -> a
    ($...) = apply'

instance Ap a i r => Ap (i -> a) i r where
    apply f xs x = \y -> apply f (x:xs) y
    apply' f x = \y -> apply f [x] y

instance Ap r i r where
    apply f xs x = f $ x:xs
    apply' f x = f [x]

Now we can write our desired function as an application of a list-admitting function to any number of arguments:

foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
    where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
          g = f . sort

You'll still have to type annotate it at every call site, like this:

λ foo' 4 5 10 :: Integer
-1

− But so far, that's the best I can do.

 


The more I study Haskell, the more I am certain that nothing is impossible.

Upvotes: 4

leftaroundabout
leftaroundabout

Reputation: 120751

is there a general way of doing this independent of the number of arguments?

Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.

Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).

That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:

{-# LANGUAGE FlexibleInstances         #-}

class UsingList f where
  usingList :: ([Int] -> Int) -> f

instance UsingList Int where
  usingList f = f []

instance UsingList r => UsingList (Int -> r) where
  usingList f a = usingList (f . (a:))

foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort

It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!

Upvotes: 6

Related Questions