@@ -76,6 +76,17 @@ type loc_kind =
7676 | Loc_POS
7777 | Loc_FUNCTION
7878
79+ type atomic_kind =
80+ | Ref (* operation on an atomic reference (takes only a pointer) *)
81+ | Field (* operation on an atomic field (takes a pointer and an offset) *)
82+ | Loc (* operation on a first-class field (takes a (pointer, offset) pair *)
83+
84+ type atomic_op =
85+ | Load
86+ | Exchange
87+ | Cas
88+ | Faa
89+
7990type prim =
8091 | Primitive of Lambda .primitive * int
8192 | External of Primitive .description
@@ -91,6 +102,7 @@ type prim =
91102 | Identity
92103 | Apply
93104 | Revapply
105+ | Atomic of atomic_op * atomic_kind
94106
95107let used_primitives = Hashtbl. create 7
96108let add_used_primitive loc env path =
@@ -113,12 +125,11 @@ let prim_sys_argv =
113125 Primitive. simple ~name: " caml_sys_argv" ~arity: 1 ~alloc: true
114126
115127let prim_atomic_exchange =
116- Primitive. simple ~name: " caml_atomic_exchange " ~arity: 2 ~alloc: false
128+ Primitive. simple ~name: " caml_atomic_exchange_field " ~arity: 3 ~alloc: false
117129let prim_atomic_cas =
118- Primitive. simple ~name: " caml_atomic_cas " ~arity: 3 ~alloc: false
130+ Primitive. simple ~name: " caml_atomic_cas_field " ~arity: 4 ~alloc: false
119131let prim_atomic_fetch_add =
120- Primitive. simple ~name: " caml_atomic_fetch_add" ~arity: 2 ~alloc: false
121-
132+ Primitive. simple ~name: " caml_atomic_fetch_add_field" ~arity: 3 ~alloc: false
122133
123134let primitives_table =
124135 create_hashtable 57 [
@@ -371,10 +382,18 @@ let primitives_table =
371382 " %greaterequal" , Comparison (Greater_equal , Compare_generic );
372383 " %greaterthan" , Comparison (Greater_than , Compare_generic );
373384 " %compare" , Comparison (Compare , Compare_generic );
374- " %atomic_load" , Primitive (Patomic_load , 1 );
375- " %atomic_exchange" , External prim_atomic_exchange;
376- " %atomic_cas" , External prim_atomic_cas;
377- " %atomic_fetch_add" , External prim_atomic_fetch_add;
385+ " %atomic_load" , Atomic (Load , Ref );
386+ " %atomic_exchange" , Atomic (Exchange , Ref );
387+ " %atomic_cas" , Atomic (Cas , Ref );
388+ " %atomic_fetch_add" , Atomic (Faa , Ref );
389+ " %atomic_load_field" , Atomic (Load , Field );
390+ " %atomic_exchange_field" , Atomic (Exchange , Field );
391+ " %atomic_cas_field" , Atomic (Cas , Field );
392+ " %atomic_fetch_add_field" , Atomic (Faa , Field );
393+ " %atomic_load_loc" , Atomic (Load , Loc );
394+ " %atomic_exchange_loc" , Atomic (Exchange , Loc );
395+ " %atomic_cas_loc" , Atomic (Cas , Loc );
396+ " %atomic_fetch_add_loc" , Atomic (Faa , Loc );
378397 " %runstack" , Primitive (Prunstack , 3 );
379398 " %reperform" , Primitive (Preperform , 3 );
380399 " %perform" , Primitive (Pperform , 1 );
@@ -657,6 +676,79 @@ let lambda_of_loc kind sloc =
657676 let scope_name = Debuginfo.Scoped_location. string_of_scoped_location sloc in
658677 Lconst (Const_immstring scope_name)
659678
679+ let atomic_arity op (kind : atomic_kind ) =
680+ let arity_of_op =
681+ match op with
682+ | Load -> 1
683+ | Exchange -> 2
684+ | Cas -> 3
685+ | Faa -> 2
686+ in
687+ let extra_kind_arity =
688+ match kind with
689+ | Ref | Loc -> 0
690+ | Field -> 1
691+ in
692+ arity_of_op + extra_kind_arity
693+
694+ let lambda_of_atomic prim_name loc op (kind : atomic_kind ) args =
695+ if List. length args <> atomic_arity op kind then
696+ raise (Error (to_location loc, Wrong_arity_builtin_primitive prim_name)) ;
697+ let split = function
698+ | [] ->
699+ (* split is only called when [arity >= 1] *)
700+ assert false
701+ | first :: rest ->
702+ first, rest
703+ in
704+ let prim =
705+ match op with
706+ | Load -> Patomic_load
707+ | Exchange -> Pccall prim_atomic_exchange
708+ | Cas -> Pccall prim_atomic_cas
709+ | Faa -> Pccall prim_atomic_fetch_add
710+ in
711+ match kind with
712+ | Ref ->
713+ (* the primitive application
714+ [Lprim(%atomic_exchange, [ref; v])]
715+ becomes
716+ [Lprim(caml_atomic_exchange_field, [ref; 0; v])]
717+ *)
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+ [Lprim(%atomic_exchange_field, [ptr; ofs; v])]
724+ becomes
725+ [Lprim(caml_atomic_exchange_field, [ptr; ofs; v])] *)
726+ Lprim (prim, args, loc)
727+ | Loc ->
728+ (* the primitive application
729+ [Lprim(%atomic_exchange_loc, [(ptr, ofs); v])]
730+ becomes
731+ [Lprim(caml_atomic_exchange_field, [ptr; ofs; v])]
732+ and in the general case of a non-tuple expression <loc>
733+ [Lprim(%atomic_exchange_loc, [loc; v])]
734+ becomes
735+ [Llet(p, loc,
736+ Lprim(caml_atomic_exchange_field, [Field(p, 0); Field(p, 1); v]))]
737+ *)
738+ let loc_arg, rest = split args in
739+ match loc_arg with
740+ | Lprim (Pmakeblock _ , [ptr ; ofs ], _argloc ) ->
741+ let args = ptr :: ofs :: rest in
742+ Lprim (prim, args, loc)
743+ | _ ->
744+ let varg = Ident. create_local " atomic_arg" in
745+ let ptr = Lprim (Pfield (0 , Pointer , Immutable ), [Lvar varg], loc) in
746+ let ofs =
747+ Lprim (Pfield (1 , Immediate , Immutable ), [Lvar varg], loc)
748+ in
749+ let args = ptr :: ofs :: rest in
750+ Llet (Strict , Pgenval , varg, loc_arg, Lprim (prim, args, loc))
751+
660752let caml_restore_raw_backtrace =
661753 Primitive. simple ~name: " caml_restore_raw_backtrace" ~arity: 2 ~alloc: false
662754
@@ -743,10 +835,13 @@ let lambda_of_prim prim_name prim loc args arg_exps =
743835 ap_inlined = Default_inline ;
744836 ap_specialised = Default_specialise ;
745837 }
838+ | Atomic (op , kind ), args ->
839+ lambda_of_atomic prim_name loc op kind args
746840 | (Raise _ | Raise_with_backtrace
747841 | Lazy_force | Loc _ | Primitive _ | Comparison _
748842 | Send | Send_self | Send_cache | Frame_pointers | Identity
749- | Apply | Revapply ), _ ->
843+ | Apply | Revapply
844+ ), _ ->
750845 raise(Error (to_location loc, Wrong_arity_builtin_primitive prim_name))
751846
752847let check_primitive_arity loc p =
@@ -765,6 +860,7 @@ let check_primitive_arity loc p =
765860 | Frame_pointers -> p.prim_arity = 0
766861 | Identity -> p.prim_arity = 1
767862 | Apply | Revapply -> p.prim_arity = 2
863+ | Atomic (op , kind ) -> p.prim_arity = atomic_arity op kind
768864 in
769865 if not ok then raise(Error (loc, Wrong_arity_builtin_primitive p.prim_name))
770866
@@ -838,7 +934,11 @@ let primitive_needs_event_after = function
838934 lambda_primitive_needs_event_after (comparison_primitive comp knd)
839935 | Lazy_force | Send | Send_self | Send_cache
840936 | Apply | Revapply -> true
841- | Raise _ | Raise_with_backtrace | Loc _ | Frame_pointers | Identity -> false
937+ | Raise _ | Raise_with_backtrace
938+ | Loc _
939+ | Frame_pointers | Identity
940+ | Atomic (_, _)
941+ -> false
842942
843943let transl_primitive_application loc p env ty path exp args arg_exps =
844944 let prim =
0 commit comments