[GHC] #14897: QuantifiedConstraints: Can't print type of quantified constraint

#14897: QuantifiedConstraints: Can't print type of quantified constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language QuantifiedConstraints, FlexibleInstances, UndecidableInstances, MonoLocalBinds #-} class (forall xx. Functor (f xx)) => Functor' f instance (forall xx. Functor (f xx)) => Functor' f fmap' :: Functor' f => (b -> b') -> (f a b -> f a b') fmap' = fmap }}} load in ghci and check the type of `fmap'` {{{ $ ... -ignore-dot-ghci Bug2.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Bug2.hs, interpreted ) Ok, one module loaded. *Main> :t fmap' <interactive>:1:1: error: No instance for (Functor (f xx)) arising from a use of ‘fmap'’ *Main> }}} Simpler example {{{ GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help Prelude> :set -XRankNTypes -XQuantifiedConstraints Prelude> let a :: (forall xx. Monoid (f xx)) => f a; a = mempty Prelude> :t a <interactive>:1:1: error: No instance for (Monoid (f xx)) arising from a use of ‘a’ Prelude> }}} I expected the same output as `:t +v` {{{ Prelude> :t +v a a :: (forall xx. Monoid (f xx)) => f a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14897 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14897: QuantifiedConstraints: Can't print type of quantified constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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 Iceland_jack): I know printing isn't the problem, “over-eagerly resolves quantified constraint...” something -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14897#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14897: QuantifiedConstraints: Can't print type of quantified constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: What `:t e` does is to infer the type of the expression `e` and print it. So with `a :: (forall xx. Monoid (f xx)) => f a`, it's as if you'd typed the top level decl {{{ foo = a }}} What happens? We instantiate the type of `a` to get a Wanted constraint {{{ [W] forall x. Monoid (f1 x) }}} and the type `f1 a1`, where `f1` and `a1` are unification variables. Now we try to simplify the constraints and infer the most general type for `foo`. Unsurprisingly, we fail with the reported error message. If, rather than inferring the type of an arbitrary ''expression'', you want to ask for the type (and other info) about an ''identifier'', use `:info a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14897#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC