warn-redundant-constraints present as errors

Simon Peyton Jones simonpj at microsoft.com
Fri Jan 9 12:18:39 UTC 2015


Now I get
Foo1.hs:39:8: Not in scope: ‘SYB.everythingStaged’
Foo1.hs:39:29: Not in scope: data constructor ‘SYB.Renamer’

Do you think you could open a ticket with a reproducible test case?  That would be helpful

Simon

From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com]
Sent: 09 January 2015 11:54
To: Simon Peyton Jones
Cc: ghc-devs at haskell.org
Subject: Re: warn-redundant-constraints present as errors

In the original definingSigsNames requires the constraint, I left that out to simplify the example, as the movement of the warning to an error still happens.
Original definingSigsNames

------------------
-- |Find those type signatures for the specified GHC.Names.
definingSigsNames :: (SYB.Data t) =>
            [GHC.Name] -- ^ The specified identifiers.
            ->t        -- ^ A collection of declarations.
            ->[GHC.LSig GHC.Name]  -- ^ The result.
definingSigsNames pns ds = def ds
  where
   def decl
     = SYB.everythingStaged SYB.Renamer (++) [] ([]  `SYB.mkQ` inSig) decl
     where
      inSig :: (GHC.LSig GHC.Name) -> [GHC.LSig GHC.Name]
      inSig (GHC.L l (GHC.TypeSig ns t p))
       | defines' ns /= [] = [(GHC.L l (GHC.TypeSig (defines' ns) t p))]
      inSig _ = []

      defines' (p::[GHC.Located GHC.Name])
        = filter (\(GHC.L _ n) -> n `elem` pns) p
----------------------

On Fri, Jan 9, 2015 at 1:48 PM, Simon Peyton Jones <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
If you remove the constraint from duplicateDecl, then I get

    Redundant constraint: SYB.Data t
    In the type signature for:
       definingSigsNames :: SYB.Data t =>
                            [GHC.Name] -> t -> [GHC.LSig GHC.Name]

which is 100% correct: defininingSigssNames doesn’t use its SYB.Data t constraint

Simon

From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com<mailto:alan.zimm at gmail.com>]
Sent: 09 January 2015 11:22
To: Simon Peyton Jones
Cc: ghc-devs at haskell.org<mailto:ghc-devs at haskell.org>
Subject: Re: warn-redundant-constraints present as errors

Thanks.
I've found a case where it warns of a redundant constraint, but if I remove the constraint I get an error saying the constraint is required

--------------------------------------------
import qualified GHC           as GHC

import qualified Data.Generics as SYB

duplicateDecl :: (SYB.Data t) =>   -- **** The constraint being warned against *******
  [GHC.LHsBind GHC.Name]  -- ^ The declaration list
  ->t                     -- ^ Any signatures are in here
  ->GHC.Name              -- ^ The identifier whose definition is to be duplicated
  ->GHC.Name              -- ^ The new name (possibly qualified)
  ->IO [GHC.LHsBind GHC.Name]  -- ^ The result
duplicateDecl decls sigs n newFunName
 = do
     let sspan = undefined
     newSpan <- case typeSig of
        [] -> return sspan
        _  -> do
          let Just sspanSig = getSrcSpan typeSig
          toksSig <- getToksForSpan sspanSig

          let [(GHC.L sspanSig' _)] = typeSig

          return sspanSig'

     undefined
   where
     typeSig = definingSigsNames [n] sigs

-- |Find those type signatures for the specified GHC.Names.
definingSigsNames :: (SYB.Data t) =>
            [GHC.Name] -- ^ The specified identifiers.
            ->t        -- ^ A collection of declarations.
            ->[GHC.LSig GHC.Name]  -- ^ The result.
definingSigsNames pns ds = def ds
  where def = undefined

getSrcSpan = undefined
getToksForSpan = undefined

--------------------------------------------

On Fri, Jan 9, 2015 at 1:08 PM, Simon Peyton Jones <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
I’ve fixed this

From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com<mailto:alan.zimm at gmail.com>]
Sent: 08 January 2015 21:46
To: ghc-devs at haskell.org<mailto:ghc-devs at haskell.org>; Simon Peyton Jones
Subject: warn-redundant-constraints present as errors

This is a great feature, here is some feedback

My syntax highlighter in emacs expects warnings to have the word "warning" in them.
So for the two warnings reported below, the first is highlighted as an error, and the second as a warning


Language/Haskell/Refact/Utils/TypeUtils.hs:3036:17:
    Redundant constraint: SYB.Data t
    In the type signature for:
       duplicateDecl :: SYB.Data t =>
                        [GHC.LHsBind GHC.Name]
                        -> t -> GHC.Name -> GHC.Name -> RefactGhc [GHC.LHsBind GHC.Name]

Language/Haskell/Refact/Utils/TypeUtils.hs:3045:7: Warning:
    Defined but not used: ‘toks
This is in a ghci session, and the file loads without problems, so it is indeed a warning.
Can we perhaps add the word "Warning" to the output for Redundant constraints?
I also had a situation where it asked me to remove a whole lot of constraints from different functions, I did them in batches, so did not remove them all from the file at once, and at some point I had to add at least one of them back, albeit based on an error message.

Regards
  Alan


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20150109/0f215d79/attachment-0001.html>


More information about the ghc-devs mailing list