[GHC] #7862: Could not deduce (A) from the context (A, ...)

GHC ghc-devs at haskell.org
Sun Nov 9 07:12:26 UTC 2014


#7862: Could not deduce (A) from the context (A, ...)
-------------------------------------+-------------------------------------
              Reporter:  alang9      |            Owner:
                  Type:  bug         |           Status:  new
              Priority:  normal      |        Milestone:
             Component:  Compiler    |          Version:  7.6.2
  (Type checker)                     |         Keywords:
            Resolution:              |     Architecture:  x86_64 (amd64)
      Operating System:  Linux       |       Difficulty:  Unknown
       Type of failure:  GHC         |       Blocked By:
  rejects valid program              |  Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Comment (by spacekitteh):

 Another example of this bug:


 {{{

 {-# LANGUAGE AllowAmbiguousTypes, DefaultSignatures,
 MultiParamTypeClasses,
  FlexibleInstances, FlexibleContexts, UndecidableInstances, PolyKinds,
 ConstraintKinds,  InstanceSigs, TypeFamilies #-}
 module Control.SmallCategory where

 import GHC.Exts
 import Control.Category

 class Vacuous (a:: i)
 instance Vacuous a


 class SmallCategory cat  where
     type Objects cat :: i  -> Constraint
     type Objects cat = Vacuous
     type Morphisms cat :: a -> a -> b
     id :: (Objects cat a) => (Morphisms cat) a a
     (.) :: (Objects cat a, Objects cat b, Objects cat c) => (Morphisms
 cat) b c -> (Morphisms cat) a b -> (Morphisms cat) a c

 instance (Category c, Category (Morphisms c)) => SmallCategory c where
     type Objects c = Vacuous
     type (Morphisms c) = c
     id = Control.Category.id
     (.) = (Control.Category..)

 src/Control/SmallCategory.hs:34:10:
     Could not deduce (Category (Morphisms c))
       arising from a use of ‘Control.Category.id’
     from the context (Category c, Category (Morphisms c))
       bound by the instance declaration
       at src/Control/SmallCategory.hs:31:10-64
     or from (Objects c a)
       bound by the type signature for
                  id :: (Objects c a) => Morphisms c a a
       at src/Control/SmallCategory.hs:34:5-6
     In the expression: Control.Category.id
     In an equation for ‘id’: id = Control.Category.id
     In the instance declaration for ‘SmallCategory c’

 src/Control/SmallCategory.hs:35:11:
     Could not deduce (Category (Morphisms c))
       arising from a use of ‘Control.Category..’
     from the context (Category c, Category (Morphisms c))
       bound by the instance declaration
       at src/Control/SmallCategory.hs:31:10-64
     or from (Objects c a, Objects c b, Objects c c1)
       bound by the type signature for
                  (.) :: (Objects c a, Objects c b, Objects c c1) =>
                         Morphisms c b c1 -> Morphisms c a b -> Morphisms c
 a c1
       at src/Control/SmallCategory.hs:35:5-7
     In the expression: (Control.Category..)
     In an equation for ‘.’: (.) = (Control.Category..)
     In the instance declaration for ‘SmallCategory c’

 }}}

  in 7.8.3.

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


More information about the ghc-tickets mailing list