Parameter order

From HaskellWiki
Revision as of 15:13, 25 February 2008 by Lemming (talk | contribs) (functionally dependent parameters)
Jump to navigation Jump to search

The parameter order of Haskell functions is an important design decision when programming libraries. The parameter order shall

  • allow piping,
  • be consistent across similar functions.

Motivation

= Application

Parameters in Haskell are rather reversed compared to imperative or object oriented languages. In an object oriented language, the object to work on is the very first parameter. In a function call it is often written even before the function name, say file in file.write("bla"). Strictly spoken, in Haskell it is not possible to alter objects, but there are many functions which return a somehow altered input object. This object should be the last parameter because then you can compose a sequence of operations on this object using the function composition operator .. The code

sum . map f . filter p . scanl (*) 1

describes a function, which applies three transformations to a list. This can be written so easily because the list is always the last parameter.

The order of the parameters except the last one is not so critical. However you should keep in mind that also transformations on functions are perfectly ok in Haskell. That's why function operators like the differentiation and integration in functional analysis should have the parameter of the derived/integrated function at the last position and the transformed function should be the parameter before the last one.

integrate :: a -> (a -> a) -> (a -> a)
integrate f0 f x = ...

differentiate :: a -> (a -> a) -> (a -> a)
differentiate h f x = ...

-- continuous extension, aka function limit
continuous :: (a -> a) -> (a -> a)
continuous f x = ...

exampleTransform = differentiate h . continuous


The third thing to consider is that it is easily possible to fix parameters, which are at the beginning. E.g.

sum = foldl (+) 0
product = foldl (*) 1

that's why we can consider the parameter order of foldl to be a good one. We also see in this example that it is easily possible to generate a function with the first parameters fixed and that functions shall be prepared for this.

Consider two parameters sampleRate :: Double and signal :: [Double], where the sample rate functionally depends on the signal, that is every signal has a unique sampling rate. You will make sampleRate the first parameter and signal the second parameter, because there are more signals with the same sampling rate, but only one sample rate per signal. This makes it more likely that you want to fix the sampling rate than to fix the signal parameter. (You might not want to organize the sampling rate and the signal in one record, because an operation like mixing processes multiple signals, but all with the same sampling rate.)


Implementation

Also for the implementation of a function the order of parameters count. If you do a case analysis on a parameter, this one should be the last function parameter. Function parameters that are handled the same way for all cases should be first. If you use case instead of pattern matching on function parameters, a carefully chosen parameter order can simplify the implementation, and this order should also be prefered. Say, you want to know which of the signatures

formatMsg :: String -> Maybe Int -> String
formatMsg :: Maybe Int -> String -> String

shall be used. The implementation might be

formatMsg :: String -> Maybe Int -> String
formatMsg msg Nothing  = msg ++ "\n"
formatMsg msg (Just n) = msg ++ " " ++ show n ++ "\n"

If you use case instead, you can factor out common parts of the implementation.

formatMsg :: String -> Maybe Int -> String
formatMsg msg mn =
   msg ++
     (case mn of
        Nothing -> ""
        Just n  -> " " ++ show n) ++
   "\n"

You can even omit the parameter you apply the case analysis to.

formatMsg :: String -> Maybe Int -> String
formatMsg msg =
   (msg ++) . (++ "\n") . maybe "" (\n -> " " ++ show n)


Bad examples

Sometimes library writers have infix usage of functions in mind. See for instance Data.Bits and Cons of syntactic sugar. Unfortunately the order of arguments to infix operators, which seems to be natural for many programmers, is reversed with respect to the one we encourage above. Maybe this only indicates that parameter order should be reverse, at all, meaning that the name of the called function comes after the arguments (Reverse Polish Notation).

The operators (-), (/), (^), (^^), (**), div, mod (used as a `div` b, a `mod` b) are adaptions of the mathematical tradition. However when using section, in most cases the first argument is omitted. This strongly indicates that their parameter order is unnatural in the Haskell sense. However, for the subtraction there also exists subtract, which is better for partial application.

There are more cases where there is even no simple reason, why the parameter order was chosen in an unnatural way.

  • Data.Map.lookup :: (Monad m, Ord k) => k -> Map k a -> m a
  • Data.Map.findWithDefault :: Ord k => a -> k -> Map k a -> a
  • Data.Map.lookupIndex :: (Monad m, Ord k) => k -> Map k a -> m Int
  • Data.Map.findIndex :: Ord k => k -> Map k a -> Int

Since objects of type Map represent mappings, it is natural to have some function which transforms a Map object to the represented function. All of the functions above do this in some way, where Data.Map.findWithDefault is certainly closest to the ideal Map->Function transformer.

See the type
flip (Data.Map.findWithDefault deflt) :: Ord k => Map k a -> (k -> a)
.

Unfortunately the parameters are ordered in a way that requires a flip for revealing this connection. Maybe the library designer immitated the signature of Data.List.lookup here.


Context

Say a set of your functions works within a certain context. You have a function which run these functions within that context.

startSound :: (SoundServer -> IO a) -> IO a

You wonder whether to make the SoundServer context the first or the last parameter of according sound functions. Since a context is something that varies not very frequently it should be the first parameter.

play :: SoundServer -> Sound -> IO ()

This way it is easy to play a sequence of sounds, say

startSound (\server -> mapM_ (play server) [soundA, soundB, soundC])   .

On the other hand the parameter order

play' :: Sound -> SoundServer -> IO ()

simplifies the calls to single sound functions:

startSound (play' soundA)    .

In this case we should actually make the context the last argument, but hide it in a Reader monad.

type SoundAction a = ReaderT SoundServer IO a

playM :: Sound -> SoundAction ()
playM = ReaderT . play'

startSoundM :: SoundAction a -> IO a
startSoundM = startSound . runReaderT

This way, both of the above examples become equally simple.

startSoundM (mapM_ playM [soundA, soundB, soundC])
startSoundM (playM soundA)

Note: Instead of f :: a -> b -> Reader r c you could also use the signature f :: Reader r (a -> b -> c) which gets us back to the parameter order proposed initially. Currently this prohibits reasonable commenting with Haddock, but this should be fixed in future. I have to think more carefully about it.


The rule of thumb

What do we learn from all this considerations?

The more important the parameter, the more frequently it changes, the more it shall be moved to the end of the parameter list. If there is some recursion involved, probably the parameter, which you recurse on, is the one which should be at the last position. If parameter b functionally dependends on parameter a, then b should be before a.