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

On a slightly unrelated note I should say it would be great to have errors
contain word "Error:". This is especially nice to have because when you
build with "-j" your error that stops compilation gets lost somewhere in
the middle of many warnings (which my projects have, unfortunately).
On Thu, Jan 8, 2015 at 11:45 PM, Alan & Kim Zimmerman
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
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

Alan’s point is a bug – I will fix.
Konstantine’s point is reasonable. we could easily say
Language/Haskell/Refact/Utils/TypeUtils.hs:3045:7: Error:
blah blah
(the bit in red is the new bit)
But I’m not sure that everyone else would want that. If a consensus forms it would be easy to excecute
I suppose there could be yet another flag to control it (!)
Simon
From: Konstantine Rybnikov [mailto:k-bx@k-bx.com]
Sent: 09 January 2015 09:19
To: Alan & Kim Zimmerman
Cc: ghc-devs@haskell.org; Simon Peyton Jones
Subject: Re: warn-redundant-constraints present as errors
On a slightly unrelated note I should say it would be great to have errors contain word "Error:". This is especially nice to have because when you build with "-j" your error that stops compilation gets lost somewhere in the middle of many warnings (which my projects have, unfortunately).
On Thu, Jan 8, 2015 at 11:45 PM, Alan & Kim Zimmerman

I think using the words error and warning makes sense. For example, this is
how Clang (LLVM) does it:
format-strings.c:91:13: warning: '.*' specified field precision is missing
a matching 'int' argument
printf("%.*d");
^
t.c:7:39: error: invalid operands to binary expression ('int' and 'struct
A')
return y + func(y ? ((SomeA.X + 40) + SomeA) / 42 + SomeA.X : SomeA.X);
~~~~~~~~~~~~~~ ^ ~~~~~
(Also note how lovely it is to have a caret pointing at the error.)
On Fri, Jan 9, 2015 at 10:39 AM, Simon Peyton Jones
Alan’s point is a bug – I will fix.
Konstantine’s point is reasonable. we could easily say
Language/Haskell/Refact/Utils/TypeUtils.hs:3045:7: Error: blah blah
(the bit in red is the new bit)
But I’m not sure that everyone else would want that. If a consensus forms it would be easy to excecute
I suppose there could be yet another flag to control it (!)
Simon
*From:* Konstantine Rybnikov [mailto:k-bx@k-bx.com] *Sent:* 09 January 2015 09:19 *To:* Alan & Kim Zimmerman *Cc:* ghc-devs@haskell.org; Simon Peyton Jones *Subject:* Re: warn-redundant-constraints present as errors
On a slightly unrelated note I should say it would be great to have errors contain word "Error:". This is especially nice to have because when you build with "-j" your error that stops compilation gets lost somewhere in the middle of many warnings (which my projects have, unfortunately).
On Thu, Jan 8, 2015 at 11:45 PM, Alan & Kim Zimmerman
wrote: 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
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

I’ve fixed this From: Alan & Kim Zimmerman [mailto:alan.zimm@gmail.com] Sent: 08 January 2015 21:46 To: ghc-devs@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

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
I’ve fixed this
*From:* Alan & Kim Zimmerman [mailto:alan.zimm@gmail.com] *Sent:* 08 January 2015 21:46 *To:* ghc-devs@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

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@gmail.com]
Sent: 09 January 2015 11:22
To: Simon Peyton Jones
Cc: ghc-devs@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

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
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@gmail.com] *Sent:* 09 January 2015 11:22 *To:* Simon Peyton Jones *Cc:* ghc-devs@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
wrote: I’ve fixed this
*From:* Alan & Kim Zimmerman [mailto:alan.zimm@gmail.com] *Sent:* 08 January 2015 21:46 *To:* ghc-devs@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

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@gmail.com]
Sent: 09 January 2015 11:54
To: Simon Peyton Jones
Cc: ghc-devs@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

See https://ghc.haskell.org/trac/ghc/ticket/9973, my original file did not
in fact exhibit the bug.
On Fri, Jan 9, 2015 at 2:18 PM, Simon Peyton Jones
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@gmail.com] *Sent:* 09 January 2015 11:54
*To:* Simon Peyton Jones *Cc:* ghc-devs@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
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@gmail.com] *Sent:* 09 January 2015 11:22 *To:* Simon Peyton Jones *Cc:* ghc-devs@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
wrote: I’ve fixed this
*From:* Alan & Kim Zimmerman [mailto:alan.zimm@gmail.com] *Sent:* 08 January 2015 21:46 *To:* ghc-devs@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
participants (4)
-
Alan & Kim Zimmerman
-
Johan Tibell
-
Konstantine Rybnikov
-
Simon Peyton Jones