Appending code to a module via script is a valid use case, but then you just use top imports. This doesn't make a point towards forbidding bottom imports.
The point is: there are a number of reasons to do top imports and another number of reasons to do bottom imports. I think bottom imports could be very useful. Even literate Haskell could read better with bottom imports, in my opinion.
On 23 April 2014 04:28, Niklas Haas <haskell@nand.wakku.to> wrote:
> On Tue, 22 Apr 2014 14:59:44 -0300, Thiago Negri <evohunz@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)
>> """
>
> A practical reason is that this lets you process modules dependency
> graphs without ever analyzing the structure past the import list.
Also so when you're reading the code you have an idea up-front of what
kind of external modules it might be using; otherwise - especially if
the names are generic (e.g. "Parser") or using some form of overloaded
extension (e.g. OverloadedStrings) - you might not be able to tell as
easily the behaviour of the code.
After all, two different parser libraries might behave differently
(how they deal with backtracking is usually a big difference), and if
you see someone using OverloadedStrings with ByteStrings then you know
to be more careful about the code if using characters not expressable
in a single byte.
Whilst I doubt this is a common use-case in practice, it's also
possible someone might want to add some code to a file using a shell
script: if the imports are at the top you can just append it; if the
imports are at the bottom you have to be more careful.
--
Ivan Lazar Miljenovic
Ivan.Miljenovic@gmail.com
http://IvanMiljenovic.wordpress.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe