
I'm trying to implement a single primop to replace sameMutVar#, sameMutableArray#, etc. The primop should have type unliftedPtrEquality# :: forall (a :: TYPE 'UnliftedRep). a -> a -> Int# Unfortunately, I don't see a way to express this type in primops.pp.txt. Is it possible? If not, what's the right way to give the primop the right type?

I don’t quite know how primops.txt.pp is processed, but perhaps by utils/genprimopcode. You may need to update the syntax a bit?
Simon
From: ghc-devs

On Monday, August 20, 2018 12:11:14 PM EDT Simon Peyton Jones via ghc-devs wrote:
I don’t quite know how primops.txt.pp is processed, but perhaps by utils/genprimopcode. You may need to update the syntax a bit?
The whole thing is a mystery to me. Whatever it's doing seems to generate code that puts things in TysPrim.hs together, and that module also looks rather murky to the uninitiated.

David Feuer
On Monday, August 20, 2018 12:11:14 PM EDT Simon Peyton Jones via ghc-devs wrote:
I don’t quite know how primops.txt.pp is processed, but perhaps by utils/genprimopcode. You may need to update the syntax a bit?
The whole thing is a mystery to me. Whatever it's doing seems to generate code that puts things in TysPrim.hs together, and that module also looks rather murky to the uninitiated.
primops.txt.pp is processed by genprimopcode, as suggested by Simon. genprimopcode has several modes, each of which produces a different output. These are listed in compiler/ghc.mk; grep for preprocessCompilerFiles. They broadly fall into three categories: * A set of headers which define the `PrimOp` type and functions defining primops' various properties (e.g. out-of-line-ness) * The GHC.PrimopWrappers module of `ghc-prim`, which defines functions wrapping each of the primops; these are used by GHCi (see Note [Primop Wrappers] * The `GHC.Prim`module of `ghc-prim`, which has no code but rather merely serves as a documented source file to be used by Haddock. genprimopcode's notion of non-Type kinded tyvars is very limited. It provides a few tyvars of kind Type (namely a, b, and c) and an "open-kinded" tyvar of any runtime rep (namely o). I believe you would need to add an additional binder to the genopcode parser to get what you want. I suspect this would only require a few lines, however. Cheers, - Ben

But how do I have to build something like "openAlphaTyVar" for TYPE
'UnliftedRep in the primitive space? I don't understand the toolkit.
On Tue, Aug 21, 2018, 11:07 AM Ben Gamari
David Feuer
writes: On Monday, August 20, 2018 12:11:14 PM EDT Simon Peyton Jones via ghc-devs wrote:
I don’t quite know how primops.txt.pp is processed, but perhaps by utils/genprimopcode. You may need to update the syntax a bit?
The whole thing is a mystery to me. Whatever it's doing seems to generate code that puts things in TysPrim.hs together, and that module also looks rather murky to the uninitiated.
primops.txt.pp is processed by genprimopcode, as suggested by Simon. genprimopcode has several modes, each of which produces a different output. These are listed in compiler/ghc.mk; grep for preprocessCompilerFiles. They broadly fall into three categories:
* A set of headers which define the `PrimOp` type and functions defining primops' various properties (e.g. out-of-line-ness)
* The GHC.PrimopWrappers module of `ghc-prim`, which defines functions wrapping each of the primops; these are used by GHCi (see Note [Primop Wrappers]
* The `GHC.Prim`module of `ghc-prim`, which has no code but rather merely serves as a documented source file to be used by Haddock.
genprimopcode's notion of non-Type kinded tyvars is very limited. It provides a few tyvars of kind Type (namely a, b, and c) and an "open-kinded" tyvar of any runtime rep (namely o). I believe you would need to add an additional binder to the genopcode parser to get what you want. I suspect this would only require a few lines, however.
Cheers,
- Ben

David Feuer
But how do I have to build something like "openAlphaTyVar" for TYPE 'UnliftedRep in the primitive space? I don't understand the toolkit.
I'm not sure I understand the question. openAlphaTyVar is defined in TysPrim. Perhaps looking there will clear up the confusion. Cheers, - Ben

I see the definition, but I don't understand it, so I don't know how to
adapt it to the less-polymorphic version I need.
On Tue, Aug 21, 2018, 4:14 PM Ben Gamari
David Feuer
writes: But how do I have to build something like "openAlphaTyVar" for TYPE 'UnliftedRep in the primitive space? I don't understand the toolkit.
I'm not sure I understand the question. openAlphaTyVar is defined in TysPrim. Perhaps looking there will clear up the confusion.
Cheers,
- Ben

Huh! It looks like what we currently do for some primops is just use a totally bogus kind. For example, mkWeak# will happily accept an Int# as its first argument. So we *could* follow that precedent and generalize reallyUnsafePtrEquality#, makeStableName#, etc., to accept anything, whether it makes sense or not. Or we can work out how to do what I was trying to do and then duplicate those primitives as appropriate (mkLiftedWeak#, mkUnliftedWeak#, makeLiftedStableName#, makeUnliftedStableName#, etc.).

| Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument. Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #)) and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic. The type from primops.txt.pp is processed into various Haskell source files including compiler/stage1/build/primop-primop-info.hs-incl which includes primOpInfo MkWeakOp = mkGenPrimOp (fsLit "mkWeak#") [runtimeRep1TyVar, openAlphaTyVar, betaTyVar, gammaTyVar] [openAlphaTy, betaTy, (mkFunTy (mkStatePrimTy realWorldTy) ((mkTupleTy Unboxed [ mkStatePrimTy realWorldTy, gammaTy]))) , mkStatePrimTy realWorldTy] ((mkTupleTy Unboxed [mkStatePrimTy realWorldTy, mkWeakPrimTy betaTy])) So it looks as if (rightly or wrongly) mkWeak# is deliberately levity-polymorphic. It would be good to write this stuff down. A good starting point is https://ghc.haskell.org/trac/ghc/wiki/Commentary/PrimOps Simon So we *could* follow that precedent and generalize | reallyUnsafePtrEquality#, makeStableName#, etc., to accept anything, | whether it makes sense or not. Or we can work out how to do what I was | trying to do and then duplicate those primitives as appropriate | (mkLiftedWeak#, mkUnliftedWeak#, makeLiftedStableName#, | makeUnliftedStableName#, etc.).

Simon Peyton Jones
| Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument.
Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #))
and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic.
Right; currently (largely for historical reasons) we use `o` to accommodate cases that accept both lifted and unlifted pointers. Cheers, - Ben

The problem is that this also accepts things that aren't pointers at all!
We could fix that *for primops* by changing RuntimeRep to something like
data RuntimeRep
= PtrRep Liftedness
| ...
But that would only work for primops (at least for now) so it may not be
worth the breakage.
On Wed, Aug 22, 2018, 7:45 AM Ben Gamari
Simon Peyton Jones
writes: | Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument.
Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #))
and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic.
Right; currently (largely for historical reasons) we use `o` to accommodate cases that accept both lifted and unlifted pointers.
Cheers,
- Ben

Gah. We have no way to be polymorphic over all pointers (both lifted and unlifted) but not over Int# etc.
As you say, this is too much of a special case to make an invasive change.
I’m quite dubious about making weak poitners to unlifted heap-allocated objects. I can’t say it’s wrong but it feels dodgy to me.
Simon
From: David Feuer
| Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument.
Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #))
and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic.
Right; currently (largely for historical reasons) we use `o` to accommodate cases that accept both lifted and unlifted pointers. Cheers, - Ben

Weak pointers to unlifted heap objects are the opposite of dodgy! We have
base library functions (e.g., Data.IORef.mkWeakIORef) for creating weak
references to lifted objects that *actually* create references to the
underlying unlifted objects instead. This is much more reliable, because
the wrapper (e.g., the STRef constructor) could be stripped away by
worker-wrapper, while the underlying object (e.g., the MutVar#) won't be.
On Thu, Aug 23, 2018, 5:43 PM Simon Peyton Jones
Gah. We have no way to be polymorphic over all pointers (both lifted and unlifted) but not over Int# etc.
As you say, this is too much of a special case to make an invasive change.
I’m quite dubious about making weak poitners to unlifted heap-allocated objects. I can’t say it’s wrong but it feels dodgy to me.
Simon
*From:* David Feuer
*Sent:* 22 August 2018 14:59 *To:* Ben Gamari *Cc:* Simon Peyton Jones ; David Feuer < david@well-typed.com>; ghc-devs *Subject:* Re: Unlifted primop types The problem is that this also accepts things that aren't pointers at all! We could fix that *for primops* by changing RuntimeRep to something like
data RuntimeRep
= PtrRep Liftedness
| ...
But that would only work for primops (at least for now) so it may not be worth the breakage.
On Wed, Aug 22, 2018, 7:45 AM Ben Gamari
wrote: Simon Peyton Jones
writes: | Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument.
Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #))
and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic.
Right; currently (largely for historical reasons) we use `o` to accommodate cases that accept both lifted and unlifted pointers.
Cheers,
- Ben

Don't pay *too* much attention to mkWeakIORef in particular; for some
reason it only makes a weak reference from an IORef to itself. It *should*
have been written
mkWeakIORef :: IORef a -> b -> IO () -> IO (Weak (IORef a))
mkWeakIORef r@(IORef (STRef r#)) b (IO finalizer) = IO $ \s ->
case mkWeak# r# b finalizer s of (# s1, w #) -> (# s1, Weak w #)
and the current version should've been
mkSimpleWeakIORef r fin = mkWeakIORef r r fin
On Thu, Aug 23, 2018, 5:52 PM David Feuer
Weak pointers to unlifted heap objects are the opposite of dodgy! We have base library functions (e.g., Data.IORef.mkWeakIORef) for creating weak references to lifted objects that *actually* create references to the underlying unlifted objects instead. This is much more reliable, because the wrapper (e.g., the STRef constructor) could be stripped away by worker-wrapper, while the underlying object (e.g., the MutVar#) won't be.
On Thu, Aug 23, 2018, 5:43 PM Simon Peyton Jones
wrote: Gah. We have no way to be polymorphic over all pointers (both lifted and unlifted) but not over Int# etc.
As you say, this is too much of a special case to make an invasive change.
I’m quite dubious about making weak poitners to unlifted heap-allocated objects. I can’t say it’s wrong but it feels dodgy to me.
Simon
*From:* David Feuer
*Sent:* 22 August 2018 14:59 *To:* Ben Gamari *Cc:* Simon Peyton Jones ; David Feuer < david@well-typed.com>; ghc-devs *Subject:* Re: Unlifted primop types The problem is that this also accepts things that aren't pointers at all! We could fix that *for primops* by changing RuntimeRep to something like
data RuntimeRep
= PtrRep Liftedness
| ...
But that would only work for primops (at least for now) so it may not be worth the breakage.
On Wed, Aug 22, 2018, 7:45 AM Ben Gamari
wrote: Simon Peyton Jones
writes: | Huh! It looks like what we currently do for some primops is just use a | totally bogus kind. For example, mkWeak# will happily accept an Int# as | its first argument.
Well, I see primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> (State# RealWorld -> (# State# RealWorld, c #))
and I believe (from Ben's message) that the "o" means "open type variable", which is the old terminology for what we now call levity-polymorphic.
Right; currently (largely for historical reasons) we use `o` to accommodate cases that accept both lifted and unlifted pointers.
Cheers,
- Ben

David Feuer
The problem is that this also accepts things that aren't pointers at all! We could fix that *for primops* by changing RuntimeRep to something like
data RuntimeRep = PtrRep Liftedness | ...
But that would only work for primops (at least for now) so it may not be worth the breakage.
The runtime rep design was precisely this but IIRC this was changed since the additional polymorphism ended up costing quite a bit in type-checking effort. Cheers, - Ben
participants (4)
-
Ben Gamari
-
David Feuer
-
David Feuer
-
Simon Peyton Jones