Skip to content

Conversation

@gasche
Copy link
Member

@gasche gasche commented May 31, 2024

A proposed design for atomic record fields.

Rendered version.

In summary:

(* in the stdlib *)
module Atomic : sig
  ...
  module Field : sig
    type ('r, 'a) t
    val get : 'r -> ('r, 'a) t -> 'a
    val compare_and_set : 'r -> ('r, 'a) t -> 'a -> 'a -> bool
  end
end

(* user code example *)
type t = {
  id : int;
  mutable state : st [@atomic];
}

let rec evolve v =
  let cur = v.state in (* <- strong atomic read *)
  let next = next_state cur in
  if not Atomic.Field.compare_and_set v [%atomic.field state] cur next
  then evolve v

Copy link

@OlivierNicole OlivierNicole left a comment

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I strongly support this, it looks like a good solution for a problem that seemed intractable to me at first glance.

Comment on lines +138 to +140
For example, if we have `type 'a t = { atomic mutable state : 'a st }`,
then `[%atomic.field state]` is a polymorphic constant of type
`('a t, 'a st) Atomic.Field.t`.

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I wonder how hard it would be to have a third type parameter, which would be instantiated to a different (opaque) type for every field of a record. This way, when two fields have the same type, it would be impossible to mistakenly access the wrong one.

Comment on lines +180 to +182
We can expose atomic arrays with the same mechanism: a builtin type
`'a Atomic.Array.t`, with a primitive function to build an index from
an integer:

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I like the idea of having a uniform interface for atomic fields and arrays. It would also make it natural to use the same runtime primitives for both, reducing the number of primitives to create.

Comment on lines +192 to +196
We can reuse the `Field.t` type and its atomic-operation API, but note
that the index here may be outside the bounds of the array, and will
have to be checked on access. (The index is not bound-checked by the
`index` function, as it may be called on different arrays later.) For
`Field.t` values at record type, no such bound checking is necessary.

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I’m reminded (by @polytypic) that non-bound-checked accesses would be desirable as well for performance-critical code.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thinking more about this, I notice that there is a weakness in my proposal related to arrays. When using Atomic.Field.t for records, we do not want any bound-checking, as the indices are in-bounds by construction. So the Atomic.Field.t primitives will not perform any bound-checking. We can reuse the same primitives to implement array access, but the specific proposal I made in the PR leads to non-bound-checked array accesses by default, not to bound-checked array accesses. I think this is wrong: I'm happy to offer both, but bound-checked accesses should be the default.

I see two approaches to solve this:

  1. We could of course expose different primitives in Atomic.Array.t, which would perform bound-checking first and then call the same runtime primitives as those of the Atomic.Field.t API. (More precisely: for each access function, offer a checked and an unchecked version in Atomic.Array.t.) I think that this would be perfectly reasonable, and/but it duplicates the API surface which I thought we could avoid.
  2. We could change our index function to have index : 'a t -> int -> ('a Array.t, 'a) Field.t, and also val unsafe_index : int -> ('a Array.t, 'a) Field.t, wich index in charge of doing bound-checking against a specific array. This is a bit wonky: the index you get has been checked against one array and it is in fact unsafe/unchecked to use it against another array. So only the fragment Atomic.Field.<op> arr (Atomic.Array.index arr i) is safe, where you use the index for indexing right away, on the same array. This avoids the API duplication but the API is a bit weird. This would be acceptable for an advanced, expert-users-seeking-performance-only internal API, but I am not fond of the extra complexity (it is more work to explain and to use), so I would rather support (1).

My gut feeling is thus that the best move would be to remove this paragraph on supporting arrays, which was tentative and does not pan out as I had hoped, and simply bite the bullet and offer a Atomic.Array submodule without any of the field stuff getting involved. (... and we could also have Atomic.ContendedArray if we wanted to, for a fourth copy of the list of primitives.)

Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I’m reminded (by @polytypic) that non-bound-checked accesses would be desirable as well for performance-critical code.

See Saturn's spsc_queue for example. All accesses are made with an index modulo the size of the array, so there is no need for a bound check.

@gasche
Copy link
Member Author

gasche commented Jun 4, 2024

@bclement-ocp has an alternate proposal, where we use an
extension point to denote a (value, offset) pair, instead of
just the offset. This would look like this -- adapting the
previous example:

(* in library code *)
module Atomic : sig
  ...
  module Loc : sig
    type 'a t
    val get : 'a t -> 'a
    val compare_and_set : 'a t -> 'a -> 'a -> bool
  end
end

(* in user code *)
type t = {
  id : int;
  mutable state : st [@atomic];
}

let rec evolve v =
  let cur = v.state in (* <- strong atomic read *)
  let next = next_state cur in
  if not Atomic.Loc.compare_and_set [%atomic.field v.state] cur next
  then evolve v

Upsides of this proposal:

  • the phantom-typed value has a simpler type: 'a t instead of ('r, 'a) t
  • in particular, it is possible to expose a single set of primitive for
    all of atomic values, atomic record fields
    [%atomic.field v.state], and atomic arrays [%atomic.index a.(i)],
    [%atomic.unsafe_index a.(i)]

Downside: internally this is represented as a (value, offset)
tuple, so it is inefficient if the tuple ends up being built, in
particular for code of the form
let loc = if ... then [%atomic.index foo] else ....
On the other hand, direct applications to a primitive should be
easy to compile to optimize the tuple construction away.

@gasche
Copy link
Member Author

gasche commented Jun 13, 2024

I thought more about the suggestion of @bclement-ocp, and I see four
different designs that are worth discussing.

Running example:

type t = {
  id : int;
  mutable state : st [@atomic];
}

The designs

1. A new two-parameter type ('r, 'v) Atomic.Field.t

With the current proposal, [%atomic.field state] has type (t, st) Atomic.Field.t. This type ('r, 'v) Field.t represents values of
type 'v inside a larger structure or type 'r.

2. A new one-parameter type 'v Atomic.Loc.t

This was my initial understanding of the idea of @bclement-ocp: if
foo has type t, then [%atomic.field foo.state] has type int Atomic.Loc.t.

This is an improvement over the two-parameter type because it is
simpler. It avoids some subtleties coming from the first-class-field
nature of the two-parameter proposal, for example any worries related
to type-directed disambiguation is gone.

Internally 'v Atomic.Loc.t is represented as a pair of a value and
an offset, something like Obj.t * int. The construction
[%atomic.field foo.state] desugars to (Obj.obj foo, 1), but the
idea is that when directly applied to a primitive
Atomic.Loc.fetch_and_add (Obj.obj foo, 1) 42 the compiler will
unpack the pair and avoid any allocation. One way to think of the
optimization is that the code gets rewritten into
Atomic.Field.fetch_and_add (Obj.obj foo) 1 42, where Field is now
a secret module, not exposed to users, which includes two-arguments
atomic primitives.

3. Full extension of 'v Atomic.t to include pointer+offset pairs

In fact we could get rid of this new type 'v Atomic.Loc.t and just
extend 'v Atomic.t for this purpose under the hood:

module Atomic = struct
  type t =
    | Single of { mutable v : 'a }
    | Pair of Obj.t * int
end

The case Single corresponds to the memory representation of atomics
today (the same as ref cells), and the new Pair constructor adds
pointer+offset pairs to it. (This is not type-safe so this definition
would be hidden/private.) With this design, we can give
[%atomic.field foo.state] the type Atomic.t, and we do not need to
introduce a second battery of atomic functions (fetch_and_add
and stuff). The compiler can still optimize Atomic.fetch_and_add [%atomic.field foo.state] to avoid materializing the pair.

I was very happy with this proposal until I noticed a fatal flaw with
it: if you do this, then any call on an atomic that is not
statically known to be a Pair, in particular all atomics that are in
use today, requires a dynamic check to tell if they are in the
Single or in the Pair case. This is a big no-no. (In practice the
test would be cheap, but people who use atomics want precise control
over the code, not dynamic tests added for convenience.)

4. Static extension of 'v Atomic.t

A variant of proposal (3) is to do as if the type Atomic.t was
extended with a Pair constructor, but statically reject all programs
where Pair would have to be materialized / cannot be optimized away
by the compiler. So either [%atomic.field foo.state] gets passed to
a compiler-optimized Atomic.foo primitive, gets rewritten (morally)
into a two-argument Atomic.Field.foo primitive, or the compiler
rejects the program.

If you do this, then you know that all Atomic.t values reaching the
runtime will in fact use the Single constructor (just like today),
and you do not need to add new dynamic checks.

In other words, with this proposal [%atomic.field foo.state]
pretends to be of type int Atomic.t, but this is a magic
Atomic.t value that will never exist at runtime: it must be passed
to an Atomic.foo primitive directly, which will separate the pointer
from the offset.

My current thinking

I think that (3, full extension) is not acceptable for our users in
practice. I prefer (2, new one-parameter type) and (4, static extension)
to (1, new two-parameter type).

I find it a bit hard to compare (2, new one-parameter type) and (4,
static extension).

  • The new one-parameter type proposal (2) leads to more duplication in
    the API, for reasons that will not be apparent to our users. It
    relies less on magic: you want to reason about whether the pair gets
    optimized away when writing code, but the code works as expected
    (and is in fact decently fast) in any case. Being able to
    materialize the pointer+offset pair can also be convenient for some
    use-cases, it is a desirable feature to offer to our users.

  • The proposal (4, static extension) is much less invasive in terms of
    API surface, we add [%atomic.field foo.state] and also
    {,unsafe_}index : 'a array -> int -> 'a Atomic.t primitives and
    that's it. I like the minimality.

    I think that we can do a good job of clear error messages in the
    cases where the value+offset pair cannot be optimized away, so
    I don't think that it will feel hard to use in practice. On the
    other hand, it remains more complex (more things to explain), and we
    lose the expressivity of being able to dynamically create
    pointer+offset pairs and pass them around conveniently.

@lpw25
Copy link
Contributor

lpw25 commented Jun 14, 2024

Even if you do 2 you might as well define the types like:

type ('r, 'v) field
type 'v loc = Loc : 'r * ('r, 'v) field -> 'v loc

Then people can still get 1 if they like.

@kayceesrk kayceesrk added the memory-model Memory model related discussions label Jun 25, 2024
@OlivierNicole
Copy link

I like how (2) fits simply into the compiler, using only things that already exist (extension points, types, compiler primitives). In comparison, (4) seems to add a lot of complexity for a gain that is not so big to me, namely no API duplication. I think we can easily explain to our users that Atomic.t is the simple path that will suffice for many applications, and atomic record fields and atomic accesses in arrays are slightly more advanced and are operated by a distinct set of functions in order to fit nicely into the language.

@gasche
Copy link
Member Author

gasche commented Jul 5, 2024

Thanks, this is useful feedback. I agree that (2) is simpler. It's also probably not too hard to implement (4) on top of (2) later if we decide to do it, so in a sense (2) is a minimum viable proposal.

@OlivierNicole
Copy link

OlivierNicole commented Jul 5, 2024

For the record, I disagree with the memory-model label on this RFC, as the proposal is inside the bounds of the current memory model, as long as we make sure that atomic locations remain separate from non-atomic ones.

Speaking of this, I like the fact that atomic arrays can use the same access functions as atomic record fields; but to satisfy the separation of atomic and non-atomic locations, we need to allow atomic locations to be created only from a 'a Atomic.Array.t values, and not from regular arrays. So, as much as it pains me, it seems that there will be a bit of API duplication between Array and Atomic.Array.

Edit.: I just realized that it’s already the case in your proposal.

@kayceesrk
Copy link

For the record, I disagree with the memory-model label on this RFC, as the proposal is inside the bounds of the current memory model, as long as we make sure that atomic locations remain separate from non-atomic ones.

In my mind, anything to do with atomics, relaxed memory semantics and their compilation fall under the broad category of memory model. Recall that atomics in OCaml were introduced in the PLDI 2017 “memory model” paper. I’m using the tag only to find memory model related RFCs easily.

gasche added a commit to gasche/ocaml that referenced this pull request Aug 24, 2024
In trunk, all atomic functions exposed in the runtime are also exposed
as language primitives in our intermediate representations (lambda,
clambda). But except for `Patomic_load`, which benefits from
dedicated code generation, they are all transformed into C calls
on all backends.

The present PR simplifies the code noticeably by removing the
intermediate primitives, by producing C calls directly in
lambda/translprim.ml.

This reduces the amount of boilerplate to modify to implement
atomic record fields (ocaml/RFCs#39).

Co-authored-by: Clément Allain <[email protected]>
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche added a commit to gasche/ocaml that referenced this pull request Aug 25, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
clef-men added a commit to clef-men/ocaml that referenced this pull request Aug 26, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
clef-men added a commit to clef-men/ocaml that referenced this pull request Aug 26, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to clef-men/ocaml that referenced this pull request Aug 26, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to clef-men/ocaml that referenced this pull request Aug 26, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to clef-men/ocaml that referenced this pull request Aug 27, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to clef-men/ocaml that referenced this pull request Aug 27, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
@gasche
Copy link
Member Author

gasche commented Aug 28, 2024

There is now an implementation of this RFC -- the [%atomic.loc foo.bar] design evolved from the discussion, not the original description -- as a PR by @clef-men and myself: ocaml/ocaml#13404 .

clef-men added a commit to clef-men/ocaml that referenced this pull request Sep 21, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
clef-men added a commit to clef-men/ocaml that referenced this pull request Sep 21, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
clef-men added a commit to clef-men/ocaml that referenced this pull request Sep 21, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to gasche/ocaml that referenced this pull request Sep 26, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to gasche/ocaml that referenced this pull request Sep 26, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to clef-men/ocaml that referenced this pull request Sep 27, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to clef-men/ocaml that referenced this pull request Sep 27, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche pushed a commit to gasche/ocaml that referenced this pull request Oct 31, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche pushed a commit to clef-men/ocaml that referenced this pull request Oct 31, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
@polytypic
Copy link

polytypic commented Nov 5, 2024

I was asked to comment about whether there might be some reason to prefer the more complex initial design with two type parameters representing an offset into a block of some type and the design with a single type parameter that logically holds a pair of a block and offset into that block.

My initial thought was that there probably aren't that many applications for the added generality of having first-class offsets to atomic fields. However, I then went running last night and realized there might actually be some practically important use cases for the more complex design.

Consider the following FGL sketch:

module FGL : sig
  type state [@@immediate]
  val init : unit -> state
  val lock : 'block -> ('block, state) Atomic.Loc.t -> unit
  val unlock : 'block -> ('block, state) Atomic.Loc.t -> unit
end = struct
  type state = int
  (* ... *)
end

The idea is that a FGL takes only one word and can e.g. be embedded into the nodes of a data structure without allocations. This allows efficient Fine-Grained Locking approaches.

Only a couple of bits are needed to represent the state of an efficient lock and the queue of awaiters can be stored externally just like with a futex.

The init operation generates random bits and masks out the couple of bits used for the lock state. The random bits are then used as the hash value and the (identity of the) block value is used as the key for identifying the queue of awaiters corresponding to a specific FGL.

Addition: You actually want to use both the block address and the field offset to identify the FGL. This way you will be able to have multiple FGLs per block. You might also use bits from the offset as part of the hash value.

For reference:

You can, of course, implement something similar with the other design:

module FGL : sig
  type state [@@immediate]
  val init : unit -> state
  val lock : 'unique_key -> state Atomic.Loc.t -> unit
  val unlock : 'unique_key -> state Atomic.Loc.t -> unit
end = struct
  type state = int
  (* ... *)
end

One issue here is now that the lock and unlock operations need to be inlined, IIUC, to avoid an allocation. Also, there is no longer a connection between the 'unique_key and the atomic state.

@gasche
Copy link
Member Author

gasche commented Nov 5, 2024

Thanks @polytypic. Your reply got me thinking about how we can move from one design to the other. (The value-and-offset design and the offset-only design.)

From the offset-only design, it is possible to implement the field-and-offset design with a GADT, as pointed by @lpw25 at #39 (comment) .

From the value-and-offset design, it is possible to recover the field, but not its typing information: val obj : 'a Atomic.Loc.t -> Obj.t (which just takes the first element of the pair). This would be enough for your FGL use-case but it is not very nice.

The pair that is giving me pause about the offset-only design is the fact that the type-inference code is more complex, as we have to deal with type-based disambiguation, and probably require a type annotation from the user. It is easy to type-check [%atomic.loc r.f], this is just the usual type-checking code for record field access, but harder to type-checker [%atomic.field f] in isolation, in absence of expected type. We would need to experiment with this to see whether it works out okay in practice (without requiring a type annotation). My hunch is that idiomatic applications like Atomc.Loc.fetch_and_add r [%atomic.loc count] 1 would work okay in non-principal mode (the default), but emit a warning in principal mode, due to the fact that the propagation of type information during application is not considered principal. I guess this would behave similarly to the following:

# type t = { x : int };;
# type u = { x : int };;
# let (vt : t), (vu : u) = { x = 0 }, { x = 1 };;
val vt : t = {x = 0}
val vu : u = {x = 1}
# let access r f = f r;;
val access : 'a -> ('a -> 'b) -> 'b = <fun>
# access vt (fun r -> r.x), access vu (fun r -> r.x);;
- : int * int = (0, 1)
# #principal true;;
# access vt (fun r -> r.x), access vu (fun r -> r.x);;
Warning 18 [not-principal]: this type-based field disambiguation is not principal.

- : int * int = (0, 1)

@polytypic
Copy link

probably require a type annotation from the user

I wouldn't expect this to be a practically significant imbediment. I believe it is likely that the vast majority of uses of atomic record fields will be hidden inside data structure implementations written by people who are relatively experts in these matters. The FGL example, which takes an offset as a parameter, also falls into this category. The main use case for FGL would be writing data structures with fine-grained locking, which requires some expertise, and would usually be hidden behind the data structure abstraction.

@gasche
Copy link
Member Author

gasche commented Nov 7, 2024

Today I thought more about how we would go for design one (('r, 'v) Atomic.Field.t) and how it relates to design two ('v Atomic.Loc.t). As Leo pointed out, if you have atomic fields, then you can define atomic locations as:

type 'v loc = Loc : 'r * ('r, 'v) Field.t -> 'v loc

There is no point in exposing atomic operations on 'v loc in addition to operations on ('r, 'v) Field.t, but this remains useful for expert users if they want to carry a 'v loc around as a first-class location, say in a data structure.

There are two upsides to having atomic operations take a 'r and a ('r, 'v) FIeld.t separately:

  • this is transparent from a performance perspective, it does not rely on the compiler optimizing the tuple away, so it is probably more robust/modular
  • it is slightly more expressive, with a reasonable example proposed by @polytypic above

I see two clear downsides to ('r, 'v) Field.t (besides "it's more work because we haven't implemented it yet"):

  • As pointed out earlier, it is harder to type-checker [%atomic.field x] than [%atomic.loc r.x] in principal mode, we don't have the type of r at hand to guide disambiguation.
  • As @clef-men remarked, when 'r is an inline record type (the record in Foo of { ... }), then the record type cannot be named in the surface syntax, so users have no way to annotate the field access to disambiguate the field name. This is a serious limitation because inline record types are common in @polytypic programs and would benefit from atomic fields.

I considered three ways out of this quagmire:

  1. We could expose both ('r, 'v) Field.t (as a primiritive type) and 'v Loc.t (defined as a GADT, without atomic operations on it), and then have both [%atomic.field x] and [%atomic.loc r.v], the latter can be used even with inline records.
  2. We could expose surface syntax for inline record types, to make the second downside go away. (This is something that Alain originally proposed when he introduced inline records, say t.Foo for the type of the record argument of the constructor Foo at type t).
  3. We could expose only 'v Loc.t as a primitive type, with a low-level function repr : 'v Loc.t -> Obj.t * int, which is ugly but happens to suffice to implement FGL, if I understand correctly. (This remains less expressive than ('r, 'v) Field.t, because it does not let us safely build an index for a record and then reuse it for another element of the same type.)

Note: If we decide to go for a design with 'v Loc.t as a primitive, we can always revisit this later and expose ('r, 'v) Field.t and re-define 'v Loc.t as the GADT on top of it. But one aspect of the design that I liked was to avoid exposing too many versions of atomic operations, and that approach loses on this front, as one would then end up with three copies of each atomic operation, Atomic.foo, Atomic.Loc.foo and Atomic.Field.foo. (And then possibly Atomic.Array.{unsafe_,}foo, urgh.)

gasche added a commit to gasche/ocaml that referenced this pull request Nov 21, 2024
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to gasche/ocaml that referenced this pull request Nov 21, 2024
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
@gasche
Copy link
Member Author

gasche commented Jan 5, 2025

In ocaml/ocaml#13707 I implement %atomic.field on top of the current PR (ocaml/ocaml#13404) implementing %atomic.loc; the type-based disambiguation code is more involved, as expected, but more importantly the interaction with inline records is much worse than I thought it would be, basically the feature is unusable on inline records -- they cannot have atomic fields.

Let me quote my preliminary conclusions at the end of the description of that PR:

I see three reasonable options going forward:

  1. Give up on %atomic.field and merge Atomic record fields ocaml#13404 which implements the simpler %atomic.loc, has been morally approved and carefully reviewed.

  2. Merge something like the current state of the present PR, with a fully working %atomic.loc and additionally a version of %atomic.field that has advantages but does not work with inline records. Later we can consider changing the type-checking of inline records to lift this limitation, and we would end up with two features that work well. (And some duplication as each atomic primitive foo would be available as Atomic.Field.foo and also Atomic.Loc.foo, but there are 5 of them so it's okay.)

  3. Decide that we absolutely want %atomic.field and not %atomic.loc, and that we must first change the type-checking of inline records to lift the current limitations of %atomic.field.

clef-men added a commit to clef-men/ocaml that referenced this pull request Apr 22, 2025
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
clef-men added a commit to clef-men/ocaml that referenced this pull request Apr 22, 2025
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche pushed a commit to clef-men/ocaml that referenced this pull request Apr 23, 2025
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to gasche/ocaml that referenced this pull request May 7, 2025
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to gasche/ocaml that referenced this pull request May 7, 2025
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
gasche added a commit to gasche/ocaml that referenced this pull request May 7, 2025
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
gasche pushed a commit to gasche/ocaml that referenced this pull request May 7, 2025
This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.
matthewelse pushed a commit to matthewelse/flambda-backend that referenced this pull request May 26, 2025
Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>
anmonteiro added a commit to melange-re/melange-compiler-libs that referenced this pull request Jun 2, 2025
* BOOTSTRAP

* Changed interface of compare_package to take packages as argument

* Factor subtype_package out of subtype_rec

* Changed interface of package_subtype to take packages as arguments

* Factor unify_package out of unify3

* Factor moregen_package out of moregen

* Factor eqtype_package out of eqtype

* Changed interface of type_package to take a package as argument and return a package

* Small improvement of presentation

* Changed interface of modtype_of_package to take a package as argument

* Introduce a new record for package types in outcometree

* Changes

* Renamed pack_fields to pack_cstrs in package_type for coherence

* Renamed fileds of Typedtree.package_type for less ambiguity with Types.package

* Refactor complete_type_list to take a package as argument

* #13702 error messages: specialized error messages for non-functors (#13865)

This commit adds a specialized error message for functor appearing in a context where non-functors were expected (and reciprocally) rather than using the generic error message for mismatched functor parameters.

* Add reviewers to Changes entry for #13407

* gitignore: ignore macOS executable debug symbols directory

When an executable is linked using the -g flag, a directory for debug
symbols is created under macOS. It's only appearing for sak, and
creates noise with git status. Ignore it.

* Add a test showing unexpected approximated shapes
when indexing modules in constructor paths.

* Use `Pextra_ty` for specific shape paths and correctly index modules in these.

This makes the handling of the custom cases when resolving shape paths less ad-hoc and fixes shape resolution for modules in constructor and labels paths.

Suggested-by: Florian Angeletti <[email protected]>

Refactor and add apply case

Introduce a [scrape_extra_ty] function

* Add changelog entry

Changes: add reviewer

* Fix C _Atomic in header incompatibility with C++

_Atomic is standard C11 but is not standard C++ (although sometimes
available as a compiler extension). Use atomic_uintnat from our
camlatomic.h.

    In file included from all-includes.h:6:
    /Users/antonin/Tarides/ocaml/trunk/runtime/caml/custom.h:54:12: error: '_Atomic' does not name a type; did you mean 'Atom'?
       54 | CAMLextern _Atomic uintnat caml_custom_major_ratio;
          |            ^~~~~~~
          |            Atom

* Correct regression with `unused-type-declaration` warning

* Merge pull request #13829 from clementblaudeau/recsig-substitution-cyclic-check

Fix missing check of illegal recursive module when using module type substitutions

* Remove quotes around \var{...} in intfc manual

The quotes prevent the `\var` operator from being applied, resulting in
"\var{...}" literally being displayed on the page.

Signed-off-by: Stephen Sherratt <[email protected]>

* Fix documentation of Array.compare regarding the ordering. (#13908)

* Enforce evaluation order for generic applications in Closure (#13882)

* Mark tests that actually require multicore (#13906)

Some tests fail or hang on mono-core systems. In this commit, we
introduce the "multicore" predicate in ocamltest, and mark the
affected tests.

Bug-Debian: https://bugs.debian.org/1101353

* Fix definition of Fibonacci numbers in the manual (#13912)

* Apply BUILD_PATH_PREFIX_MAP to Sys.argv.(0) in cmt

Cmt_format.cmt_infos.cmt_args includes a copy of Sys.argv from the
compiler invocation. The user is in control of the arguments passed to a
binary (Sys.argv.(1) and above) and can avoid embedding absolute paths,
but Sys.argv.(0) on some platforms is converted to an absolute path,
regardless of how the executable was invoked.

* GHA: remove PRISTINE_PATH

Should be unnecessary

* GHA: bash is part of Cygwin base

* GHA: tell Cygwin's bash to ignore CR line endings

As suggested by the cygwin-install action. Makes much nicer looking
shell scripts!

https://github.com/cygwin/cygwin-install-action?tab=readme-ov-file#line-endings

* GHA: revisit limits on concurrent Make jobs

- When using MinGW-w64 on Linux, Make may spawn too many processes,
  triggering the OOM-killer, and ending the build.
- Running `make test` with `-j` has no effect, the test runner is
  already built and is responsible of running tests in parallel.

* GHA: store the Autoconf cache key in the step output

Avoid using Cygwin when computing the cache key.

* GHA: don't set CC as an env variable

Makes a cleaner ./configure invocation.

* GHA: refactor configure calls in runner.sh

* GHA: typo

* GHA: split configuration and build

Matches the other workflows.

* GHA: use a fold for config.log in GHA

If configure fails, it is useful to have config.log, but the error is
initially more useful, and that's often harder to spot at the end of
config.log

* Get rid of the @SInCE attribute for the Uchar.hash function

Given that this function is present in the module since it was
introduced, the convension is to not have any @SInCE attribute
at the function level, since the module-level one applies.

This commit reverts the addition of the attribute done in PR #13240, see
commit 9585cfe.

* Add Result.product and Result.Syntax (#13696)

* Repr.equal is not an operator (#13914)

Co-authored-by: Hazem ElMasry <[email protected]>

* Add examples to the `Fun` module

* Reword some paragraphs in `Fun` examples

* Reword more paragraphs in `Fun` examples

* Add more examples to `Fun.id` and `const`

* Remove problematic examples and add descriptions

* Expand the Fun.id dispatching description

And make the example conform to the description

* Add "advanced"/"real-world" examples

These are instead of the problematic examples

* Make function refs headers

* Add `Fun.compose` examples

And warn about too many combinators

* Deindent and improve formatting

* Reword some descriptions

* Remove problematic `flip` examples

* Replace a `compose` example with more involved one

* Typos in the Uchar example

* Some rewording

* Replace the windows path conversion example

* Add a Scanf example to id

* Add example to const, remove example from compose

* Indent code blocks, reorder, reformat, reword

* Remove scanf and floatarray examples from id

* Prevent overlong lines in code examples

* Add a Changes entry

* Enrich ocamltest doc about scripts (#13902)

* manual: alerts: add sections, in preparation for following commits

* manual: alerts: annotate code section as ocaml code

For presumably marginally nicer display.

* manual: alerts: document how to put alerts on all structure/signature items

Personally, I had no idea it was possible to put an alert on a let binding
until I saw it mentioned on a github issue, because it's undocumented.
Ideally, warning 53 would teach users that write:

    let x = 1 [@@deprecated]

to write:

    let x [@deprecated] = 1

instead, but I'm only changing doc here. And arguably, the first form
could be interpreted as the second form, when the pattern contains a
single variable (and fail otherwise), as that's how alerts works for
all other binding constructs.

* Makefile.dev: work around #13817 (#13818)

* [refactor] runtime: auxiliary function for allocated_words update

* runtime: "suspended" and "resumed" allocations affect the major GC speed

This is a buildup commit, currently there is no control in the GC to suspend or resume specific allocations, so these counters are always 0.

The intuition is to "suspend" allocations during ramp-up phases, and "resume" allocations during ramp-down.

* runtime: simplistic support for [ramp_up], [ramp_down]

During [ramp_up], the deallocation work coming from allocations is
"suspended". It can be "resumed" by calling [ramp_down].

[ramp_up] does not currently count the total number of suspended
allocations (this needs more domain state that is not reset on each
major state), so the user would not know which value to provided to
[ramp_down]. This will be added next.

* runtime: count the work suspended by each ramp-up phase

* runtime: support nested ramp-up phases

* expose ramp_up, ramp_down as externals in stdlib/Gc

* Changes entry

* runtime: log ramp-up / ramp-down in SLICESIZE GC logs

* Gc.ramp_up: re-raise exceptions, but ramp-down right before

Suggested-by: Guillaume Munch-Maccagnoni <[email protected]>

* [minor] stray fix in runtime/array.c

* runtime/array.c: expose {uniform_,float}array_concat, use it in Float.Array

* Rename ccomptype to ccomp_type for consistency (#13927)

* Add Result.{get_ok',error_to_failure} (#13720)

* Add Result.get_ok'.

* Result.error_to_failure

* Update changes.

* Add List.singleton and Seq.singleton

Set.S already has singleton, and dual of {Bytes,String,Array}.make 1
and Option.some

* Fix @SInCE 5.0 annotation loss in domain.mli and effect.mli by swapping alert and header (#13934)

* mystery reviewer for 13643

* Added tests for abstraction of whole module types during avoidance

* Removed abstraction of whole module types when avoiding a field

* Not backward compatible: code could use this behavior to create signatures
with abstract module type fields, and place them in negative positions with
[module type of], but it is highly unlikely intentional. There is no loss of
expressivity: the desired resulting signature can still be obtained with an
explicit signature constraint.

* Added Change entry

* Fix test weak-ephe-final/ephe_custom.ml (#13940)

* [refactoring] move Matching.get_mod_field to Lambda.transl_mod_field

* [refactoring] Lambda.transl_mod_field, move 'lazy' to clients

* [refactor] Lambda: merge transl_mod_field and transl_prim

* update .depend

* Fix #13939

* Typeopt: better handling of deeply nested unboxed types

* Add test

* Changes

* runtime: migrate caml_{alloc,update}_dummy from alloc.c to obj.c

* caml_update_dummy: the [Infix_tag] case is dead code

We stopped using dummies for values at a function type in OCaml 5.2,
and the matching [caml_alloc_dummy_infix] function was removed in
cd48dc0.

* [minor] value_rec_compiler: refactor alloc/update calls

* recursive values: introduce [caml_update_dummy_lazy]

* regression test for lazy shortcutting in recursive values

* Changes

* lazy + letrec: insert indirections on lazy update to avoid concurrency issues

* use a dedicated [caml_alloc_dummy] primitive

Suggested-by: Vincent Laviron <[email protected]>

* Improved changelog message

* document [caml_domain_alone] reasoning

* spawn: increment [caml_num_domains_running] earlier to ease reasoning

* Changes

* Pin Cygwin back to 3.6.1 until AppVeyor updates

Avoids broken 3.5.5 version in the runner image.

* List.sort_uniq : remove non-first duplicates. (#13862)

* Move match_printer_type in order to share it between toplevel and debugger

* Move find_printer to Topprinters (to be shared with the degugger)

* Move debugger printers fetching logic

* Debugger uses Topprinters.find_printer

The behavior is purely identical.

* release-info: update calendar

* Use dune.3.18.0 which is compatible with trunk

* Bump qcheck and multicoretests to the latest releases

* Changed occur_rec in typing/ctype.ml to traverse type as a graph and not a tree

* Changes

* Renamed some arguments of occur_rec

* Add signal definitions for SIGIO and SIGWINCH.

* Add signal_to_string function

* Add signal type alias and signal_to_string.

* Export signal conversion functions as primitives.

* Export signal conversion functions as primitives in Sys

* Update documentation in Unix module

* Check int and signal argument ranges for conversion functions

Signal_to_string and signal_to_int call invalid_arg if presented with
an unrecognised negative number. signal_of_int calls invalid_arg for
all negative numbers.

* Add changelog

* Allow 'effect' as attribute id (#13957)

* ocamltest: fix typos

(cherry picked from commit 62672b75a315e52e39275dce10d87f22df73e254)

* Teach ocamltest about colors

As the compiler drivers and various ocaml tools, ocamltest now accepts
the -color flag, and recognizes the OCAML_COLOR and NO_COLOR
environment variables.

It uses them to pass a corresponding --color flag to diff, if it was
detected during configure that diff supports this flag.

* GHA: update to macOS 15 and Xcode 16.3

* tests: native-debugger: build C test code without optimizations

Fixes warnings and spurious failures in the CI.

* tests: native-debugger: sanitize library path

Debian and Fedora derivatives have different libpaths:

    -Using host libthread_db library "/lib/aarch64-linux-gnu/libthread_db.so.1".
    +Using host libthread_db library "/lib64/libthread_db.so.1".

fixup_libthread

* tests: native-debugger: fix GDB version parsing

* tests: native-debugger: disable disabling ASLR

This allows running the tests more easily in Docker images. The
sanitization step takes care of removing artifacts of randomization
anyway.

* tests: native-debugger: sanitize trailing blanks

* tests: native-debugger: simplify shell scripts

Don't redeclare variables that ocamltest always provides in scripts.

* Apply suggestions from review

* Check separately in configure if DIFF supports --color

* Fix hygiene check for generating `configure` (#13935)

* Allow check-configure.sh to be run locally

* Re-bash the autoconf test

* Simplify - and correct - check-configure.sh

The script contained an unused feature to be able to check PRs as one -
this is never wanted, as we should always be checking that every commit
has a valid committed configure script.

The mechanism for checking whether commits should be tested is shifted
back to the actual trawl of the log. This is both simpler (because it
can be done with a simple file list) but also fixes a bug, since commits
which _didn't_ update configure could reset a failure from an earlier
commit.

* Wrong parameter checked in check-configure.sh

* Review

* Added printing of presence flag in typedtree (#13963)

* fix .depend

* [minor] value_rec_compiler: move primitive declarations earlier

* fix #13931

* Add profiling with perf chapter OCaml manual

This covers the use of Linux perf to profile OCaml native code
including the overlap with frame pointers and DWARF CFI information

* Collapse profiling into a single chapter.

* add an invariant function to check that loc_ghost is set correctly

spoiler alert: it isn't

* parser: partially align use of loc_ghost with what the documentation says

Mostly in:
- the productions for keyword%extension syntaxes
- the implied 'self in `object ('self) end`

* parser: refactor previous commit, by removing error prone functions

* parser: regenerate parser.ml

* Add test of princiaplity from polymorphic type constraints

* Keep generalized structure from patterns when typing let

* Add changelog entry

* Renamed the flag `transparent_modules` into `no_alias_deps`

* Update driver/makedepend.ml

Co-authored-by: Kate <[email protected]>

* Updated Changelog with pr number

* Update changes

* ocamlopt: pass -fPIC when compiling C files

* Changes

* Changes

* Uniformize definition of native_cflags, bytecode_cflags

* Changes

* last commit before branching 5.4

* first commit on branch 5.4

* Merge pull request #13950 from OlivierNicole/bugfix-array-sub

Avoid tearing in Array.sub

(cherry picked from commit 331b5e64a174f47da6b37fa47bf23acdf1625399)

* Merge pull request #13921 from dra27/more-cloexec

Preserve `O_CLOEXEC` when converting `Unix.file_descr` to a CRT fd on Windows

(cherry picked from commit 23852ccb806fbe72d8fe847ddff7a8c2add4421d)

* Bump magic numbers for 5.4

* Fix memory corruption when an exception is raised during demarshaling. (#14015)

(cherry picked from commit e6321cf1e3f3bfb0795108ab4d6c66c559ea9b63)

* Merge pull request #13909 from OlivierNicole/dynarray-unsafe-to-iarray

Add Dynarray.unsafe_to_iarray

(cherry picked from commit aa7e2856ecb2f002e1fabd468638df12046a7be6)

* [minor] printcmm: print atomic loads

* [testsuite] test the compilation of atomic functions

* [refactor] Define [caml_atomic_cas] in terms of [caml_atomic_cas_field].

* [breaking] Change the prototype of [caml_atomic_cas_field].

This is a breaking change because this function was (unfortunately)
exposed outside CAML_INTERNALS, and is used by exactly one external
user, you guessed it:
  https://github.com/ocaml-multicore/multicore-magic/blob/360c2e829c9addeca9ccaee1c71f4ad36bb14a79/src/Multicore_magic.mli#L181-L185
  https://github.com/ocaml-multicore/multicore-magic/blob/360c2e829c9addeca9ccaee1c71f4ad36bb14a79/src/unboxed5/multicore_magic_atomic_array.ml#L36-L43

We chose to change the prototype to remain consistent with the naming
convention for the new caml_atomic_*_field primitives, which will be
added to support atomic record fields.

User code can easily adapt to this new prototype we are using, but not
in a way that is compatible with both old and new versions of
OCaml (not without some preprocessing at least).

Another option would be to expose

    int caml_atomic_cas_field(value obj, intnat fld, value, value)
    value caml_atomic_cas_field_boxed(value obj, value vfld, value, value)

but no other group of primitives in the runtime uses this _boxed
terminology, they instead use

    int caml_atomic_cas_field_unboxed(value obj, intnat fld, value, value)
    value caml_atomic_cas_field(value obj, value vfld, value, value)

and this would again break compatiblity -- it is not easier to convert
code to that two-version proposal, and not noticeably more efficient.

So in this case we decided to break compatibility (of an obscure,
experimental, undocumented but exposed feature) in favor of
consistency and simplificity of the result.

* runtime: Add atomic primitives [caml_atomic_load_field], [caml_atomic_exchange_field] and [caml_atomic_fetch_add_field].

* lambda: Add support for new atomic primitives.

Uses of existing atomic primitives %atomic_foo, which act on
single-field references, are now translated into %atomic_foo_field,
which act on a pointer and an offset -- passed as separate arguments.

In particular, note that the arity of the internal Lambda primitive
    Patomic_load
increases by one with this patchset. (Initially we renamed it into
    Patomic_load_field
but this creates a lot of churn for no clear benefits.)

We also support primitives of the form %atomic_foo_loc, which
expects a pair of a pointer and an offset (as a single argument),
as we proposed in the RFC on atomic fields
  ocaml/RFCs#39
(but there is no language-level support for atomic record fields yet)

Co-authored-by: Clément Allain <[email protected]>

* Add support for atomic record fields.

Requires a bootstrap.

Co-authored-by: Gabriel Scherer <[email protected]>

* atomic fields in ocamldoc

* Bootstrap.

To reproduce (see BOOTSTRAP.adoc for details):
- go to the earlier commit "lambda: Add support for new atomic
  primitives" as a known-good state, build that one
- keep the build artifacts around, come here and do `make bootstrap`

* Add tests for atomic record fields.

* [minor] Make test_untypeast.ml more readable.

* Add predefined type ['a atomic_loc].

This type will be used for ['a Atomic.Loc.t], as proposed
in the RFC
  ocaml/RFCs#39

We implement this here to be able to use it in the stdlib later,
after a bootstrap.

* [refactor] more general type for Env.mark_*_used

We want to use [mark_label_used] in a context where we cannot easily
find the label declaration, only the label description (from the
environment).

* Add extension [%atomic.loc record.field].

* Bootstrap.

This bootstrap is not required by a compiler change, but it enables
the use of the predefined type `'a atomic_loc` and the
expression-former [%atomic.loc ...] in the standard library.

* Add module [Stdlib.Atomic.Loc].

* Add tests for [Atomic.Loc].

* Reimplement [Atomic.t] using [Atomic.Loc.t].

* Forbid atomic fields in patterns.

* Changes

* testsuite for pattern-matching on atomic reads

* allow wildcard patterns under atomic record fields

Suggested-by: Olivier Nicole <[email protected]>

* stdlib/Atomic: move the Loc module below in the .mli

* stdlib/Atomic: minimal documentation

* revert a type_approx change from labeled tuples

* Merge pull request #13991 from gasche/atomic_fields_manual

describe atomic record fields in the reference manual

(cherry picked from commit 0c16a7c8fa15894f486e0240d47a1adf2721fe9b)

* fix atomic-locs/cmm.compilers.reference

* Merge pull request #13987 from OlivierNicole/fix-tsan-false-alarm

Fix #13427

(cherry picked from commit e0154dc23244cc3e57f4489b9cbf27421b20c884)

* Merge pull request #14032 from jmid/flexdll-0.44

Update FlexDLL to 0.44 and reenable lib-dynlink-domains test on Windows

(cherry picked from commit 6cca9ffc5e1181040717f7f72a1a9468a8ff1ec0)

* Merge pull request #13675 from stedolan/memprof-map-file

Ensure that all Bigarray memory managed by the GC is tracked by Memprof

(cherry picked from commit 820bc29b9fc801f50dbc556fd2dab1d3bb4bfb6a)

* manual: move the TeX header of each language extension into the extension-specific .etex file (#14041)

(cherry picked from commit 0728f6af2aae32a97c2a7a1214c25736a26a479b)

* minor Changes fixes

* 5.4 Changes: complete and reorder entries

* No need for the stale workflow on branches

* Merge pull request #14013 from dra27/more-ci-tweaks

GHA: add an optional wider test matrix (Cygwin, static, minimal, etc.)
(cherry picked from commit 96b56fd4c822c92b4b81ff4ac7903ae8afb16a52)

* Merge pull request #14025 from gasche/orphan-shared-heap-before-STW-exit

domain_terminate: orphan the shared heap before STW exit

(cherry picked from commit d325f299896417c5f1d477171135acfdf402e770)

* last commit before tagging 5.4.0~alpha1

* release 5.4.0~alpha1

* increment version number after tagging 5.4.0~alpha1

---------

Signed-off-by: Stephen Sherratt <[email protected]>
Co-authored-by: samsa1 <[email protected]>
Co-authored-by: Florian Angeletti <[email protected]>
Co-authored-by: Seb Hinderer <[email protected]>
Co-authored-by: Antonin Décimo <[email protected]>
Co-authored-by: Ulysse Gérard <[email protected]>
Co-authored-by: Gabriel Scherer <[email protected]>
Co-authored-by: Clément Blaudeau <[email protected]>
Co-authored-by: Stephen Sherratt <[email protected]>
Co-authored-by: Guillaume Melquiond <[email protected]>
Co-authored-by: Vincent Laviron <[email protected]>
Co-authored-by: Stéphane Glondu <[email protected]>
Co-authored-by: Jean-Christophe Filliatre <[email protected]>
Co-authored-by: David Allsopp <[email protected]>
Co-authored-by: Daniel Bünzli <[email protected]>
Co-authored-by: Haz <[email protected]>
Co-authored-by: Hazem ElMasry <[email protected]>
Co-authored-by: Olivier Nicole <[email protected]>
Co-authored-by: Valentin Gatien-Baron <[email protected]>
Co-authored-by: Nicolás Ojeda Bär <[email protected]>
Co-authored-by: Hanliang Xu <[email protected]>
Co-authored-by: Blaudeau Clément <[email protected]>
Co-authored-by: Benoit <[email protected]>
Co-authored-by: Pierre Boutillier <[email protected]>
Co-authored-by: Jan Midtgaard <[email protected]>
Co-authored-by: Tim McGilchrist <[email protected]>
Co-authored-by: Pieter Goetschalckx <[email protected]>
Co-authored-by: Leo White <[email protected]>
Co-authored-by: Kate <[email protected]>
Co-authored-by: octachron <[email protected]>
Co-authored-by: Benoît Vaugon <[email protected]>
Co-authored-by: Clément <[email protected]>
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Labels

memory-model Memory model related discussions

Projects

None yet

Development

Successfully merging this pull request may close these issues.

6 participants