@@ -6,17 +6,20 @@ module Kind = struct
6
6
| Intf
7
7
| Impl
8
8
9
- let of_fname p =
9
+ let of_fname_opt p =
10
10
match Filename. extension p with
11
- | ".ml" | ".eliom" | ".re" -> Impl
12
- | ".mli" | ".eliomi" | ".rei" -> Intf
13
- | ext ->
14
- Jsonrpc.Response.Error. raise
15
- (Jsonrpc.Response.Error. make
16
- ~code: InvalidRequest
17
- ~message: " unsupported file extension"
18
- ~data: (`Assoc [ (" extension" , `String ext) ])
19
- () )
11
+ | ".ml" | ".eliom" | ".re" -> Some Impl
12
+ | ".mli" | ".eliomi" | ".rei" -> Some Intf
13
+ | _ -> None
14
+
15
+ let unsupported uri =
16
+ let p = Uri. to_path uri in
17
+ Jsonrpc.Response.Error. raise
18
+ (Jsonrpc.Response.Error. make
19
+ ~code: InvalidRequest
20
+ ~message: " unsupported file extension"
21
+ ~data: (`Assoc [ (" extension" , `String (Filename. extension p)) ])
22
+ () )
20
23
end
21
24
22
25
module Syntax = struct
@@ -178,6 +181,7 @@ type merlin =
178
181
; timer : Lev_fiber.Timer.Wheel .task
179
182
; merlin_config : Merlin_config .t
180
183
; syntax : Syntax .t
184
+ ; kind : Kind .t option
181
185
}
182
186
183
187
type t =
@@ -204,12 +208,24 @@ let source t = Msource.make (text t)
204
208
let version t = Text_document. version (tdoc t)
205
209
206
210
let make_merlin wheel merlin_db pipeline tdoc syntax =
207
- let + timer = Lev_fiber.Timer.Wheel. task wheel in
208
- let merlin_config =
209
- let uri = Text_document. documentUri tdoc in
210
- Merlin_config.DB. get merlin_db uri
211
+ let * timer = Lev_fiber.Timer.Wheel. task wheel in
212
+ let uri = Text_document. documentUri tdoc in
213
+ let path = Uri. to_path uri in
214
+ let merlin_config = Merlin_config.DB. get merlin_db uri in
215
+ let * mconfig = Merlin_config. config merlin_config in
216
+ let kind =
217
+ let ext = Filename. extension path in
218
+ List. find_map mconfig.merlin.suffixes ~f: (fun (impl , intf ) ->
219
+ if String. equal ext intf then Some Kind. Intf
220
+ else if String. equal ext impl then Some Kind. Impl
221
+ else None )
211
222
in
212
- Merlin { merlin_config; tdoc; pipeline; timer; syntax }
223
+ let kind =
224
+ match kind with
225
+ | Some _ as k -> k
226
+ | None -> Kind. of_fname_opt path
227
+ in
228
+ Fiber. return (Merlin { merlin_config; tdoc; pipeline; timer; syntax; kind })
213
229
214
230
let make wheel config pipeline (doc : DidOpenTextDocumentParams.t )
215
231
~position_encoding =
@@ -252,7 +268,10 @@ module Merlin = struct
252
268
253
269
let timer (t : t ) = t.timer
254
270
255
- let kind t = Kind. of_fname (Uri. to_path (uri (Merlin t)))
271
+ let kind t =
272
+ match t.kind with
273
+ | Some k -> k
274
+ | None -> Kind. unsupported (Text_document. documentUri t.tdoc)
256
275
257
276
let with_pipeline ?name (t : t ) f =
258
277
Single_pipeline. use ?name t.pipeline ~doc: t.tdoc ~config: t.merlin_config ~f
@@ -346,21 +365,30 @@ let close t =
346
365
(fun () -> Merlin_config. destroy t.merlin_config)
347
366
(fun () -> Lev_fiber.Timer.Wheel. cancel t.timer)
348
367
349
- let get_impl_intf_counterparts uri =
368
+ let get_impl_intf_counterparts m uri =
350
369
let fpath = Uri. to_path uri in
351
370
let fname = Filename. basename fpath in
352
371
let ml, mli, eliom, eliomi, re, rei, mll, mly =
353
372
(" ml" , " mli" , " eliom" , " eliomi" , " re" , " rei" , " mll" , " mly" )
354
373
in
355
374
let exts_to_switch_to =
375
+ let kind =
376
+ match m with
377
+ | Some m -> Merlin. kind m
378
+ | None -> (
379
+ (* still try to guess the kind *)
380
+ match Kind. of_fname_opt fpath with
381
+ | Some k -> k
382
+ | None -> Kind. unsupported uri)
383
+ in
356
384
match Syntax. of_fname fname with
357
385
| Dune | Cram -> []
358
386
| Ocaml -> (
359
- match Kind. of_fname fname with
387
+ match kind with
360
388
| Intf -> [ ml; mly; mll; eliom; re ]
361
389
| Impl -> [ mli; mly; mll; eliomi; rei ])
362
390
| Reason -> (
363
- match Kind. of_fname fname with
391
+ match kind with
364
392
| Intf -> [ re; ml ]
365
393
| Impl -> [ rei; mli ])
366
394
| Ocamllex -> [ mli; rei ]
0 commit comments