Skip to content

Commit f3a4771

Browse files
authored
Add ocamlformat-mlx and most ocaml features for .mlx (#1528)
* setup doesn't work, time to push * run ci * Enable ocamlformat * Keep ci as before * Resolve doubt about get_impl_intf_counterparts * Add mlx as exts_to_switch_to * Kind ensures --impl is passed to ocamlformat-mlx * Reorder get_impl_intf_counterparts * Enable mlx as interference * Ensure ocamlformat-mlx has --impl for mlx * Enable code_actions for mlx * Pass impl first * Support mlx for merlin diagnostics * Add changelog entry * Move mlx's changelog entry into unreleased
1 parent dc01af3 commit f3a4771

File tree

8 files changed

+25
-9
lines changed

8 files changed

+25
-9
lines changed

CHANGES.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
## Features
44

55
- Make `code-lens` for nested let bindings configurable (#1567)
6+
- Add support for `.mlx` files, including formatting via `ocamlformat-mlx` and most OCaml LSP features (diagnostics, code actions, hover, etc.) (#1528)
67

78
## Fixes
89

ocaml-lsp-server/src/code_actions.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,7 @@ let compute server (params : CodeActionParams.t) =
125125
(match Document.syntax doc with
126126
| Ocamllex | Menhir | Cram | Dune ->
127127
Fiber.return (Reply.now (actions (dune_actions @ open_related)), state)
128-
| Ocaml | Reason ->
128+
| Ocaml | Reason | Mlx ->
129129
let reply () =
130130
let+ code_action_results = compute_ocaml_code_actions params state doc in
131131
List.concat [ code_action_results; dune_actions; open_related; merlin_jumps ]

ocaml-lsp-server/src/document.ml

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module Kind = struct
88

99
let of_fname_opt p =
1010
match Filename.extension p with
11-
| ".ml" | ".eliom" | ".re" | ".mll" | ".mly" -> Some Impl
11+
| ".ml" | ".eliom" | ".re" | ".mll" | ".mly" | ".mlx" -> Some Impl
1212
| ".mli" | ".eliomi" | ".rei" -> Some Intf
1313
| _ -> None
1414
;;
@@ -32,6 +32,7 @@ module Syntax = struct
3232
| Menhir
3333
| Cram
3434
| Dune
35+
| Mlx
3536

3637
let human_name = function
3738
| Ocaml -> "OCaml"
@@ -40,6 +41,7 @@ module Syntax = struct
4041
| Menhir -> "Menhir/ocamlyacc"
4142
| Cram -> "Cram"
4243
| Dune -> "Dune"
44+
| Mlx -> "OCaml.mlx"
4345
;;
4446

4547
let all =
@@ -52,6 +54,7 @@ module Syntax = struct
5254
; "dune", Dune
5355
; "dune-project", Dune
5456
; "dune-workspace", Dune
57+
; "ocaml.mlx", Mlx
5558
]
5659
;;
5760

@@ -61,6 +64,7 @@ module Syntax = struct
6164
| s ->
6265
(match Filename.extension s with
6366
| ".eliomi" | ".eliom" | ".mli" | ".ml" -> Ok Ocaml
67+
| ".mlx" -> Ok Mlx
6468
| ".rei" | ".re" -> Ok Reason
6569
| ".mll" -> Ok Ocamllex
6670
| ".mly" -> Ok Menhir
@@ -252,7 +256,7 @@ let make wheel config pipeline (doc : DidOpenTextDocumentParams.t) ~position_enc
252256
let tdoc = Text_document.make ~position_encoding doc in
253257
let syntax = Syntax.of_text_document tdoc in
254258
match syntax with
255-
| Ocaml | Reason -> make_merlin wheel config pipeline tdoc syntax
259+
| Ocaml | Reason | Mlx -> make_merlin wheel config pipeline tdoc syntax
256260
| Ocamllex | Menhir | Cram | Dune -> Fiber.return (Other { tdoc; syntax }))
257261
;;
258262

@@ -421,8 +425,8 @@ let close t =
421425
let get_impl_intf_counterparts m uri =
422426
let fpath = Uri.to_path uri in
423427
let fname = Filename.basename fpath in
424-
let ml, mli, eliom, eliomi, re, rei, mll, mly =
425-
"ml", "mli", "eliom", "eliomi", "re", "rei", "mll", "mly"
428+
let ml, mli, eliom, eliomi, re, rei, mll, mly, mlx =
429+
"ml", "mli", "eliom", "eliomi", "re", "rei", "mll", "mly", "mlx"
426430
in
427431
let exts_to_switch_to =
428432
let kind =
@@ -436,13 +440,17 @@ let get_impl_intf_counterparts m uri =
436440
in
437441
match Syntax.of_fname fname with
438442
| Dune | Cram -> []
443+
| Mlx ->
444+
(match kind with
445+
| Intf -> [ ml; mly; mll; mlx; re ]
446+
| Impl -> [ rei; mli; mly; mll; rei ])
439447
| Ocaml ->
440448
(match kind with
441-
| Intf -> [ ml; mly; mll; eliom; re ]
449+
| Intf -> [ ml; mly; mll; eliom; re; mlx ]
442450
| Impl -> [ mli; mly; mll; eliomi; rei ])
443451
| Reason ->
444452
(match kind with
445-
| Intf -> [ re; ml ]
453+
| Intf -> [ re; ml; mlx ]
446454
| Impl -> [ rei; mli ])
447455
| Ocamllex -> [ mli; rei ]
448456
| Menhir -> [ mli; rei ]

ocaml-lsp-server/src/document.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Syntax : sig
1010
| Menhir
1111
| Cram
1212
| Dune
13+
| Mlx
1314

1415
val human_name : t -> string
1516
val markdown_name : t -> string

ocaml-lsp-server/src/inference.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,7 @@ let language_id_of_fname s =
7171
| ".mli" | ".eliomi" -> "ocaml.interface"
7272
| ".ml" | ".eliom" -> "ocaml"
7373
| ".rei" | ".re" -> "reason"
74+
| ".mlx" -> "ocaml.mlx"
7475
| ".mll" -> "ocaml.ocamllex"
7576
| ".mly" -> "ocaml.menhir"
7677
| ext -> Code_error.raise "unsupported file extension" [ "extension", String ext ]

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -203,7 +203,7 @@ let set_diagnostics detached diagnostics doc =
203203
in
204204
Diagnostics.set diagnostics (`Merlin (uri, [ no_reason_merlin ]));
205205
async (fun () -> Diagnostics.send diagnostics (`One uri))
206-
| Reason | Ocaml ->
206+
| Reason | Ocaml | Mlx ->
207207
async (fun () ->
208208
let* () = Diagnostics.merlin_diagnostics diagnostics merlin in
209209
Diagnostics.send diagnostics (`One uri)))

ocaml-lsp-server/src/ocamlformat.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -100,9 +100,11 @@ let message = function
100100
type formatter =
101101
| Reason of Document.Kind.t
102102
| Ocaml of Uri.t
103+
| Mlx of Uri.t
103104

104105
let args = function
105106
| Ocaml uri -> [ sprintf "--name=%s" (Uri.to_path uri); "-" ]
107+
| Mlx uri -> [ "--impl"; sprintf "--name=%s" (Uri.to_path uri); "-" ]
106108
| Reason kind ->
107109
[ "--parse"; "re"; "--print"; "re" ]
108110
@
@@ -114,6 +116,7 @@ let args = function
114116
let binary_name t =
115117
match t with
116118
| Ocaml _ -> "ocamlformat"
119+
| Mlx _ -> "ocamlformat-mlx"
117120
| Reason _ -> "refmt"
118121
;;
119122

@@ -128,6 +131,7 @@ let formatter doc =
128131
match Document.syntax doc with
129132
| (Dune | Cram | Ocamllex | Menhir) as s -> Error (Unsupported_syntax s)
130133
| Ocaml -> Ok (Ocaml (Document.uri doc))
134+
| Mlx -> Ok (Mlx (Document.uri doc))
131135
| Reason ->
132136
Ok
133137
(Reason

ocaml-lsp-server/src/ocamlformat.mli

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
(** Generic formatting facility for OCaml and Reason sources.
22
3-
Relies on [ocamlformat] for OCaml and [refmt] for reason *)
3+
Relies on [ocamlformat] for OCaml, [ocamlformat-mlx] for OCaml.mlx, and
4+
[refmt] for Reason. *)
45

56
open Import
67

0 commit comments

Comments
 (0)