[GHC] #7624: Handling ImplicitParams in Instance Declaration

GHC cvs-ghc at haskell.org
Fri Jan 25 19:11:13 CET 2013


#7624: Handling ImplicitParams in Instance Declaration
---------------------------------+------------------------------------------
    Reporter:  philipjf          |       Owner:                   
        Type:  bug               |      Status:  new              
    Priority:  normal            |   Milestone:                   
   Component:  Documentation     |     Version:  7.6.1            
    Keywords:  ImplicitParams    |          Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  |     Failure:  Documentation bug
  Difficulty:  Unknown           |    Testcase:                   
   Blockedby:                    |    Blocking:                   
     Related:                    |  
---------------------------------+------------------------------------------

Comment(by philipjf):

 Hm...
 I'm not sure that is different from what happen currently with local
 evidence and/or implicitParams
 {{{
 {-# LANGUAGE GADTs, ImplicitParams #-}
 class C a where
   op :: a -> a

 data X a where
   X :: C a => X a

 fooGADT X xs = (length xs, op xs)

 fooIP xs ys = let ?op = const ys in (length xs, ?op xs)
 }}}
 GHC infers types for both of these terms, and has rules to do it.  We have
 `fooGADT :: C [a] => X t -> [a] -> (Int, [a])` inferred, but this type
 will be rejected if we give it as an annotation because it has a non type
 variable argument, and is no more general than `fooGADT :: X [a] -> [a] ->
 (Int, [a])`.

 Actually, giving a type annotation is not good enough in the presence of
 local type information to determine behavior
 {{{
 fooGADT' :: X [a] -> X [a] -> [a] -> (Int,[a])
 fooGADT' X X xs = (length xs, op xs)
 }}}
 or the really unclear
 {{{
 data X' a where
  X' :: (?op :: a -> a) => X' a

 fooGADT'' :: X' [a] -> X' [a] -> [a] -> (Int,[a])
 fooGADT'' X' X' xs = (length xs, ?op xs)

 whatShouldThisDo :: [a] -> [a] -> (Int, [a])
 whatShouldThisDo xs ys
      = let a = (let ?op = const ys in X')
              b = (let ?op = id in X')
          in  fooGADT'' a b xs
 }}}

 The point is, I think this is a general problem, and not one unique to
 allowing implicits in instances.  With orphan instnaces you don't need
 implicit params at all to make this problem show up.

 Allowing implicits in class constraints seems more suspect though.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7624#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list