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

Herbert Valerio Riedel hvr at gnu.org
Wed Oct 7 07:35:21 UTC 2015


On 2015-10-06 at 19:41:51 +0200, Sven Panne wrote:
> 2015-10-06 18:47 GMT+02:00 Herbert Valerio Riedel <hvr at gnu.org>:
>
>> [...] 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`
>> [...]
>> --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.
>>
>
> OK, so the trick is that you're effectively hiding Applicative from the
> Prelude (which might be a no-op). This "works" somehow, but is not
> satisfactory IMHO for several reasons:

[...]

Btw, I've also seen the trick below, in which you use the aliased `A.`
prefix just once so GHC considers the import non-redundant, and don't
have to suffer from prefixed operators in the style of `A.<*>`.

Is this any better?

--8<---------------cut here---------------start------------->8---
import Control.Applicative as A (Applicative(..))

data Maybe' a = Nothing' | Just' a

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

instance A.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---

-- hvr  


More information about the Haskell-Cafe mailing list