Skip to content

Commit

Permalink
Use compat lib where required
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Oct 4, 2024
1 parent 318fdde commit 073f6c7
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 5 deletions.
9 changes: 7 additions & 2 deletions ocaml-lsp-server/src/code_actions/action_extract.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
open Import
open Option.O
module H = Ocaml_parsing.Ast_helper
module Typedtree_utils = Merlin_analysis.Typedtree_utils

let range_contains_loc range loc =
match Range.of_loc_opt loc with
Expand Down Expand Up @@ -75,8 +76,12 @@ let tightest_enclosing_binder_position typedtree range =
| Texp_open (_, body) -> found_if_expr_contains body
| Texp_letop { body; _ } -> found_if_case_contains [ body ]
| Texp_function (_, Tfunction_cases { cases; _ }) -> found_if_case_contains cases
| Texp_match (_, cases, _) -> found_if_case_contains cases
| Texp_try (_, cases) -> found_if_case_contains cases
| Texp_match _ ->
let m = Typedtree_utils.texp_match_of_expr expr |> Option.value_exn in
found_if_case_contains m.computation_cases
| Texp_try _ ->
let t = Typedtree_utils.texp_try_of_expr expr |> Option.value_exn in
found_if_case_contains t.value_cases
| _ -> ())
in
let structure_item_iter (iter : I.iterator) (item : Typedtree.structure_item) =
Expand Down
3 changes: 2 additions & 1 deletion ocaml-lsp-server/src/folding_range.ml
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,8 @@ let fold_over_parsetree (parsetree : Mreader.parsetree) =
| Ppat_exception _
| Ppat_extension _
| Ppat_open _
| Ppat_any -> Ast_iterator.default_iterator.pat self p
| Ppat_any
| _ -> Ast_iterator.default_iterator.pat self p
in
let expr (self : Ast_iterator.iterator) (expr : Parsetree.expression) =
match expr.pexp_desc with
Expand Down
6 changes: 4 additions & 2 deletions ocaml-lsp-server/src/semantic_highlighting.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
open Import
open Fiber.O
module Array_view = Lsp.Private.Array_view
module Parsetree_utils = Merlin_analysis.Parsetree_utils

(* TODO:
Expand Down Expand Up @@ -508,7 +509,7 @@ end = struct

let const loc (constant : Parsetree.constant) =
let token_type =
match constant with
match Parsetree_utils.constant_desc constant with
| Parsetree.Pconst_integer _ | Pconst_float _ -> Token_type.of_builtin Number
| Pconst_char _ | Pconst_string _ -> Token_type.of_builtin String
in
Expand Down Expand Up @@ -718,7 +719,8 @@ end = struct
| Ppat_tuple _
| Ppat_lazy _
| Ppat_any
| Ppat_interval _ -> `Default_iterator
| Ppat_interval _
| _ -> `Default_iterator
with
| `Default_iterator -> Ast_iterator.default_iterator.pat self pat
| `Custom_iterator -> self.attributes self ppat_attributes
Expand Down

0 comments on commit 073f6c7

Please sign in to comment.