[jhc] darcs patch: src/Support/Inst.hs: don't define instances present in...
John Meacham
john at repetae.net
Tue May 13 22:14:26 UTC 2014
Cool. thanks. I was actually wondering why those instances didn't
exist as they seemed pretty obvious and I almost made them
conditional. I'll modify your patch to be an actual feature check with
the HAS_TRAVERSABLE_TUPLE check.
On Tue, May 13, 2014 at 11:20 AM, Sergei Trofimovich
<slyfox at community.haskell.org> wrote:
> 1 patch for repository http://repetae.net/repos/jhc:
>
> Tue May 13 21:19:19 FET 2014 Sergei Trofimovich <slyfox at community.haskell.org>
> * src/Support/Inst.hs: don't define instances present in ghc-7.8
>
> [ 85 of 183] Compiling Support.Inst ( src/Support/Inst.hs, src/Support/Inst.o )
>
> src/Support/Inst.hs:7:10:
> Duplicate instance declarations:
> instance [overlap ok] Foldable ((,) a)
> -- Defined at src/Support/Inst.hs:7:10
> instance Foldable ((,) a) -- Defined in 'Data.Foldable'
>
> src/Support/Inst.hs:9:10:
> Duplicate instance declarations:
> instance [overlap ok] Traversable ((,) a)
> -- Defined at src/Support/Inst.hs:9:10
> instance Traversable ((,) a) -- Defined in 'Data.Traversable'
>
>
> [src/Support/Inst.hs: don't define instances present in ghc-7.8
> Sergei Trofimovich <slyfox at community.haskell.org>**20140513181919
> Ignore-this: 846e90c9a24c9eccc5c7358078529a72
>
> [ 85 of 183] Compiling Support.Inst ( src/Support/Inst.hs, src/Support/Inst.o )
>
> src/Support/Inst.hs:7:10:
> Duplicate instance declarations:
> instance [overlap ok] Foldable ((,) a)
> -- Defined at src/Support/Inst.hs:7:10
> instance Foldable ((,) a) -- Defined in 'Data.Foldable'
>
> src/Support/Inst.hs:9:10:
> Duplicate instance declarations:
> instance [overlap ok] Traversable ((,) a)
> -- Defined at src/Support/Inst.hs:9:10
> instance Traversable ((,) a) -- Defined in 'Data.Traversable'
> ] hunk ./src/Support/Inst.hs 1
> +{-# LANGUAGE CPP #-}
> module Support.Inst where
>
> import Control.Applicative
> hunk ./src/Support/Inst.hs 8
> import Data.Foldable
> import Data.Traversable
>
> +#if __GLASGOW_HASKELL__ < 708
> instance Foldable ((,) a) where
> foldMap = foldMapDefault
> instance Traversable ((,) a) where
> hunk ./src/Support/Inst.hs 13
> traverse f (x,y) = (,) x <$> f y
> +#endif
>
> instance Functor ((,,) a b) where
> fmap = fmapDefault
>
>
--
John Meacham - http://notanumber.net/
More information about the jhc
mailing list