CallStack naming

Joachim Breitner mail at joachim-breitner.de
Wed Jan 20 11:50:46 UTC 2016


Hi,

Am Mittwoch, den 20.01.2016, 10:32 +0000 schrieb Simon Peyton Jones:
> >  foo x :: AppendsCallStack => a -> a
> 
> Remove the "x"!

heh. Silly me. So let’s try again:


With 7.10 it now works:

    ==> AppendCallStack.hs <==
    {-# LANGUAGE ConstraintKinds, ImplicitParams #-}
    module AppendCallStack (AppendsCallStack) where

    import GHC.Stack

    type AppendsCallStack = ?callStack::CallStack

    ==> Bar.hs <==
    {-# LANGUAGE FlexibleContexts #-}
    module Main where

    import AppendCallStack
    import MyError

    foo :: AppendsCallStack => a -> a
    foo x = myerror "Test"

    main = print (foo ())

    ==> MyError.hs <==
    {-# LANGUAGE ImplicitParams #-}
    module MyError where

    import GHC.Stack

    myerror :: (?callStack :: CallStack) => String -> a
    myerror msg = error (msg ++ ": " ++ showCallStack ?callStack)


Note that I need FlexibleContexts on the usage site to be able to use
this, otherwise I get

     Non type-variable argument
      in the constraint: ?callStack::GHC.Stack.CallStack

See it in action:

    $ ghc --make Bar && ./Bar
    Bar: Test: ?callStack, called at ./MyError.hs:7:51 in main:MyError
      myerror, called at Bar.hs:8:9 in main:Main
      foo, called at Bar.hs:10:15 in main:Main


With GHC-HEAD, it compiles no longer(!):

    [1 of 2] Compiling AppendCallStack  ( AppendCallStack.hs,
    AppendCallStack.o )

    AppendCallStack.hs:6:1: error:
        • Illegal implicit parameter ‘?callStack::CallStack’
        • In the type synonym declaration for ‘AppendsCallStack’


So Richard, does it do what you want with GHC-7.10? And given that GHC
HEAD rejects it, was 7.10 wrong or is there a bug in HEAD?

Greetings,
Joachim

-- 
Joachim “nomeata” Breitner
  mail at joachim-breitner.dehttp://www.joachim-breitner.de/
  Jabber: nomeata at joachim-breitner.de  • GPG-Key: 0xF0FBF51F
  Debian Developer: nomeata at debian.org

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 819 bytes
Desc: This is a digitally signed message part
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20160120/e7fd0bc9/attachment.sig>


More information about the ghc-devs mailing list