[GHC] #14450: GHCi spins forever

GHC ghc-devs at haskell.org
Sat Nov 11 06:59:00 UTC 2017


#14450: GHCi spins forever
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:  TypeInType,    |  Operating System:  Unknown/Multiple
  PolyKinds                          |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code compiles just fine (8.3.20170920)

 {{{#!hs
 {-# Language KindSignatures, TypeOperators, PolyKinds, TypeOperators,
 ConstraintKinds, TypeFamilies, DataKinds, TypeInType, GADTs,
 AllowAmbiguousTypes, InstanceSigs #-}

 import Data.Kind

 data TyFun :: Type -> Type -> Type

 type a ~> b = TyFun a b -> Type

 type Cat ob = ob -> ob -> Type

 type SameKind (a :: k) (b :: k) = (() :: Constraint)

 type family
   Apply (f :: a ~> b) (x :: a) :: b where
   Apply IddSym0 x = Idd x

 class Varpi (f :: i ~> j) where
   type Dom (f :: i ~> j) :: Cat i
   type Cod (f :: i ~> j) :: Cat j

   varpa :: Dom f a a' -> Cod f (Apply f a) (Apply f a')

 type family
   Idd (a::k) :: k where
   Idd (a::k) = a

 data IddSym0 :: k ~> k where
   IddSym0KindInference :: IddSym0 l

 instance Varpi (IddSym0 :: Type ~> Type) where
   type Dom (IddSym0 :: Type ~> Type) = (->)
   type Cod (IddSym0 :: Type ~> Type) = (->)

   varpa :: (a -> a') -> (a -> a')
   varpa = id
 }}}

 But if you change the final instance to

 {{{#!hs
 instance Varpi (IddSym0 :: k ~> k) where
   type Dom (IddSym0 :: Type ~> Type) = (->)
 }}}

 it sends GHC for a spin.

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


More information about the ghc-tickets mailing list