[GHC] #11621: GHC doesn't see () as a Constraint in type family

GHC ghc-devs at haskell.org
Sun Feb 21 18:21:59 UTC 2016


#11621: GHC doesn't see () as a Constraint in type family
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE DataKinds, TypeOperators, KindSignatures,
 MultiParamTypeClasses, TypeFamilies #-}

 import Data.Kind

 class NotFound

 type family
   F b where
   F 'False = (NotFound :: Constraint)
   F 'True  = (() :: Constraint)
 }}}

 works fine. Removing all constraints and final line it works without any
 annotations and infers the type of `F :: Bool -> Constraint`:

 {{{#!hs
 type family
   F b where
   F 'False = NotFound
 }}}

 GHC seems determined that `() :: Type` unless explicitly told otherwise, I
 would like to be able to write:

 {{{#!hs
 type family
   F b where
   F 'False = NotFound
   F 'True  = ()
 }}}

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


More information about the ghc-tickets mailing list