@@ -43,6 +43,7 @@ type abstract_type_constr = [
4343 | `Extension_constructor
4444 | `Floatarray
4545 | `Iarray
46+ | `Atomic_loc
4647]
4748type data_type_constr = [
4849 | `Bool
@@ -57,7 +58,7 @@ type type_constr = [
5758 | data_type_constr
5859]
5960
60- let all_type_constrs = [
61+ let all_type_constrs : type_constr list = [
6162 `Int ;
6263 `Char ;
6364 `String ;
@@ -78,6 +79,7 @@ let all_type_constrs = [
7879 `Extension_constructor ;
7980 `Floatarray ;
8081 `Iarray ;
82+ `Atomic_loc ;
8183]
8284
8385let ident_int = ident_create " int"
@@ -100,8 +102,9 @@ and ident_string = ident_create "string"
100102and ident_extension_constructor = ident_create " extension_constructor"
101103and ident_floatarray = ident_create " floatarray"
102104and ident_iarray = ident_create " iarray"
105+ and ident_atomic_loc = ident_create " atomic_loc"
103106
104- let ident_of_type_constr = function
107+ let ident_of_type_constr : type_constr -> Ident.t = function
105108 | `Int -> ident_int
106109 | `Char -> ident_char
107110 | `String -> ident_string
@@ -122,6 +125,7 @@ let ident_of_type_constr = function
122125 | `Extension_constructor -> ident_extension_constructor
123126 | `Floatarray -> ident_floatarray
124127 | `Iarray -> ident_iarray
128+ | `Atomic_loc -> ident_atomic_loc
125129
126130let path_int = Pident ident_int
127131and path_char = Pident ident_char
@@ -143,6 +147,7 @@ and path_string = Pident ident_string
143147and path_extension_constructor = Pident ident_extension_constructor
144148and path_floatarray = Pident ident_floatarray
145149and path_iarray = Pident ident_iarray
150+ and path_atomic_loc = Pident ident_atomic_loc
146151
147152let path_of_type_constr typ =
148153 Pident (ident_of_type_constr typ)
@@ -168,6 +173,7 @@ and type_string = tconstr path_string []
168173and type_extension_constructor = tconstr path_extension_constructor []
169174and type_floatarray = tconstr path_floatarray []
170175and type_iarray t = tconstr path_iarray [t]
176+ and type_atomic_loc t = tconstr path_atomic_loc [t]
171177
172178let find_type_constr =
173179 let all_predef_paths =
@@ -306,7 +312,9 @@ let decl_of_type_constr tconstr =
306312 | `Continuation ->
307313 let variance = Variance. (contravariant, covariant) in
308314 decl2 ~variance ()
309- | `Array ->
315+ | `Array
316+ | `Atomic_loc
317+ ->
310318 decl1 ~variance: Variance. full ()
311319 | `Iarray ->
312320 decl1 ~variance: Variance. covariant ()
0 commit comments