`Applicative []` on infinite lists

This is a non-terminating expression: repeat id <*> [].

The reason for this is that the Applicative [] instance is defined using list comprehensions:

instance Applicative [] where
    {-# INLINE pure #-}
    pure x    = [x]
    {-# INLINE (<*>) #-}
    fs <*> xs = [f x | f <- fs, x <- xs]
    {-# INLINE liftA2 #-}
    liftA2 f xs ys = [f x y | x <- xs, y <- ys]
    {-# INLINE (*>) #-}
    xs *> ys  = [y | _ <- xs, y <- ys]

The source code points to this Note by way of explanation:

Note: [List comprehensions and inlining]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The list monad operations are traditionally described in terms of concatMap:

xs >>= f = concatMap f xs

Similarly, mconcat for lists is just concat. Here in Base, however, we don’t
have concatMap, and we’ll refrain from adding it here so it won’t have to be
hidden in imports. Instead, we use GHC’s list comprehension desugaring
mechanism to define mconcat and the Applicative and Monad instances for lists.
We mark them INLINE because the inliner is not generally too keen to inline
build forms such as the ones these desugar to without our insistence. Defining
these using list comprehensions instead of foldr has an additional potential
benefit, as described in compiler/GHC/HsToCore/ListComp.hs: if optimizations
needed to make foldr/build forms efficient are turned off, we’ll get reasonably
efficient translations anyway.

This is a reasonable explanation for Monad [], but for Applicative [] it begs the question of why (something equivalent to) a concatMap-based implementation is desirable in the first place. A guarding clause on (<*>) and friends suffices to solve the problem:

instance Applicative [] where
  [] <*> _ = []  -- EDIT: added to prevent `[] <*> undefined` from becoming an error
  _ <*> [] = []
  fs <*> xs = [f x | f <- fs, x <- xs]
  -- etc.

I’m sure this was proposed by someone at some point in the history of Haskell. But has anyone written up why it’s inferior to what we have? Is it list fusion? If so, it’s because (<*>) would no longer be a ‘good consumer’ of its second argument, but it would still be a good consumer of its first and a ‘good producer’ overall, right? (I have been looking for an adequate definition of these hinted-at terms and have come up empty.) In what circumstances does this difference matter?

Could the desired list fusion properties be restored with this (edited to start from the actual desugaring of the list comprehension; edited again to handle [] <*> undefined)?

fs <*> xs =
  build (\c n ->
    foldr (\f b1 ->
      foldr (\_ _ ->
        foldr (\x b2 -> c (f x) b2) b1 xs
      ) n xs
    ) n fs
  )

Or is that not how it works?

If a one-clause list comprehension implementation is better for other reasons, could GHC do an ApplicativeDo-like analysis on list comprehensions (that is, detect cases where later source lists don’t depend on earlier ones) and produce code for [f x | f <- fs, x <- xs] that surely terminates if either fs or xs is empty? What are the trade-offs here?

2 Likes

Huh, this is surprising to me. What’s the actual desugaring of the comprehension then?

GHC seems to use two separate code paths for desugaring, neither of which I have a particularly strong grasp of, but they both exhibit this behavior (which makes sense in the general case of desugaring list comprehensions in which later source lists do depend on the elements of earlier ones).

The two desugarings have a high-level description:

“Normal”:

TE << [ e | qs ] >>  =  TQ << [ e | qs ] ++ Nil (typeOf e) >>

(Rule C)
TQ << [ e | ] ++ L >> = Cons (typeOf e) TE <<e>> TE <<L>>

(Rule B)
TQ << [ e | b , qs ] ++ L >> =
    if TE << b >> then TQ << [ e | qs ] ++ L >> else TE << L >>

(Rule A')
TQ << [ e | p <- L1, qs ]  ++  L2 >> =
  letrec
    h = \ u1 ->
          case u1 of
            []        ->  TE << L2 >>
            (u2 : u3) ->
                  (( \ TE << p >> -> ( TQ << [e | qs]  ++  (h u3) >> )) u2)
                    [] (h u3)
  in
    h ( TE << L1 >> )

"h", "u1", "u2", and "u3" are new variables.

“Fold/build”:

TE[ e | ]            c n = c e n
TE[ e | b , q ]      c n = if b then TE[ e | q ] c n else n
TE[ e | p <- l , q ] c n = let
                                f = \ x b -> case x of
                                                  p -> TE[ e | q ] c b
                                                  _ -> b
                           in
                           foldr f n l

So the fold/build desugaring of <*> would be:

build (\c n -> foldr (\ f b1 -> foldr (\ x b2 -> c (f x) b2) b1 xs) n fs)
1 Like

This looks like it does two passes over xs. That seems inefficient.

It does look like that, but the outer ‘pass’ only runs for one step.

I don’t have benchmarks backing me up, though.

Or, here’s the same concept, but starting from the nice desugaring you’ve kindly provided:

fs <*> xs = build (\c n -> foldr (\_ _ -> foldr (\ f b1 -> foldr (\ x b2 -> c (f x) b2) b1 xs) n fs) n xs)

Might be better?

1 Like

This would make the Applicative instance not satisfy the requirement that

m1 <*> m2 = m1 >>= (\x1 -> m2 >>= (\x2 -> return (x1 x2)))

Why not? This is non-terminating in GHCi:

repeat id >>= (\x1 -> [] >>= (\x2 -> return (x1 x2)))

Right, and therefore making repeat id <*> [] terminate, as I would like to do, would break that law.

I don’t know how concerned we should be over that, honestly. Class laws are often a little fuzzy in the limiting cases of non-terminating or infinite inputs, and this violation in particular simply allows more programs to terminate with morally correct results.

Slightly more concerning in my mind is the case of [] <*> undefined, which currently is not an error and should not become one (as it does with the implementations I’ve tossed out above). Could fix that with one more clause (or renesting the foldr) checking for empty lists on the first argument first, but things are starting to get complicated.

Based on this remark:

…some “semantic peculiarity” is to be expected - had Applicative arrived before Monad perhaps matters would be different, with the new monadic code having to work with existing applicative code.

Okay, but regardless of how anyone feels about AMP, I’m interested in the question of whether and why this particular Applicative has the semantics we think are best. ‘Because it’s a superclass of Monad’ isn’t enlightening; that plus ‘it’s important that the law relating (<*>) and (>>=) be not just “morally correct” but also exactly correct with respect to termination on infinite inputs, and this is why…’ would be.

Special-casing particular arguments to <*> when the list comprehension would have handled it seems suspicious from the mathematical viewpoint. A path to potentially introduce law-breaking behaviour. The more pressing question in my eyes is then: Why don’t we special case list comprehension itself? So, would we not want

[expr x y ... z | x <- ...,  z <- []]

to always be the empty list? It seems right from a combinatorics point of view.

1 Like

I don’t know how concerned we should be over that, honestly. Class laws are often a little fuzzy in the limiting cases of non-terminating or infinite inputs, and this violation in particular simply allows more programs to terminate with morally correct results.

I don’t know if that justifies it.

After all, liftA2 is just one case. You could say that liftA3 should also result in [] given [] as the third argument. Following this line of reasoning, we would need to have all possible liftAn in the class, and each function would need to inspect each argument for []. Edit: This wouldn’t be required.

Here’s my attempt at justifying the current behaviour. The type [()] is the type of natural numbers, and repeat () is infinity. The operator *> which is derived from <*> behaves like multiplication. So with repeat () *> [] you are essentially asking to multiply infinity by zero. Do you want that to be zero, and if yes, what justification is there for that choice?

2 Likes

You’ll get that for free given the modified semantics for liftA2 and (<*>).

1 Like

Because [] *> repeat () is []. It depends on how you extend multiplication past the naturals whether you believe it should remain commutative or not, so I’m skeptical of using that as an intuition pump.

1 Like

Indeed, [()] is topologically the one-point compactification of the natural numbers, and multiplication can be extended to it in a continuous and commutative way by making zero times infinity be zero. The other total option, infinity, renders multiplication non-continuous.

Another intuition (equally dismissable as contrived): Arbitrary non-empty unions of empty sets are empty. This is what repeat id <*> [] tries to compute: an infinite concatenation of empty lists. Since the general concatenation operator itself can not be sure that the infinite list of lists doesn’t somewhere contain a non-empty list, it can not decide on the constructor of the result. Only the <*> itself has access to that information.

So yes, I agree that (_:_) <*> [] should be [].

2 Likes

So what about backwards compatibility ? If the F-A-M would have forced the rewrite of most Haskell codebases, it would have never happened.

Like it or not, Monad arrived first in Haskell. Therefore Applicative had to be adapted to work in that context - it’s the principle of least surprise in action. So the changes you’re interested in also have to work in that context, too.

Now as @janus noted earlier:

repeat id >>= (\x1 -> [] >>= (\x2 -> return (x1 x2)))

…also doesn’t terminate. So could (>>=) for lists be more lazy in some way?

xs >>= f = [y | x <- xs, y <- f x]

Hmm - it uses a list comprehension too! As (also) mentioned earlier:

Then both Monad, Applicative for lists (and list comprehensions everywhere else) would benefit…if it doesn’t break most, or all of that existing code.

It does, but the expression f x depends on the earlier list in this case, where it does not in the definition of (<*>). That’s the important difference: in the (<*>) case, if the second list is empty once, it’s always empty. There are no gains to be had for (>>=) here, because of that dependency (not without asking the compiler to do some deep interprocedural optimization, anyway).

I’m all for making the change at the level of list comprehensions instead of in the Applicative instance. We would just need to alter the desugaring rules to support short-cutting through parts of the comprehension when a source expression or predicate doesn’t depend on the most recently bound variables. That would leave Monad unaffected.

To elaborate on solving this from within list comprehensions: focusing on the fold/build desugaring (the other one is more complicated but conceptually similar, I think), I’d start by adding this function somewhere in userspace:

foldrOrElse :: (a -> b -> b) -> b -> b -> [a] -> b
foldrOrElse _ _ z0 []       = z0
foldrOrElse f z _  (x : xs) = f x (foldr f z xs)

Then in the desugaring rules, I’d replace the n metaparameter currently holding a variable with a stack holding variables and predicates that report at what level of the comprehension a given variable is bound.

data NStack = Bottom Var | Push (Var -> Bool) Var NStack

top :: NStack -> Var
top (Bottom v) = v
top (Push _ v _) = v

break :: Expr -> NStack -> Var
break _ (Bottom v) = v
break e (Push pred v ns) | any pred fvs = v
                         | otherwise = break e ns
  where
  fvs = (free variables in e)

push :: Pattern -> Var -> NStack -> NStack
push p = Push (`elem` bvs)
  where
  bvs = (variables bound by p)

And then the new rules would be:

TE[ e | ]            c ns = c e $(top ns)
TE[ e | b , q ]      c ns = if b then TE[ e | q ] c ns else $(break b ns)
TE[ e | p <- l , q ] c ns =
  let
       f = \ x b -> case x of
                         p -> TE[ e | q ] c $(push p b ns)
                         _ -> b
  in
  foldrOrElse f $(top ns) $(break l ns) l