diff --git a/CHANGES.md b/CHANGES.md index edbddcf9f..52c82514e 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -6,6 +6,11 @@ # 1.23.1 +## Features + +- Add support for `.mlx` files, including formatting via `ocamlformat-mlx` and + most OCaml LSP features (diagnostics, code actions, hover, etc.) (#1528) + ## Fixes - Fix hover on method calls not showing the type. (#1553, fixes #1552) diff --git a/ocaml-lsp-server/src/code_actions.ml b/ocaml-lsp-server/src/code_actions.ml index 662599eea..c2f7b9060 100644 --- a/ocaml-lsp-server/src/code_actions.ml +++ b/ocaml-lsp-server/src/code_actions.ml @@ -125,7 +125,7 @@ let compute server (params : CodeActionParams.t) = (match Document.syntax doc with | Ocamllex | Menhir | Cram | Dune -> Fiber.return (Reply.now (actions (dune_actions @ open_related)), state) - | Ocaml | Reason -> + | Ocaml | Reason | Mlx -> let reply () = let+ code_action_results = compute_ocaml_code_actions params state doc in List.concat [ code_action_results; dune_actions; open_related; merlin_jumps ] diff --git a/ocaml-lsp-server/src/document.ml b/ocaml-lsp-server/src/document.ml index fdee76287..213de261a 100644 --- a/ocaml-lsp-server/src/document.ml +++ b/ocaml-lsp-server/src/document.ml @@ -8,7 +8,7 @@ module Kind = struct let of_fname_opt p = match Filename.extension p with - | ".ml" | ".eliom" | ".re" | ".mll" | ".mly" -> Some Impl + | ".ml" | ".eliom" | ".re" | ".mll" | ".mly" | ".mlx" -> Some Impl | ".mli" | ".eliomi" | ".rei" -> Some Intf | _ -> None ;; @@ -32,6 +32,7 @@ module Syntax = struct | Menhir | Cram | Dune + | Mlx let human_name = function | Ocaml -> "OCaml" @@ -40,6 +41,7 @@ module Syntax = struct | Menhir -> "Menhir/ocamlyacc" | Cram -> "Cram" | Dune -> "Dune" + | Mlx -> "OCaml.mlx" ;; let all = @@ -52,6 +54,7 @@ module Syntax = struct ; "dune", Dune ; "dune-project", Dune ; "dune-workspace", Dune + ; "ocaml.mlx", Mlx ] ;; @@ -61,6 +64,7 @@ module Syntax = struct | s -> (match Filename.extension s with | ".eliomi" | ".eliom" | ".mli" | ".ml" -> Ok Ocaml + | ".mlx" -> Ok Mlx | ".rei" | ".re" -> Ok Reason | ".mll" -> Ok Ocamllex | ".mly" -> Ok Menhir @@ -252,7 +256,7 @@ let make wheel config pipeline (doc : DidOpenTextDocumentParams.t) ~position_enc let tdoc = Text_document.make ~position_encoding doc in let syntax = Syntax.of_text_document tdoc in match syntax with - | Ocaml | Reason -> make_merlin wheel config pipeline tdoc syntax + | Ocaml | Reason | Mlx -> make_merlin wheel config pipeline tdoc syntax | Ocamllex | Menhir | Cram | Dune -> Fiber.return (Other { tdoc; syntax })) ;; @@ -421,8 +425,8 @@ let close t = let get_impl_intf_counterparts m uri = let fpath = Uri.to_path uri in let fname = Filename.basename fpath in - let ml, mli, eliom, eliomi, re, rei, mll, mly = - "ml", "mli", "eliom", "eliomi", "re", "rei", "mll", "mly" + let ml, mli, eliom, eliomi, re, rei, mll, mly, mlx = + "ml", "mli", "eliom", "eliomi", "re", "rei", "mll", "mly", "mlx" in let exts_to_switch_to = let kind = @@ -436,13 +440,17 @@ let get_impl_intf_counterparts m uri = in match Syntax.of_fname fname with | Dune | Cram -> [] + | Mlx -> + (match kind with + | Intf -> [ ml; mly; mll; mlx; re ] + | Impl -> [ rei; mli; mly; mll; rei ]) | Ocaml -> (match kind with - | Intf -> [ ml; mly; mll; eliom; re ] + | Intf -> [ ml; mly; mll; eliom; re; mlx ] | Impl -> [ mli; mly; mll; eliomi; rei ]) | Reason -> (match kind with - | Intf -> [ re; ml ] + | Intf -> [ re; ml; mlx ] | Impl -> [ rei; mli ]) | Ocamllex -> [ mli; rei ] | Menhir -> [ mli; rei ] diff --git a/ocaml-lsp-server/src/document.mli b/ocaml-lsp-server/src/document.mli index 735bfd659..6585b6f0b 100644 --- a/ocaml-lsp-server/src/document.mli +++ b/ocaml-lsp-server/src/document.mli @@ -10,6 +10,7 @@ module Syntax : sig | Menhir | Cram | Dune + | Mlx val human_name : t -> string val markdown_name : t -> string diff --git a/ocaml-lsp-server/src/inference.ml b/ocaml-lsp-server/src/inference.ml index d51401e31..c313b7bd2 100644 --- a/ocaml-lsp-server/src/inference.ml +++ b/ocaml-lsp-server/src/inference.ml @@ -71,6 +71,7 @@ let language_id_of_fname s = | ".mli" | ".eliomi" -> "ocaml.interface" | ".ml" | ".eliom" -> "ocaml" | ".rei" | ".re" -> "reason" + | ".mlx" -> "ocaml.mlx" | ".mll" -> "ocaml.ocamllex" | ".mly" -> "ocaml.menhir" | ext -> Code_error.raise "unsupported file extension" [ "extension", String ext ] diff --git a/ocaml-lsp-server/src/ocaml_lsp_server.ml b/ocaml-lsp-server/src/ocaml_lsp_server.ml index ec7f8e119..39e58db09 100644 --- a/ocaml-lsp-server/src/ocaml_lsp_server.ml +++ b/ocaml-lsp-server/src/ocaml_lsp_server.ml @@ -203,7 +203,7 @@ let set_diagnostics detached diagnostics doc = in Diagnostics.set diagnostics (`Merlin (uri, [ no_reason_merlin ])); async (fun () -> Diagnostics.send diagnostics (`One uri)) - | Reason | Ocaml -> + | Reason | Ocaml | Mlx -> async (fun () -> let* () = Diagnostics.merlin_diagnostics diagnostics merlin in Diagnostics.send diagnostics (`One uri))) diff --git a/ocaml-lsp-server/src/ocamlformat.ml b/ocaml-lsp-server/src/ocamlformat.ml index 28437f21f..4c6ce3757 100644 --- a/ocaml-lsp-server/src/ocamlformat.ml +++ b/ocaml-lsp-server/src/ocamlformat.ml @@ -100,9 +100,11 @@ let message = function type formatter = | Reason of Document.Kind.t | Ocaml of Uri.t + | Mlx of Uri.t let args = function | Ocaml uri -> [ sprintf "--name=%s" (Uri.to_path uri); "-" ] + | Mlx uri -> [ "--impl"; sprintf "--name=%s" (Uri.to_path uri); "-" ] | Reason kind -> [ "--parse"; "re"; "--print"; "re" ] @ @@ -114,6 +116,7 @@ let args = function let binary_name t = match t with | Ocaml _ -> "ocamlformat" + | Mlx _ -> "ocamlformat-mlx" | Reason _ -> "refmt" ;; @@ -128,6 +131,7 @@ let formatter doc = match Document.syntax doc with | (Dune | Cram | Ocamllex | Menhir) as s -> Error (Unsupported_syntax s) | Ocaml -> Ok (Ocaml (Document.uri doc)) + | Mlx -> Ok (Mlx (Document.uri doc)) | Reason -> Ok (Reason diff --git a/ocaml-lsp-server/src/ocamlformat.mli b/ocaml-lsp-server/src/ocamlformat.mli index 0d6edc6c1..186f692ba 100644 --- a/ocaml-lsp-server/src/ocamlformat.mli +++ b/ocaml-lsp-server/src/ocamlformat.mli @@ -1,6 +1,7 @@ (** Generic formatting facility for OCaml and Reason sources. - Relies on [ocamlformat] for OCaml and [refmt] for reason *) + Relies on [ocamlformat] for OCaml, [ocamlformat-mlx] for OCaml.mlx, and + [refmt] for Reason. *) open Import