[GHC] #15459: Wredundant-constraints does not work when constraint synonym is used

GHC ghc-devs at haskell.org
Mon Jul 30 21:31:43 UTC 2018


#15459: Wredundant-constraints does not work when constraint synonym is used
-------------------------------------+-------------------------------------
           Reporter:  flip101        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{
 {-# 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.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15459>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list