@@ -43,6 +43,7 @@ type abstract_type_constr = [
43
43
| `Extension_constructor
44
44
| `Floatarray
45
45
| `Iarray
46
+ | `Atomic_loc
46
47
]
47
48
type data_type_constr = [
48
49
| `Bool
@@ -57,7 +58,7 @@ type type_constr = [
57
58
| data_type_constr
58
59
]
59
60
60
- let all_type_constrs = [
61
+ let all_type_constrs : type_constr list = [
61
62
`Int ;
62
63
`Char ;
63
64
`String ;
@@ -78,6 +79,7 @@ let all_type_constrs = [
78
79
`Extension_constructor ;
79
80
`Floatarray ;
80
81
`Iarray ;
82
+ `Atomic_loc ;
81
83
]
82
84
83
85
let ident_int = ident_create " int"
@@ -100,8 +102,9 @@ and ident_string = ident_create "string"
100
102
and ident_extension_constructor = ident_create " extension_constructor"
101
103
and ident_floatarray = ident_create " floatarray"
102
104
and ident_iarray = ident_create " iarray"
105
+ and ident_atomic_loc = ident_create " atomic_loc"
103
106
104
- let ident_of_type_constr = function
107
+ let ident_of_type_constr : type_constr -> Ident.t = function
105
108
| `Int -> ident_int
106
109
| `Char -> ident_char
107
110
| `String -> ident_string
@@ -122,6 +125,7 @@ let ident_of_type_constr = function
122
125
| `Extension_constructor -> ident_extension_constructor
123
126
| `Floatarray -> ident_floatarray
124
127
| `Iarray -> ident_iarray
128
+ | `Atomic_loc -> ident_atomic_loc
125
129
126
130
let path_int = Pident ident_int
127
131
and path_char = Pident ident_char
@@ -143,6 +147,7 @@ and path_string = Pident ident_string
143
147
and path_extension_constructor = Pident ident_extension_constructor
144
148
and path_floatarray = Pident ident_floatarray
145
149
and path_iarray = Pident ident_iarray
150
+ and path_atomic_loc = Pident ident_atomic_loc
146
151
147
152
let path_of_type_constr typ =
148
153
Pident (ident_of_type_constr typ)
@@ -168,6 +173,7 @@ and type_string = tconstr path_string []
168
173
and type_extension_constructor = tconstr path_extension_constructor []
169
174
and type_floatarray = tconstr path_floatarray []
170
175
and type_iarray t = tconstr path_iarray [t]
176
+ and type_atomic_loc t = tconstr path_atomic_loc [t]
171
177
172
178
let find_type_constr =
173
179
let all_predef_paths =
@@ -306,7 +312,9 @@ let decl_of_type_constr tconstr =
306
312
| `Continuation ->
307
313
let variance = Variance. (contravariant, covariant) in
308
314
decl2 ~variance ()
309
- | `Array ->
315
+ | `Array
316
+ | `Atomic_loc
317
+ ->
310
318
decl1 ~variance: Variance. full ()
311
319
| `Iarray ->
312
320
decl1 ~variance: Variance. covariant ()
0 commit comments