Skip to content

Commit adf029c

Browse files
authored
Enable support for OCaml 5.4 and prepare release 1.24.0 (#1559)
* Restore compatibility with merlin for ocaml 5.4 * Update CI * Bump ocaml version in pkg * Update deps * Update changelog * Fix compiler name in CI
1 parent e29fa98 commit adf029c

File tree

8 files changed

+35
-22
lines changed

8 files changed

+35
-22
lines changed

.github/workflows/build-and-test.yml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -45,11 +45,11 @@ jobs:
4545
- name: Set-up OCaml
4646
uses: ocaml/setup-ocaml@v3
4747
with:
48-
ocaml-compiler: "ocaml-base-compiler.5.3.0"
48+
ocaml-compiler: "ocaml-variants.5.4.0+trunk"
4949

5050
# Remove this pin once a compatible version of Merlin has been released
5151
- name: Pin dev Merlin
52-
run: opam --cli=2.1 pin --with-version=5.5-503 https://github.com/ocaml/merlin.git#main
52+
run: opam --cli=2.1 pin --with-version=5.6-504 https://github.com/voodoos/merlin.git#504-rebase
5353

5454
- name: Build and install dependencies
5555
run: opam install .
@@ -81,7 +81,7 @@ jobs:
8181
- name: Set-up OCaml
8282
uses: ocaml/setup-ocaml@v3
8383
with:
84-
ocaml-compiler: "ocaml-base-compiler.5.3.0"
84+
ocaml-compiler: "ocaml-variants.5.4.0+trunk"
8585

8686
- name: Set git user
8787
run: |
@@ -90,7 +90,7 @@ jobs:
9090
9191
# Remove this pin once a compatible version of Merlin has been released
9292
- name: Pin dev Merlin
93-
run: opam --cli=2.1 pin --with-version=5.5-503 https://github.com/ocaml/merlin.git#main
93+
run: opam --cli=2.1 pin --with-version=5.6-504 https://github.com/voodoos/merlin.git#504-rebase
9494

9595
- name: Install dependencies
9696
run: |

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,9 @@
1+
# 1.24.0
2+
3+
## Features
4+
5+
- Support for OCaml 5.4 (#1559)
6+
17
# 1.23.1
28

39
## Fixes

dune-project

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ possible and does not make any assumptions about IO.
5656
dyn
5757
stdune
5858
(fiber (and (>= 3.1.1) (< 4.0.0)))
59-
(ocaml (and (>= 5.3) (< 5.4)))
59+
(ocaml (and (>= 5.4) (< 5.5)))
6060
xdg
6161
ordering
6262
dune-build-info
@@ -70,7 +70,8 @@ possible and does not make any assumptions about IO.
7070
(csexp (>= 1.5))
7171
(ocamlformat-rpc-lib (>= 0.21.0))
7272
(odoc :with-doc)
73-
(merlin-lib (and (>= 5.5) (< 5.7)))
73+
(merlin-lib (and (>= 5.6) (< 5.7)))
74+
(ocaml-index :post)
7475
(ppx_yojson_conv :with-dev-setup)))
7576

7677
(package

ocaml-lsp-server.opam

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ depends: [
3131
"dyn"
3232
"stdune"
3333
"fiber" {>= "3.1.1" & < "4.0.0"}
34-
"ocaml" {>= "5.3" & < "5.4"}
34+
"ocaml" {>= "5.4" & < "5.5"}
3535
"xdg"
3636
"ordering"
3737
"dune-build-info"
@@ -45,7 +45,8 @@ depends: [
4545
"csexp" {>= "1.5"}
4646
"ocamlformat-rpc-lib" {>= "0.21.0"}
4747
"odoc" {with-doc}
48-
"merlin-lib" {>= "5.5" & < "5.7"}
48+
"merlin-lib" {>= "5.6" & < "5.7"}
49+
"ocaml-index" {post}
4950
"ppx_yojson_conv" {with-dev-setup}
5051
]
5152
dev-repo: "git+https://github.com/ocaml/ocaml-lsp.git"

ocaml-lsp-server/src/code_actions/action_inline.ml

Lines changed: 13 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,7 @@ end = struct
160160
let pat_iter (type k) (iter : I.iterator) (pat : k Typedtree.general_pattern) =
161161
match pat.pat_desc with
162162
| Tpat_var (id, { loc; _ }, _) -> paths := Loc.Map.set !paths loc (Pident id)
163-
| Tpat_alias (pat, id, { loc; _ }, _) ->
163+
| Tpat_alias (pat, id, { loc; _ }, _, _) ->
164164
paths := Loc.Map.set !paths loc (Pident id);
165165
I.default_iterator.pat iter pat
166166
| _ -> I.default_iterator.pat iter pat
@@ -217,9 +217,12 @@ let beta_reduce (paths : Paths.t) (app : Parsetree.expression) =
217217
if is_pure arg then body else with_let ()
218218
| Ppat_var param | Ppat_constraint ({ ppat_desc = Ppat_var param; _ }, _) ->
219219
if is_pure arg then with_subst param else with_let ()
220-
| Ppat_tuple pats ->
220+
| Ppat_tuple ( pats, _) ->
221+
let pats = List.map ~f:snd pats in
221222
(match arg.pexp_desc with
222-
| Pexp_tuple args -> List.fold_left2 ~f:beta_reduce_arg ~init:body pats args
223+
| Pexp_tuple args ->
224+
let args = List.map ~f:snd args in
225+
List.fold_left2 ~f:beta_reduce_arg ~init:body pats args
223226
| _ -> with_let ())
224227
| _ -> with_let ()
225228
in
@@ -275,16 +278,16 @@ let inline_edits pipeline task =
275278
env
276279
(iter : I.iterator)
277280
(label : Asttypes.arg_label)
278-
(m_arg_expr : Typedtree.expression option)
281+
(m_arg_expr : Typedtree.apply_arg)
279282
=
280283
match label, m_arg_expr with
281284
(* handle the labeled argument shorthand `f ~x` when inlining `x` *)
282-
| Labelled name, Some { exp_desc = Texp_ident (Pident id, { loc; _ }, _); _ }
285+
| Labelled name, Arg { exp_desc = Texp_ident (Pident id, { loc; _ }, _); _ }
283286
(* inlining is allowed for optional arguments that are being passed a Some
284287
parameter, i.e. `x` may be inlined in `let x = 1 in (fun ?(x = 0) -> x)
285288
~x` *)
286289
| ( Optional name
287-
, Some
290+
, Arg
288291
{ exp_desc =
289292
(* construct is part of desugaring, assumed to be Some *)
290293
Texp_construct
@@ -294,13 +297,14 @@ let inline_edits pipeline task =
294297
when Ident.same task.inlined_var id && not_shadowed env ->
295298
let newText = sprintf "%s:%s" name newText in
296299
insert_edit newText loc
297-
| Optional _, Some ({ exp_desc = Texp_construct _; _ } as arg_expr) ->
300+
| Optional _, Arg ({ exp_desc = Texp_construct _; _ } as arg_expr) ->
298301
iter.expr iter arg_expr
299302
(* inlining is _not_ allowed for optional arguments that are being passed an
300303
optional parameter i.e. `x` may _not_ be inlined in `let x = Some 1 in
301304
(fun ?(x = 0) -> x) ?x` *)
302-
| Optional _, Some _ -> ()
303-
| _, _ -> Option.iter m_arg_expr ~f:(iter.expr iter)
305+
| Optional _, Arg _ -> ()
306+
| _, Arg arg -> iter.expr iter arg
307+
| _, _ -> ()
304308
in
305309
let paths = Paths.of_typedtree task.inlined_expr in
306310
let inlined_pexpr = find_parsetree_loc_exn pipeline task.inlined_expr.exp_loc in

ocaml-lsp-server/src/code_actions/action_mark_remove_unused.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ let rec mark_value_unused_edit name contexts =
8989
{ range = Range.create ~start:start_pos ~end_:start_pos; newText = "_" }
9090
| _ -> None
9191
: Longident.t Loc.loc
92-
* Types.label_description
92+
* Data_types.label_description
9393
* Typedtree.value Typedtree.general_pattern
9494
-> TextEdit.t option)
9595
in

ocaml-lsp-server/src/import.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -238,6 +238,7 @@ include struct
238238
module Path = Path
239239
module Typedtree = Typedtree
240240
module Types = Types
241+
module Data_types = Data_types
241242
end
242243

243244
include struct

ocaml-lsp-server/src/semantic_highlighting.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -518,10 +518,10 @@ end = struct
518518

519519
let pexp_apply (self : Ast_iterator.iterator) (expr : Parsetree.expression) args =
520520
match expr.pexp_desc with
521-
| Pexp_ident { txt = Ldot (Lident "Array", "set"); _ }
522-
| Pexp_ident { txt = Ldot (Lident "Array", "get"); _ }
523-
| Pexp_ident { txt = Ldot (Lident "String", "set"); _ }
524-
| Pexp_ident { txt = Ldot (Lident "String", "get"); _ } ->
521+
| Pexp_ident { txt = Ldot ({ txt = Lident "Array"; _ }, { txt = "set"; _ }); _ }
522+
| Pexp_ident { txt = Ldot ({ txt = Lident "Array"; _ }, { txt = "get"; _ }); _ }
523+
| Pexp_ident { txt = Ldot ({ txt = Lident "String"; _ }, { txt = "set"; _ }); _ }
524+
| Pexp_ident { txt = Ldot ({ txt = Lident "String"; _ }, { txt = "get"; _ }); _ } ->
525525
List.iter args ~f:(fun ((_ : Asttypes.arg_label), e) -> self.expr self e);
526526
`Custom_iterator
527527
| Pexp_ident lid ->

0 commit comments

Comments
 (0)