Re: ByteArray# as a foreign import argument?

2019-10-11 Thread Sylvain Henry
> But I can't find such a ByteArray type definition in today's common 
packages. What's the rationale for this piece of code?


Doing some archeology they seem to have been removed from 
ghc/lib/std/PrelArr.lhs in e921b2e307532e0f30eefa88b11a124be592bde4 (1999):


 data Ix ix => Array ix elt        = Array        ix ix (Array# elt)
-data Ix ix => ByteArray ix      = ByteArray ix ix ByteArray#
 data Ix ix => MutableArray s ix elt = MutableArray ix ix 
(MutableArray# s elt)
-data Ix ix => MutableByteArray s ix = MutableByteArray ix ix 
(MutableByteArray# s)


So it's probably dead code since then.

Cheers,
Sylvain


On 10/10/2019 21:15, Shao, Cheng wrote:

Hello devs,

I've been trying to figure out how to pass lifted types as foreign
types, then encountered the following code in the `DsCCall` module
(https://gitlab.haskell.org/ghc/ghc/blob/master/compiler/deSugar/DsCCall.hs#L172):

```
   -- Byte-arrays, both mutable and otherwise; hack warning
   -- We're looking for values of type ByteArray, MutableByteArray
   --data ByteArray  ix = ByteArrayix ix ByteArray#
   --data MutableByteArray s ix = MutableByteArray ix ix
(MutableByteArray# s)
   | is_product_type &&
 data_con_arity == 3 &&
 isJust maybe_arg3_tycon &&
 (arg3_tycon ==  byteArrayPrimTyCon ||
  arg3_tycon ==  mutableByteArrayPrimTyCon)
   = do case_bndr <- newSysLocalDs arg_ty
vars@[_l_var, _r_var, arr_cts_var] <- newSysLocalsDs data_con_arg_tys
return (Var arr_cts_var,
\ body -> Case arg case_bndr (exprType body) [(DataAlt
data_con,vars,body)]
   )
```

It seems we allow a "ByteArray" type as a foreign import argument, if
the third field of the datacon is a ByteArray# or MutableByteArray#.
But I can't find such a ByteArray type definition in today's common
packages. What's the rationale for this piece of code?

Cheers,
Cheng
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ByteArray# as a foreign import argument?

2019-10-11 Thread Sylvain Henry

Or better 98668305453ea1158c97c8a2c1a90c108aa3585a (2001):

From the commit message:

    - finally, remove the last vestiges of ByteArray and MutableByteArray
  from the core libraries.  Deprecated implementations will be 
available

  in the lang compatibility package.


On 11/10/2019 10:32, Sylvain Henry wrote:
> But I can't find such a ByteArray type definition in today's common 
packages. What's the rationale for this piece of code?


Doing some archeology they seem to have been removed from 
ghc/lib/std/PrelArr.lhs in e921b2e307532e0f30eefa88b11a124be592bde4 
(1999):


 data Ix ix => Array ix elt        = Array        ix ix (Array# elt)
-data Ix ix => ByteArray ix      = ByteArray ix ix ByteArray#
 data Ix ix => MutableArray s ix elt = MutableArray ix ix 
(MutableArray# s elt)
-data Ix ix => MutableByteArray s ix = MutableByteArray ix ix 
(MutableByteArray# s)


So it's probably dead code since then.

Cheers,
Sylvain


On 10/10/2019 21:15, Shao, Cheng wrote:

Hello devs,

I've been trying to figure out how to pass lifted types as foreign
types, then encountered the following code in the `DsCCall` module
(https://gitlab.haskell.org/ghc/ghc/blob/master/compiler/deSugar/DsCCall.hs#L172): 



```
   -- Byte-arrays, both mutable and otherwise; hack warning
   -- We're looking for values of type ByteArray, MutableByteArray
   --    data ByteArray  ix = ByteArray    ix ix ByteArray#
   --    data MutableByteArray s ix = MutableByteArray ix ix
(MutableByteArray# s)
   | is_product_type &&
 data_con_arity == 3 &&
 isJust maybe_arg3_tycon &&
 (arg3_tycon ==  byteArrayPrimTyCon ||
  arg3_tycon ==  mutableByteArrayPrimTyCon)
   = do case_bndr <- newSysLocalDs arg_ty
    vars@[_l_var, _r_var, arr_cts_var] <- newSysLocalsDs 
data_con_arg_tys

    return (Var arr_cts_var,
    \ body -> Case arg case_bndr (exprType body) [(DataAlt
data_con,vars,body)]
   )
```

It seems we allow a "ByteArray" type as a foreign import argument, if
the third field of the datacon is a ByteArray# or MutableByteArray#.
But I can't find such a ByteArray type definition in today's common
packages. What's the rationale for this piece of code?

Cheers,
Cheng
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


atomicModifyMutVar2

2019-10-11 Thread Simon Peyton Jones via ghc-devs
David
I'm deeply puzzled atomicModifyMutVar2#.  I have read the 
proposal,
 and the comments in primops.txt.pp (reproduced below).
Question 1
I think the "real" type of atomicModifyMutVar2 is

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> (a,b))

 -> State# s

 -> (# State# s, a, (a, b) #)
Nowhere is this explicitly stated, but I believe that the intended semantics of 
a call

case (atomicModifyMutVar2# mv f s) of (# s', x, r #) -> blah
Then, suppose the old value of the MutVar was 'old'

  *   The primop builds a thunk  t = f old
  *   The new value of the mutable variable is (fst t)
  *   The result r is t
  *   The result x is old
Question: is that correct?   We should state it explicitly.
Question 2
Next question: Why does f have to return a pair?  So far as I can tell, it's 
only so that a client can force it.   The 'b' part never seems to play a useful 
role.   So we could equally well have had

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> Box a)

 -> State# s

 -> (# State# s, a, Unit a #)
where Unit is defined in Data.Tuple

data Unit a = Unit a
Now you can force the result of (f old), just as with a pair.  But the 'b' 
would no longer complicate matters.
Question: is the 'b' in the pair significant?   Or could we use Unit?
Question 3
In the comments below you say "but we don't know about pairs here".   Are you 
sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy footwork 
is one more complication, if it could be avoided.

Thanks
Simon


primop  AtomicModifyMutVar2Op "atomicModifyMutVar2#" GenPrimOp

   MutVar# s a -> (a -> c) -> State# s -> (# State# s, a, c #)

   { Modify the contents of a {\tt MutVar\#}, returning the previous

 contents and the result of applying the given function to the

 previous contents. Note that this isn't strictly

 speaking the correct type for this function; it should really be

 {\tt MutVar\# s a -> (a -> (a,b)) -> State\# s -> (\# State\# s, a, (a, b) 
\#)},

 but we don't know about pairs here. }

   with

   out_of_line = True

   has_side_effects = True

   can_fail = True
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: atomicModifyMutVar2

2019-10-11 Thread David Feuer
On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
wrote:

> David
>
> I’m deeply puzzled atomicModifyMutVar2#.  I have read the proposal
> ,
> and the comments in primops.txt.pp (reproduced below).
> Question 1
>
> I think the “real” type of atomicModifyMutVar2 is
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> (a,b))
>
>  -> State# s
>
>  -> (# State# s, a, (a, b) #)
>

Close, but not quite. The result doesn't have to be a pair. It can be a
tuple of any size at all. Indeed, it can even be an arbitrary record type
whose first pointer field has the appropriate type.

Nowhere is this explicitly stated, but I believe that the intended
> semantics of a call
>
> case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
>
> Then, suppose the old value of the MutVar was ‘*old’*
>
>- The primop builds a thunk  *t *= *f old*
>- The new value of the mutable variable is *(fst t)*
>- The result *r* is t
>- The result *x* is *old*
>
> Question: is that correct?   We should state it explicitly.
>
Yes, that sounds right.

> Question 2
>
> Next question: Why does f have to return a pair?  So far as I can tell,
> it’s only so that a client can force it.   The ‘b’ part never seems to play
> a useful role.   So we could equally well have had
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> Box a)
>
>  -> State# s
>
>  -> (# State# s, a, Unit a #)
>
> where Unit is defined in Data.Tuple
>
> data Unit a = Unit a
>
> Now you can force the result of (f old), just as with a pair.  But the ‘b’
> would no longer complicate matters.
>
> Question: is the ‘b’ in the pair significant?   Or could we use Unit?
>
Yes, it's somewhat significant. You actually can use Unit with the new
primop (it's a tuple of arity 1), so that option is free. But using a pair
gets you a bit more: you can build a thunk that's *shared* between the
value installed in the MutVar and the one returned to the outside. Consider

atomicModifyMutVar2# mv $ \a ->

  let foo = expensive_computation a

  in ([3,foo], foo)

> Question 3
>
> In the comments below you say "but we don't know about pairs here”.   Are
> you sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy
> footwork is one more complication, if it could be avoided.
>
That whole regime came before my time, but since we win a bit by *not*
fixing it, o wouldn't jump on it too quick.

>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: atomicModifyMutVar2

2019-10-11 Thread Simon Peyton Jones via ghc-devs
The result doesn't have to be a pair. It can be a tuple of any size at all. 
Indeed, it can even be an arbitrary record type whose first pointer field has 
the appropriate type.

I think that is 100.0% undocumented, in the code, or in the proposal.  Are you 
sure this is a settled consensus among the interested parties?

Adopting it would impose new invariants on the representation of values in GHC 
that I am deeply reluctant to impose.  I would much much prefer to stick with 
the pair that is (somewhat) documented.

About pair vs Unit, yes, I can see (just) your point about why a pair might be 
useful.  Here’s a better example:

Suppose mv :: MutVar# Int


atomicModifyMutVar2# mv $ \a ->

  let foo = f a

  in (g foo, foo)

Now, if f is expensive, and g is not invertible, then sharing foo might be 
useful.  It’s hard to think of a credible example, though.  Regardless, we 
should document it.

Simon

From: David Feuer 
Sent: 11 October 2019 17:03
To: Simon Peyton Jones 
Cc: ghc-devs 
Subject: Re: atomicModifyMutVar2

On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
David
I’m deeply puzzled atomicModifyMutVar2#.  I have read the 
proposal,
 and the comments in primops.txt.pp (reproduced below).
Question 1
I think the “real” type of atomicModifyMutVar2 is

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> (a,b))

 -> State# s

 -> (# State# s, a, (a, b) #)

Close, but not quite. The result doesn't have to be a pair. It can be a tuple 
of any size at all. Indeed, it can even be an arbitrary record type whose first 
pointer field has the appropriate type.

Nowhere is this explicitly stated, but I believe that the intended semantics of 
a call

case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
Then, suppose the old value of the MutVar was ‘old’

  *   The primop builds a thunk  t = f old
  *   The new value of the mutable variable is (fst t)
  *   The result r is t
  *   The result x is old
Question: is that correct?   We should state it explicitly.
Yes, that sounds right.
Question 2
Next question: Why does f have to return a pair?  So far as I can tell, it’s 
only so that a client can force it.   The ‘b’ part never seems to play a useful 
role.   So we could equally well have had

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> Box a)

 -> State# s

 -> (# State# s, a, Unit a #)
where Unit is defined in Data.Tuple

data Unit a = Unit a
Now you can force the result of (f old), just as with a pair.  But the ‘b’ 
would no longer complicate matters.
Question: is the ‘b’ in the pair significant?   Or could we use Unit?
Yes, it's somewhat significant. You actually can use Unit with the new primop 
(it's a tuple of arity 1), so that option is free. But using a pair gets you a 
bit more: you can build a thunk that's *shared* between the value installed in 
the MutVar and the one returned to the outside. Consider


atomicModifyMutVar2# mv $ \a ->

  let foo = expensive_computation a

  in ([3,foo], foo)

Question 3
In the comments below you say "but we don't know about pairs here”.   Are you 
sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy footwork 
is one more complication, if it could be avoided.
That whole regime came before my time, but since we win a bit by *not* fixing 
it, o wouldn't jump on it too quick.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: atomicModifyMutVar2

2019-10-11 Thread Carter Schonwald
that additional representation invariant requirement is why i ultimately
chose not to include the user space version of davids work in primitive

https://github.com/haskell/primitive/pull/194

theres some really clever ideas, but i couldnt tease apart a natural
example of where i'd want to use it

On Fri, Oct 11, 2019 at 12:56 PM Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org> wrote:

> The result doesn't have to be a pair. It can be a tuple of any size at
> all. Indeed, it can even be an arbitrary record type whose first pointer
> field has the appropriate type.
>
>
>
> I think that is 100.0% undocumented, in the code, or in the proposal.  Are
> you sure this is a settled consensus among the interested parties?
>
>
>
> Adopting it would impose new invariants on the representation of values in
> GHC that I am deeply reluctant to impose.  I would much much prefer to
> stick with the pair that is (somewhat) documented.
>
>
>
> About pair vs Unit, yes, I can see (just) your point about why a pair
> might be useful.  Here’s a better example:
>
>
>
> Suppose mv :: MutVar# Int
>
>
>
> atomicModifyMutVar2# mv $ \a ->
>
>   let foo = f a
>
>   in (g foo, foo)
>
>
>
> Now, if f is expensive, *and g is not invertible*, then sharing foo might
> be useful.  It’s hard to think of a credible example, though.  Regardless,
> we should document it.
>
>
>
> Simon
>
>
>
> *From:* David Feuer 
> *Sent:* 11 October 2019 17:03
> *To:* Simon Peyton Jones 
> *Cc:* ghc-devs 
> *Subject:* Re: atomicModifyMutVar2
>
>
>
> On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
> wrote:
>
> David
>
> I’m deeply puzzled atomicModifyMutVar2#.  I have read the proposal
> ,
> and the comments in primops.txt.pp (reproduced below).
> Question 1
>
> I think the “real” type of atomicModifyMutVar2 is
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> (a,b))
>
>  -> State# s
>
>  -> (# State# s, a, (a, b) #)
>
>
>
> Close, but not quite. The result doesn't have to be a pair. It can be a
> tuple of any size at all. Indeed, it can even be an arbitrary record type
> whose first pointer field has the appropriate type.
>
>
>
> Nowhere is this explicitly stated, but I believe that the intended
> semantics of a call
>
> case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
>
> Then, suppose the old value of the MutVar was ‘*old’*
>
>- The primop builds a thunk  *t *= *f old*
>- The new value of the mutable variable is *(fst t)*
>- The result *r* is t
>- The result *x* is *old*
>
> Question: is that correct?   We should state it explicitly.
>
> Yes, that sounds right.
>
> Question 2
>
> Next question: Why does f have to return a pair?  So far as I can tell,
> it’s only so that a client can force it.   The ‘b’ part never seems to play
> a useful role.   So we could equally well have had
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> Box a)
>
>  -> State# s
>
>  -> (# State# s, a, Unit a #)
>
> where Unit is defined in Data.Tuple
>
> data Unit a = Unit a
>
> Now you can force the result of (f old), just as with a pair.  But the ‘b’
> would no longer complicate matters.
>
> Question: is the ‘b’ in the pair significant?   Or could we use Unit?
>
> Yes, it's somewhat significant. You actually can use Unit with the new
> primop (it's a tuple of arity 1), so that option is free. But using a pair
> gets you a bit more: you can build a thunk that's *shared* between the
> value installed in the MutVar and the one returned to the outside. Consider
>
>
>
> atomicModifyMutVar2# mv $ \a ->
>
>   let foo = expensive_computation a
>
>   in ([3,foo], foo)
>
> Question 3
>
> In the comments below you say "but we don't know about pairs here”.   Are
> you sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy
> footwork is one more complication, if it could be avoided.
>
> That whole regime came before my time, but since we win a bit by *not*
> fixing it, o wouldn't jump on it too quick.
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: atomicModifyMutVar2

2019-10-11 Thread Simon Peyton Jones via ghc-devs
David,

Wait!  It gets worse!

Question 4

As I understand it, the idea in the proposal is that you can force the pair 
that comes back from the primop, and that helps you cure a space leak.  Thus


case atomicModifyMutVar2# mv f s of

   (# s’, old, pr #) -> pr `seq`  (# s’, () #)


But it’s extremely easy to write calls that complete defeat such a strategy.  
Your examples and mine below both have this property. Suppose f is

(\x. let v = expensive x in (v,v))
Well, forcing that pair will do nothing at all!  It certainly won’t force v!   
You should probably write

(\x. let v = expensive x in v `seq` (v,v))
or something like that.

Is this right?   At least this should be documented super-clearly.

Simon

From: ghc-devs  On Behalf Of Simon Peyton Jones 
via ghc-devs
Sent: 11 October 2019 17:56
To: David Feuer 
Cc: ghc-devs 
Subject: RE: atomicModifyMutVar2

The result doesn't have to be a pair. It can be a tuple of any size at all. 
Indeed, it can even be an arbitrary record type whose first pointer field has 
the appropriate type.

I think that is 100.0% undocumented, in the code, or in the proposal.  Are you 
sure this is a settled consensus among the interested parties?

Adopting it would impose new invariants on the representation of values in GHC 
that I am deeply reluctant to impose.  I would much much prefer to stick with 
the pair that is (somewhat) documented.

About pair vs Unit, yes, I can see (just) your point about why a pair might be 
useful.  Here’s a better example:

Suppose mv :: MutVar# Int


atomicModifyMutVar2# mv $ \a ->

  let foo = f a

  in (g foo, foo)

Now, if f is expensive, and g is not invertible, then sharing foo might be 
useful.  It’s hard to think of a credible example, though.  Regardless, we 
should document it.

Simon

From: David Feuer mailto:david.fe...@gmail.com>>
Sent: 11 October 2019 17:03
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: ghc-devs mailto:ghc-devs@haskell.org>>
Subject: Re: atomicModifyMutVar2

On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
David
I’m deeply puzzled atomicModifyMutVar2#.  I have read the 
proposal,
 and the comments in primops.txt.pp (reproduced below).
Question 1
I think the “real” type of atomicModifyMutVar2 is

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> (a,b))

 -> State# s

 -> (# State# s, a, (a, b) #)

Close, but not quite. The result doesn't have to be a pair. It can be a tuple 
of any size at all. Indeed, it can even be an arbitrary record type whose first 
pointer field has the appropriate type.

Nowhere is this explicitly stated, but I believe that the intended semantics of 
a call

case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
Then, suppose the old value of the MutVar was ‘old’

  *   The primop builds a thunk  t = f old
  *   The new value of the mutable variable is (fst t)
  *   The result r is t
  *   The result x is old
Question: is that correct?   We should state it explicitly.
Yes, that sounds right.
Question 2
Next question: Why does f have to return a pair?  So far as I can tell, it’s 
only so that a client can force it.   The ‘b’ part never seems to play a useful 
role.   So we could equally well have had

atomicModifyMutVar2# :: MutVar# s a

 -> (a -> Box a)

 -> State# s

 -> (# State# s, a, Unit a #)
where Unit is defined in Data.Tuple

data Unit a = Unit a
Now you can force the result of (f old), just as with a pair.  But the ‘b’ 
would no longer complicate matters.
Question: is the ‘b’ in the pair significant?   Or could we use Unit?
Yes, it's somewhat significant. You actually can use Unit with the new primop 
(it's a tuple of arity 1), so that option is free. But using a pair gets you a 
bit more: you can build a thunk that's *shared* between the value installed in 
the MutVar and the one returned to the outside. Consider


atomicModifyMutVar2# mv $ \a ->

  let foo = expensive_computation a

  in ([3,foo], foo)

Question 3
In the comments below you say "but we don't know about pairs here”.   Are you 
sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy footwork 
is one more complication, if it could be avoided.
That whole regime came before my time, but since we win a bit by *not* fixing 
it, o wouldn't jump on it too quick.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: atomicModifyMutVar2

2019-10-11 Thread David Feuer
I don't remember what documentation, if any, it has. You're right that
taking advantage of it is potentially risky. Here's what I think we really
want:

atomicModifyMutVarQ# :: MutVar# s a -> (q -> a) -> (a -> q)  -> State# s ->
(# State# s, a, q #)

where there's a special rule that (q -> a) is "obviously" a selector that
selects a pointer.

On Fri, Oct 11, 2019, 12:56 PM Simon Peyton Jones 
wrote:

> The result doesn't have to be a pair. It can be a tuple of any size at
> all. Indeed, it can even be an arbitrary record type whose first pointer
> field has the appropriate type.
>
>
>
> I think that is 100.0% undocumented, in the code, or in the proposal.  Are
> you sure this is a settled consensus among the interested parties?
>
>
>
> Adopting it would impose new invariants on the representation of values in
> GHC that I am deeply reluctant to impose.  I would much much prefer to
> stick with the pair that is (somewhat) documented.
>
>
>
> About pair vs Unit, yes, I can see (just) your point about why a pair
> might be useful.  Here’s a better example:
>
>
>
> Suppose mv :: MutVar# Int
>
>
>
> atomicModifyMutVar2# mv $ \a ->
>
>   let foo = f a
>
>   in (g foo, foo)
>
>
>
> Now, if f is expensive, *and g is not invertible*, then sharing foo might
> be useful.  It’s hard to think of a credible example, though.  Regardless,
> we should document it.
>
>
>
> Simon
>
>
>
> *From:* David Feuer 
> *Sent:* 11 October 2019 17:03
> *To:* Simon Peyton Jones 
> *Cc:* ghc-devs 
> *Subject:* Re: atomicModifyMutVar2
>
>
>
> On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
> wrote:
>
> David
>
> I’m deeply puzzled atomicModifyMutVar2#.  I have read the proposal
> ,
> and the comments in primops.txt.pp (reproduced below).
> Question 1
>
> I think the “real” type of atomicModifyMutVar2 is
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> (a,b))
>
>  -> State# s
>
>  -> (# State# s, a, (a, b) #)
>
>
>
> Close, but not quite. The result doesn't have to be a pair. It can be a
> tuple of any size at all. Indeed, it can even be an arbitrary record type
> whose first pointer field has the appropriate type.
>
>
>
> Nowhere is this explicitly stated, but I believe that the intended
> semantics of a call
>
> case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
>
> Then, suppose the old value of the MutVar was ‘*old’*
>
>- The primop builds a thunk  *t *= *f old*
>- The new value of the mutable variable is *(fst t)*
>- The result *r* is t
>- The result *x* is *old*
>
> Question: is that correct?   We should state it explicitly.
>
> Yes, that sounds right.
>
> Question 2
>
> Next question: Why does f have to return a pair?  So far as I can tell,
> it’s only so that a client can force it.   The ‘b’ part never seems to play
> a useful role.   So we could equally well have had
>
> atomicModifyMutVar2# :: MutVar# s a
>
>  -> (a -> Box a)
>
>  -> State# s
>
>  -> (# State# s, a, Unit a #)
>
> where Unit is defined in Data.Tuple
>
> data Unit a = Unit a
>
> Now you can force the result of (f old), just as with a pair.  But the ‘b’
> would no longer complicate matters.
>
> Question: is the ‘b’ in the pair significant?   Or could we use Unit?
>
> Yes, it's somewhat significant. You actually can use Unit with the new
> primop (it's a tuple of arity 1), so that option is free. But using a pair
> gets you a bit more: you can build a thunk that's *shared* between the
> value installed in the MutVar and the one returned to the outside. Consider
>
>
>
> atomicModifyMutVar2# mv $ \a ->
>
>   let foo = expensive_computation a
>
>   in ([3,foo], foo)
>
> Question 3
>
> In the comments below you say "but we don't know about pairs here”.   Are
> you sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy
> footwork is one more complication, if it could be avoided.
>
> That whole regime came before my time, but since we win a bit by *not*
> fixing it, o wouldn't jump on it too quick.
>
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: atomicModifyMutVar2

2019-10-11 Thread David Feuer
Actually, maybe we can do better! We don't inherently need the function to
be a selector. But to make it more general, we'll need to take some care to
make sure to produce good code when it *is* a selector.

On Fri, Oct 11, 2019, 6:59 PM David Feuer  wrote:

> I don't remember what documentation, if any, it has. You're right that
> taking advantage of it is potentially risky. Here's what I think we really
> want:
>
> atomicModifyMutVarQ# :: MutVar# s a -> (q -> a) -> (a -> q)  -> State# s ->
> (# State# s, a, q #)
>
> where there's a special rule that (q -> a) is "obviously" a selector that
> selects a pointer.
>
> On Fri, Oct 11, 2019, 12:56 PM Simon Peyton Jones 
> wrote:
>
>> The result doesn't have to be a pair. It can be a tuple of any size at
>> all. Indeed, it can even be an arbitrary record type whose first pointer
>> field has the appropriate type.
>>
>>
>>
>> I think that is 100.0% undocumented, in the code, or in the proposal.
>> Are you sure this is a settled consensus among the interested parties?
>>
>>
>>
>> Adopting it would impose new invariants on the representation of values
>> in GHC that I am deeply reluctant to impose.  I would much much prefer to
>> stick with the pair that is (somewhat) documented.
>>
>>
>>
>> About pair vs Unit, yes, I can see (just) your point about why a pair
>> might be useful.  Here’s a better example:
>>
>>
>>
>> Suppose mv :: MutVar# Int
>>
>>
>>
>> atomicModifyMutVar2# mv $ \a ->
>>
>>   let foo = f a
>>
>>   in (g foo, foo)
>>
>>
>>
>> Now, if f is expensive, *and g is not invertible*, then sharing foo
>> might be useful.  It’s hard to think of a credible example, though.
>> Regardless, we should document it.
>>
>>
>>
>> Simon
>>
>>
>>
>> *From:* David Feuer 
>> *Sent:* 11 October 2019 17:03
>> *To:* Simon Peyton Jones 
>> *Cc:* ghc-devs 
>> *Subject:* Re: atomicModifyMutVar2
>>
>>
>>
>> On Fri, Oct 11, 2019, 11:08 AM Simon Peyton Jones 
>> wrote:
>>
>> David
>>
>> I’m deeply puzzled atomicModifyMutVar2#.  I have read the proposal
>> ,
>> and the comments in primops.txt.pp (reproduced below).
>> Question 1
>>
>> I think the “real” type of atomicModifyMutVar2 is
>>
>> atomicModifyMutVar2# :: MutVar# s a
>>
>>  -> (a -> (a,b))
>>
>>  -> State# s
>>
>>  -> (# State# s, a, (a, b) #)
>>
>>
>>
>> Close, but not quite. The result doesn't have to be a pair. It can be a
>> tuple of any size at all. Indeed, it can even be an arbitrary record type
>> whose first pointer field has the appropriate type.
>>
>>
>>
>> Nowhere is this explicitly stated, but I believe that the intended
>> semantics of a call
>>
>> case (atomicModifyMutVar2# mv f s) of (# s’, x, r #) -> blah
>>
>> Then, suppose the old value of the MutVar was ‘*old’*
>>
>>- The primop builds a thunk  *t *= *f old*
>>- The new value of the mutable variable is *(fst t)*
>>- The result *r* is t
>>- The result *x* is *old*
>>
>> Question: is that correct?   We should state it explicitly.
>>
>> Yes, that sounds right.
>>
>> Question 2
>>
>> Next question: Why does f have to return a pair?  So far as I can tell,
>> it’s only so that a client can force it.   The ‘b’ part never seems to play
>> a useful role.   So we could equally well have had
>>
>> atomicModifyMutVar2# :: MutVar# s a
>>
>>  -> (a -> Box a)
>>
>>  -> State# s
>>
>>  -> (# State# s, a, Unit a #)
>>
>> where Unit is defined in Data.Tuple
>>
>> data Unit a = Unit a
>>
>> Now you can force the result of (f old), just as with a pair.  But the
>> ‘b’ would no longer complicate matters.
>>
>> Question: is the ‘b’ in the pair significant?   Or could we use Unit?
>>
>> Yes, it's somewhat significant. You actually can use Unit with the new
>> primop (it's a tuple of arity 1), so that option is free. But using a pair
>> gets you a bit more: you can build a thunk that's *shared* between the
>> value installed in the MutVar and the one returned to the outside. Consider
>>
>>
>>
>> atomicModifyMutVar2# mv $ \a ->
>>
>>   let foo = expensive_computation a
>>
>>   in ([3,foo], foo)
>>
>> Question 3
>>
>> In the comments below you say "but we don't know about pairs here”.   Are
>> you sure?  What stops you importing Data.Tuple into GHC.Prim?   This fancy
>> footwork is one more complication, if it could be avoided.
>>
>> That whole regime came before my time, but since we win a bit by *not*
>> fixing it, o wouldn't jump on it too quick.
>>
>>
>>
>>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/c