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

GHC ghc-devs at haskell.org
Sun Feb 25 16:21:58 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
      Resolution:                    |             Keywords:  InstanceSigs
                                     |  TypeInType
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 In case you're worried about that `UndecidableInstances` part, here's a
 version that doesn't use `UndecidableInstances`:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE EmptyCase #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE InstanceSigs #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeInType #-}
 module Bug where

 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 xx (structured::Struct (cls :: k -> Constraint)) where
   struct :: AStruct structured

 instance (Structured xx cls ~ structured, cls xx) => StructI xx 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 xx a => ríki a a

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

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


More information about the ghc-tickets mailing list