@@ -315,6 +315,80 @@ module DuneDiagnostics = struct
315
315
[@@@ end]
316
316
end
317
317
318
+ module SyntaxDocumentation = struct
319
+ type t = { enable : bool [@ default false ] }
320
+ [@@ deriving_inline yojson ] [@@ yojson.allow_extra_fields]
321
+
322
+ let _ = fun (_ : t ) -> ()
323
+
324
+ let t_of_yojson =
325
+ (let _tp_loc =
326
+ " ocaml-lsp-server/src/config_data.ml.SyntaxDocumentation.t"
327
+ in
328
+ function
329
+ | `Assoc field_yojsons as yojson -> (
330
+ let enable_field = ref Ppx_yojson_conv_lib.Option. None
331
+ and duplicates = ref []
332
+ and extra = ref [] in
333
+ let rec iter = function
334
+ | (field_name , _field_yojson ) :: tail ->
335
+ (match field_name with
336
+ | "enable" -> (
337
+ match Ppx_yojson_conv_lib. ( ! ) enable_field with
338
+ | Ppx_yojson_conv_lib.Option. None ->
339
+ let fvalue = bool_of_yojson _field_yojson in
340
+ enable_field := Ppx_yojson_conv_lib.Option. Some fvalue
341
+ | Ppx_yojson_conv_lib.Option. Some _ ->
342
+ duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
343
+ | _ -> () );
344
+ iter tail
345
+ | [] -> ()
346
+ in
347
+ iter field_yojsons;
348
+ match Ppx_yojson_conv_lib. ( ! ) duplicates with
349
+ | _ :: _ ->
350
+ Ppx_yojson_conv_lib.Yojson_conv_error. record_duplicate_fields
351
+ _tp_loc
352
+ (Ppx_yojson_conv_lib. ( ! ) duplicates)
353
+ yojson
354
+ | [] -> (
355
+ match Ppx_yojson_conv_lib. ( ! ) extra with
356
+ | _ :: _ ->
357
+ Ppx_yojson_conv_lib.Yojson_conv_error. record_extra_fields
358
+ _tp_loc
359
+ (Ppx_yojson_conv_lib. ( ! ) extra)
360
+ yojson
361
+ | [] ->
362
+ let enable_value = Ppx_yojson_conv_lib. ( ! ) enable_field in
363
+ { enable =
364
+ (match enable_value with
365
+ | Ppx_yojson_conv_lib.Option. None -> false
366
+ | Ppx_yojson_conv_lib.Option. Some v -> v)
367
+ }))
368
+ | _ as yojson ->
369
+ Ppx_yojson_conv_lib.Yojson_conv_error. record_list_instead_atom
370
+ _tp_loc
371
+ yojson
372
+ : Ppx_yojson_conv_lib.Yojson.Safe. t -> t)
373
+
374
+ let _ = t_of_yojson
375
+
376
+ let yojson_of_t =
377
+ (function
378
+ | { enable = v_enable } ->
379
+ let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
380
+ let bnds =
381
+ let arg = yojson_of_bool v_enable in
382
+ (" enable" , arg) :: bnds
383
+ in
384
+ `Assoc bnds
385
+ : t -> Ppx_yojson_conv_lib.Yojson.Safe. t)
386
+
387
+ let _ = yojson_of_t
388
+
389
+ [@@@ end]
390
+ end
391
+
318
392
type t =
319
393
{ codelens : Lens .t Json.Nullable_option .t
320
394
[@ default None ] [@ yojson_drop_default ( = )]
@@ -324,6 +398,10 @@ type t =
324
398
[@ key "inlayHints" ] [@ default None ] [@ yojson_drop_default ( = )]
325
399
; dune_diagnostics : DuneDiagnostics .t Json.Nullable_option .t
326
400
[@ key "duneDiagnostics" ] [@ default None ] [@ yojson_drop_default ( = )]
401
+ ; syntax_documentation : SyntaxDocumentation .t Json.Nullable_option .t
402
+ [@ key "syntaxDocumentation" ]
403
+ [@ default None ]
404
+ [@ yojson_drop_default ( = )]
327
405
}
328
406
[@@ deriving_inline yojson ] [@@ yojson.allow_extra_fields]
329
407
@@ -337,6 +415,7 @@ let t_of_yojson =
337
415
and extended_hover_field = ref Ppx_yojson_conv_lib.Option. None
338
416
and inlay_hints_field = ref Ppx_yojson_conv_lib.Option. None
339
417
and dune_diagnostics_field = ref Ppx_yojson_conv_lib.Option. None
418
+ and syntax_documentation_field = ref Ppx_yojson_conv_lib.Option. None
340
419
and duplicates = ref []
341
420
and extra = ref [] in
342
421
let rec iter = function
@@ -362,6 +441,17 @@ let t_of_yojson =
362
441
extended_hover_field := Ppx_yojson_conv_lib.Option. Some fvalue
363
442
| Ppx_yojson_conv_lib.Option. Some _ ->
364
443
duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
444
+ | "syntaxDocumentation" -> (
445
+ match Ppx_yojson_conv_lib. ( ! ) syntax_documentation_field with
446
+ | Ppx_yojson_conv_lib.Option. None ->
447
+ let fvalue =
448
+ Json.Nullable_option. t_of_yojson
449
+ SyntaxDocumentation. t_of_yojson
450
+ _field_yojson
451
+ in
452
+ syntax_documentation_field := Ppx_yojson_conv_lib.Option. Some fvalue
453
+ | Ppx_yojson_conv_lib.Option. Some _ ->
454
+ duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
365
455
| "inlayHints" -> (
366
456
match Ppx_yojson_conv_lib. ( ! ) inlay_hints_field with
367
457
| Ppx_yojson_conv_lib.Option. None ->
@@ -384,7 +474,7 @@ let t_of_yojson =
384
474
dune_diagnostics_field := Ppx_yojson_conv_lib.Option. Some fvalue
385
475
| Ppx_yojson_conv_lib.Option. Some _ ->
386
476
duplicates := field_name :: Ppx_yojson_conv_lib. ( ! ) duplicates)
387
- | _ -> () );
477
+ | _ -> () );
388
478
iter tail
389
479
| [] -> ()
390
480
in
@@ -406,11 +496,13 @@ let t_of_yojson =
406
496
let ( codelens_value
407
497
, extended_hover_value
408
498
, inlay_hints_value
409
- , dune_diagnostics_value ) =
499
+ , dune_diagnostics_value
500
+ , syntax_documentation_value ) =
410
501
( Ppx_yojson_conv_lib. ( ! ) codelens_field
411
502
, Ppx_yojson_conv_lib. ( ! ) extended_hover_field
412
503
, Ppx_yojson_conv_lib. ( ! ) inlay_hints_field
413
- , Ppx_yojson_conv_lib. ( ! ) dune_diagnostics_field )
504
+ , Ppx_yojson_conv_lib. ( ! ) dune_diagnostics_field
505
+ , Ppx_yojson_conv_lib. ( ! ) syntax_documentation_field )
414
506
in
415
507
{ codelens =
416
508
(match codelens_value with
@@ -428,6 +520,10 @@ let t_of_yojson =
428
520
(match dune_diagnostics_value with
429
521
| Ppx_yojson_conv_lib.Option. None -> None
430
522
| Ppx_yojson_conv_lib.Option. Some v -> v)
523
+ ; syntax_documentation =
524
+ (match syntax_documentation_value with
525
+ | Ppx_yojson_conv_lib.Option. None -> None
526
+ | Ppx_yojson_conv_lib.Option. Some v -> v)
431
527
}))
432
528
| _ as yojson ->
433
529
Ppx_yojson_conv_lib.Yojson_conv_error. record_list_instead_atom
@@ -443,7 +539,8 @@ let yojson_of_t =
443
539
; extended_hover = v_extended_hover
444
540
; inlay_hints = v_inlay_hints
445
541
; dune_diagnostics = v_dune_diagnostics
446
- } ->
542
+ ; syntax_documentation =
543
+ v_syntax_documentation } ->
447
544
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
448
545
let bnds =
449
546
if None = v_dune_diagnostics then bnds
@@ -465,6 +562,16 @@ let yojson_of_t =
465
562
let bnd = (" inlayHints" , arg) in
466
563
bnd :: bnds
467
564
in
565
+ let bnds =
566
+ if None = v_syntax_documentation then bnds
567
+ else
568
+ let arg =
569
+ (Json.Nullable_option. yojson_of_t SyntaxDocumentation. yojson_of_t)
570
+ v_syntax_documentation
571
+ in
572
+ let bnd = (" syntaxDocumentation" , arg) in
573
+ bnd :: bnds
574
+ in
468
575
let bnds =
469
576
if None = v_extended_hover then bnds
470
577
else
@@ -497,4 +604,5 @@ let default =
497
604
; inlay_hints =
498
605
Some { hint_pattern_variables = false ; hint_let_bindings = false }
499
606
; dune_diagnostics = Some { enable = true }
607
+ ; syntax_documentation = Some { enable = false }
500
608
}
0 commit comments