In the ongoing attempts to improve list literal syntax, one thing that comes up sometimes is the idea to use layout instead of brackets.

However, one thing that doesn't seem to come up is that this is already sort of supported—by using the QualifiedDo extension. This allows you to write

list :: [Int]
list = List.do
  1
  2
  3
  []

Below, we'll explore how to make that work, for lists and tuples. It can be easily extended to any other data structure that has a cons-like operation, e.g. heterogeneous lists or Data.Sequence.

Lists

The basic idea of QualifiedDo is this: A M.do-block is desugared into >> and >>= as usual, but instead of using the operators in Prelude, GHC looks for M.>> and M.>>=. In particular, there is no rule that the types of these operators must have any kind of stucture resembling Monad, though that is the intended use-case.

You could come up with some interesting things to do with >>=/<-, but I don't really have a good idea in this case, and will stick to just defining >>.

A do-block like do a; b; c is desugared into a >> (b >> c). Conveniently, the operator we're interested in in this case, (:), is right-associative, matching that structure. This also means, though, that if you want to use layout for something left-associative, you're essentially out of luck.

But since that's not us, the code we need is really simple:

module Layout.List where
  (>>) = (:)

Then, you can import and use it like this:

{-# LANGUAGE QualifiedDo #-}
        
import qualified Layout.List as List

list = List.do
  1
  2
  3
  []

Yes, you do need the [] at the end. That's a bit of a shame, but when I tried to get rid of it using a class-based approach, I ran into two major obstacles:

Which is one reason why it might still make sense to pursue a native layout-based solution.

Tuples

Tuples don't really have a cons-like operation like lists do with (:). But we can make one. Since tuples have fundamentally different types, the operator will need to be part of a class, so we can overload it:

{-# LANGUAGE TypeFamilyDependencies #-}

module TupleLayout where
import Data.Tuple

class ConsTuple a tup where
  type ConsedTuple a tup = tup' | tup' -> a tup
  (>>) :: a -> tup -> ConsedTuple a tup

The result type ConsedTuple is a type family that is intended to tell us what happens when you prepend an a to the tuple type tup. (I added the injectivity annoation tup' -> a tup after Solonarv in Discord suggested it may lead to better type inference - I haven't run into such a case yet, but it does at least produce more straightforward error messages sometimes).

For the base case, we need to think about what happens when you prepend an element to the empty tuple. It might be tempting to say that the result is just the element itself, but that could become problematic, since any type would be a "tuple type" and we'd need a very general instance ConsTuple a b, which is unpleasant to work with in terms of type inference and instance selection. Instead, we'll use the one-element tuple type that GHC provides, Solo.

instance ConsTuple a () where
  type ConsedTuple a () = Solo a
  a >> () = MkSolo a

From there, we just need to add more instances:

instance ConsTuple a (Solo b) where
  type ConsedTuple a (Solo b) = (a, b)
  a >> MkSolo b = (a, b)

instance ConsTuple a (b, c) where
  type ConsedTuple a (b, c) = (a, b, c)
  a >> (b, c) = (a, b, c)

instance ConsTuple a (b, c, d) where
  type ConsedTuple a (b, c, d) = (a, b, c, d)
  a >> (b, c, d) = (a, b, c, d)

I'll stop here, but ideally you'd go all the way to tuples of size 64, the largest size supported by GHC.

Since the operator is already named >>, we don't need to separately define >> in this case, we can simply use it as is, like so:

{-# LANGUAGE QualifiedDo, BlockArguments #-}

import qualified Layout.Tuple as Tuple

main = print Tuple.do
  42
  "foo"
  13.5e72
  ()

This will output (42, "foo", 1.35e72).

And that's it! You can find the full code (including all 64 tuple instances) here.


Update (2024-06-12): There is some related prior art here.