[Haskell-cafe] Naming inner elements

Manuel Gómez targen at gmail.com
Thu Dec 31 03:16:57 UTC 2015


On Dec 30, 2015 10:05 PM, <amindfv at gmail.com> wrote:
> The major difference from just `foo = "thing1" ; things = [foo, ...` is
that it's much more visually clear which values are in `things` (imagine I
create a `baz` but forget to add it to `things`).

The best I've found is to use `where` profusely:

```
things
  = [ foo
    , bar
    , baz
    ]
  where
    foo = _
    bar = _
    baz = _
```

If you forget to define `baz` but include it in the list, you get an error
for a name not bound, and if you define it but forget to include it in the
list, you get an error with `-Wall -Werror` for an unused binding.

Now, if you want some of them at the top level, you do this ugly thing:

```
(
  foo,
  bar,
  things
  ) = (
    foo,
    bar,
    things
  )
  where
    things
      = [ foo
        , bar
        , baz
        ]
    foo = _
    bar = _
    baz = _
```

Just don't get the order wrong on the tuples for things with the same
types.  Welp!

It's a bit less awful if you always want all the items in e. g. a list
exported to the top level, as in your example, but this is a bit more
general.  It's still awful, but using tuples instead of list patterns
allows you heterogeneous toplevel exports and more structures than just
lists.

You could also define a record:

```
{-# LANGUAGE RecordWildCards #-}

data R
  = R
    { foo :: {- something -}
    , bar :: {- something else -}
    , things :: {- stuff -}
    }

R {..} = R {..} where
  foo = _
  bar = _
  baz = _
  things
    = [ foo
      , bar
      , baz
      ]
```

This costs you explicit type signatures in the record declaration, but
`-Wall` would ask for those on toplevel bindings anyway.

I don't think this could be solved easily with syntax; consider

```
things x = foo@(x, x + 1)
```

`foo` can't be made toplevel easily.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20151230/e227c3ba/attachment.html>


More information about the Haskell-Cafe mailing list