
#14218: GHC.Stack.HasCallStack not compatible with ConstraintKinds -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: -------------------------------------+------------------------------------- The programs `Good` and `Bad` are the same, except that `Bad` uses a constraint synonym including `GHC.Stack.HasCallStack` whereas `Good` inlines the constraints. I expect them to produce the same output, but they don't: {{{ $ ./Good ["callStack","f"] $ ./Bad ["f"] }}} Here is the source for `Good.hs`: {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} -- For nullary 'Trivial' class module Main where import qualified GHC.Stack as Ghc class Trivial where instance Trivial where -- | Print the functions on the call stack. callStack :: (Ghc.HasCallStack, Trivial) => IO () callStack = print $ map fst (Ghc.getCallStack Ghc.callStack) f :: (Ghc.HasCallStack, Trivial) => IO () f = callStack main :: IO () main = f -- Should print @["callStack", "f"]@. }}} Here is the source for `Bad.hs`: {{{#!hs {-# LANGUAGE ConstraintKinds #-} -- For 'C' {-# LANGUAGE MultiParamTypeClasses #-} -- For nullary 'Trivial' class module Main where import qualified GHC.Stack as Ghc class Trivial where instance Trivial where type C = (Ghc.HasCallStack, Trivial) -- | Print the functions on the call stack. callStack :: C => IO () callStack = print $ map fst (Ghc.getCallStack Ghc.callStack) f :: C => IO () f = callStack main :: IO () main = f -- Should print @["callStack", "f"]@. }}} Tested compiled and interpreted with GHC 8.2.1 and 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler