Skip to content

Commit b5a0333

Browse files
committed
Minor printing fix
1 parent ed83961 commit b5a0333

File tree

4 files changed

+16
-3
lines changed

4 files changed

+16
-3
lines changed

middle_end/flambda/from_lambda/cps_conversion.ml

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,15 @@ module I = Ilambda
2424
module L = Lambda
2525
module C = Lambda_conversions
2626

27+
module Continuation = struct
28+
include Continuation
29+
30+
let r = ref 0
31+
let create ?sort () =
32+
let name = Format.asprintf "k%d" (incr r; !r) in
33+
create ?sort ~name ()
34+
end
35+
2736
type primitive_transform_result =
2837
| Primitive of L.primitive * L.lambda list * L.scoped_location
2938
| Transformed of L.lambda

middle_end/flambda/unboxing/unboxing_epa.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -129,12 +129,12 @@ let extra_args_for_const_ctor_of_variant
129129
| Zero ->
130130
begin match variant_arg with
131131
| Not_a_constant_constructor -> const_ctors_decision
132-
| Maybe_constant_constructor _ ->
132+
| Maybe_constant_constructor { arg_being_unboxed; _ } ->
133133
Misc.fatal_errorf
134134
"The unboxed variant parameter was determined to have \
135135
no constant cases when deciding to unbox it (using the \
136136
parameter type), but at the use site, it is a constant \
137-
constructor."
137+
constructor.@\narg: %a@." _print_unboxed_arg arg_being_unboxed;
138138
end
139139
| At_least_one { ctor = Do_not_unbox reason; is_int; } ->
140140
let is_int =

middle_end/flambda/unboxing/unboxing_types.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module Extra_param_and_args = struct
4444
Format.fprintf fmt "@[<hv 1>(\
4545
@[<hov>(param %a)@]@ \
4646
@[<v 2>(args@ <...>)@]\
47-
)"
47+
)@]"
4848
Variable.print param
4949
(* (Apply_cont_rewrite_id.Map.print EPA.Extra_arg.print) args *)
5050
end

middle_end/flambda/unboxing/unboxing_types.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,10 @@ and decision =
7272
| Unbox of unboxing_decision
7373
| Do_not_unbox of do_not_unbox_reason
7474

75+
val print_decision : Format.formatter -> decision -> unit
76+
(** Printing function for individual decisions. *)
77+
78+
7579
module Decisions : sig
7680
type t = {
7781
decisions : (KP.t * decision) list;

0 commit comments

Comments
 (0)