@@ -192,7 +192,10 @@ module InlayHints = struct
192192end
193193
194194module Lens = struct
195- type t = { enable : bool [@ default true ] }
195+ type t =
196+ { enable : bool [@ default true ]
197+ ; for_nested_bindings : bool [@ default false ]
198+ }
196199 [@@ deriving_inline yojson ] [@@ yojson.allow_extra_fields]
197200
198201 let _ = fun (_ : t ) -> ()
@@ -202,6 +205,7 @@ module Lens = struct
202205 function
203206 | `Assoc field_yojsons as yojson ->
204207 let enable_field = ref Ppx_yojson_conv_lib.Option. None
208+ and for_nested_bindings_field = ref Ppx_yojson_conv_lib.Option. None
205209 and duplicates = ref []
206210 and extra = ref [] in
207211 let rec iter = function
@@ -214,6 +218,13 @@ module Lens = struct
214218 enable_field := Ppx_yojson_conv_lib.Option. Some fvalue
215219 | Ppx_yojson_conv_lib.Option. Some _ ->
216220 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)
217228 | _ -> () );
218229 iter tail
219230 | [] -> ()
@@ -233,11 +244,18 @@ module Lens = struct
233244 (Ppx_yojson_conv_lib. ( ! ) extra)
234245 yojson
235246 | [] ->
236- let enable_value = Ppx_yojson_conv_lib. ( ! ) enable_field in
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
237251 { enable =
238252 (match enable_value with
239253 | Ppx_yojson_conv_lib.Option. None -> true
240254 | 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)
241259 }))
242260 | _ as yojson ->
243261 Ppx_yojson_conv_lib.Yojson_conv_error. record_list_instead_atom _tp_loc yojson
@@ -248,8 +266,12 @@ module Lens = struct
248266
249267 let yojson_of_t =
250268 (function
251- | { enable = v_enable } ->
269+ | { enable = v_enable ; for_nested_bindings = v_for_nested_bindings } ->
252270 let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
271+ let bnds =
272+ let arg = yojson_of_bool v_for_nested_bindings in
273+ (" for_nested_bindings" , arg) :: bnds
274+ in
253275 let bnds =
254276 let arg = yojson_of_bool v_enable in
255277 (" enable" , arg) :: bnds
@@ -921,7 +943,7 @@ let _ = yojson_of_t
921943[@@@ end]
922944
923945let default =
924- { codelens = Some { enable = false }
946+ { codelens = Some { enable = false ; for_nested_bindings = false }
925947 ; extended_hover = Some { enable = false }
926948 ; standard_hover = Some { enable = true }
927949 ; inlay_hints =
0 commit comments