[GHC] #13201: Type-level naturals aren't instantiate with GHCi debugger

#13201: Type-level naturals aren't instantiate with GHCi debugger -------------------------------------+------------------------------------- Reporter: konn | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHCi debugger cannot use the information of specific value type-level natural number, even if it is explicitly specified. For example, consider the following code: {{{#!hs {-# LANGUAGE DataKinds, KindSignatures, StandaloneDeriving, TypeOperators #-} module Main where import GHC.TypeLits data Foo (n :: Nat) = Foo deriving instance KnownNat n => Show (Foo n) fooSucc :: Foo n -> Foo (n + 1) fooSucc Foo = Foo foos :: Foo n -> [Foo (n + 1)] foos f = loop 5 where loop 0 = [] loop n = fooSucc f : loop (n - 1) main :: IO () main = print $ foos (Foo :: Foo 5) }}} Loading it with GHCi Debugger, we cannot `show` the value of `f`, because GHCi debugger doesn't know the specific value of `n` (in`Foo n`), even though we specify it in `main`! {{{#!hs ghci> :l tmp.hs [1 of 1] Compiling Main ( tmp.hs, interpreted ) Ok, modules loaded: Main. ghci> :break foos Breakpoint 0 activated at tmp.hs:13:10-15 ghci> :set stop :list ghci> main Stopped in Main.foos, tmp.hs:13:10-15 _result :: [Foo (n + 1)] = _ loop :: (Num t, Eq t) => t -> [Foo (n + 1)] = _ 12 foos :: Foo n -> [Foo (n + 1)] 13 foos f = loop 5 14 where ghci> :step Stopped in Main.foos.loop, tmp.hs:16:14-37 _result :: [Foo (n + 1)] = _ f :: Foo n = _ n :: Integer = 5 15 loop 0 = [] 16 loop n = fooSucc f : loop (n - 1) 17 ghci> :t f f :: Foo n ghci> f <interactive>:8:1: error: • No instance for (KnownNat n) arising from a use of ‘print’ • In a stmt of an interactive GHCi command: print it }}} Of course, we can inspect the internal representation via `:print` or `:force` command, but it is rather impractical when we cannot easily read its pretty form from its internal representation . I tested this with GHC 7.0.1 and 7.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13201 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13201: Type-level naturals aren't instantiate 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: | -------------------------------------+------------------------------------- Comment (by goldfire): Sadly, the GHCi debugger has no current maintainer. It is slowly rotting. Would you (for all values of "you") be able to step in and help? :) I can't even offer to advise, because I have no clue how the code works. But, if someone stood up to say that they would maintain it, we could perhaps hunt down the original implementor and get more info. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13201#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13201: Type-level naturals aren't instantiate 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: | -------------------------------------+------------------------------------- Comment (by rwbarton): I took a quick look at this, thinking the issue would be that, in `foos`, the information of the specific type `n` is unavailable at runtime. But apparently it's not so simple, since if you write an ordinary parametrically polymorphic function like {{{#!hs myFun :: [a] -> [a] myFun l = l ++ reverse l }}} and step into `myFun`, ghci is still capable of displaying the specific type of `l`. So, my conclusion is that how this works is a mystery. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13201#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13201#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#13201: Type-level naturals aren't instantiated with GHCi debugger -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: debugger 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 RyanGlScott): * keywords: => debugger * component: Compiler => GHCi -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13201#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC