[GHC] #10846: PartialTypeSignatures change implicit CallStack behavior

GHC ghc-devs at haskell.org
Sun Sep 6 17:55:32 UTC 2015


#10846: PartialTypeSignatures change implicit CallStack behavior
-------------------------------------+-------------------------------------
        Reporter:  nitromaster101    |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.10.2
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by nitromaster101:

Old description:

> I have two functions, f and f2 which are identical expect for the use of
> PartialTypeSignatures in f2. GHC produces a warning and says that f2's
> wildcard is filled in by String, which is correct.
>
> {{{#!hs
> {-# LANGUAGE ImplicitParams, PartialTypeSignatures #-}
>
> import GHC.Types
>
> f :: (?loc :: CallStack) => String
> f = show $ map (srcLocStartLine . snd) $ getCallStack ?loc
>
> f2 :: (?loc :: CallStack) => _
> f2 = show $ map (srcLocStartLine . snd) $ getCallStack ?loc
>
> f_caller = f
> f2_caller = f2
> }}}
> {{{
> [1 of 1] Compiling Main             ( Bug2.hs, interpreted )
>
> Bug2.hs:8:30: warning:
>     Found type wildcard ‘_’ standing for ‘String’
>     In the type signature for:
>       f2 :: (?loc :: CallStack) => _
> Ok, modules loaded: Main.
> *Main> f_caller
> "[6,11]"
> *Main> f2_caller
> "[9]"
> }}}
>
> f2_caller should have two entries (f2_caller's line and f2's line), just
> like f_caller.

New description:

 I'm using GHC head at 062feee4e7408ad5b9d882e5fed2c700e337db72

 I have two functions, f and f2 which are identical expect for the use of
 PartialTypeSignatures in f2. GHC produces a warning and says that f2's
 wildcard is filled in by String, which is correct.

 {{{#!hs
 {-# LANGUAGE ImplicitParams, PartialTypeSignatures #-}

 import GHC.Types

 f :: (?loc :: CallStack) => String
 f = show $ map (srcLocStartLine . snd) $ getCallStack ?loc

 f2 :: (?loc :: CallStack) => _
 f2 = show $ map (srcLocStartLine . snd) $ getCallStack ?loc

 f_caller = f
 f2_caller = f2
 }}}
 {{{
 [1 of 1] Compiling Main             ( Bug2.hs, interpreted )

 Bug2.hs:8:30: warning:
     Found type wildcard ‘_’ standing for ‘String’
     In the type signature for:
       f2 :: (?loc :: CallStack) => _
 Ok, modules loaded: Main.
 *Main> f_caller
 "[6,11]"
 *Main> f2_caller
 "[9]"
 }}}

 f2_caller should have two entries (f2_caller's line and f2's line), just
 like f_caller.

--

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


More information about the ghc-tickets mailing list