@@ -10,9 +10,10 @@ module File_kind = struct
10
10
; extension : string
11
11
; preprocess : (Loc .t * Action .t ) option
12
12
; format : (Loc .t * Action .t * string list ) option
13
+ ; merlin_reader : (Loc .t * string list ) option
13
14
}
14
15
15
- let encode { kind; extension; preprocess; format } =
16
+ let encode { kind; extension; preprocess; format; merlin_reader } =
16
17
let open Dune_lang.Encoder in
17
18
let kind =
18
19
string
@@ -28,16 +29,18 @@ module File_kind = struct
28
29
[ field " extension" string extension
29
30
; field_o " preprocess" Action. encode (Option. map ~f: snd preprocess)
30
31
; field_o " format" Action. encode (Option. map ~f: (fun (_ , x , _ ) -> x) format)
32
+ ; field_o " merlin_reader" (list string ) (Option. map ~f: snd merlin_reader)
31
33
])
32
34
;;
33
35
34
- let to_dyn { kind; extension; preprocess; format } =
36
+ let to_dyn { kind; extension; preprocess; format; merlin_reader } =
35
37
let open Dyn in
36
38
record
37
39
[ " kind" , Ml_kind. to_dyn kind
38
40
; " extension" , string extension
39
41
; " preprocess" , option (fun (_ , x ) -> Action. to_dyn x) preprocess
40
42
; " format" , option (fun (_ , x , y ) -> pair Action. to_dyn (list string ) (x, y)) format
43
+ ; " merlin_reader" , option (fun (_ , x ) -> list string x) merlin_reader
41
44
]
42
45
;;
43
46
end
@@ -78,13 +81,17 @@ let decode =
78
81
field_o
79
82
" format"
80
83
(map ~f: (fun (loc , x ) -> loc, x, [] ) (located Action. decode_dune_file))
84
+ and + merlin_reader =
85
+ field_o
86
+ " merlin_reader"
87
+ (Dune_lang.Syntax. since Stanza. syntax (3 , 11 ) >>> located (repeat1 string ))
81
88
and + syntax_ver = Syntax. get_exn Stanza. syntax in
82
89
let ver = 3 , 9 in
83
90
if syntax_ver < ver && Option. is_some (String. index_from extension 1 '.' )
84
91
then (
85
92
let what = " the possibility of defining extensions containing periods" in
86
93
Syntax.Error. since loc Stanza. syntax ver ~what );
87
- { File_kind. kind; extension; preprocess; format }
94
+ { File_kind. kind; extension; preprocess; format; merlin_reader }
88
95
in
89
96
fields
90
97
(let + name = field " name" string
@@ -130,6 +137,13 @@ let format { file_kinds; _ } ml_kind =
130
137
x.format
131
138
;;
132
139
140
+ let merlin_reader { file_kinds; _ } ml_kind =
141
+ let open Option.O in
142
+ let * x = Ml_kind.Dict. get file_kinds ml_kind in
143
+ let + _, merlin_reader = x.merlin_reader in
144
+ x.extension, merlin_reader
145
+ ;;
146
+
133
147
let ocaml =
134
148
let format kind =
135
149
let flag_of_kind = function
@@ -154,6 +168,7 @@ let ocaml =
154
168
( Loc. none
155
169
, format kind
156
170
, [ " .ocamlformat" ; " .ocamlformat-ignore" ; " .ocamlformat-enable" ] )
171
+ ; merlin_reader = None
157
172
}
158
173
in
159
174
let intf = Some (file_kind Ml_kind. Intf " .mli" ) in
@@ -179,6 +194,7 @@ let reason =
179
194
; extension
180
195
; preprocess = Some (Loc. none, preprocess)
181
196
; format = Some (Loc. none, format, [] )
197
+ ; merlin_reader = None
182
198
}
183
199
in
184
200
let intf = Some (file_kind Ml_kind. Intf " .rei" ) in
@@ -207,6 +223,7 @@ let rescript =
207
223
; extension
208
224
; preprocess = Some (Loc. none, preprocess)
209
225
; format = Some (Loc. none, format, [] )
226
+ ; merlin_reader = None
210
227
}
211
228
in
212
229
let intf = Some (file_kind Ml_kind. Intf " .resi" ) in
@@ -227,43 +244,61 @@ module DB = struct
227
244
type t =
228
245
{ by_name : dialect String.Map .t
229
246
; by_extension : dialect String.Map .t
230
- ; mutable extensions_for_merlin : string option Ml_kind.Dict .t list option
247
+ ; for_merlin : for_merlin Lazy .t
248
+ }
249
+
250
+ and for_merlin =
251
+ { extensions : string option Ml_kind.Dict .t list
252
+ ; readers : string list String.Map .t
231
253
}
232
254
233
255
let fold { by_name; _ } = String.Map. fold by_name
234
256
235
257
let empty =
236
258
{ by_name = String.Map. empty
237
259
; by_extension = String.Map. empty
238
- ; extensions_for_merlin = None
260
+ ; for_merlin = lazy { extensions = [] ; readers = String.Map. empty }
239
261
}
240
262
;;
241
263
242
- let set_extensions_for_merlin t =
243
- let v =
244
- fold t ~init: [] ~f: (fun d s ->
245
- let impl = extension d Ml_kind. Impl in
246
- let intf = extension d Ml_kind. Intf in
247
- if (* Only include dialects with no preprocessing and skip default file
248
- extensions *)
249
- preprocess d Ml_kind. Impl <> None
250
- || preprocess d Ml_kind. Intf <> None
251
- || (impl = extension ocaml Ml_kind. Impl && intf = extension ocaml Ml_kind. Intf )
252
- then s
253
- else { Ml_kind.Dict. impl; intf } :: s)
264
+ let compute_for_merlin by_name =
265
+ let extensions =
266
+ String.Map. fold by_name ~init: [] ~f: (fun d s ->
267
+ let ext_for kind =
268
+ let ext = extension d kind in
269
+ if ext = extension ocaml kind
270
+ then (* this is standard dialect, exclude *) None
271
+ else if merlin_reader d kind <> None
272
+ then (* we have merlin reader defined, it will handle these files *) ext
273
+ else if preprocess d kind <> None
274
+ then (* we have preprocessor defined *) None
275
+ else ext
276
+ in
277
+ let impl = ext_for Ml_kind. Impl in
278
+ let intf = ext_for Ml_kind. Intf in
279
+ match impl, intf with
280
+ | None , None -> s
281
+ | _ -> { Ml_kind.Dict. impl; intf } :: s)
254
282
|> List. sort ~compare: (Ml_kind.Dict. compare (Option. compare String. compare))
255
283
in
256
- t.extensions_for_merlin < - Some v;
257
- v
284
+ let readers =
285
+ String.Map. fold by_name ~init: String.Map. empty ~f: (fun d s ->
286
+ let add kind s =
287
+ match merlin_reader d kind with
288
+ | None -> s
289
+ | Some (extension , reader ) ->
290
+ (* Ok to use [add_exn] here as we are validating below in [add]
291
+ function that we have extensions registered only once. *)
292
+ String.Map. add_exn s extension reader
293
+ in
294
+ s |> add Ml_kind. Impl |> add Ml_kind. Intf )
295
+ in
296
+ { extensions; readers }
258
297
;;
259
298
260
- let extensions_for_merlin t =
261
- match t.extensions_for_merlin with
262
- | Some s -> s
263
- | None -> set_extensions_for_merlin t
264
- ;;
299
+ let for_merlin t = Lazy. force t.for_merlin
265
300
266
- let add { by_name; by_extension; extensions_for_merlin = _ } ~loc dialect =
301
+ let add { by_name; by_extension; for_merlin = _ } ~loc dialect =
267
302
let by_name =
268
303
match String.Map. add by_name dialect.name dialect with
269
304
| Ok by_name -> by_name
@@ -287,7 +322,7 @@ module DB = struct
287
322
let by_extension =
288
323
add_ext (add_ext by_extension dialect.file_kinds.intf) dialect.file_kinds.impl
289
324
in
290
- { by_name; by_extension; extensions_for_merlin = None }
325
+ { by_name; by_extension; for_merlin = lazy (compute_for_merlin by_name) }
291
326
;;
292
327
293
328
let of_list dialects = List. fold_left ~f: (add ~loc: Loc. none) ~init: empty dialects
0 commit comments