[Haskell-cafe] How best to deal with Monoid/Applicative changes in 7.10 in a backwards-compatable way

Yuras Shumovich shumovichy at gmail.com
Wed Dec 24 15:51:37 UTC 2014


On Wed, 2014-12-24 at 09:49 -0500, Doug Burke wrote:
> I'm trying out the ghc 7.10 RC and am seeing lots of warnings about Monoid
> and some symbols from Control.Applicative - e.g.
> 
>     The import of ‘Data.Monoid’ is redundant
>       except perhaps to import instances from ‘Data.Monoid’
>     To import instances alone, use: import Data.Monoid()
> 
> For now I'm wrapping the import with some CPP so that it will still compile
> with older ghc versions (and a probably-pointless attempt to be
> non-ghc-specific, since I have never tested my code with other compilers):
> 
> #if (!defined(__GLASGOW_HASKELL__)) || (__GLASGOW_HASKELL__ < 710)
> import Control.Applicative (Applicative(pure), (<$>), (<*>))
> import Data.Monoid (Monoid(..))
> #else
> import Control.Applicative ((<$>))
> #endif
> 
> Is this the best way? Am I missing something really obvious?

I don't even have plans to adopt ghc-7.10 yet, so I don't know the best
way to handle that. But for similar issue I usually avoid CPP at use
side. It is better to make compatibility layer that hides all the CPP.

I successfully used that approach to handle `catch` removal from
`Prelude`. I have `Prelude.hs` visible to ghc with the next contents:


> {-# LANGUAGE PackageImports #-}
> {-# LANGUAGE CPP #-}
> 
> module Prelude
> (
> module P
> )
> where
> 
> #if MIN_VERSION_base(4,6,0)
> import "base" Prelude as P
> #else
> import "base" Prelude as P hiding (catch)
> #endif

I think the same trick can be used to handle AMP changes. E.g. you can
add "Control/Monad.hs" file that reexports `Control.Applicative`.

Probably you can avoid CPP altogether if you specify different
`hs-source-dirs` for different ghc versions in cabal file.

Thanks,
Yuras

> 
> Thanks,
> Doug
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list