Wredundant-constraints does not work when constraint synonym is used
{-# LANGUAGE ConstraintKinds #-}
{-# OPTIONS_GHC -Wredundant-constraints #-}
module Main where
import Data.List
main :: IO ()
main = return ()
withWarning :: (Show a, Ord a) => [a] -> [a]
withWarning = sort
type ConstraintSynonym a = (Show a, Ord a)
withoutWarning :: ConstraintSynonym a => [a] -> [a]
withoutWarning = sort
Main.hs:12:1: warning: [-Wredundant-constraints]
• Redundant constraint: Show a
• In the type signature for:
withWarning :: forall a. (Show a, Ord a) => [a] -> [a]
|
14 | withWarning :: (Show a, Ord a) => [a] -> [a]
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
The withoutWarning function does not need the (Show a) constraint but there is no warning for it.
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |