[GHC] #13201: Type-level naturals aren't instantiated with GHCi debugger
GHC
ghc-devs at haskell.org
Mon Feb 6 05:18:28 UTC 2017
#13201: Type-level naturals aren't instantiated with GHCi debugger
-------------------------------------+-------------------------------------
Reporter: konn | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by akio):
* cc: akio (added)
Comment:
Here is a test case that doesn't use type-level naturals:
{{{#!hs
{-# LANGUAGE StandaloneDeriving #-}
data Foo a = Foo
deriving instance (Show a) => Show (Foo a)
fooSucc :: Foo a -> Foo [a]
fooSucc Foo = Foo
foos :: Foo a -> [Foo [a]]
foos f = loop 5
where
loop 0 = []
loop n = fooSucc f : loop (n - 1)
main :: IO ()
main = print $ foos (Foo :: Foo Int)
}}}
By no means I'm an export on this, but as far as I know, the GHCi debugger
tries to re-construct the type information as much as possible by
inspecting the runtime representation (closures) of the values. This means
it cannot distinguish between different types with the exact same
representation. For example, it cannot distinguish a newtype from its
content type, nor can it determine a phantom type parameter of a data
type.
In this example, since `n` is only used as a phantom parameter of the
datatype `Foo`, the GHCi debugger has no way of reconstructing it at
runtime, I think.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13201#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list