[GHC] #15341: :info prints kinds in closed type family equations without enabling -fprint-explicit-kinds
GHC
ghc-devs at haskell.org
Wed Jul 4 16:21:45 UTC 2018
#15341: :info prints kinds in closed type family equations without enabling
-fprint-explicit-kinds
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Keywords: TypeFamilies | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Load this file into GHCi:
{{{#!hs
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where
type family Foo (a :: k) :: k where
Foo a = a
}}}
And run `:info` on `Foo`:
{{{
$ /opt/ghc/8.4.3/bin/ghci Bug.hs
GHCi, version 8.4.3: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/ryanglscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Ok, one module loaded.
λ> :i Foo
type family Foo (a :: k) :: k
where Foo k a = a
-- Defined at Bug.hs:5:1
}}}
Note that when printing the equation for `Foo`, the kind `k` is treated as
though it were the first visible argument to `Foo`, even though `-fprint-
explicit-kinds` is not enabled. This is because `ppr_tc_args` in
`IfaceType` does not take `-fprint-explicit-kinds` into account.
Patch incoming (pending a `./validate`).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15341>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list