Proposal: give Ptr a nominal role

Currently, we have data Ptr a = Ptr Addr# type role Ptr phantom This is weird: accidentally coercing a pointer to a different type is very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions. Thankfully, we have enough power to fix this now. data Addr = Ptr_ Addr# newtype Ptr a = Ptr_ Addr type role Ptr nominal pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#) castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion I propose that we do this.

hey David, heres a simpler version (attached below), that I think
accomplishes the same goal.
One issue, that would need to be evaluated empirically: how many type class
instances would break from this change? Would any?
is it Storable instances that are an issue, or things that use storable?
what safety is gained vs what is impacted? (i guess i mostly just wanna
understand what would be broken by this change, a lot of code in the wild
uses pointers for systems integrations)
newtype Ptr a = Ptr Addr#
type role Ptr nominal
castPtr :: Ptr a -> Ptr b
castPtr = unsafeCoerce
ptrCoercible
:: ((forall a b. Coercible (Ptr a) (Ptr b)) => r)
-> r
ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b)
ptrCoercion = Coercion
On Tue, Oct 30, 2018 at 1:57 PM David Feuer
Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Your simpler version won't even compile, and it gives Ptr the wrong kind.
I don't *think* anything breaks at all, unless it's using coerce on Ptr
types (the fix is easy). Note in particular that Ptr doesn't have a Generic
instance.
The extra safety is at the Storable use sites. If you have some type that
has a Ptr buried in it somewhere, coerce it to something else, and then
call a function that uses a (different) Storable instance for that field,
you're in trouble. With this change, the compiler will let you know that
there's a buried Ptr in there and (after verifying that it's okay) you can
introduce the coercibility explicitly to explain that it's fine.
On Tue, Oct 30, 2018, 2:06 PM Carter Schonwald
hey David, heres a simpler version (attached below), that I think accomplishes the same goal.
One issue, that would need to be evaluated empirically: how many type class instances would break from this change? Would any?
is it Storable instances that are an issue, or things that use storable?
what safety is gained vs what is impacted? (i guess i mostly just wanna understand what would be broken by this change, a lot of code in the wild uses pointers for systems integrations)
newtype Ptr a = Ptr Addr# type role Ptr nominal
castPtr :: Ptr a -> Ptr b castPtr = unsafeCoerce
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
On Tue, Oct 30, 2018 at 1:57 PM David Feuer
wrote: Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Oct 30, 2018, at 11:18 AM, David Feuer
wrote: Your simpler version won't even compile,
Here are the two versions edited so that both can compile (they needed some tweaks) for those playing along at home: {-# Language PatternSynonyms, FlexibleContexts, RoleAnnotations, RankNTypes, MagicHash #-} module Help where import GHC.Exts hiding (Ptr) import Data.Type.Coercion import Unsafe.Coerce {- Carter's version data Ptr a = Ptr Addr# type role Ptr nominal castPtr :: Ptr a -> Ptr b castPtr = unsafeCoerce ptrCoercible :: (forall a b. Coercible (Ptr a) (Ptr b) => r) -> r ptrCoercible r = r ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion -} data Addr = Addr_ Addr# newtype Ptr a = Ptr_ Addr type role Ptr nominal pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr_ a#) castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a ptrCoercible :: (forall a b. Coercible (Ptr a) (Ptr b) => r) -> r ptrCoercible r = r ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion

Are you sure that modification of Carter's will compile?
On Tue, Oct 30, 2018, 2:20 PM Eric Mertens
On Oct 30, 2018, at 11:18 AM, David Feuer
wrote: Your simpler version won't even compile,
Here are the two versions edited so that both can compile (they needed some tweaks) for those playing along at home:
{-# Language PatternSynonyms, FlexibleContexts, RoleAnnotations, RankNTypes, MagicHash #-} module Help where
import GHC.Exts hiding (Ptr) import Data.Type.Coercion import Unsafe.Coerce
{- Carter's version data Ptr a = Ptr Addr# type role Ptr nominal
castPtr :: Ptr a -> Ptr b castPtr = unsafeCoerce
ptrCoercible :: (forall a b. Coercible (Ptr a) (Ptr b) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion -}
data Addr = Addr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr_ a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: (forall a b. Coercible (Ptr a) (Ptr b) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion

No, it won’t compile, but it at least loads far enough to generate the right error that you can’t coerce data like that. I thought about sending a clarifying email afterward but I didn’t want to spam the list with a second message. The point is that all the syntactic errors are cleaned up to the point that one can actually play with the code now.
On Oct 30, 2018, at 11:22 AM, David Feuer
wrote: Are you sure that modification of Carter's will compile?

so i'm taking a look at the current docs / definition in base (and i'm
testing testing out seeing what happens if we changed the role and just
build ghc and base as is)
https://github.com/ghc/ghc/blob/82a716431cc680392e332bc2b1a1fd0d7faa4cd8/lib...
i'm replicating the docs below:
but the important detail is the phantom role in the current code is
deliberate ...
because no guarantees are made about the relationship between the choice in
type parameter ( which putatively will always have the same heap rep in
haskell land)
and the representation at the other side of the pointer.
a good example might be Ptr Char. Is this a single location of a 32bit /
utf32 code point, or an array of utf8 code points or utf32 code points?
is it null terminated vs there being an extra sequence length? These are
all valid things that can be happening. And
-- Data pointers.
-- The role of Ptr's parameter is phantom, as there is no 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)
-- redundant role annotation checks that this doesn't change
type role Ptr phantom
data Ptr a = Ptr Addr#
deriving ( Eq -- ^ @since 2.01
, Ord -- ^ @since 2.01
)
-- ^ 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@.
--
-- The type @a@ will often be an instance of class
-- 'Foreign.Storable.Storable' which provides the marshalling operations.
-- However this is not essential, and you can provide your own operations
-- to access the pointer. For example you might write small foreign
-- functions to get or set the fields of a C @struct@.
unrelatedly, while i'm not familiar with how to use modern coercible bits,
the folllowing subset of what i mentioned earlier seems to work fine
{-# Language PatternSynonyms, FlexibleContexts, RoleAnnotations,
RankNTypes, MagicHash #-}
module Ptr where
import GHC.Exts hiding (Ptr)
import Data.Type.Coercion
import Unsafe.Coerce
data Ptr a = Ptr Addr#
type role Ptr nominal
castPtr :: Ptr a -> Ptr b
castPtr = unsafeCoerce
ptrCoercible
:: (forall a b. Coercible (Ptr a) (Ptr b) => r)
-> r
ptrCoercible r = r
On Tue, Oct 30, 2018 at 2:24 PM Eric Mertens
No, it won’t compile, but it at least loads far enough to generate the right error that you can’t coerce data like that. I thought about sending a clarifying email afterward but I didn’t want to spam the list with a second message. The point is that all the syntactic errors are cleaned up to the point that one can actually play with the code now.
On Oct 30, 2018, at 11:22 AM, David Feuer
wrote: Are you sure that modification of Carter's will compile?

On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
a good example might be Ptr Char. Is this a single location of a 32bit / utf32 code point, or an array of utf8 code points or utf32 code points? is it null terminated vs there being an extra sequence length? These are all valid things that can be happening. And
I'm not sure if it affects your point, but I sure hope a 'Ptr Char' points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and array indexing will go out of bounds. Of course, in the C case, whether or not there are further chars after that and if they are terminated and what is the encoding is all ambiguous, as it always is for C.

Indeed. I think the point is that Ptr should be thought of as tied to
Storable. If you want to use an Addr# for something else, then you
shouldn't be using Ptr!
On Thu, Nov 1, 2018, 2:13 PM Evan Laforge On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
a good example might be Ptr Char. Is this a single location of a 32bit
/ utf32 code point, or an array of utf8 code points or utf32 code points?
is it null terminated vs there being an extra sequence length? These are
all valid things that can be happening. And I'm not sure if it affects your point, but I sure hope a 'Ptr Char'
points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points
to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and
array indexing will go out of bounds. Of course, in the C case, whether or not there are further chars after
that and if they are terminated and what is the encoding is all
ambiguous, as it always is for C.
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

... Ptr *is not* tied to storable, Storable is a convenience for FFI
integration .. storable is tied to ptr
there are whole MOUNTAINS of haskell code that underly this, and we can't
lawyer it away with some opinions
On Thu, Nov 1, 2018 at 2:16 PM David Feuer
Indeed. I think the point is that Ptr should be thought of as tied to Storable. If you want to use an Addr# for something else, then you shouldn't be using Ptr!
On Thu, Nov 1, 2018, 2:13 PM Evan Laforge
On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
wrote: a good example might be Ptr Char. Is this a single location of a 32bit / utf32 code point, or an array of utf8 code points or utf32 code points? is it null terminated vs there being an extra sequence length? These are all valid things that can be happening. And
I'm not sure if it affects your point, but I sure hope a 'Ptr Char' points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and array indexing will go out of bounds.
Of course, in the C case, whether or not there are further chars after that and if they are terminated and what is the encoding is all ambiguous, as it always is for C. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

phrased differnetly: storable provides one (c compatible) isomorphism
between fixed size values in haskell and c
the moment you want to talk about something that isn't fixed sized, like a
unicode character (which is a sequence of one or more code points, which we
call Char in haskell), storable doesn't apply.
On Thu, Nov 1, 2018 at 2:23 PM Carter Schonwald
... Ptr *is not* tied to storable, Storable is a convenience for FFI integration .. storable is tied to ptr
there are whole MOUNTAINS of haskell code that underly this, and we can't lawyer it away with some opinions
On Thu, Nov 1, 2018 at 2:16 PM David Feuer
wrote: Indeed. I think the point is that Ptr should be thought of as tied to Storable. If you want to use an Addr# for something else, then you shouldn't be using Ptr!
On Thu, Nov 1, 2018, 2:13 PM Evan Laforge
a good example might be Ptr Char. Is this a single location of a 32bit / utf32 code point, or an array of utf8 code points or utf32 code
On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
wrote: points? is it null terminated vs there being an extra sequence length? These are all valid things that can be happening. And
I'm not sure if it affects your point, but I sure hope a 'Ptr Char' points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and array indexing will go out of bounds.
Of course, in the C case, whether or not there are further chars after that and if they are terminated and what is the encoding is all ambiguous, as it always is for C. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

i agree with carter regarding the Storable-Ptr relationship. It seems to me
that Storable is tied to Ptr. Some concrete evidence of this is in the
Data.Primitive.Ptr API
On Thu, Nov 1, 2018 at 2:26 PM Carter Schonwald
phrased differnetly: storable provides one (c compatible) isomorphism between fixed size values in haskell and c
the moment you want to talk about something that isn't fixed sized, like a unicode character (which is a sequence of one or more code points, which we call Char in haskell), storable doesn't apply.
On Thu, Nov 1, 2018 at 2:23 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
... Ptr *is not* tied to storable, Storable is a convenience for FFI integration .. storable is tied to ptr
there are whole MOUNTAINS of haskell code that underly this, and we can't lawyer it away with some opinions
On Thu, Nov 1, 2018 at 2:16 PM David Feuer
wrote: Indeed. I think the point is that Ptr should be thought of as tied to Storable. If you want to use an Addr# for something else, then you shouldn't be using Ptr!
On Thu, Nov 1, 2018, 2:13 PM Evan Laforge
a good example might be Ptr Char. Is this a single location of a 32bit / utf32 code point, or an array of utf8 code points or utf32 code
On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
wrote: points? is it null terminated vs there being an extra sequence length? These are all valid things that can be happening. And
I'm not sure if it affects your point, but I sure hope a 'Ptr Char' points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and array indexing will go out of bounds.
Of course, in the C case, whether or not there are further chars after that and if they are terminated and what is the encoding is all ambiguous, as it always is for C. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I am +1 on this change.
On Thu, Nov 1, 2018 at 3:33 PM Daniel Cartwright
i agree with carter regarding the Storable-Ptr relationship. It seems to me that Storable is tied to Ptr. Some concrete evidence of this is in the Data.Primitive.Ptr API
On Thu, Nov 1, 2018 at 2:26 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
phrased differnetly: storable provides one (c compatible) isomorphism between fixed size values in haskell and c
the moment you want to talk about something that isn't fixed sized, like a unicode character (which is a sequence of one or more code points, which we call Char in haskell), storable doesn't apply.
On Thu, Nov 1, 2018 at 2:23 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
... Ptr *is not* tied to storable, Storable is a convenience for FFI integration .. storable is tied to ptr
there are whole MOUNTAINS of haskell code that underly this, and we can't lawyer it away with some opinions
On Thu, Nov 1, 2018 at 2:16 PM David Feuer
wrote: Indeed. I think the point is that Ptr should be thought of as tied to Storable. If you want to use an Addr# for something else, then you shouldn't be using Ptr!
On Thu, Nov 1, 2018, 2:13 PM Evan Laforge
a good example might be Ptr Char. Is this a single location of a 32bit / utf32 code point, or an array of utf8 code points or utf32 code
On Thu, Nov 1, 2018 at 10:47 AM Carter Schonwald
wrote: points? is it null terminated vs there being an extra sequence length? These are all valid things that can be happening. And
I'm not sure if it affects your point, but I sure hope a 'Ptr Char' points to a 4 byte haskell Char as it claims, and 'Ptr CChar' points to a 1 byte C char, as it claims. Otherwise, sizeOf will be wrong and array indexing will go out of bounds.
Of course, in the C case, whether or not there are further chars after that and if they are terminated and what is the encoding is all ambiguous, as it always is for C. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

David Feuer wrote:
Indeed. I think the point is that Ptr should be thought of as tied to Storable. If you want to use an Addr# for something else, then you shouldn't be using Ptr!
Thanks for that... This indeed seems to be the heart of this discussion, and the Addr thread as well. Currently, Ptr a serves a double role, with at least three facets: 1. Storable a => Ptr a, where the Storable instance describes the object being pointed to. This has an internal and a user-facing facet: * user-facing: peekElemOff, pokeElemOff, peek, poke for accessing the stored objects * internal: peekByteOff, pokeByteOff these can be used to access subobjects of a larger objects, for example when implementing a Storable instance for a C struct 2. Ptr a, a type-tagged address with no further semantics; also used as plain addresses (Ptr () or fully polymorphic Ptr a). * the internal Storable API can be re-used for such type-tagged pointers. I for one am happy with maintaining this double role, because it's well established, and econmical (no duplication of APIs just for dealing with plain addresses), and I don't see how code dealing with pointers would automatically become more correct by introducing an extra type for the second role. (This is tricky; code becomes more correct only if more actual errors become type errors without introducing many false positives. This lack of false positives is important; if the code becomes littered with explicit conversions as a result of introducing an extra type, then the signaling value of such conversions is lost.) But obviously there's room for different opinions on this. As for the question whether the argument of Ptr should be nominal or phantom, again I don't see a big difference; coercions have to be explicit either way, and all code dealing with Ptr is unsafe to begin with. Cheers, Bertram

Making `Ptr` (and ForeignPtr) have a nominal role would have prevented
recent bugs where it was possible to coerce Vectors between any types.
See: https://github.com/haskell/vector/pull/224
and: https://phabricator.haskell.org/D4941
On Tue, Oct 30, 2018 at 5:57 PM David Feuer
Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

my understanding is ANY non phantom role suffices in this case .. i dont use the coercible class in this context, my main concern is how role selection will impact client type classes / GND / etc On Fri, Nov 2, 2018 at 6:34 AM Matthew Pickering < matthewtpickering@gmail.com> wrote:
Making `Ptr` (and ForeignPtr) have a nominal role would have prevented recent bugs where it was possible to coerce Vectors between any types.
See: https://github.com/haskell/vector/pull/224 and: https://phabricator.haskell.org/D4941 On Tue, Oct 30, 2018 at 5:57 PM David Feuer
wrote: Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is
very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

woops:
i mis stated my previous email, misread some stuff, please ignore it :)
On Fri, Nov 2, 2018 at 7:25 PM Carter Schonwald
my understanding is ANY non phantom role suffices in this case ..
i dont use the coercible class in this context, my main concern is how role selection will impact client type classes / GND / etc
On Fri, Nov 2, 2018 at 6:34 AM Matthew Pickering < matthewtpickering@gmail.com> wrote:
Making `Ptr` (and ForeignPtr) have a nominal role would have prevented recent bugs where it was possible to coerce Vectors between any types.
See: https://github.com/haskell/vector/pull/224 and: https://phabricator.haskell.org/D4941 On Tue, Oct 30, 2018 at 5:57 PM David Feuer
wrote: Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is
very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

https://ghc.haskell.org/trac/ghc/ticket/9163 seems to talk about *why* Ptr
being phantom actually has a pretty measurable impact on code. (cast ptr
becomes a noop and this has a measurable impact on a number of application
measures)
On Fri, Nov 2, 2018 at 7:27 PM Carter Schonwald
woops:
i mis stated my previous email, misread some stuff, please ignore it :)
On Fri, Nov 2, 2018 at 7:25 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
my understanding is ANY non phantom role suffices in this case ..
i dont use the coercible class in this context, my main concern is how role selection will impact client type classes / GND / etc
On Fri, Nov 2, 2018 at 6:34 AM Matthew Pickering < matthewtpickering@gmail.com> wrote:
Making `Ptr` (and ForeignPtr) have a nominal role would have prevented recent bugs where it was possible to coerce Vectors between any types.
See: https://github.com/haskell/vector/pull/224 and: https://phabricator.haskell.org/D4941 On Tue, Oct 30, 2018 at 5:57 PM David Feuer
wrote: Currently, we have
data Ptr a = Ptr Addr# type role Ptr phantom
This is weird: accidentally coercing a pointer to a different type is
very bad. The only reason Ptr has this role is that without it, castPtr and such may not be free or will involve unsafe coercions.
Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Carter Schonwald wrote:
https://ghc.haskell.org/trac/ghc/ticket/9163 seems to talk about *why* Ptr being phantom actually has a pretty measurable impact on code. (cast ptr becomes a noop and this has a measurable impact on a number of application measures)
David's point, I believe, is that the same performance problem could have been solved by turning Ptr into a newtype, without giving up the representational that it had before. In fact he brought this up in the same trac ticket, https://ghc.haskell.org/trac/ghc/ticket/9163#comment:38
On Tue, Oct 30, 2018 at 5:57 PM David Feuer
wrote: Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this.
This will break some imports, since import GHC.Ptr (Ptr (..)) will not import the pattern synonym. This is how Ptr is imported in both bytestring and vector. But it's not a big deal, I suppose. Cheers, Bertram

Pattern synonyms can be bundled with type constructors these days. On Sun, Nov 4, 2018, 7:01 AM Bertram Felgenhauer via Libraries < libraries@haskell.org wrote:
Carter Schonwald wrote:
https://ghc.haskell.org/trac/ghc/ticket/9163 seems to talk about *why* Ptr being phantom actually has a pretty measurable impact on code. (cast ptr becomes a noop and this has a measurable impact on a number of application measures)
David's point, I believe, is that the same performance problem could have been solved by turning Ptr into a newtype, without giving up the representational that it had before. In fact he brought this up in the same trac ticket,
https://ghc.haskell.org/trac/ghc/ticket/9163#comment:38
On Tue, Oct 30, 2018 at 5:57 PM David Feuer
wrote: Thankfully, we have enough power to fix this now.
data Addr = Ptr_ Addr#
newtype Ptr a = Ptr_ Addr type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a pattern Ptr a# = Ptr_ (Addr a#)
castPtr :: Ptr a -> Ptr b castPtr (Ptr a) = Ptr a
ptrCoercible :: ((forall a b. Coercible (Ptr a) (Ptr b)) => r) -> r ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b) ptrCoercion = Coercion
I propose that we do this.
This will break some imports, since
import GHC.Ptr (Ptr (..))
will not import the pattern synonym. This is how Ptr is imported in both bytestring and vector. But it's not a big deal, I suppose.
Cheers,
Bertram _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (7)
-
Bertram Felgenhauer
-
Carter Schonwald
-
Daniel Cartwright
-
David Feuer
-
Eric Mertens
-
Evan Laforge
-
Matthew Pickering