[GHC] #14942: QuantifiedConstraints: GHC can't infer

GHC ghc-devs at haskell.org
Mon Mar 19 21:55:05 UTC 2018


#14942: QuantifiedConstraints: GHC can't infer
-------------------------------------+-------------------------------------
           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:
-------------------------------------+-------------------------------------
 This works

 {{{#!hs
 {-# Language QuantifiedConstraints, GADTs, KindSignatures, RankNTypes,
 ConstraintKinds #-}

 import Data.Kind

 newtype Free :: (Type -> Constraint) -> (Type -> Type) where
   Free :: (forall x. cls x => (a -> x) -> x) -> Free cls a

 var :: a -> Free cls a
 var a = Free $ \var ->
   var a

 oneTwo :: (forall x. semi x => Semigroup x) => Free semi Int
 oneTwo = Free $ \var ->
   var 1 <> var 2

 nil :: (forall x. mon x => Monoid x) => Free mon Int
 nil = Free $ \var ->
   mempty

 together :: (forall x. mon x => Monoid x) => [Free mon Int]
 together = [var 0, nil, oneTwo]
 }}}

 If we comment out `together`'s type signature GHC cannot infer it back,
 shouldn't it be able to though?

 {{{
 $ ./ghc-stage2 --interactive -ignore-dot-ghci Proposal.hs
 GHCi, version 8.5.20180128: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( Proposal.hs, interpreted )

 Proposal.hs:21:20: error:
     • Could not deduce (Monoid x) arising from a use of ‘nil’
       from the context: cls x
         bound by a quantified context at Proposal.hs:21:1-31
       Possible fix: add (Monoid x) to the context of a quantified context
     • In the expression: nil
       In the expression: [var 0, nil, oneTwo]
       In an equation for ‘together’: together = [var 0, nil, oneTwo]
    |
 21 | together = [var 0, nil, oneTwo]
    |                    ^^^

 Proposal.hs:21:25: error:
     • Could not deduce (Semigroup x) arising from a use of ‘oneTwo’
       from the context: cls x
         bound by a quantified context at Proposal.hs:21:1-31
       Possible fix:
         add (Semigroup x) to the context of a quantified context
     • In the expression: oneTwo
       In the expression: [var 0, nil, oneTwo]
       In an equation for ‘together’: together = [var 0, nil, oneTwo]
    |
 21 | together = [var 0, nil, oneTwo]
    |                         ^^^^^^
 Failed, no modules loaded.
 Prelude>
 }}}

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


More information about the ghc-tickets mailing list