[GHC] #9018: GHC suppresses too much kind information

GHC ghc-devs at haskell.org
Mon Apr 21 11:04:10 UTC 2014


#9018: GHC suppresses too much kind information
------------------------------------+-------------------------------------
       Reporter:  simonpj           |             Owner:
           Type:  feature request   |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.8.2
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 GHC tends to hide important kind polymorphism in error messages and in
 GHCi. (I came across this when looking at #9017.)   For example, try this:
 {{{
 bash$ cat Test.hs
 {-# LANGUAGE PolyKinds #-}
 module Test where
 foo :: m a
 foo = foo

 bash$ ghci Test.hs
 ghci> :t foo
 foo :: m a
 ghci> :i foo
 foo :: m a

 bash$ ghci Test.hs -XPolyKinds
 ghci> :t foo
 foo :: m a
 ghci> :i foo
 goo :: m a

 bash$ ghci Test.hs -fprint-explicit-foralls -fprint-explicit-kinds
 ghci> :t foo
 foo :: foo :: forall (m :: * -> *) d. m d
 ghci> :i foo
 foo :: forall (k :: BOX) (m :: k -> *) (d :: k). m d

 bash$ ghci Test.hs -XPolyKinds -fprint-explicit-foralls -fprint-explicit-
 kinds
 ghci> :t foo
 foo :: forall (k :: BOX) (m :: k -> *) (d :: k). m d
 ghci> :i foo
 foo :: forall (k :: BOX) (m :: k -> *) (d :: k). m d
 }}}
 Pretty confusing eh?

  * Without `-fprint-explicit-foralls -fprint-explicit-kinds` you don't see
 the kinds on the types at all.

  * Without `-XPolyKinds` in GHCi, when you say `:t foo` you are asking for
 the type of the expression `foo` (it could be an arbitrary expression).
 So `foo` is instantiated and then re-generalised; but without
 `-XPolyKinds` we don't get a poly-kinded type.  Hence the difference in
 what is printed by `:type` and `:info`.

 Here's a proposal: even without `-fprint-explicit-foralls`, we should
 print any foralls that bind a type variable whose kind includes a kind
 variable.

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


More information about the ghc-tickets mailing list