[commit: base] master: Add asProxyTypeOf and Trustworthy pragma to Data.Proxy (51ad1c6)

Richard Eisenberg eir at ghc.haskell.org
Wed Jul 31 19:35:27 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/51ad1c68130d494e4624b1e732a27c6ad26b6173

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

commit 51ad1c68130d494e4624b1e732a27c6ad26b6173
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Jul 31 18:35:10 2013 +0100

    Add asProxyTypeOf and Trustworthy pragma to Data.Proxy

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

 Data/Proxy.hs |   12 ++++++++++--
 1 file changed, 10 insertions(+), 2 deletions(-)

diff --git a/Data/Proxy.hs b/Data/Proxy.hs
index 65a33f9..bda295e 100644
--- a/Data/Proxy.hs
+++ b/Data/Proxy.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude, Trustworthy #-}
 #ifdef __GLASGOW_HASKELL__
 {-# LANGUAGE PolyKinds #-}
 #endif
@@ -18,7 +18,7 @@
 
 module Data.Proxy
   (
-        Proxy(..)
+        Proxy(..), asProxyTypeOf
 #ifdef __GLASGOW_HASKELL__
       , KProxy(..)
 #endif
@@ -95,3 +95,11 @@ instance Monad Proxy where
     {-# INLINE return #-}
     _ >>= _ = Proxy
     {-# INLINE (>>=) #-}
+
+-- | 'asProxyTypeOf' is a type-restricted version of 'const'.
+-- It is usually used as an infix operator, and its typing forces its first
+-- argument (which is usually overloaded) to have the same type as the tag
+-- of the second.
+asProxyTypeOf :: a -> Proxy a -> a
+asProxyTypeOf = const
+{-# INLINE asProxyTypeOf #-}
\ No newline at end of file






More information about the ghc-commits mailing list