Skip to content

Commit 6d924e4

Browse files
committed
Parse alerts as alerts directly
1 parent 64a1c1c commit 6d924e4

File tree

7 files changed

+106
-103
lines changed

7 files changed

+106
-103
lines changed

bin/rpc/rpc_common.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -170,6 +170,9 @@ let wrap_build_outcome_exn ~print_on_success build_outcome =
170170
nb_errors + 1, nb_warnings
171171
| Warning ->
172172
User_warning.emit_message main;
173+
nb_errors, nb_warnings + 1
174+
| Alert ->
175+
Console.print_user_message main;
173176
nb_errors, nb_warnings + 1)
174177
in
175178
(match nb_errors, nb_warnings with

otherlibs/dune-rpc/private/diagnostics_v1.ml

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -38,11 +38,6 @@ type t =
3838
; related : Related.t list
3939
}
4040

41-
let sexp_severity =
42-
let open Conv in
43-
enum [ "error", Diagnostic.Error; "warning", Warning ]
44-
;;
45-
4641
let sexp =
4742
let open Conv in
4843
let from { targets; message; loc; severity; promotion; directory; id; related } =
@@ -54,7 +49,7 @@ let sexp =
5449
let loc = field "loc" (optional Loc.sexp) in
5550
let message = field "message" (required sexp_pp_unit) in
5651
let targets = field "targets" (required (list Target.sexp)) in
57-
let severity = field "severity" (optional sexp_severity) in
52+
let severity = field "severity" (optional Diagnostic.sexp_severity) in
5853
let directory = field "directory" (optional string) in
5954
let promotion = field "promotion" (required (list Diagnostic.Promotion.sexp)) in
6055
let id = field "id" (required Diagnostic.Id.sexp) in

otherlibs/dune-rpc/private/exported_types.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -470,6 +470,7 @@ module Diagnostic = struct
470470
type severity =
471471
| Error
472472
| Warning
473+
| Alert
473474

474475
module Promotion = struct
475476
type t =
@@ -542,12 +543,13 @@ module Diagnostic = struct
542543

543544
let sexp_severity =
544545
let open Conv in
545-
enum [ "error", Error; "warning", Warning ]
546+
enum [ "error", Error; "warning", Warning; "alert", Alert ]
546547
;;
547548

548549
let severity_to_dyn = function
549550
| Error -> Dyn.string "error"
550551
| Warning -> Dyn.string "warning"
552+
| Alert -> Dyn.string "alert"
551553
;;
552554

553555
let sexp =
@@ -790,9 +792,7 @@ module Compound_user_error = struct
790792
match report.severity with
791793
| Error _ -> Error
792794
| Warning _ -> Warning
793-
| Alert _ ->
794-
(* FIXME: tests expect this, but it's unclear if that should change. *)
795-
Error
795+
| Alert _ -> Alert
796796
in
797797
make_with_severity ~main ~related ~severity)
798798
;;

otherlibs/dune-rpc/private/exported_types.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,9 @@ module Diagnostic : sig
9494
type severity =
9595
| Error
9696
| Warning
97+
| Alert
98+
99+
val sexp_severity : severity Conv.value
97100

98101
module Promotion : sig
99102
type t =

otherlibs/dune-rpc/v1.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -194,6 +194,7 @@ module Diagnostic : sig
194194
type severity =
195195
| Error
196196
| Warning
197+
| Alert
197198

198199
module Promotion : sig
199200
type t

test/expect-tests/dune_rpc/dune_rpc_tests.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -886,10 +886,10 @@ let%expect_test "print digests for all public RPCs" =
886886
{|
887887
Version 1:
888888
Request: Unit
889-
Response: ffd3de9652c685594aacfc51d28f2533
889+
Response: f7a8c7eae4461445617c9e5c9237fa86
890890
Version 2:
891891
Request: Unit
892-
Response: 0d4442e0c36d6727a9acf9aabce6a6ad
892+
Response: 76dbee17207380c4a728fff5875b2fda
893893
|}];
894894
Decl.Notification.print_generations Procedures.Public.shutdown;
895895
[%expect {| Version 1: Unit |}];
@@ -933,10 +933,10 @@ let%expect_test "print digests for all public RPCs" =
933933
{|
934934
Version 1:
935935
Request: Sexp
936-
Response: 443627a52ab5595206164d020ff01c56
936+
Response: d44d202638590f8f3709a0a59baf7b8d
937937
Version 2:
938938
Request: Sexp
939-
Response: 12995aa06697c01ef35c0339bd2fa29e
939+
Response: 274830a542b2a8af4ff618db0a4e5e5f
940940
|}];
941941
Decl.Request.print_generations (Procedures.Poll.poll Procedures.Poll.running_jobs);
942942
[%expect

test/expect-tests/dune_rpc_e2e/dune_rpc_diagnostics.ml

Lines changed: 90 additions & 89 deletions
Original file line numberDiff line numberDiff line change
@@ -703,118 +703,119 @@ let g = A.f
703703
let+ () = print_diagnostics poll in
704704
[%expect
705705
{|
706-
[ "Add"
707-
; [ [ "directory"; "$CWD" ]
708-
; [ "id"; "0" ]
709-
; [ "loc"
710-
; [ [ "start"
711-
; [ [ "pos_bol"; "0" ]
712-
; [ "pos_cnum"; "8" ]
713-
; [ "pos_fname"; "$CWD/foo.ml" ]
714-
; [ "pos_lnum"; "11" ]
715-
]
706+
[ "Add"
707+
; [ [ "directory"; "$CWD" ]
708+
; [ "id"; "0" ]
709+
; [ "loc"
710+
; [ [ "start"
711+
; [ [ "pos_bol"; "0" ]
712+
; [ "pos_cnum"; "8" ]
713+
; [ "pos_fname"; "$CWD/foo.ml" ]
714+
; [ "pos_lnum"; "11" ]
716715
]
717-
; [ "stop"
718-
; [ [ "pos_bol"; "0" ]
719-
; [ "pos_cnum"; "11" ]
720-
; [ "pos_fname"; "$CWD/foo.ml" ]
721-
; [ "pos_lnum"; "11" ]
722-
]
716+
]
717+
; [ "stop"
718+
; [ [ "pos_bol"; "0" ]
719+
; [ "pos_cnum"; "11" ]
720+
; [ "pos_fname"; "$CWD/foo.ml" ]
721+
; [ "pos_lnum"; "11" ]
723722
]
724723
]
725724
]
726-
; [ "message"; [ "Verbatim"; "foobar\n\
727-
" ] ]
728-
; [ "promotion"; [] ]
729-
; [ "related"; [] ]
730-
; [ "severity"; "error" ]
731-
; [ "targets"; [] ]
732725
]
726+
; [ "message"; [ "Verbatim"; "foobar\n\
727+
" ] ]
728+
; [ "promotion"; [] ]
729+
; [ "related"; [] ]
730+
; [ "severity"; "alert" ]
731+
; [ "targets"; [] ]
733732
]
734-
[ "Add"
735-
; [ [ "directory"; "$CWD" ]
736-
; [ "id"; "1" ]
737-
; [ "loc"
738-
; [ [ "start"
739-
; [ [ "pos_bol"; "0" ]
740-
; [ "pos_cnum"; "8" ]
741-
; [ "pos_fname"; "$CWD/foo.ml" ]
742-
; [ "pos_lnum"; "12" ]
743-
]
733+
]
734+
[ "Add"
735+
; [ [ "directory"; "$CWD" ]
736+
; [ "id"; "1" ]
737+
; [ "loc"
738+
; [ [ "start"
739+
; [ [ "pos_bol"; "0" ]
740+
; [ "pos_cnum"; "8" ]
741+
; [ "pos_fname"; "$CWD/foo.ml" ]
742+
; [ "pos_lnum"; "12" ]
744743
]
745-
; [ "stop"
746-
; [ [ "pos_bol"; "0" ]
747-
; [ "pos_cnum"; "11" ]
748-
; [ "pos_fname"; "$CWD/foo.ml" ]
749-
; [ "pos_lnum"; "12" ]
750-
]
744+
]
745+
; [ "stop"
746+
; [ [ "pos_bol"; "0" ]
747+
; [ "pos_cnum"; "11" ]
748+
; [ "pos_fname"; "$CWD/foo.ml" ]
749+
; [ "pos_lnum"; "12" ]
751750
]
752751
]
753752
]
754-
; [ "message"; [ "Verbatim"; "foobar\n\
755-
" ] ]
756-
; [ "promotion"; [] ]
757-
; [ "related"; [] ]
758-
; [ "severity"; "error" ]
759-
; [ "targets"; [] ]
760753
]
754+
; [ "message"; [ "Verbatim"; "foobar\n\
755+
" ] ]
756+
; [ "promotion"; [] ]
757+
; [ "related"; [] ]
758+
; [ "severity"; "alert" ]
759+
; [ "targets"; [] ]
761760
]
762-
[ "Add"
763-
; [ [ "directory"; "$CWD" ]
764-
; [ "id"; "2" ]
765-
; [ "loc"
766-
; [ [ "start"
767-
; [ [ "pos_bol"; "0" ]
768-
; [ "pos_cnum"; "4" ]
769-
; [ "pos_fname"; "$CWD/foo.ml" ]
770-
; [ "pos_lnum"; "11" ]
771-
]
761+
]
762+
[ "Add"
763+
; [ [ "directory"; "$CWD" ]
764+
; [ "id"; "2" ]
765+
; [ "loc"
766+
; [ [ "start"
767+
; [ [ "pos_bol"; "0" ]
768+
; [ "pos_cnum"; "4" ]
769+
; [ "pos_fname"; "$CWD/foo.ml" ]
770+
; [ "pos_lnum"; "11" ]
772771
]
773-
; [ "stop"
774-
; [ [ "pos_bol"; "0" ]
775-
; [ "pos_cnum"; "5" ]
776-
; [ "pos_fname"; "$CWD/foo.ml" ]
777-
; [ "pos_lnum"; "11" ]
778-
]
772+
]
773+
; [ "stop"
774+
; [ [ "pos_bol"; "0" ]
775+
; [ "pos_cnum"; "5" ]
776+
; [ "pos_fname"; "$CWD/foo.ml" ]
777+
; [ "pos_lnum"; "11" ]
779778
]
780779
]
781780
]
782-
; [ "message"; [ "Verbatim"; "unused value f.\n\
783-
" ] ]
784-
; [ "promotion"; [] ]
785-
; [ "related"; [] ]
786-
; [ "severity"; "error" ]
787-
; [ "targets"; [] ]
788781
]
782+
; [ "message"; [ "Verbatim"; "unused value f.\n\
783+
" ] ]
784+
; [ "promotion"; [] ]
785+
; [ "related"; [] ]
786+
; [ "severity"; "error" ]
787+
; [ "targets"; [] ]
789788
]
790-
[ "Add"
791-
; [ [ "directory"; "$CWD" ]
792-
; [ "id"; "3" ]
793-
; [ "loc"
794-
; [ [ "start"
795-
; [ [ "pos_bol"; "0" ]
796-
; [ "pos_cnum"; "4" ]
797-
; [ "pos_fname"; "$CWD/foo.ml" ]
798-
; [ "pos_lnum"; "12" ]
799-
]
789+
]
790+
[ "Add"
791+
; [ [ "directory"; "$CWD" ]
792+
; [ "id"; "3" ]
793+
; [ "loc"
794+
; [ [ "start"
795+
; [ [ "pos_bol"; "0" ]
796+
; [ "pos_cnum"; "4" ]
797+
; [ "pos_fname"; "$CWD/foo.ml" ]
798+
; [ "pos_lnum"; "12" ]
800799
]
801-
; [ "stop"
802-
; [ [ "pos_bol"; "0" ]
803-
; [ "pos_cnum"; "5" ]
804-
; [ "pos_fname"; "$CWD/foo.ml" ]
805-
; [ "pos_lnum"; "12" ]
806-
]
800+
]
801+
; [ "stop"
802+
; [ [ "pos_bol"; "0" ]
803+
; [ "pos_cnum"; "5" ]
804+
; [ "pos_fname"; "$CWD/foo.ml" ]
805+
; [ "pos_lnum"; "12" ]
807806
]
808807
]
809808
]
810-
; [ "message"; [ "Verbatim"; "unused value g.\n\
811-
" ] ]
812-
; [ "promotion"; [] ]
813-
; [ "related"; [] ]
814-
; [ "severity"; "error" ]
815-
; [ "targets"; [] ]
816809
]
817-
] |}])
810+
; [ "message"; [ "Verbatim"; "unused value g.\n\
811+
" ] ]
812+
; [ "promotion"; [] ]
813+
; [ "related"; [] ]
814+
; [ "severity"; "error" ]
815+
; [ "targets"; [] ]
816+
]
817+
]
818+
|}])
818819
;;
819820

820821
let%expect_test "cyclic dependency error simple" =

0 commit comments

Comments
 (0)