Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : imp-param-class

http://hackage.haskell.org/trac/ghc/changeset/351ee7d1249fabea2b2a8a120dd4a184ea5d5472

>---------------------------------------------------------------

commit 351ee7d1249fabea2b2a8a120dd4a184ea5d5472
Author: Iavor S. Diatchki <[email protected]>
Date:   Sun May 27 16:53:50 2012 -0700

    Remove parameter from `ipDef`

>---------------------------------------------------------------

 GHC/IP.hs |   10 ++++------
 1 files changed, 4 insertions(+), 6 deletions(-)

diff --git a/GHC/IP.hs b/GHC/IP.hs
index b433276..26fee1a 100644
--- a/GHC/IP.hs
+++ b/GHC/IP.hs
@@ -3,7 +3,7 @@
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE DataKinds #-}
 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
-module GHC.IP (IP, IPName(..), IPValue, ipUse, ipDef) where
+module GHC.IP (IP, IPName(..), ipUse, ipDef) where
 
 import GHC.TypeLits
 
@@ -22,11 +22,9 @@ ipUse x = case val x of
   where val :: IP x a => IPName x -> IPValue x a
         val _ = ip
 
--- | This is used when we construct evidence for the 'IP' class.
--- @let ?x = e in ...@ uses @ipDef (IPName :: "x") e@ to cinstruct
--- a new implict parameter.
-ipDef :: IPName x -> a -> IPValue x a
-ipDef _ a = IPValue a
+-- Used internally by the compiler to create `IP` dictionaries.
+ipDef :: a -> IPValue x a
+ipDef = IPValue
 
 -- | The syntax @?x :: a@ is desugared into @IP "x" a@
 class IP x a | x -> a where



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to