Skip to content

Commit

Permalink
Fix destruct crashing on closed variant types (#1602)
Browse files Browse the repository at this point in the history
from voodoos/repro-issue-1601
  • Loading branch information
voodoos authored May 25, 2023
2 parents b22a75c + c803ab5 commit 7e8eb2c
Show file tree
Hide file tree
Showing 3 changed files with 55 additions and 4 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@ unreleased
- Fix incorrect locations for string literals (#1574)
- Fixed an issue that caused `errors` to erroneously alert about missing
`cmi` files (#1577)
- Prevent destruct from crashing on closed variant types (#1602,
fixes #1601)
+ editor modes
- emacs: call the user's configured completion UI in
`merlin-construct` (#1598)
Expand Down
19 changes: 15 additions & 4 deletions src/analysis/destruct.ml
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,9 @@ let placeholder =

let rec gen_patterns ?(recurse=true) env type_expr =
let open Types in
log ~title:"gen_patterns" "%a" Logger.fmt (fun fmt ->
Format.fprintf fmt "Generating patterns for type %a"
Printtyp.type_expr type_expr);
match get_desc type_expr with
| Tlink _ -> assert false (* impossible after [Btype.repr] *)
| Tvar _ -> raise (Not_allowed "non-immediate type")
Expand Down Expand Up @@ -158,7 +161,14 @@ let rec gen_patterns ?(recurse=true) env type_expr =
| lbl, Rpresent param_opt ->
let popt = Option.map param_opt ~f:(fun _ -> Patterns.omega) in
Some (Tast_helper.Pat.variant env type_expr lbl popt (ref row_desc))
| _, _ -> None
| _, Reither (_, l, _) ->
let popt = match l with
| [] -> None
| _ :: _ -> Some Patterns.omega
in
Some (Tast_helper.Pat.variant env type_expr lbl popt (ref row_desc))
| _, _ ->
log ~title:"gen_patterns" "Absent"; None
)
| _ ->
let fmt, to_string = Format.to_string () in
Expand Down Expand Up @@ -547,17 +557,18 @@ let rec node config source selected_node parents =
let str = Mreader.print_pretty config source (Pretty_case_list cases) in
loc, str
| [] ->
(* The match is already complete, we try to refine it *)
begin match Typedtree.classify_pattern patt with
| Computation -> raise (Not_allowed ("computation pattern"));
| Value ->
let _patt : Typedtree.value Typedtree.general_pattern = patt in
if not (destructible patt) then raise Nothing_to_do else
let ty = patt.Typedtree.pat_type in
(* Printf.eprintf "pouet cp \n%!" ; *)
begin match gen_patterns patt.Typedtree.pat_env ty with
| [] -> assert false (* we raise Not_allowed, but never return [] *)
| [] ->
(* gen_patterns might raise Not_allowed, but should never return [] *)
assert false
| [ more_precise ] ->
(* Printf.eprintf "one cp \n%!" ; *)
(* If only one pattern is generated, then we're only refining the
current pattern, not generating new branches. *)
let ppat = filter_pat_attr (Untypeast.untype_pattern more_precise) in
Expand Down
38 changes: 38 additions & 0 deletions tests/test-dirs/destruct/issue1601.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
$ cat >main.ml <<EOF
> let foo : [< \`Foo ] option = None
>
> let () =
> match foo with
> | None | Some _ -> ()
> EOF

$ $MERLIN single case-analysis -start 5:16 -end 5:16 \
> -filename main.ml <main.ml |
> jq '.value[1]'
"`Foo"

$ cat >main.ml <<EOF
> let foo : [> \`Foo ] option = None
>
> let () =
> match foo with
> | None | Some _ -> ()
> EOF

$ $MERLIN single case-analysis -start 5:16 -end 5:16 \
> -filename main.ml <main.ml |
> jq '.value[1]'
"`Foo"

$ cat >main.ml <<EOF
> let foo : [< \`Foo | \`Bar > \`Foo] option = None
>
> let () =
> match foo with
> | None | Some _ -> ()
> EOF

$ $MERLIN single case-analysis -start 5:16 -end 5:16 \
> -filename main.ml <main.ml |
> jq '.value[1]'
"None | Some `Bar | Some `Foo"

0 comments on commit 7e8eb2c

Please sign in to comment.