Generalizing function composition

The implementation of the legendary holla-holla-get-dolla operator
Published on October 17, 2014 under the tag haskell

TL;DR

In this blogpost I present a proof-of-concept operator $.$, which allows you to replace:

foo x0 x1 x2 ... xN = bar $ qux x0 x1 x2 ... xN

by:

foo = bar $.$ qux

Introduction

This is a literate Haskell file, which means you should be able to just drop it into GHCi and play around with it. You can find the raw .lhs file here. Do note that this requires GHC 7.8 (it was tested on GHC 7.8.2).

{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE TypeOperators        #-}
import Data.Char (toLower)

If you have been writing Haskell code for a while, you have undoubtedly used the $ operator to “wrap” some expression with another function, mapping over the result type. For example, we can “wrap” the expression toLower 'A' with print to output the result.

print $ toLower 'A'

It is not unlikely either to have functions that just wrap other functions, e.g.:

printLower :: Char -> IO ()
printLower x = print $ toLower x

If the function that is being wrapped (toLower in the previous example) has only one argument, the . operator allows writing a very concise definition of functions which just wrap those single-argument functions.

printLower' :: Char -> IO ()
printLower' = print . toLower

However, this gets tedious when the number arguments increases. Say that we have the following function which takes three arguments (don’t worry about the horrible implementation, but rather focus on the type):

-- | Formats a double using a simple spec. Doesn't do proper rounding.
formatDouble
    :: Bool    -- ^ Drop trailing '0'?
    -> Int     -- ^ #digits after decimal point
    -> Double  -- ^ Argument
    -> String  -- ^ Result
formatDouble dropTrailingZero numDigits double =
    let (pre, post) = case break (== '.') (show double) of
            (x, '.' : y) -> (x, y)
            (x, y)       -> (x, y)
        post'       = take numDigits (post ++ repeat '0')
        pre'        = case pre of
            '0' : x -> if dropTrailingZero then x else pre
            _       -> pre
    in pre' ++ "." ++ post'

We can wrap formatDouble using print by successively using the . operator, but the result does not look pretty, nor very readable:

printDouble :: Bool -> Int -> Double -> IO ()
printDouble = (.) ((.) ((.) print)) formatDouble

The $.$ operator

This makes one wonder if we can’t define an additional operator $.$ (pronounced holla-holla-get-dolla) which can be used like this:

printDouble' :: Bool -> Int -> Double -> IO ()
printDouble' = print $.$ formatDouble

Additionally, it should be generic, as in, it should work for an arbitrary number of arguments, so that we can also have:

printMax' :: Int -> Int -> IO ()
printMax' = print $.$ max
printLower'' :: Char -> IO ()
printLower'' = print $.$ toLower

From this, it becomes clear that the type of $.$ should be something like:

($.$)
    :: (a -> b)
    -> (x0 -> x1 -> ... -> xn -> a)
    -> (x0 -> x1 -> ... -> xn -> b)

The first question is obviously, can we write such an operator? And if we can, how generic is it?

When my colleague Alex asked me this question, I spent some time figuring it out. I previously thought it was not possible to write such an operator in a reasonably nice way, but after some experiments with the closed type families in GHC 7.8 I managed to get something working. However, the solution is far from trivial (and I now suspect more elegant solutions might exist).

A possible solution

Thanks to my colleague Alex for proofreading!

ce0f13b2-4a83-4c1c-b2b9-b6d18f4ee6d2