Are varargs functions discouraged in haskell?

I have read online that it is nontrivial to create functions with a variable number of arguments. Does this mean that it is not good practice to write them? Should the function accept a list instead?
Suppose I have a function of the type:

myFun f a1 a2 a3 ...    -- min 2 args (f and a1)

Should I make MyFun capable of accepting varargs or should I make it accept only f and [a]?
What is better in haskell?

1 Like

Yes, you should avoid varargs. Accepting a list is much easier.

But that is only possible if all the arguments have the same type. If the arguments have different types, then you might consider defining some combinators instead. The most common example of that are the <$> and <*> combinators which can be combined to take an arbitrary number of arguments:

f <$> x
f <$> x <*> y
f <$> x <*> y <*> z
...
8 Likes

Keep it simple.

f :: NonEmpty a -> Int or f :: a -> [a] -> Int are valid options too, if you want to make sure with types the function is never called without a mandatory a.

1 Like

Thank you for your answers

What if I wanted to do something like this instead?

myFun f a1 a2 a3 =
    (f a1 a2 a3, strangeComputation a1 a3)

where:
– myFun takes f, a1, a2, a3
– f takes all a1, a2, a3
– strangeComputation takes only some of the a
– a1, a2, a3 can have different types or be of the same type
How can I make it so that MyFun can take an arbitrary number of a?

Can you be more specific about your use case? This is an unusual pattern to say the least; in particular, how is myFun going to decide which arguments to pass to strangeComputation?

This is my type:

import Numeric.AD
---
data Measurement a = Measurement !a !a

This is how I calculate a function on my type:

sqrtDiff :: Floating a => (forall a1. Floating a1 => a1 -> a1) -> a -> a -> a
sqrtDiff f a b = sqrt ((b**2) * diff f a ** 2)
newMeasurement :: Floating a => (forall a1. Floating a1 => a1 -> a1) -> Measurement a -> Measurement a
newMeasurement f (Measurement c d) = Measurement (f c) (sqrtDiff f c d)

If I have a = Measurement 3.0 0.1 and I want to compute the exponential I write: newMeasurement exp a.


If I want to compute a function with more than 1 argument I can’t. I have to write another function, here an example with a function with 2 args.

nM :: Floating a => (forall a1. Floating a1 => [a1] -> a1) -> Measurement a -> Measurement a -> Measurement a
nM f (Measurement a b) (Measurement c d) = Measurement (f [a, c]) (sqrt (((g !! 0) * b)**2 + ((g !! 1) * d)**2))
                                                where g = grad f [a, c]

If I want to compute a function with 3 args I have to write another function.

1 Like

Thanks, that’s much clearer.

Since you’re depending on the functionality of ad here, which works with functions that operate on homogeneous traversable structures (like lists, for example), you should probably do the same with your API. Something like this should do:

nM :: (Floating a, MonadZip f, Traversable f) => (forall a1. Floating a1 => f a1 -> a1) -> f (Measurement a) -> Measurement a
nM f measurements =
  case grad' f (fmap measFst measurements) of
    (a, das) -> Measurement a (sqrt (sum (fmap (** 2) (mzipWith (*) (fmap measSnd measurements) das))))
  where
  measFst (Measurement a _) = a
  measSnd (Measurement _ a) = a

You could easily specialize this to fixed numbers of arguments as conveniences, and there are a couple of ways to do that, but you will be writing a function per number of arguments that you want to support that way. (All the real math will live in nM, at least.)

2 Likes

A low-tech way to do what you want could be tuples.

-- assuming e.g. strangeComputation :: Int -> String -> Bool
-- f needs to take a tuple, not curried args

myFun ::
  -- fn w/ 'variable' input
  (a -> b) ->
  -- fn's input
  a ->
  -- projection from fn's input to strangeComputation's 1st input.
  (a -> Int) ->
  -- projection from fn's input to strangeComputation's 2nd input.
  (a -> String) ->
  -- (f output, strangeComputation output)
  (b, Bool)
myFun f x g h = (f x, strangeComputation (g x) (h x))

-- call like
myFun f (a1, a2, a3) (\(a1, _, _) -> a1) (\(_, _, a3) -> a3)
2 Likes

tend to agree that :

myFun :: F -> [Measure] -> R
myFun f mx = mconcat $ map f mx

Depends does the logic you want fit Monoid ? If you can’t define it recursively then I don’t think there is a way around 1 defn per arity.

myFun f [x] = ...
myFun f [x, y] = ... 
1 Like

Can you give me an example?
How would you write a function that takes many numbers and calculates the sum of them?


If I were to emulate a varargs function I would write something like this (in julia):

function my_vararg_sum(acc, x)
    if x == nothing
        return acc
    else
        return y -> my_vararg_sum(acc + x, y)
    end
end
# and then I call
my_vararg_sum(0, 1)(34)(6)(1)(nothing) # 42

This seems functional style, why doesn’t it work in haskell?

It is functional (and can be achieved with some type class tricks) but what would be its type signature ? (In Haskell, everything has a type. If you write something that the compiler can’t figure the type of, then it is invalid Haskell …)

1 Like

You can use lists as suggested and there is already a function for that:

> sum [0, 1, 34, 6, 1]
42

Or the combinator approach, which for addition of numbers is hundreds of years old:

> 0 + 1 + 34 + 6 + 1
42

I guess one tricky thing is that you throw in a nothing at the end. That’s not easy to do. You could introduce a new addition operator that allows you to add maybes onto integers:

(+.) :: Int -> Maybe Int -> Int
(+.) x (Just y) = x + y
(+.) x Nothing = x

And then write:

> 0 + 1 + 34 + 6 + (1 +. Nothing)

(We can even get rid of those parentheses if we write a proper fixity declaration.)

But this example sounds a bit to contrived to really see what the right solution is.

1 Like

Correct :



Furthermore, what would be the type of this “definition” ?

ignore _ = ignore
1 Like

None of the other replies mentioned the printf trick. So there you go, if you really, really want a variadic function a-la Julia, you can use that.

That said, unless you’re making a highly specific EDSL, using data structures is generally a better approach, at least because it’s a lot easier to fold/traverse data structures.

In the specific example above you can, reasonably speaking, introduce a type class and implement newMeasurement as a “method” of that type class, with one instance per operation arity, provided the computation is the same for all operations of the same arity.

That being said, as far as I can tell, you’re implementing a system for tracking measurement errors across computations. If you only intend to use standard math (i.e. methods in Floating and superclasses) on Measurement, simply directly implementing Num, Fractional and Floating for the Measurement type shouldn’t be out of the question.


Edit: in the interest of transparency, the initial version of this post contained the following passage:

Side note, unless you’re not showing something huge, you don’t need rank-2 polymorphism there.

sqrtDiff :: Floating a => (a -> a) -> a -> a -> a
newMeasurement :: Floating a => (a -> a) -> Measurement a -> Measurement a

Given your implementations, these types behave largely the same in the end, but are a lot easier on the eyes.

This would be correct, if not for ad, which wants rank-2 polymorphism.

1 Like

ha and now we’re back to the original question :slight_smile:

EDIT: OP, perhaps you might want to define the instances again, and just make newMeas, newMeas2, newMeas3 helpers for each arity you need. It’s a bit more boilerplate, but at least you won’t be exposing it to users

1 Like

Oh, that other question clarifies things even more. So you want to be able to use normal math operations with your Measurement types, but you want them to propagate their errors using the ad library, and the polymorphism in the interface to ad is making this difficult.

The way I would probably do this is by deferring the actual math inside the definition of Measurement. The direction you seem to be headed in that other question is towards doing this manually, by making your users wrap all of their computations in newMeasurement. But you can instead make Measurement quantify over the type of number it represents, and hold its dependencies instead of its error term, and only compute the error term when you finally want to leave the Measurement type.

Edit: The previous version of this code made it impossible to actually create raw Measurement objects with non-zero errors, which is obviously a problem. This new iteration shouldn’t have that issue.

Here’s what I mean:

data Measurement = Measurement (forall a. Floating a => (a, a))

runMeasurement :: Floating a => Measurement -> (a, a)
runMeasurement (Measurement thunk) = thunk

wrapMeasurement :: (forall a. Floating a => [a] -> a) -> [Measurement] -> Measurement
wrapMeasurement f deps = Measurement $ let
  (inputs, errors) = unzip (fmap runMeasurement deps)
  (a, das) = grad' f inputs
  in (a, sqrt (sum (fmap (** 2) (zipWith (*) errors das))))

wrap0 :: (forall a. Floating a => a) -> Measurement
wrap0 a = wrapMeasurement (\[] -> a) []

wrap1 :: (forall a. Floating a => a -> a) -> Measurement -> Measurement
wrap1 f ma = wrapMeasurement (\[a] -> f a) [ma]

wrap2 :: (forall a. Floating a => a -> a -> a) -> Measurement -> Measurement -> Measurement
wrap2 f ma mb = wrapMeasurement (\[a, b] -> f a b) [ma, mb]

instance Num Measurement where
  (+) = wrap2 (+)
  (-) = wrap2 (-)
  (*) = wrap2 (*)
  abs = wrap1 abs
  signum = wrap1 signum
  fromInteger i = wrap0 (fromInteger i)
  
instance Fractional Measurement where
  (/) = wrap2 (/)
  fromRational r = wrap0 (fromRational r)
  
instance Floating Measurement where
  pi = wrap0 pi
  exp = wrap1 exp
  log = wrap1 log
  sin = wrap1 sin
  cos = wrap1 cos
  asin = wrap1 asin
  acos = wrap1 acos
  atan = wrap1 atan
  sinh = wrap1 sinh
  cosh = wrap1 cosh
  asinh = wrap1 asinh
  acosh = wrap1 acosh
  atanh = wrap1 atanh

instance Show Measurement where
  show = show . runMeasurement
2 Likes

I am not yet able to quickly understand types in haskell. How can I create an object of the type Measurement you defined?
Can you show me how to use the type you defined?

No wonder you’re having trouble; I gave you a type that was only possible to create from terms with zero error! That’s probably not what you want. :sweat_smile:

I edited the post; the new iteration should be more intuitive too, but for completeness, your options are:

  • from a literal: 42 :: Measurement
  • from a variable holding a pure number: \(x :: Double) -> fromRational x :: Measurement
  • from a (value, error) pair (but these must be polymorphic, not concrete types like Double!): Measurement (value, error)
1 Like

I have a post on how to define an arity-generic function encompassing all of

liftA  f = \(a :: f a)                       -> pure f <*> a
liftA2 f = \(a :: f a) (b :: f b)            -> pure f <*> a <*> b
liftA3 f = \(a :: f a) (b :: f b) (c :: f c) -> pure f <*> a <*> b <*> c
...

in case you’re curious.

I use arity-generic functions occasionally (printf in particular, but sometimes custom ones, mostly to fit some updated code into an old API), but most of the time it’s just not worth it.

1 Like