[commit: base] master: Mark the roles of Ptr and FunPtr as R, not P! (ab9e8e3)
Richard Eisenberg
eir at ghc.haskell.org
Fri Aug 2 16:59:54 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/ab9e8e309e427fa7153e8e1cd124b4c7c1531ef4
>---------------------------------------------------------------
commit ab9e8e309e427fa7153e8e1cd124b4c7c1531ef4
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Fri Aug 2 15:52:02 2013 +0100
Mark the roles of Ptr and FunPtr as R, not P!
>---------------------------------------------------------------
GHC/Ptr.lhs | 6 +++---
1 file changed, 3 insertions(+), 3 deletions(-)
diff --git a/GHC/Ptr.lhs b/GHC/Ptr.lhs
index 3a4f3e8..385a427 100644
--- a/GHC/Ptr.lhs
+++ b/GHC/Ptr.lhs
@@ -1,6 +1,6 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, RoleAnnotations #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
@@ -38,7 +38,7 @@ import Numeric ( showHex )
------------------------------------------------------------------------
-- Data pointers.
-data Ptr a = Ptr Addr# deriving (Eq, Ord)
+data Ptr a at R = Ptr Addr# deriving (Eq, Ord)
-- ^ A value of type @'Ptr' a@ represents a pointer to an object, or an
-- array of objects, which may be marshalled to or from Haskell values
-- of type @a at .
@@ -82,7 +82,7 @@ minusPtr (Ptr a1) (Ptr a2) = I# (minusAddr# a1 a2)
------------------------------------------------------------------------
-- Function pointers for the default calling convention.
-data FunPtr a = FunPtr Addr# deriving (Eq, Ord)
+data FunPtr a at R = FunPtr Addr# deriving (Eq, Ord)
-- ^ A value of type @'FunPtr' a@ is a pointer to a function callable
-- from foreign code. The type @a@ will normally be a /foreign type/,
-- a function type with zero or more arguments where
More information about the ghc-commits
mailing list