[GHC] #14643: Partial type signatures interact unexpectedly with :browse (was: Partial type signatures in spliced TH declarations behave unexpectedly)
GHC
ghc-devs at haskell.org
Mon Jan 8 00:00:47 UTC 2018
#14643: Partial type signatures interact unexpectedly with :browse
-------------------------------------+-------------------------------------
Reporter: mnislaih | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.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 RyanGlScott):
Note that this has nothing to do with Template Haskell. You can also
trigger the issue with this (slightly more) minimal file:
{{{#!hs
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE TemplateHaskell #-}
module Bug where
f :: (Monad m, _) => [m a] -> m [a]
f' :: (Monad m, _) => [m a] -> m [a]
f = f'
f' [] = return []
f' (x:xx) = f xx
g, g' :: (Monad m, _) => [m a] -> m [a]
g = g'
g' [] = return []
g' (x:xx) = g xx
}}}
{{{
$ ghci Bug.hs -Wno-partial-type-signatures
GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Ok, one module loaded.
λ> :browse
f :: (Monad m, Monad m) => [m a] -> m [a]
f' :: (Monad m, Monad m) => [m a] -> m [a]
g ::
(Monad GHC.Types.Any, Monad m) =>
[GHC.Types.Any GHC.Types.Any] -> GHC.Types.Any [GHC.Types.Any]
g' :: (Monad GHC.Types.Any, Monad m) => [m a] -> m [a]
}}}
The same behavior also happens with `:type v` (but not `:type`, since that
performs deep instantiation of the types):
{{{
λ> :type +v f
f :: (Monad m, Monad m) => [m a] -> m [a]
λ> :type +v f'
f' :: (Monad m, Monad m) => [m a] -> m [a]
λ> :type +v g
g :: (Monad GHC.Types.Any, Monad m) =>
[GHC.Types.Any GHC.Types.Any] -> GHC.Types.Any [GHC.Types.Any]
λ> :type +v g'
g' :: (Monad GHC.Types.Any, Monad m) => [m a] -> m [a]
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14643#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list