
#14633: -fwarn-redundant-constraints false positive -------------------------------------+------------------------------------- Reporter: ghorn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I had code which compiled cleanly on GHC 8.0.2 with -fwarn-redundant- constraints which now gives a warning on GHC 8.2.2. Here is the code, and my workaround: {{{#!haskell {-# OPTIONS_GHC -Wall -Werror -fwarn-redundant-constraints #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} module Bug ( bug , workaround ) where import GHC.Generics ( D1, Datatype, Meta, Rep, datatypeName ) import Data.Proxy ( Proxy ) -- /home/greghorn/hslibs/ghc82_bug_maybe/Bug.hs:17:1: warning: [-Wredundant-constraints] -- • Redundant constraint: Rep a ~ D1 d p -- • In the type signature for: -- bug :: forall a (d :: Meta) (p :: * -> *). -- (Datatype d, Rep a ~ D1 d p) => -- Proxy a -> String -- | -- 25 | bug :: forall a d p . (Datatype d, Rep a ~ D1 d p) => Proxy a -> String -- | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ bug :: forall a d p . (Datatype d, Rep a ~ D1 d p) => Proxy a -> String bug = const name where name = datatypeName (undefined :: D1 d p b) type family GetD a :: Meta where GetD (D1 d p) = d workaround :: forall a d p . (Datatype (GetD (Rep a)), Rep a ~ D1 d p) => Proxy a -> String workaround = const name where name = datatypeName (undefined :: D1 d p b) }}} I suspect it is a bug because if I remove the "redundant" constraint it no longer typechecks. Here is a minimal setup to reproduce with stack: {{{ name: bug version: 0.0.0.2 license: AllRightsReserved author: Greg Horn maintainer: gregmainland@gmail.com build-type: Simple cabal-version: >=1.10 library exposed-modules: Bug build-depends: base >= 4.7 && < 5 default-language: Haskell2010 }}} {{{ resolver: lts-10.2 compiler-check: newer-minor # Local packages, usually specified by relative directory name packages: - . }}} Alternatively: {{{ git clone https://github.com/ghorn/ghc-redundant-constraint-bug cd ghc-redundant-constraint-bug stack build }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14633 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler