[GHC] #9376: Recursive closed type families fails

GHC ghc-devs at haskell.org
Tue Jul 29 07:52:43 UTC 2014


#9376: Recursive closed type families fails
-------------------------------------+-------------------------------------
              Reporter:              |            Owner:
  MikeIzbicki                        |           Status:  new
                  Type:  bug         |        Milestone:
              Priority:  normal      |          Version:  7.8.2
             Component:  Compiler    |         Keywords:
  (Type checker)                     |     Architecture:  Unknown/Multiple
            Resolution:              |       Difficulty:  Unknown
      Operating System:              |       Blocked By:
  Unknown/Multiple                   |  Related Tickets:
       Type of failure:              |
  None/Unknown                       |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Are you sure that GHC 7.8.2 compiles this (the non-recursive version)?
 {{{
 {-# LANGUAGE ConstraintKinds, TypeFamilies #-}

 module T9376 where
 import GHC.Prim
 import Data.Proxy
 import qualified Data.Set as Set

 type family OrdRec (f :: * -> *) a b  :: Constraint where
     OrdRec f a (f b) = ( Ord a, Ord (f b), Ord (f b) )
     OrdRec f a b = ( Ord a, Ord b )

 setmap :: OrdRec Set.Set a b => (a -> b) -> Set.Set a -> Set.Set b
 setmap f set = Set.map f set
 }}}
 I get
 {{{
 bash$ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 7.8.2
 bash$ ghc -c T9376.hs

 T9376.hs:13:16:
     Could not deduce (Ord b) arising from a use of ‘Set.map’
     from the context (OrdRec Set.Set a b)
       bound by the type signature for
                  setmap :: (OrdRec Set.Set a b) =>
                            (a -> b) -> Set.Set a -> Set.Set b
       at T9376.hs:12:11-66
     Possible fix:
       add (Ord b) to the context of
         the type signature for
           setmap :: (OrdRec Set.Set a b) =>
                     (a -> b) -> Set.Set a -> Set.Set b
     In the expression: Set.map f set
     In an equation for ‘setmap’: setmap f set = Set.map f set
 }}}
 And so it should!  We can't simplify `OrdRec Set a b` to `(Ord a, Ord b)`
 because in some call to `setmap` you might instantiate `b` to an
 application.  The paper on closed type families elaborates.

 I'm puzzled how you get the behaviour you describe.

 Simon

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


More information about the ghc-tickets mailing list