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

On branch  : imp-param-class

http://hackage.haskell.org/trac/ghc/changeset/c6ff62c1f9e6d4b0e2d5be1830624cffcaff8450

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

commit c6ff62c1f9e6d4b0e2d5be1830624cffcaff8450
Author: Iavor S. Diatchki <[email protected]>
Date:   Sun Jun 10 15:30:36 2012 -0700

    Switch back to simple IP class.

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

 GHC/IP.hs |   21 +++------------------
 1 files changed, 3 insertions(+), 18 deletions(-)

diff --git a/GHC/IP.hs b/GHC/IP.hs
index dd75d07..762f26b 100644
--- a/GHC/IP.hs
+++ b/GHC/IP.hs
@@ -3,27 +3,12 @@
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE DataKinds #-}
 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
-module GHC.IP (IP, IPName(..), ipUse) where
+module GHC.IP (IP(..)) where
 
 import GHC.TypeLits
 
--- | A singleton type used to name implicit parameters.
-data IPName (name :: Symbol) = IPName
-
--- | A type used to give values to implicit parameters.
--- The name is a phantom parameter because it needs no run-time representation.
-newtype IPValue (name :: Symbol) a = IPValue a
-
-
--- | The syntax @?x@ is desuagred into @ipUse (IPName :: "x")@
-ipUse :: IP x a => IPName x -> a
-ipUse x = case val x of
-            IPValue a -> a
-  where val :: IP x a => IPName x -> IPValue x a
-        val _ = ip
-
 -- | The syntax @?x :: a@ is desugared into @IP "x" a@
-class IP x a | x -> a where
-  ip :: IPValue x a
+class IP (x :: Symbol) a | x -> a where
+  ip :: a
 
 



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

Reply via email to