@@ -194,90 +194,89 @@ end
194194module Lens = struct
195195 type t =
196196 { enable : bool [@ default true ]
197- ; for_nested_bindings : bool [@ default false ]
197+ ; for_nested_bindings : bool [@ key "forNestedBindings" ] [ @ default false ]
198198 }
199199 [@@ deriving_inline yojson ] [@@ yojson.allow_extra_fields]
200200
201201 let _ = fun (_ : t ) -> ()
202202
203- let t_of_yojson =
204- (let _tp_loc = " ocaml-lsp-server/src/config_data.ml.Lens.t" in
205- function
206- | `Assoc field_yojsons as yojson ->
203+
204+ let t_of_yojson =
205+ (let _tp_loc = " ocaml-lsp-server/src/config_data.ml.Lens.t" in
206+ function
207+ | `Assoc field_yojsons as yojson ->
207208 let enable_field = ref Ppx_yojson_conv_lib.Option. None
208209 and for_nested_bindings_field = ref Ppx_yojson_conv_lib.Option. None
209210 and duplicates = ref []
210211 and extra = ref [] in
211- let rec iter = function
212- | (field_name , _field_yojson ) :: tail ->
213- (match field_name with
214- | "enable" ->
215- (match Ppx_yojson_conv_lib. ( ! ) enable_field with
216- | Ppx_yojson_conv_lib.Option. None ->
217- let fvalue = bool_of_yojson _field_yojson in
218- enable_field := Ppx_yojson_conv_lib.Option. Some fvalue
219- | Ppx_yojson_conv_lib.Option. Some _ ->
220- duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
221- | "for_nested_bindings" ->
222- (match Ppx_yojson_conv_lib. ( ! ) for_nested_bindings_field with
223- | Ppx_yojson_conv_lib.Option. None ->
224- let fvalue = bool_of_yojson _field_yojson in
225- for_nested_bindings_field := Ppx_yojson_conv_lib.Option. Some fvalue
226- | Ppx_yojson_conv_lib.Option. Some _ ->
227- duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
228- | _ -> () );
229- iter tail
230- | [] -> ()
231- in
232- iter field_yojsons;
233- (match Ppx_yojson_conv_lib. ( ! ) duplicates with
234- | _ :: _ ->
235- Ppx_yojson_conv_lib.Yojson_conv_error. record_duplicate_fields
236- _tp_loc
237- (Ppx_yojson_conv_lib. ( ! ) duplicates)
238- yojson
239- | [] ->
240- (match Ppx_yojson_conv_lib. ( ! ) extra with
241- | _ :: _ ->
242- Ppx_yojson_conv_lib.Yojson_conv_error. record_extra_fields
243- _tp_loc
244- (Ppx_yojson_conv_lib. ( ! ) extra)
245- yojson
246- | [] ->
247- let enable_value, for_nested_bindings_value =
248- ( Ppx_yojson_conv_lib. ( ! ) enable_field
249- , Ppx_yojson_conv_lib. ( ! ) for_nested_bindings_field )
250- in
251- { enable =
252- (match enable_value with
253- | Ppx_yojson_conv_lib.Option. None -> true
254- | Ppx_yojson_conv_lib.Option. Some v -> v)
255- ; for_nested_bindings =
256- (match for_nested_bindings_value with
257- | Ppx_yojson_conv_lib.Option. None -> false
258- | Ppx_yojson_conv_lib.Option. Some v -> v)
259- }))
260- | _ as yojson ->
261- Ppx_yojson_conv_lib.Yojson_conv_error. record_list_instead_atom _tp_loc yojson
262- : Ppx_yojson_conv_lib.Yojson.Safe. t -> t)
212+ let rec iter =
213+ function
214+ | (field_name , _field_yojson )::tail ->
215+ ((match field_name with
216+ | "enable" ->
217+ (match Ppx_yojson_conv_lib. (! ) enable_field with
218+ | Ppx_yojson_conv_lib.Option. None ->
219+ let fvalue = bool_of_yojson _field_yojson in
220+ enable_field :=
221+ (Ppx_yojson_conv_lib.Option. Some fvalue)
222+ | Ppx_yojson_conv_lib.Option. Some _ ->
223+ duplicates := (field_name ::
224+ (Ppx_yojson_conv_lib. (! ) duplicates)))
225+ | "forNestedBindings" ->
226+ (match Ppx_yojson_conv_lib. (! ) for_nested_bindings_field
227+ with
228+ | Ppx_yojson_conv_lib.Option. None ->
229+ let fvalue = bool_of_yojson _field_yojson in
230+ for_nested_bindings_field :=
231+ (Ppx_yojson_conv_lib.Option. Some fvalue)
232+ | Ppx_yojson_conv_lib.Option. Some _ ->
233+ duplicates := (field_name ::
234+ (Ppx_yojson_conv_lib. (! ) duplicates)))
235+ | _ -> () );
236+ iter tail)
237+ | [] -> () in
238+ (iter field_yojsons;
239+ (match Ppx_yojson_conv_lib. (! ) duplicates with
240+ | _ ::_ ->
241+ Ppx_yojson_conv_lib.Yojson_conv_error. record_duplicate_fields
242+ _tp_loc (Ppx_yojson_conv_lib. (! ) duplicates) yojson
243+ | [] ->
244+ (match Ppx_yojson_conv_lib. (! ) extra with
245+ | _ ::_ ->
246+ Ppx_yojson_conv_lib.Yojson_conv_error. record_extra_fields
247+ _tp_loc (Ppx_yojson_conv_lib. (! ) extra) yojson
248+ | [] ->
249+ let (enable_value, for_nested_bindings_value) =
250+ ((Ppx_yojson_conv_lib. (! ) enable_field),
251+ (Ppx_yojson_conv_lib. (! ) for_nested_bindings_field)) in
252+ {
253+ enable =
254+ ((match enable_value with
255+ | Ppx_yojson_conv_lib.Option. None -> true
256+ | Ppx_yojson_conv_lib.Option. Some v -> v));
257+ for_nested_bindings =
258+ ((match for_nested_bindings_value with
259+ | Ppx_yojson_conv_lib.Option. None -> false
260+ | Ppx_yojson_conv_lib.Option. Some v -> v))
261+ })))
262+ | _ as yojson ->
263+ Ppx_yojson_conv_lib.Yojson_conv_error. record_list_instead_atom _tp_loc
264+ yojson : Ppx_yojson_conv_lib.Yojson.Safe. t -> t)
263265 ;;
264266
265267 let _ = t_of_yojson
266268
267- let yojson_of_t =
268- (function
269- | { enable = v_enable ; for_nested_bindings = v_for_nested_bindings } ->
269+
270+ let yojson_of_t =
271+ (function
272+ | { enable = v_enable ; for_nested_bindings = v_for_nested_bindings } ->
270273 let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
271274 let bnds =
272275 let arg = yojson_of_bool v_for_nested_bindings in
273- (" for_nested_bindings" , arg) :: bnds
274- in
276+ (" forNestedBindings" , arg) :: bnds in
275277 let bnds =
276- let arg = yojson_of_bool v_enable in
277- (" enable" , arg) :: bnds
278- in
279- `Assoc bnds
280- : t -> Ppx_yojson_conv_lib.Yojson.Safe. t)
278+ let arg = yojson_of_bool v_enable in (" enable" , arg) :: bnds in
279+ `Assoc bnds : t -> Ppx_yojson_conv_lib.Yojson.Safe. t)
281280 ;;
282281
283282 let _ = yojson_of_t
0 commit comments