[Haskell-cafe] MRP, 3-year-support-window, and the non-requirement of CPP

Herbert Valerio Riedel hvr at gnu.org
Tue Oct 6 16:47:08 UTC 2015


On 2015-10-06 at 10:10:01 +0200, Johan Tibell wrote:
[...]
>> You say that you stick to the 3-major-ghc-release support-window
>> convention for your libraries. This is good, because then you don't need
>> any CPP at all! Here's why:
>>
>> [...]
>>
>
> So what do I have to write today to have my Monad instances be:
>
>  * Warning free - Warnings are useful. Turning them off or having spurious
> warnings both contribute to bugs.

Depends on the warnings. Some warnings are more of an advisory kind
(hlint-ish). I wouldn't consider redundant imports a source of
bugs. Leaving off a top-level signature shouldn't be a source of
correctness bugs either. Also, warnings about upcoming changes
(i.e. deprecation warnings) also are not necessarily a bug, but rather a
way to raise awareness of API changes.

At the other end of the spectrum are more serious warnings I'd almost
consider errors, such as failing to define a non-defaulting method or
violating a MINIMAL pragma specification, as that can lead to bottoms
either in the form of runtime errors or even worse, hanging computations
(in case of cyclic definitions).

IMO, GHC should classify its warnings into severities/categories or
introduce some compromise between -Wall and not-Wall.

>  * Use imports that either are qualified or have explicit import lists -
> Unqualified imports makes code more likely to break when dependencies add
> exports.
>  * Don't use CPP.

That being said, as how to write your Monad instances today with GHC
7.10 w/o CPP, while supporting at least GHC 7.4/7.6/7.8/7.10: This
*does* work (admittedly for an easy example, but this can be
generalised):


--8<---------------cut here---------------start------------->8---
module MyMaybe where

import Control.Applicative (Applicative(..))
import Prelude (Functor(..), Monad(..), (.))
-- or alternatively: `import qualified Prelude as P`

data Maybe' a = Nothing' | Just' a

instance Functor Maybe' where
    fmap f (Just' v) = Just' (f v)
    fmap _ Nothing'  = Nothing'

instance Applicative Maybe' where
    pure = Just'
    f1 <*> f2   = f1 >>= \v1 -> f2 >>= (pure . v1)

instance Monad Maybe' where
    Nothing' >>= _  = Nothing'
    Just' x  >>= f  = f x

    return = pure -- "deprecated" since GHC 7.10

--8<---------------cut here---------------end--------------->8---

This example above compiles -Wall-clean and satisfies all your 3 stated
requirements afaics. I do admit this probably not what you had in mind.

But to be consistent, if you want to avoid unqualified imports at all
costs in order to have full control of what gets imported into your
namespace, you shouldn't tolerate an implicit unqualified wildcard
`Prelude` import either. As `Prelude` can, even if seldom, gain new
exports as well (or even loose them -- `interact` *could* be a candidate
for removal at some point).


> Neither AMP or MRP includes a recipe for this in their proposal.

That's because -Wall-hygiene (w/o opting out of harmless) warnings
across multiple GHC versions is not considered a show-stopper.

In the specific case of MRP, I can offer you a Wall-perfect transition
scheme by either using `ghc-options: -fno-mrp-warnings` in your
cabal-file, or if that doesn't satisfy you, we can delay phase1
(i.e. redundant return-def warnings) to GHC 8.2:

Now you can continue to write `return = pure` w/o GHC warning bothering
you until GHC 8.2, at which point the 3-year-window will reach to GHC
7.10.

Then starting with GHC 8.2 you can drop the `return` definition, and
keep your 


More generally though, we need more language-features and/or
modifications to the way GHC triggers warnings to make such
refactorings/changes to the libraries -Wall-perfect as well.

Beyond what Ben already suggested in another post, there was also the
more general suggestion to implicitly suppress warnings when you
explicitly name an import. E.g.

  import Control.Applicative (Applicative(..))
 
would suppress the redundant-import warning for Applicative via Prelude,
because we specifically requested Applicative, so we don't mind that
Prelude re-exports the same symbol.


> AMP got one post-facto on the Wiki. It turns out that the workaround
> there didn't work (we tried it in Cabal and it conflicted with one of
> the above requirements.)

Yes, that unqualified `import Prelude`-last trick mentioned on the Wiki
breaks down for more complex imports with (redundant) explicit import
lists.

However, the Maybe-example above works at the cost of a wordy
Prelude-import, but it's more robust, as you pin down exactly which
symbol you expect to get from each module.



> The problem by discussions is that they are done between two groups with
> quite a difference in experience. On one hand you have people like Bryan,
> who have considerable contributions to the Haskell ecosystem and much
> experience in large scale software development (e.g. from Facebook). On the
> other hand you have people who don't. That's okay. We've all been at the
> latter group at some point of our career.
[...]

At the risk of stating the obvious: I don't think it matters from which
group a given argument comes from as its validity doesn't depend on the
messenger. Neither does it matter whether an argument is repeated
several times or stated only once. Also, every argument deserves to be
considered regardless of its origin or frequency.


-- hvr


More information about the Haskell-Cafe mailing list