[GHC] #14846: Renamer hangs (because of -XInstanceSigs?)

GHC ghc-devs at haskell.org
Fri Feb 23 16:17:02 UTC 2018


#14846: Renamer hangs (because of -XInstanceSigs?)
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.5
           Keywords:  InstanceSigs   |  Operating System:  Unknown/Multiple
  TypeInType                         |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# Language RankNTypes, TypeInType, EmptyCase, GADTs, FlexibleInstances,
 ConstraintKinds, UndecidableInstances, AllowAmbiguousTypes, InstanceSigs
 #-}

 import Data.Kind
 import Data.Proxy

 type Cat ob = ob -> ob -> Type

 data Struct :: (k -> Constraint) -> Type where
   S :: Proxy (a::k) -> Struct (cls::k -> Constraint)

 type Structured a cls = (S ('Proxy :: Proxy a)::Struct cls)

 data AStruct :: Struct cls -> Type where
   AStruct :: cls a => AStruct (Structured a cls)

 class StructI (structured::Struct (cls :: k -> Constraint)) where
   struct :: AStruct structured

 instance (Structured xx cls ~ structured, cls xx) => StructI structured
 where
   struct :: AStruct (Structured xx cls)
   struct = AStruct

 data Hom :: Cat k -> Cat (Struct cls) where

 class Category (cat::Cat ob) where
   i :: StructI a => ríki a a

 instance Category ríki => Category (Hom ríki :: Cat (Struct cls)) where
   i :: forall a. StructI a => Hom ríki a a
   i = case struct :: AStruct (Structured a cls) of
 }}}

 Running on 8.2.1 and 8.5.20180105 both loop until interrupted

 {{{
 $ ghci -ignore-dot-ghci 199.hs
 GHCi, version 8.5.20180105: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( 199.hs, interpreted )
 ^CInterrupted.
 >
 >
 }}}

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


More information about the ghc-tickets mailing list