@@ -77,6 +77,17 @@ type loc_kind =
7777 | Loc_POS
7878 | Loc_FUNCTION
7979
80+ type atomic_kind =
81+ | Ref (* operation on an atomic reference (takes only a pointer) *)
82+ | Field (* operation on an atomic field (takes a pointer and an offset) *)
83+ | Loc (* operation on a first-class field (takes a (pointer, offset) pair *)
84+
85+ type atomic_op =
86+ | Load
87+ | Exchange
88+ | Cas
89+ | Faa
90+
8091type prim =
8192 | Primitive of Lambda .primitive * int
8293 | External of Primitive .description
@@ -92,6 +103,7 @@ type prim =
92103 | Identity
93104 | Apply
94105 | Revapply
106+ | Atomic of atomic_op * atomic_kind
95107
96108let used_primitives = Hashtbl. create 7
97109let add_used_primitive loc env path =
@@ -114,12 +126,11 @@ let prim_sys_argv =
114126 Primitive. simple ~name: " caml_sys_argv" ~arity: 1 ~alloc: true
115127
116128let prim_atomic_exchange =
117- Primitive. simple ~name: " caml_atomic_exchange " ~arity: 2 ~alloc: false
129+ Primitive. simple ~name: " caml_atomic_exchange_field " ~arity: 3 ~alloc: false
118130let prim_atomic_cas =
119- Primitive. simple ~name: " caml_atomic_cas " ~arity: 3 ~alloc: false
131+ Primitive. simple ~name: " caml_atomic_cas_field " ~arity: 4 ~alloc: false
120132let prim_atomic_fetch_add =
121- Primitive. simple ~name: " caml_atomic_fetch_add" ~arity: 2 ~alloc: false
122-
133+ Primitive. simple ~name: " caml_atomic_fetch_add_field" ~arity: 3 ~alloc: false
123134
124135let primitives_table =
125136 create_hashtable 57 [
@@ -372,10 +383,18 @@ let primitives_table =
372383 " %greaterequal" , Comparison (Greater_equal , Compare_generic );
373384 " %greaterthan" , Comparison (Greater_than , Compare_generic );
374385 " %compare" , Comparison (Compare , Compare_generic );
375- " %atomic_load" , Primitive (Patomic_load , 1 );
376- " %atomic_exchange" , External prim_atomic_exchange;
377- " %atomic_cas" , External prim_atomic_cas;
378- " %atomic_fetch_add" , External prim_atomic_fetch_add;
386+ " %atomic_load" , Atomic (Load , Ref );
387+ " %atomic_exchange" , Atomic (Exchange , Ref );
388+ " %atomic_cas" , Atomic (Cas , Ref );
389+ " %atomic_fetch_add" , Atomic (Faa , Ref );
390+ " %atomic_load_field" , Atomic (Load , Field );
391+ " %atomic_exchange_field" , Atomic (Exchange , Field );
392+ " %atomic_cas_field" , Atomic (Cas , Field );
393+ " %atomic_fetch_add_field" , Atomic (Faa , Field );
394+ " %atomic_load_loc" , Atomic (Load , Loc );
395+ " %atomic_exchange_loc" , Atomic (Exchange , Loc );
396+ " %atomic_cas_loc" , Atomic (Cas , Loc );
397+ " %atomic_fetch_add_loc" , Atomic (Faa , Loc );
379398 " %runstack" , Primitive (Prunstack , 3 );
380399 " %reperform" , Primitive (Preperform , 3 );
381400 " %perform" , Primitive (Pperform , 1 );
@@ -658,6 +677,77 @@ let lambda_of_loc kind sloc =
658677 let scope_name = Debuginfo.Scoped_location. string_of_scoped_location sloc in
659678 Lconst (Const_immstring scope_name)
660679
680+ let atomic_arity op (kind : atomic_kind ) =
681+ let arity_of_op =
682+ match op with
683+ | Load -> 1
684+ | Exchange -> 2
685+ | Cas -> 3
686+ | Faa -> 2
687+ in
688+ let extra_kind_arity =
689+ match kind with
690+ | Ref | Loc -> 0
691+ | Field -> 1
692+ in
693+ arity_of_op + extra_kind_arity
694+
695+ let lambda_of_atomic prim_name loc op (kind : atomic_kind ) args =
696+ if List. length args <> atomic_arity op kind then
697+ raise (Error (to_location loc, Wrong_arity_builtin_primitive prim_name)) ;
698+ let split = function
699+ | [] ->
700+ (* split is only called when [arity >= 1] *)
701+ assert false
702+ | first :: rest ->
703+ first, rest
704+ in
705+ let prim =
706+ match op with
707+ | Load -> Patomic_load
708+ | Exchange -> Pccall prim_atomic_exchange
709+ | Cas -> Pccall prim_atomic_cas
710+ | Faa -> Pccall prim_atomic_fetch_add
711+ in
712+ match kind with
713+ | Ref ->
714+ (* the primitive application
715+ [%atomic_exchange ref v]
716+ becomes
717+ [caml_atomic_exchange_field(ref, Val_long(0), v)] *)
718+ let ref_arg, rest = split args in
719+ let args = ref_arg :: Lconst (Lambda. const_int 0 ) :: rest in
720+ Lprim (prim, args, loc)
721+ | Field ->
722+ (* the primitive application
723+ [%atomic_exchange_field ptr ofs v]
724+ becomes (in pseudo-code mixing C calls and OCaml expressions)
725+ [caml_atomic_exchange_field(ptr, ofs, v)] *)
726+ Lprim (prim, args, loc)
727+ | Loc ->
728+ (* the primitive application
729+ [%atomic_exchange_loc (ptr, ofs) v]
730+ becomes
731+ [caml_atomic_exchange_field(ptr, ofs, v)]
732+ and in the general case of a non-tuple expression <loc>
733+ [%atomic_exchange_loc <loc> v]
734+ becomes
735+ [let p = <loc> in
736+ caml_atomic_exchange_field(Field(p, 0), Field(p, 1), v)] *)
737+ let loc_arg, rest = split args in
738+ match loc_arg with
739+ | Lprim (Pmakeblock _ , [ptr ; ofs ], _argloc ) ->
740+ let args = ptr :: ofs :: rest in
741+ Lprim (prim, args, loc)
742+ | _ ->
743+ let varg = Ident. create_local " atomic_arg" in
744+ let ptr = Lprim (Pfield (0 , Pointer , Immutable ), [Lvar varg], loc) in
745+ let ofs =
746+ Lprim (Pfield (1 , Immediate , Immutable ), [Lvar varg], loc)
747+ in
748+ let args = ptr :: ofs :: rest in
749+ Llet (Strict , Pgenval , varg, loc_arg, Lprim (prim, args, loc))
750+
661751let caml_restore_raw_backtrace =
662752 Primitive. simple ~name: " caml_restore_raw_backtrace" ~arity: 2 ~alloc: false
663753
@@ -744,10 +834,13 @@ let lambda_of_prim prim_name prim loc args arg_exps =
744834 ap_inlined = Default_inline ;
745835 ap_specialised = Default_specialise ;
746836 }
837+ | Atomic (op , kind ), args ->
838+ lambda_of_atomic prim_name loc op kind args
747839 | (Raise _ | Raise_with_backtrace
748840 | Lazy_force | Loc _ | Primitive _ | Comparison _
749841 | Send | Send_self | Send_cache | Frame_pointers | Identity
750- | Apply | Revapply ), _ ->
842+ | Apply | Revapply
843+ ), _ ->
751844 raise(Error (to_location loc, Wrong_arity_builtin_primitive prim_name))
752845
753846let check_primitive_arity loc p =
@@ -766,6 +859,7 @@ let check_primitive_arity loc p =
766859 | Frame_pointers -> p.prim_arity = 0
767860 | Identity -> p.prim_arity = 1
768861 | Apply | Revapply -> p.prim_arity = 2
862+ | Atomic (op , kind ) -> p.prim_arity = atomic_arity op kind
769863 in
770864 if not ok then raise(Error (loc, Wrong_arity_builtin_primitive p.prim_name))
771865
@@ -838,7 +932,11 @@ let primitive_needs_event_after = function
838932 lambda_primitive_needs_event_after (comparison_primitive comp knd)
839933 | Lazy_force | Send | Send_self | Send_cache
840934 | Apply | Revapply -> true
841- | Raise _ | Raise_with_backtrace | Loc _ | Frame_pointers | Identity -> false
935+ | Raise _ | Raise_with_backtrace
936+ | Loc _
937+ | Frame_pointers | Identity
938+ | Atomic (_, _)
939+ -> false
842940
843941let transl_primitive_application loc p env ty path exp args arg_exps =
844942 let prim =
0 commit comments