Direction of Composition

One way to do function composition in Haskell is using the (.) operator.
Something like

foo = bar . baz
-- which reads like
-- foo x = bar (baz x)

Which is commonly referred to as “backwards composition”. Meaning the flow of information goes backwards, when an x fills the spot, the result can be used as the argument for bar.

Another way to compose functions is using the & (or >>> for arrows) operator, akin to |> in some languages, which is forward composition.

foo' x = x & baz & bar
-- which reads like
-- foo' x = bar (baz x)

Which, notably, has the direction of information going forwards.

Given this, I wonder why we use backwards composition? Is it because it’s more akin to mathematics, which makes mathematical algorithms perhhaps easier to translate? Is it because it’s easier to make things point-free using backwards composition? Maybe it’s closer to how you’d compose functions without (.)? Or is there some sort of inherent problem with forwards composition that I don’t know about?

IMO, forwards composition which feels like a pipeline, is much more natural for me to read and write. I really do prefer it, but most people using backwards composition in Haskell is making me wonder if there’s something I’m missing out on.

4 Likes

I “grew up” with . in Haskell, there was no & (or at least not as readily available as . was/is from Prelude). Hence I learned to read foo = bar . baz as foo is bar of baz (of x). I guess one could read foo x = x & baz & bar as foo of x is x and then baz and then bar or something similar, but to me that’s more complicated. I rather “unpeel” the whole thing vs. looking at it as if it’s a list of steps, if that makes sense.

Also, it allows for point-free code, reducing the need to name things.

1 Like

Hm. Yeah, I’ve guessed that it could be because backwards composition allows pointfree easier. In something like Agda with mixfix, you could define this as

foo = (_ & bar & baz)

I believe, but I’m not quite sure.
I personally read it “foo of x is x piped to bar piped to baz”, because of it’s pipeline-y nature.
You could omit the “piped” part, like: “x to bar to baz”, which also feels natural to me.
…but, given that most people in the Haskell community actively disencourage point-free because of it’s fringe nature and, usually, it not helping readability, I don’t think pointfree is really the reason.

I guess the reason could be that people are used to using (.), and using (&) would be unreadable (it would be way better if it’s changed to |>, where can I suggest that?) and also not very commonly known or used, rather than preferring backwards composition to forwards composition.

Nevertheless, if people still have opinions about forwards vs backwards composition in Haskell, I’d love to hear them.

1 Like

They discourage pointfree astronauts, map ((+1) . length) ["foo", "bar"] is perfectly readable and common occourrence.

In my opinion if you end up with a long sequence of functions, be it with . or >>>, you should consider refactoring.

5 Likes

Some FP literature uses a semicolon ; for left-to-right composition, e.g. Maarten Fokkinga’s Law and Order in Algorithmics. Unfortunately, that symbol is already reserved in Haskell.

On the other extreme, some people turn everything around including arrows in the type signature such that it all lines up again:

(.) :: (c <- a) <- (c <- b, b <- a)

(It doesn’t work well with currying hence the uncurried type)

1 Like

I’d say, backwards composition is the most common amongs programming languages. For example, lets consider the following code

def foo(x: int) -> int:
  return (x + 1)

# haskell: foo x = x + 1

def bar(y: int) -> int:
 return (y*2)

# haskell: bar x = x * 2

w = foo(bar(3))

# haskell: w = foo . bar $ 3

As you can see the order of functions is the same in Python (and any other imperative-ish lang) as it is in Haskell. Probably because composition is all about passing to some function the result of another.

Depending on the context one direction migth be prefered. Consider this two bash commands. Both are idiomatic way to pipe in bash.

# forwards. ouput of ls is passed to grep's input
ls | grep "something"

# backwards. output of cat is the input of while
while read i;
 do echo $i; 
done < <(cat $filepath)

So honestly, I don’t see the point of “forwards” being more natural than “backwards” as both directions seem to be natural depending on the context.

2 Likes

Most of the examples here are using functions with a single argument. With more than one, forwards composition needs you to read the expression in both directions:

length xs = xs & (foldr (const (+ 1)) 0)

Q to the floor: are there combinators such that I can write the whole of that rhs in ‘forward’ mode? In general we don’t know how many arguments there might be, or whether some sub-function is partially applied (const, (+) in that example).

2 Likes

What do you think of this:

Implementation:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}

type family Fun xs r where
  Fun '[] r = r
  Fun (x : xs) r = x -> Fun xs r

data Args xs where
  N :: Args '[]
  Cons :: x -> Args xs -> Args (x : xs)

infixr 2 &|

(&|) :: x -> Args xs -> Args (x : xs)
(&|) = Cons

infixr 1 &*

(&*) :: Args xs -> Fun xs y -> y
N &* x = x
Cons x xs &* f = xs &* f x

infixl 3 &

(&) :: a -> (a -> b) -> b
x & f = f x
length xs = 1 & (+) & const &| 
                          0 &|
                         xs &|
                          N &* foldr

Here’s a picture:

  ┌───────────────────────────────────────────────────────────────┐
  │                                                               │
  │  ┌────────┐    ┌───────┐    ┌─────────┐                       │
  │  │        │    │       │    │         │                       │
  │  │   1    ├───►│   +   ├───►│  const  ├───┐                   │
  │  │        │    │       │    │         │   │                   │
  │  └────────┘    └───────┘    └─────────┘   │                   │
  │                                           │                   │
  │                               ┌───────┐   │   ┌──────────┐    │
  │                               │       │   │   │          │    │
  │                               │   0   ├───┼───┤  foldr   ├────┼─►
  │                               │       │   │   │          │    │
  │                               └───────┘   │   └──────────┘    │
  │                                           │                   │
──┼───────────────────────────────────────────┘                   │
  │                                length                         │
  └───────────────────────────────────────────────────────────────┘
2 Likes

Ugh! Thanks: an excellent demo :wink: for O.P.'s " is there some sort of inherent problem with forwards composition?".

3 Likes

One hypothetical way to do this is via a concatenative DSL in Haskell. It would work similarly to

length xs = [ xs (const (+1)) 0  ] foldr

but otherwise, I don’t really know of a simple enough way. My mind screams “arrows” when looking at it but I don’t really know how I can use arrows to make it work. That said, I think I understand the reasoning a bit better way. For a non-concatenative language, a backwards flow of information is probably way more sensible than a forwards one, especially when it comes to partial application and higher order functions.
Though, I guess it’s another question if concatenative languages are still as readable.
Thank you very much, everyone!

2 Likes

My Haskell-addled brain is screaming ‘square brackets mean list’, and ‘space-separator means apply’. But that can’t be a list because the elements are at different types. Then round parens and comma separators?

length xs = ( xs, (const (+1)), 0  ) foldr

At least the terms are legit Haskell syntax.

Aside: you’ve chopped about the order of args. Shouldn’t they also be consistently ‘backwards’?

Thinking of comma separators … There’s some stack-based languages that use reverse Polish notation. (Forth, POP-2 come to mind.) One of them uses commas within an expression to flag: don’t evaluate this sub-term yet (maybe it’s a section); push it onto the stack; something later will take it as argument. So maybe (again there’s the question of ordering args)

length xs =  xs, (1 +, const), 0   foldr

Unlike many languages, Haskell tries to minimise its number of reserved words with fixed meaning. IOW it has to parse terms and figure out what is applying to what without knowing the arity of the lexemes. Maybe the program has a local definition of const; maybe it turns out the xs dummy arg to length is a function. So it doesn’t worry about arities until type-checking; and it doesn’t know if some lexeme is partially applied. (After all, a function of two arguments is treated as a function of one arg that returns a function that takes another arg.)

With that bash example, I suspect bash knows which args to which commands are streams/files, so it knows grep needs a string arg to make a term it can pass a stream through.

1 Like

I’d say, backwards composition is the most common amongs programming languages.

I don’t think it is as clear-cut, many programming languages have forward composition.

Take for example iterators from rust:

fibonacci().skip(4).take(4)

In object oriented languages, forward composition is also quite common. Take streams from java:

 List<Employee> employees = Stream.of(empIds)
      .map(employeeRepository::findById)
      .collect(Collectors.toList());

Or builder patterns, etc…


Most of the examples here are using functions with a single argument. With more than one, forwards composition needs you to read the expression in both directions:
length xs = xs & (foldr (const (+ 1)) 0)

I think appropriate line breaks make this even more readable, comparatively to how iterators in rust and streams in java look like:

length xs = xs
  & foldr (const (+1)) 0

Looks even more readable to me, since now, the reading direction is from top-left to bottom-right, which is in English rather natural, imo.

While I like this style very much, I admit that it depends on the context what is more readable, and sometimes I rewrite one style to the other.

3 Likes

But that’s really a mixed direction. Full forward composition would be:

()fibonacci.(4)skip.(4)take

To me it looks more like a top to bottom, right to left direction. Which I guess is better than having to switch directions inside one line.

1 Like

Fair enough, then I am arguing in favour of mixed composition direction.

2 Likes

Good point! I was refering to functions in a impertive-ish context. Certanly, OO approach of retuning the same object after calling a method is a form of forward composition.

Nevetheless at the end of the day it is a program specific decision. Sometimes is better to use backwards composition because the important part is the last function applied, which appears first if backwards. Sometimes it is just the other way around.

Pretty much the same discusion as let .. in .. vs where, or >>= vs =<<

-- Sometimes g is read better than f. Sometimes, isn't
f = getArgs >>= someComputation
g = someComputation =<< getArgs 
2 Likes

True enough. Human languages have ways to switch round the order of ‘sub-terms’ in a sentence, according to the ‘given vs new’ information content, or ‘topic-comment’ dialogue. So this is to benefit the human readers of the code, not the compiler.

2 Likes

I think this is a matter of taste and there’s no right way to do it. Having said that, I don’t think it’s fair to say that the mathematical shorthand for y(x) = f (g (x)) being y = f . g is “backwards”. It actually preserves the f and g in their original order. :slight_smile: That’s why it exists in the first place…

5 Likes

I should note that the thread is about the flow of information in composition, and in this case composition seems to have a forward flow of information. Meaning fibonnaci get’s passed to the input of skip and gets passed to the input of take. Marginally in this thread I don’t really care about the flow of information of function application, though I do believe something like bla 1 is nicer for me to read than 1 bla

And also, that’s why I call (.) “backwards” composition. As I said in the original thread, it has a backwards flow of information because the variable comes in at the end to fill the function which fills the function behind it. With &, the information comes in from the front and fills the function after it.
…though, I did mention how it’s close to composing functions normally… it’s just I wonder if there exists any sort of problem with forward composition. I think you guys definitely mentioned some good cases for some problems with it, but I think that if there would be an alternative style of forwards composition in Haskell, it could possibly have none of the issues that were pointed out. But I think that’s just me being optimistic for no reason.

2 Likes

Note that the OOP fibonacci example has no function composition in it: fibonacci().skip(4) is just the application (or more accurately method call) of .skip(4) to fibonacci().

1 Like

It seems to me that forward composition reads well when we are doing iterative process, like “Compute a as A, then b to be B, after that the result is computed from C”.

Not all of such process is impure, and you cannot just use State monad since the type of a “state” could change as well.
I wonder what would be the good way to handle this case.

Why is it bad practice to use Identity monad for forward flow?

1 Like