[infer] remove the concept of advice which does not seem to be used

Summary: The "advice" section of the error description does not seem to be used in practice.

Reviewed By: mbouaziz

Differential Revision: D7348815

fbshipit-source-id: 1d7c8c7
master
Jeremy Dubreil 7 years ago committed by Facebook Github Bot
parent c3184acd2e
commit 7851ae0389

@ -27,7 +27,7 @@ module Tags = struct
(* line where value was dereferenced *)
let escape_to = "escape_to"
(* expression wher a value escapes to *)
(* expression where a value escapes to *)
let line = "line"
(* 2nd Java type *)
@ -60,18 +60,16 @@ module Tags = struct
end
type error_desc =
{descriptions: string list; advice: string option; tags: Tags.t; dotty: string option}
{descriptions: string list; tags: Tags.t; dotty: string option}
[@@deriving compare]
(** empty error description *)
let no_desc : error_desc = {descriptions= []; advice= None; tags= []; dotty= None}
let no_desc : error_desc = {descriptions= []; tags= []; dotty= None}
(** verbatim desc from a string, not to be used for user-visible descs *)
let verbatim_desc s = {no_desc with descriptions= [s]}
let custom_desc_with_advice description advice tags =
{no_desc with descriptions= [description]; advice= Some advice; tags}
let custom_desc description tags = {no_desc with descriptions= [description]; tags}
(** pretty print an error description *)
let pp_error_desc fmt err_desc =
@ -740,7 +738,7 @@ let desc_retain_cycle cycle_str loc cycle_dotty =
Format.sprintf "Retain cycle %s involving the following objects:%s" (at_line tags loc)
cycle_str
in
{no_desc with descriptions= [desc]; tags= !tags; dotty= cycle_dotty}
{descriptions= [desc]; tags= !tags; dotty= cycle_dotty}
let registered_observer_being_deallocated_str obj_str =

@ -18,7 +18,7 @@ end
(** description field of error messages *)
type error_desc =
{descriptions: string list; advice: string option; tags: Tags.t; dotty: string option}
{descriptions: string list; tags: Tags.t; dotty: string option}
[@@deriving compare]
val no_desc : error_desc
@ -27,8 +27,8 @@ val no_desc : error_desc
val verbatim_desc : string -> error_desc
(** verbatim desc from a string, not to be used for user-visible descs *)
val custom_desc_with_advice : string -> string -> (string * string) list -> error_desc
(** verbatim desc with advice and custom tags *)
val custom_desc : string -> (string * string) list -> error_desc
(** verbatim desc with custom tags *)
module BucketLevel : sig
val b1 : string

@ -16,13 +16,11 @@ module F = Format
(** State that persists in the .specs files. *)
module ST = struct
let report_error tenv proc_name proc_desc kind loc ?(advice= None) ?(field_name= None)
?(origin_loc= None) ?(exception_kind= fun k d -> Exceptions.Checkers (k, d))
?(always_report= false) description =
let report_error tenv proc_name proc_desc kind loc ?(field_name= None) ?(origin_loc= None)
?(exception_kind= fun k d -> Exceptions.Checkers (k, d)) ?(always_report= false) description =
let lookup = Tenv.lookup tenv in
let localized_description =
Localise.custom_desc_with_advice description (Option.value ~default:"" advice)
[("always_report", string_of_bool always_report)]
Localise.custom_desc description [("always_report", string_of_bool always_report)]
in
let exn = exception_kind kind localized_description in
let proc_attributes = Specs.pdesc_resolve_attributes proc_desc in

@ -14,7 +14,7 @@ open! IStd
(** State that persists in the .specs files. *)
module ST : sig
val report_error :
Tenv.t -> Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t -> ?advice:string option
Tenv.t -> Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t
-> ?field_name:Typ.Fieldname.t option -> ?origin_loc:Location.t option
-> ?exception_kind:(IssueType.t -> Localise.error_desc -> exn) -> ?always_report:bool -> string
-> unit

@ -268,15 +268,14 @@ end
(* Strict *)
type st_report_error =
Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t -> ?advice:string option
-> ?field_name:Typ.Fieldname.t option -> ?origin_loc:Location.t option
-> ?exception_kind:(IssueType.t -> Localise.error_desc -> exn) -> ?always_report:bool -> string
-> unit
Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t -> ?field_name:Typ.Fieldname.t option
-> ?origin_loc:Location.t option -> ?exception_kind:(IssueType.t -> Localise.error_desc -> exn)
-> ?always_report:bool -> string -> unit
(** Report an error right now. *)
let report_error_now tenv (st_report_error: st_report_error) err_instance loc pdesc : unit =
let pname = Procdesc.get_proc_name pdesc in
let kind, description, advice, field_name, origin_loc =
let kind, description, field_name, origin_loc =
match err_instance with
| Condition_redundant (b, s_opt, nonnull) ->
let name =
@ -286,9 +285,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
( name
, P.sprintf "The condition %s is always %b according to the existing annotations."
(Option.value s_opt ~default:"") b
, Some
( "Consider adding a " ^ MF.monospaced_to_string "@Nullable"
^ " annotation or removing the redundant check." )
, None
, None )
| Field_not_initialized (fn, pn) ->
@ -306,7 +302,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
MF.pp_monospaced
(Typ.Fieldname.to_simplified_string fn)
constructor_name MF.pp_monospaced "@Nullable"
, None
, Some fn
, None )
| Field_not_mutable (fn, (origin_description, origin_loc, _)) ->
@ -315,7 +310,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Fieldname.to_simplified_string fn)
MF.pp_monospaced "@Mutable" origin_description
, None
, None
, origin_loc )
| Field_annotation_inconsistent (ann, fn, (origin_description, origin_loc, _)) ->
let kind_s, description =
@ -333,7 +327,7 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Fieldname.to_simplified_string fn)
MF.pp_monospaced "@Present" origin_description )
in
(kind_s, description, None, None, origin_loc)
(kind_s, description, None, origin_loc)
| Field_over_annotated (fn, pn) ->
let constructor_name =
if Typ.Procname.is_constructor pn then "the constructor"
@ -349,7 +343,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
MF.pp_monospaced
(Typ.Fieldname.to_simplified_string fn)
constructor_name MF.pp_monospaced "@Nullable"
, None
, Some fn
, None )
| Null_field_access (s_opt, fn, (origin_description, origin_loc, _), indexed) ->
@ -360,7 +353,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Fieldname.to_simplified_string fn)
origin_description
, None
, None
, origin_loc )
| Call_receiver_annotation_inconsistent (ann, s_opt, pn, (origin_description, origin_loc, _)) ->
let kind_s, description =
@ -378,7 +370,7 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Procname.to_simplified_string pn)
MF.pp_monospaced "@Present" origin_description )
in
(kind_s, description, None, None, origin_loc)
(kind_s, description, None, origin_loc)
| Parameter_annotation_inconsistent (ann, s, n, pn, _, (origin_desc, origin_loc, _)) ->
let kind_s, description =
match ann with
@ -397,7 +389,7 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Procname.to_simplified_string pn)
n MF.pp_monospaced s origin_desc )
in
(kind_s, description, None, None, origin_loc)
(kind_s, description, None, origin_loc)
| Return_annotation_inconsistent (ann, pn, (origin_description, origin_loc, _)) ->
let kind_s, description =
match ann with
@ -415,14 +407,13 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
(Typ.Procname.to_simplified_string pn)
MF.pp_monospaced "@Present" origin_description )
in
(kind_s, description, None, None, origin_loc)
(kind_s, description, None, origin_loc)
| Return_over_annotated pn ->
( IssueType.eradicate_return_over_annotated
, Format.asprintf "Method %a is annotated with %a but never returns null." MF.pp_monospaced
(Typ.Procname.to_simplified_string pn)
MF.pp_monospaced "@Nullable"
, None
, None
, None )
| Inconsistent_subclass_return_annotation (pn, opn) ->
( IssueType.eradicate_inconsistent_subclass_return_annotation
@ -432,7 +423,6 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
MF.pp_monospaced "@Nullable" MF.pp_monospaced
(Typ.Procname.to_simplified_string ~withclass:true opn)
, None
, None
, None )
| Inconsistent_subclass_parameter_annotation (param_name, pos, pn, opn) ->
let translate_position = function
@ -453,11 +443,10 @@ let report_error_now tenv (st_report_error: st_report_error) err_instance loc pd
MF.pp_monospaced "@Nullable" MF.pp_monospaced "@Nullable" MF.pp_monospaced
(Typ.Procname.to_simplified_string ~withclass:true opn)
, None
, None
, None )
in
let always_report = Strict.err_instance_get_strict tenv err_instance <> None in
st_report_error pname pdesc kind loc ~advice ~field_name ~origin_loc
st_report_error pname pdesc kind loc ~field_name ~origin_loc
~exception_kind:(fun k d -> Exceptions.Eradicate (k, d))
~always_report description

@ -73,10 +73,9 @@ type err_instance =
val node_reset_forall : Procdesc.Node.t -> unit
type st_report_error =
Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t -> ?advice:string option
-> ?field_name:Typ.Fieldname.t option -> ?origin_loc:Location.t option
-> ?exception_kind:(IssueType.t -> Localise.error_desc -> exn) -> ?always_report:bool -> string
-> unit
Typ.Procname.t -> Procdesc.t -> IssueType.t -> Location.t -> ?field_name:Typ.Fieldname.t option
-> ?origin_loc:Location.t option -> ?exception_kind:(IssueType.t -> Localise.error_desc -> exn)
-> ?always_report:bool -> string -> unit
val report_error :
Tenv.t -> st_report_error -> (Procdesc.Node.t -> Procdesc.Node.t) -> err_instance

Loading…
Cancel
Save