Skip to content
GitLab
Projects Groups Snippets
  • /
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 5,413
    • Issues 5,413
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 603
    • Merge requests 603
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell CompilerGlasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #5120
Closed
Open
Issue created Apr 15, 2011 by mikkonecny@trac-mikkonecny

inferred type of an implicit parameter rejected (associated type)

The following module:

{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoMonomorphismRestriction #-}

module Test where

class C t where
    type TF t
    ttt :: TF t -> t

b :: (C t, ?x :: TF t) => t
b = ttt ?x 

compiles fine with ghc 6.12.3 but ghc 7.0.3 says:

    Could not deduce (?x::TF t)
      arising from a use of implicit parameter `?x'
    from the context (C t, ?x::TF t)
      bound by the type signature for b :: (C t, ?x::TF t) => t
      at Test.hs:13:1-10
    In the first argument of `ttt', namely `?x'
    In the expression: ttt ?x
    In an equation for `b': b = ttt ?x

Moreover, when I comment out the type declaration for b, ghc 7.0.3 compiles it and the inferred type for b is identical to the one that was commented out:

*Test> :t b
b :: (C t, ?x::TF t) => t
Trac metadata
Trac field Value
Version 7.0.3
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler (Type checker)
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Assignee
Assign to
Time tracking