[commit: ghc] master: Revert "Make Ptr's parameter phantom" (f251afe)
git at git.haskell.org
git at git.haskell.org
Mon Jun 9 20:58:31 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f251afe4e450317c99defab9eeba63a0a998780b/ghc
>---------------------------------------------------------------
commit f251afe4e450317c99defab9eeba63a0a998780b
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Jun 9 22:58:03 2014 +0200
Revert "Make Ptr's parameter phantom"
This reverts commit 1946922c61df427e59f8a00572fd4dd6501abd98, as it
trips the build system over, and I don't see why.
>---------------------------------------------------------------
f251afe4e450317c99defab9eeba63a0a998780b
libraries/base/Data/Coerce.hs | 3 ++-
libraries/base/GHC/Ptr.lhs | 10 ++--------
2 files changed, 4 insertions(+), 9 deletions(-)
diff --git a/libraries/base/Data/Coerce.hs b/libraries/base/Data/Coerce.hs
index 9199835..fb38b36 100644
--- a/libraries/base/Data/Coerce.hs
+++ b/libraries/base/Data/Coerce.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE AutoDeriveTypeable #-}
+{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/GHC/Ptr.lhs b/libraries/base/GHC/Ptr.lhs
index 341512b..c959d1e 100644
--- a/libraries/base/GHC/Ptr.lhs
+++ b/libraries/base/GHC/Ptr.lhs
@@ -31,13 +31,13 @@ import GHC.Show
import GHC.Num
import GHC.List ( length, replicate )
import Numeric ( showHex )
-import Data.Coerce
#include "MachDeps.h"
------------------------------------------------------------------------
-- Data pointers.
+type role Ptr representational
data Ptr a = 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
@@ -49,10 +49,6 @@ data Ptr a = Ptr Addr# deriving (Eq, Ord)
-- to access the pointer. For example you might write small foreign
-- functions to get or set the fields of a C @struct at .
--- The role of Ptr's parameter is phantom, as there is relation between
--- the Haskell representation and whathever the user puts at the end of the
--- pointer. And phantom is useful to implement castPtr (see #9163)
-
-- |The constant 'nullPtr' contains a distinguished value of 'Ptr'
-- that is not associated with a valid memory location.
nullPtr :: Ptr a
@@ -60,7 +56,7 @@ nullPtr = Ptr nullAddr#
-- |The 'castPtr' function casts a pointer from one type to another.
castPtr :: Ptr a -> Ptr b
-castPtr = coerce
+castPtr (Ptr addr) = Ptr addr
-- |Advances the given address by the given offset in bytes.
plusPtr :: Ptr a -> Int -> Ptr b
@@ -128,8 +124,6 @@ data FunPtr a = FunPtr Addr# deriving (Eq, Ord)
-- > foreign import ccall "dynamic"
-- > mkFun :: FunPtr IntFunction -> IntFunction
--- The role of FunPtr is representational, to be on the safe side (see #9163)
-
-- |The constant 'nullFunPtr' contains a
-- distinguished value of 'FunPtr' that is not
-- associated with a valid memory location.
More information about the ghc-commits
mailing list