
#14643: Partial type signatures in spliced TH declarations behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- Minimal example: {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE TemplateHaskell #-} module Minimal where id [d| f :: (Monad m, _) => [m a] -> m [a] f' :: (Monad m, _) => [m a] -> m [a] f = f' f' [] = return [] f' (x:xx) = f xx |] }}} {{{ [1 of 1] Compiling Minimal ( /Users/pepe/Dropbox/code/debug- hoed/test/minimal.hs, interpreted ) /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f :: (Monad m_a7NN, _) => [m_a7NN a_a7NO] -> m_a7NN [a_a7NO] | 5 | id [d| | ^^^^^^... /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f' :: (Monad m_a7NL, _) => [m_a7NL a_a7NM] -> m_a7NL [a_a7NM] | 5 | id [d| | ^^^^^^... Ok, one module loaded. :browse f :: (Monad m, Monad m) => [m a] -> m [a] f' :: (Monad m, Monad m) => [m a] -> m [a] }}} Notice the duplicate Monad m constraint. Things get even more weird if the type signatures are declared together: {{{#!hs id [d| f, f' :: (Monad m, _) => [m a] -> m [a] f = f' f' [] = return [] f' (x:xx) = f xx |] }}} {{{ [1 of 1] Compiling Minimal ( /Users/pepe/Dropbox/code/debug- hoed/test/minimal.hs, interpreted ) /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f :: (Monad m_a88E, _) => [m_a88E a_a88F] -> m_a88E [a_a88F] | 5 | id [d| | ^^^^^^... /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f' :: (Monad m_a88E, _) => [m_a88E a_a88F] -> m_a88E [a_a88F] | 5 | id [d| | ^^^^^^... Ok, one module loaded. :browse f :: (Monad ghc-prim-0.5.1.1:GHC.Types.Any, Monad m) => [ghc-prim-0.5.1.1:GHC.Types.Any ghc-prim-0.5.1.1:GHC.Types.Any] -> ghc-prim-0.5.1.1:GHC.Types.Any [ghc-prim-0.5.1.1:GHC.Types.Any] f' :: (Monad ghc-prim-0.5.1.1:GHC.Types.Any, Monad m) => [m a] -> m [a] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler