Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 13 additions & 5 deletions ocaml-lsp-server/src/document.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ module Syntax = struct
| Menhir
| Cram
| Dune
| Mlx

let human_name = function
| Ocaml -> "OCaml"
Expand All @@ -40,6 +41,7 @@ module Syntax = struct
| Menhir -> "Menhir/ocamlyacc"
| Cram -> "Cram"
| Dune -> "Dune"
| Mlx -> "OCaml.mlx"
;;

let all =
Expand All @@ -52,6 +54,7 @@ module Syntax = struct
; "dune", Dune
; "dune-project", Dune
; "dune-workspace", Dune
; "ocaml.mlx", Mlx
]
;;

Expand All @@ -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
Expand Down Expand Up @@ -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 }))
;;

Expand Down Expand Up @@ -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 =
Expand All @@ -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 -> [ re; ml; mly; mll; mlx ]
| Impl -> [ rei; mli; mly; mll; mlx ])
| 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 ]
Expand Down
1 change: 1 addition & 0 deletions ocaml-lsp-server/src/document.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Syntax : sig
| Menhir
| Cram
| Dune
| Mlx

val human_name : t -> string
val markdown_name : t -> string
Expand Down
4 changes: 4 additions & 0 deletions ocaml-lsp-server/src/ocamlformat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -100,8 +100,10 @@ let message = function
type formatter =
| Reason of Document.Kind.t
| Ocaml of Uri.t
| Mlx of Uri.t

let args = function
| Mlx uri
| Ocaml uri -> [ sprintf "--name=%s" (Uri.to_path uri); "-" ]
| Reason kind ->
[ "--parse"; "re"; "--print"; "re" ]
Expand All @@ -114,6 +116,7 @@ let args = function
let binary_name t =
match t with
| Ocaml _ -> "ocamlformat"
| Mlx _ -> "ocamlformat-mlx"
| Reason _ -> "refmt"
;;

Expand All @@ -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
Expand Down
3 changes: 2 additions & 1 deletion ocaml-lsp-server/src/ocamlformat.mli
Original file line number Diff line number Diff line change
@@ -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

Expand Down