File tree Expand file tree Collapse file tree 4 files changed +8
-20
lines changed Expand file tree Collapse file tree 4 files changed +8
-20
lines changed Original file line number Diff line number Diff line change 88 }
99 | Diagnostic of
1010 { id : Id .t
11- ; diagnostic : Dune_rpc_private. Compound_user_error.t
11+ ; diagnostic : Compound_user_error .t
1212 ; dir : Path .t option
1313 ; promotion : Diff_promotion.Annot .t option
1414 }
@@ -29,14 +29,12 @@ let of_exn (exn : Exn_with_backtrace.t) =
2929 | User_error. E main ->
3030 let dir = Option. map ~f: Path. of_string main.dir in
3131 let promotion = User_message.Annots. find main.annots Diff_promotion.Annot. annot in
32- (match
33- User_message.Annots. find main.annots Dune_rpc_private.Compound_user_error. annot
34- with
32+ (match User_message.Annots. find main.annots Compound_user_error. annot with
3533 | None ->
3634 [ Diagnostic
3735 { dir
3836 ; id = Id. gen ()
39- ; diagnostic = Dune_rpc_private. Compound_user_error. make ~main ~related: []
37+ ; diagnostic = Compound_user_error. make ~main ~related: []
4038 ; promotion
4139 }
4240 ]
Original file line number Diff line number Diff line change @@ -26,9 +26,7 @@ val dir : t -> Path.t option
2626 metadata that are extracted into [`Diagnostic] *)
2727val description
2828 : t
29- -> [ `Exn of Exn_with_backtrace. t
30- | `Diagnostic of Dune_rpc_private.Compound_user_error. t
31- ]
29+ -> [ `Exn of Exn_with_backtrace. t | `Diagnostic of Compound_user_error. t ]
3230
3331val promotion : t -> Diff_promotion.Annot .t option
3432
@@ -58,10 +56,7 @@ module For_tests : sig
5856
5957 (* * Construct an [Error.t] *)
6058 val make
61- : description:
62- [ `Exn of Exn_with_backtrace. t
63- | `Diagnostic of Dune_rpc_private.Compound_user_error. t
64- ]
59+ : description:[ `Exn of Exn_with_backtrace. t | `Diagnostic of Compound_user_error. t ]
6560 -> dir:Path. t option
6661 -> promotion:Diff_promotion.Annot. t option
6762 -> unit
Original file line number Diff line number Diff line change @@ -4,6 +4,7 @@ module Cached_digest = Dune_digest.Cached_digest
44module Console = Dune_console
55module Metrics = Dune_metrics
66module Log = Dune_util. Log
7+ module Compound_user_error = Dune_rpc_private. Compound_user_error
78module Stringlike = Dune_util. Stringlike
89
910module type Stringlike = Dune_util. Stringlike
Original file line number Diff line number Diff line change @@ -539,15 +539,9 @@ end = struct
539539 let annots =
540540 User_message.Annots. set annots User_message.Annots. has_embedded_location ()
541541 in
542- match
543- Dune_rpc_private.Compound_user_error. parse_output ~dir output.without_color
544- with
542+ match Compound_user_error. parse_output ~dir output.without_color with
545543 | [] -> annots
546- | errors ->
547- User_message.Annots. set
548- annots
549- Dune_rpc_private.Compound_user_error. annot
550- errors)
544+ | errors -> User_message.Annots. set annots Compound_user_error. annot errors)
551545 else annots
552546 in
553547 loc, annots, dir
You can’t perform that action at this time.
0 commit comments