[Haskell-cafe] Imports at bottom, why not?

Ben Foppa benjamin.foppa at gmail.com
Tue Apr 22 18:04:56 UTC 2014


Why not have an editor that collapses them?


On Tue, Apr 22, 2014 at 1:59 PM, Thiago Negri <evohunz at gmail.com> wrote:

> When reading code, I find it quite distracting to have to get past the
> import list to reach the actual module code, as the import list can be (and
> often is) quite big.
>
> So, why not issue import statements at the bottom of a module file?
>
> Likewise, we can use "where" statements to define names used in a function
> after using them, so they don't distract the reader.
>
> I'm against imports at the middle of the file.
> But I guess being able to issue them at the end of the module could make
> sense if you want to get the reader straight to the code.
>
> A language pragma could be used to select between top imports or bottom
> imports (can't use both).
>
> What do you think?
>
> Example:
>
> """
> {-# LANGUAGE LateImports #-}
> module Foo where
>
> bar :: String
> bar = "quux"
>
> baz :: Fiz
> baz = mkFiz
>
> import Fiz (Fiz, mkFiz)
> """
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140422/5258855f/attachment.html>


More information about the Haskell-Cafe mailing list