[GHC] #14451: Need proper SCC analysis of type declarations, taking account of CUSKs

GHC ghc-devs at haskell.org
Sun Dec 2 20:09:45 UTC 2018


#14451: Need proper SCC analysis of type declarations, taking account of CUSKs
-------------------------------------+-------------------------------------
        Reporter:  Iceland_jack      |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.1
      Resolution:                    |             Keywords:  TypeInType,
                                     |  CUSKs
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #7503             |  Differential Rev(s):
       Wiki Page:                    |
  https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/KindInference|
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 Amazingly, the original program in this ticket (including the `Comp f g a
 = f · (g · a)` tweak):

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

 import Data.Kind

 data TyFun :: Type -> Type -> Type

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

 type Cat ob = ob -> ob -> Type

 type family
   Apply (f :: a ~> b) (x :: a) :: b where
   Apply (CompSym2 f g) a = Comp f g a

 data CompSym2 :: (b ~> c) -> (a ~> b) -> (a ~> c)

 type a·b = Apply a b

 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 (f·a) (f·a')

 type family
   Comp (f::k1 ~> k) (g::k2 ~> k1) (a::k2) :: k where
   Comp f g a = f · (g · a)
 }}}

 Appears to have fixed itself at some point between GHC 8.4 and 8.6, since
 it typechecks on GHC 8.6.2 and HEAD. I'm not sure what commit caused that,
 but that's cool nonetheless.

 Let me check to see if the same miracle happened to #7503.

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


More information about the ghc-tickets mailing list