[GHC] #12507: Can't deduce implicit parameter

GHC ghc-devs at haskell.org
Sat Aug 20 23:22:12 UTC 2016


#12507: Can't deduce implicit parameter
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           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:
-------------------------------------+-------------------------------------
 I tried running a [https://gist.github.com/llelf/6c01ded225877914f38a
 gist]

 {{{#!hs
 {-# LANGUAGE GADTs, ConstraintKinds, Rank2Types, ImplicitParams #-}

 data Rec fields where
   Rec :: fields => Rec fields

 infixr 1 ?
 (?) :: Rec fields -> (fields => r) -> r
 Rec ? e = e

 record :: Rec (?a :: Int, ?b :: String)
 record = Rec where ?a=42
                    ?b="hey"

 access :: Int
 access = record ? ?a
 }}}

 and got

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

 tCHB.hs:15:19: error:
     • Could not deduce: ?a::Int
         arising from a use of implicit parameter ‘?a’
       from the context: (?a::Int, ?b::String)
         bound by a type expected by the context:
                    (?a::Int, ?b::String) => Int
         at tCHB.hs:15:10-20
     • In the second argument of ‘(?)’, namely ‘?a’
       In the expression: record ? ?a
       In an equation for ‘access’: access = record ? ?a
 Failed, modules loaded: none.
 Prelude>
 }}}

 I would certainly expect the context `(?a::Int, ?b::String)` to imply
 `?a::Int`?

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


More information about the ghc-tickets mailing list