Skip to content

Commit

Permalink
Parmatch: use correct names for constructors in pat_of_constr and pat…
Browse files Browse the repository at this point in the history
…s_of_type

The dummy name was a legacy of when the name wasn't in the descriptor.
  • Loading branch information
garrigue authored and gasche committed Nov 4, 2019
1 parent 7fa72b1 commit e27120f
Showing 1 changed file with 2 additions and 2 deletions.
4 changes: 2 additions & 2 deletions typing/parmatch.ml
Original file line number Diff line number Diff line change
Expand Up @@ -974,7 +974,7 @@ let complete_tags nconsts nconstrs tags =
(* build a pattern from a constructor description *)
let pat_of_constr ex_pat cstr =
{ex_pat with pat_desc =
Tpat_construct (mknoloc (Longident.Lident "?pat_of_constr?"),
Tpat_construct (mknoloc (Longident.Lident cstr.cstr_name),
cstr, omegas cstr.cstr_arity)}

let orify x y = make_pat (Tpat_or (x, y, None)) x.pat_type x.pat_env
Expand Down Expand Up @@ -1003,7 +1003,7 @@ let pats_of_type ?(always=false) env ty =
let labels = snd (Env.find_type_descrs path env) in
let fields =
List.map (fun ld ->
mknoloc (Longident.Lident "?pat_of_label?"), ld, omega)
mknoloc (Longident.Lident ld.lbl_name), ld, omega)
labels
in
[make_pat (Tpat_record (fields, Closed)) ty env]
Expand Down

0 comments on commit e27120f

Please sign in to comment.