<p dir="ltr"><br>
On Dec 30, 2015 10:05 PM, <<a href="mailto:amindfv@gmail.com">amindfv@gmail.com</a>> wrote:<br>
> 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`).</p>
<p dir="ltr">The best I've found is to use `where` profusely:</p>
<p dir="ltr">```<br>
things<br>
  = [ foo<br>
    , bar<br>
    , baz<br>
    ]<br>
  where<br>
    foo = _<br>
    bar = _<br>
    baz = _<br>
```</p>
<p dir="ltr">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.</p>
<p dir="ltr">Now, if you want some of them at the top level, you do this ugly thing:</p>
<p dir="ltr">```<br>
(<br>
  foo,<br>
  bar,<br>
  things<br>
  ) = (<br>
    foo,<br>
    bar,<br>
    things<br>
  )<br>
  where<br>
    things<br>
      = [ foo<br>
        , bar<br>
        , baz<br>
        ]<br>
    foo = _<br>
    bar = _<br>
    baz = _<br>
```</p>
<p dir="ltr">Just don't get the order wrong on the tuples for things with the same types.  Welp!</p>
<p dir="ltr">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.</p>
<p dir="ltr">You could also define a record:</p>
<p dir="ltr">```<br>
{-# LANGUAGE RecordWildCards #-}</p>
<p dir="ltr">data R<br>
  = R<br>
    { foo :: {- something -}<br>
    , bar :: {- something else -}<br>
    , things :: {- stuff -}<br>
    }</p>
<p dir="ltr">R {..} = R {..} where<br>
  foo = _<br>
  bar = _<br>
  baz = _<br>
  things<br>
    = [ foo<br>
      , bar<br>
      , baz<br>
      ]<br>
```</p>
<p dir="ltr">This costs you explicit type signatures in the record declaration, but `-Wall` would ask for those on toplevel bindings anyway.</p>
<p dir="ltr">I don't think this could be solved easily with syntax; consider</p>
<p dir="ltr">```<br>
things x = foo@(x, x + 1)<br>
```</p>
<p dir="ltr">`foo` can't be made toplevel easily.</p>