Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,248
    • Issues 4,248
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 397
    • Merge Requests 397
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #17939

Closed
Open
Opened Mar 20, 2020 by Tom Harding@i-am-tom

Quantified constraint doesn't evidence type family instances

Summary

First up, sorry in advance: I'm unsure on the exact vocabulary for this particular problem.

In the below code, I would expect the DC constraint on eg1 to imply the CC constraint required for eg0 via the quantified constraint on D. However, it doesn't seem to be able to do so.

Interestingly, if I change the constraint on eg0 to use the Magic class (which I created because of the recent restrictions on QC instance heads), everything seems to work happily.

Is this a case of GHC not searching hard enough for the CC instance? I'm certainly not an expert, but this behaviour feels bizarre to me; my intuition until now would have been to say that CC f x and Magic f x are equivalent in all circumstances!

Steps to reproduce

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}

import Data.Kind (Constraint, Type)

class CC f x => Magic f x
instance CC f x => Magic f x

class C (f :: Type -> Type) where
  type CC f :: Type -> Constraint

  eg0 :: CC f x => f x -> f x -- Changing the constraint to `Magic f x => ...` works!
  eg0 = id

class (C f, forall x. DC f x => Magic f x) => D (f :: Type -> Type) where
  type DC f :: Type -> Constraint

eg1 :: (D f, DC f x) => f x -> f x
eg1 = eg0
    • Could not deduce: CC f x arising from a use of ‘eg0’
      from the context: (D f, DC f x)
        bound by the type signature for:
                   eg1 :: forall (f :: * -> *) x. (D f, DC f x) => f x -> f x
        at Test.hs:23:1-34
    • In the expression: eg0
      In an equation for ‘eg1’: eg1 = eg0
    • Relevant bindings include
        eg1 :: f x -> f x (bound at Test.hs:24:1)
   |
24 | eg1 = eg0
   |       ^^^

Expected behavior

I would expect the aforementioned change to be a no-op, though I suspect I'm missing some context!

Environment

  • GHC version used: 8.6.5, 8.8.1, 8.10
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#17939