<div dir="ltr"><div>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.<br><br></div>Original definingSigsNames<br><br>------------------<br>-- |Find those type signatures for the specified GHC.Names.<br>definingSigsNames :: (SYB.Data t) =><br>            [GHC.Name] -- ^ The specified identifiers.<br>            ->t        -- ^ A collection of declarations.<br>            ->[GHC.LSig GHC.Name]  -- ^ The result.<br>definingSigsNames pns ds = def ds<br>  where<br>   def decl<br>     = SYB.everythingStaged SYB.Renamer (++) [] ([]  `SYB.mkQ` inSig) decl<br>     where<br>      inSig :: (GHC.LSig GHC.Name) -> [GHC.LSig GHC.Name]<br>      inSig (GHC.L l (GHC.TypeSig ns t p))<br>       | defines' ns /= [] = [(GHC.L l (GHC.TypeSig (defines' ns) t p))]<br>      inSig _ = []<br><br>      defines' (p::[GHC.Located GHC.Name])<br>        = filter (\(GHC.L _ n) -> n `elem` pns) p<br>----------------------<br><br></div><div class="gmail_extra"><br><div class="gmail_quote">On Fri, Jan 9, 2015 at 1:48 PM, Simon Peyton Jones <span dir="ltr"><<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">





<div link="blue" vlink="purple" lang="EN-GB">
<div>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">If you remove the constraint from duplicateDecl, then I get<u></u><u></u></span></p><span class="">
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">    Redundant constraint: SYB.Data t<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">    In the type signature for:<u></u><u></u></span></p>
</span><p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">       definingSigsNames :: SYB.Data t =><u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">                            [GHC.Name] -> t -> [GHC.LSig GHC.Name]<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">which is 100% correct: defininingSigssNames doesn’t use its SYB.Data t constraint<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #e1e1e1 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US">From:</span></b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US"> Alan & Kim Zimmerman [mailto:<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>]
<br>
<b>Sent:</b> 09 January 2015 11:22<br>
<b>To:</b> Simon Peyton Jones<br>
<b>Cc:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><span class=""><br>
<b>Subject:</b> Re: warn-redundant-constraints present as errors<u></u><u></u></span></span></p>
</div>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
Thanks.<u></u><u></u></p>
</div><div><div class="h5">
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
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<br>
<br>
--------------------------------------------<br>
import qualified GHC           as GHC<br>
<br>
import qualified Data.Generics as SYB<br>
<br>
duplicateDecl :: (SYB.Data t) =>   -- **** The constraint being warned against *******<br>
  [GHC.LHsBind GHC.Name]  -- ^ The declaration list<br>
  ->t                     -- ^ Any signatures are in here<br>
  ->GHC.Name              -- ^ The identifier whose definition is to be duplicated<br>
  ->GHC.Name              -- ^ The new name (possibly qualified)<br>
  ->IO [GHC.LHsBind GHC.Name]  -- ^ The result<br>
duplicateDecl decls sigs n newFunName<br>
 = do<br>
     let sspan = undefined<br>
     newSpan <- case typeSig of<br>
        [] -> return sspan<br>
        _  -> do<br>
          let Just sspanSig = getSrcSpan typeSig<br>
          toksSig <- getToksForSpan sspanSig<br>
<br>
          let [(GHC.L sspanSig' _)] = typeSig<br>
<br>
          return sspanSig'<br>
<br>
     undefined<br>
   where<br>
     typeSig = definingSigsNames [n] sigs<br>
<br>
-- |Find those type signatures for the specified GHC.Names.<br>
definingSigsNames :: (SYB.Data t) =><br>
            [GHC.Name] -- ^ The specified identifiers.<br>
            ->t        -- ^ A collection of declarations.<br>
            ->[GHC.LSig GHC.Name]  -- ^ The result.<br>
definingSigsNames pns ds = def ds<br>
  where def = undefined<br>
<br>
getSrcSpan = undefined<br>
getToksForSpan = undefined<br>
<br>
--------------------------------------------<u></u><u></u></p>
</div></div></div><div><div class="h5">
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
<u></u> <u></u></p>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
On Fri, Jan 9, 2015 at 1:08 PM, Simon Peyton Jones <<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>> wrote:<u></u><u></u></p>
<blockquote style="border:none;border-left:solid #cccccc 1.0pt;padding:0cm 0cm 0cm 6.0pt;margin-left:4.8pt;margin-right:0cm">
<div>
<div>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">I’ve fixed this</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #e1e1e1 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US">From:</span></b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US"> Alan
 & Kim Zimmerman [mailto:<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>]
<br>
<b>Sent:</b> 08 January 2015 21:46<br>
<b>To:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a>; Simon Peyton Jones<br>
<b>Subject:</b> warn-redundant-constraints present as errors</span><u></u><u></u></p>
</div>
</div>
<div>
<div>
<p class="MsoNormal"> <u></u><u></u></p>
<div>
<div>
<div>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">This is a great feature, here is some feedback<br>
<br>
My syntax highlighter in emacs expects warnings to have the word "warning" in them.<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt">So for the two warnings reported below, the first is highlighted as an error, and the second as a warning<br>
<br>
<br>
Language/Haskell/Refact/Utils/TypeUtils.hs:3036:17:<br>
    Redundant constraint: SYB.Data t<br>
    In the type signature for:<br>
       duplicateDecl :: SYB.Data t =><br>
                        [GHC.LHsBind GHC.Name]<br>
                        -> t -> GHC.Name -> GHC.Name -> RefactGhc [GHC.LHsBind GHC.Name]<br>
<br>
Language/Haskell/Refact/Utils/TypeUtils.hs:3045:7: Warning:<br>
    Defined but not used: ‘toks<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt">This is in a ghci session, and the file loads without problems, so it is indeed a warning.<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt">Can we perhaps add the word "Warning" to the output for Redundant constraints?<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">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.<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-bottom:6.0pt"> <u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:6.0pt">Regards<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:6.0pt">  Alan<u></u><u></u></p>
</div>
</div>
</div>
</div>
</div>
</div>
</blockquote>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
</div></div></div>
</div>
</div>

</blockquote></div><br></div>