[GHC] #10903: Add an option to infer CallStack implicit parameters

GHC ghc-devs at haskell.org
Mon Sep 21 06:03:17 UTC 2015


#10903: Add an option to infer CallStack implicit parameters
-------------------------------------+-------------------------------------
              Reporter:  gridaphobe  |             Owner:
                  Type:  feature     |            Status:  new
  request                            |
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.11
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
             Test Case:              |        Blocked By:
              Blocking:              |   Related Tickets:
Differential Revisions:              |
-------------------------------------+-------------------------------------
 Adam Foltzer mentioned to me at ICFP that it would be nice if GHC had a
 "debug" mode that automatically inserted CallStack IPs in every function
 signature. Then you could easily get nice, fairly complete, call-stacks
 during development. Of course you could already do this with judicious use
 of CPP macros, but that's quite tedious (and error prone).

 As an example, consider

 {{{#!hs
 module A where

 foo xs = head xs

 head :: [a] -> a
 head (x:xs) = x
 head _ = error "bad"
 }}}

 Compiling `A` in this mode should result in the following signature

 {{{#!hs
 module A where

 foo :: (?callStack :: CallStack) => [a] -> a
 head :: (?callStack :: CallStack) => [a] -> a
 }}}

 I have a few concerns with this though:

 1. We're '''changing''' a type signature that the user wrote. It would be
 a well-defined and consistent change across the whole module, but it's
 still unsettling.

 2. How do we handle a function that already has a CallStack IP?

 {{{#!hs
 bar :: (?stk :: CallStack) => [a] -> a
 }}}

    If we're aiming for consistent insertion of CallStacks everywhere, it
 might make sense to remove the `?stk :: CallStack` and insert a
 `?callStack :: CallStack`, so they'll be appended correctly. But here
 again we'd be changing a user-written type signature. Furthermore, `bar`
 might call a function from a different module (or package) that hasn't
 been given this consistent debug treatment, and this other module might
 expect that the CallStack be named `?stk`.

 3. If the CallStack is not used, e.g.

 {{{#!hs
 null :: (?callStack :: CallStack) => [a] -> Bool
 null [] = True
 null (_:_) = False
 }}}

    it will trigger a redundant constraint warning. I think we could
 address this by bubbling up CallStack constraints in much the same way
 that other constraints are propagated, so

 {{{#!hs
 module A where

 foo xs = head xs

 head :: [a] -> a
 head (x:xs) = x
 head _ = error "bad"

 null [] = True
 null (_:_) = False
 }}}

    would get the signature

 {{{#!hs
 module A where

 foo :: (?callStack :: CallStack) => [a] -> a
 head :: (?callStack :: CallStack) => [a] -> a
 null :: [a] -> Bool
 }}}

   In other words, we would only infer a CallStack constraint for a
 function when the body induces a wanted CallStack constraint.

 4. How would this interact with cabal packages? If I accidentally install
 a package in debug mode, all downsteam packages will be compiled against
 the CallStack-laden signatures. Seems like we might need a new "debug"
 way..

 It's pretty clear to me that a debug mode would be useful (in fact I
 manually added a bunch of CallStacks to my code the other day, only to
 remove them once I was done debugging), but the concerns (particularly 4.)
 are substantial. There's also the question of how all of this interacts
 with the ongoing DWARF work.

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


More information about the ghc-tickets mailing list