I was going to merge the commit into the upstream containers repo but
couldn't find it here:

https://github.com/ghc/packages-containers/commits/master

On Wed, Jan 18, 2012 at 7:35 AM, Simon Peyton-Jones
<simo...@microsoft.com> wrote:
> Ian
>
> Fixed... but I had to add
>
> {-# OPTIONS_GHC -Wwarn #-}
>
> to containers:Data.Sequence
>
> because it contains stuff like
>
> {-# INLINE deep #-}
> {-# SPECIALIZE INLINE deep :: Digit (Elem a) -> FingerTree (Node (Elem a)) -> 
> Digit (Elem a) -> FingerTree (Elem a) #-}
>
> And the SPECIALISE really is wrong there... you should either specialise or 
> inline. Not sure which is wanted, but warning about using both is right.
>
> I don't know the protocol for updating containers, so I'm just telling you!  
> Can you do something so that everyone doesn't fall over on this?
>
> Simon
> | -----Original Message-----
> | From: Ian Lynagh [mailto:ig...@earth.li]
> | Sent: 18 January 2012 12:49
> | To: Simon Peyton-Jones
> | Cc: cvs-ghc@haskell.org
> | Subject: Re: [commit: ghc] master: Warn when a SPECIALISE pragma gives rise
> | to a totally inactive rule (6acf6cd)
> |
> |
> | Hi Simon,
> |
> | On Tue, Jan 17, 2012 at 08:02:15AM -0800, Simon Peyton-Jones wrote:
> | >
> | > commit 6acf6cd7a8156b40979321ff94fe836736b46175
> | > Author: Simon Peyton Jones <simo...@microsoft.com>
> | > Date:   Tue Jan 17 16:01:16 2012 +0000
> | >
> | >     Warn when a SPECIALISE pragma gives rise to a totally inactive rule
> | >     See Trac #5779
> |
> | I'm getting this when validating:
> |
> | "inplace/bin/ghc-stage1"   -H32m -O -Wall -Werror -H64m -O0    -package-name
> | ghc-prim-0.2.0.0 -hide-all-packages -i -ilibraries/ghc-prim/. -
> | ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist-
> | install/build/autogen -Ilibraries/ghc-prim/dist-install/build -
> | Ilibraries/ghc-prim/dist-install/build/autogen -Ilibraries/ghc-prim/.    -
> | optP-include -optPlibraries/ghc-prim/dist-
> | install/build/autogen/cabal_macros.h -package rts-1.0  -package-name 
> ghc-prim
> | -XHaskell98 -XCPP -XMagicHash -XForeignFunctionInterface -XUnliftedFFITypes 
> -
> | XUnboxedTuples -XEmptyDataDecls -XNoImplicitPrelude -O2 -O -dcore-lint -fno-
> | warn-deprecated-flags  -no-user-package-conf -rtsopts     -odir
> | libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist-
> | install/build -stubdir libraries/ghc-prim/dist-install/build -hisuf hi -osuf
> | o -hcsuf hc -c libraries/ghc-prim/./GHC/Classes.hs -o libraries/ghc-
> | prim/dist-install/build/GHC/Classes.o
> | *** Core Lint warnings : in result of Desugar (after optimization) ***
> | {-# LINE 46 "libraries/ghc-prim/GHC/Classes.hs #-}: Warning:
> |     [RHS of $c/=_a1oD :: forall a_a8L.
> |                          GHC.Classes.Eq a_a8L =>
> |                          [a_a8L] -> [a_a8L] -> GHC.Types.Bool]
> |     INLINE binder is (non-rule) loop breaker: $c/=_a1oD
> | {-# LINE 46 "libraries/ghc-prim/GHC/Classes.hs #-}: Warning:
> |     [RHS of $c/=_a1oi :: GHC.Types.Float
> |                          -> GHC.Types.Float -> GHC.Types.Bool]
> |     INLINE binder is (non-rule) loop breaker: $c/=_a1oi
> | {-# LINE 46 "libraries/ghc-prim/GHC/Classes.hs #-}: Warning:
> |     [RHS of $c/=_a1ob :: GHC.Types.Double
> |                          -> GHC.Types.Double -> GHC.Types.Bool]
> |     INLINE binder is (non-rule) loop breaker: $c/=_a1ob
> |
> |
> | libraries/ghc-prim/GHC/Classes.hs:88:5: Warning:
> |     SPECIALISE pragma on INLINE function probably won't fire: `$c/='
> |
> | <no location info>:
> | Failing due to -Werror.
> | make[1]: *** [libraries/ghc-prim/dist-install/build/GHC/Classes.o] Error 1
> | make: *** [all] Error 2
> |
> |
> |
> | Thanks
> | Ian
> |
>
>

_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to