diff --git a/infer/src/IR/AccessPath.ml b/infer/src/IR/AccessPath.ml index b65b567cd..018a3715c 100644 --- a/infer/src/IR/AccessPath.ml +++ b/infer/src/IR/AccessPath.ml @@ -65,7 +65,7 @@ module Raw = struct let lookup_field_type_annot tenv base_typ field_name = let lookup = Tenv.lookup tenv in - Typ.Struct.get_field_type_and_annotation ~lookup field_name base_typ + Struct.get_field_type_and_annotation ~lookup field_name base_typ (* Get the type of an access, or None if the type cannot be determined *) diff --git a/infer/src/IR/Exp.ml b/infer/src/IR/Exp.ml index 5d76a5284..e87c73bd8 100644 --- a/infer/src/IR/Exp.ml +++ b/infer/src/IR/Exp.ml @@ -413,7 +413,7 @@ let rec ignore_integer_cast e = let rec get_java_class_initializer tenv = function | Lfield (Lvar pvar, fn, typ) when Pvar.is_global pvar -> ( - match Typ.Struct.get_field_type_and_annotation ~lookup:(Tenv.lookup tenv) fn typ with + match Struct.get_field_type_and_annotation ~lookup:(Tenv.lookup tenv) fn typ with | Some (field_typ, annot) when Annot.Item.is_final annot -> let java_class = Typ.JavaClass (Pvar.get_name pvar) in Some diff --git a/infer/src/IR/HilExp.ml b/infer/src/IR/HilExp.ml index db5ed8b5a..5b5d42ee0 100644 --- a/infer/src/IR/HilExp.ml +++ b/infer/src/IR/HilExp.ml @@ -259,7 +259,7 @@ module AccessExpression = struct let lookup_field_type_annot tenv base_typ field_name = let lookup = Tenv.lookup tenv in - Typ.Struct.get_field_type_and_annotation ~lookup field_name base_typ + Struct.get_field_type_and_annotation ~lookup field_name base_typ let rec get_typ t tenv : Typ.t option = diff --git a/infer/src/IR/ProcAttributes.ml b/infer/src/IR/ProcAttributes.ml index 99058a922..4ac36c922 100644 --- a/infer/src/IR/ProcAttributes.ml +++ b/infer/src/IR/ProcAttributes.ml @@ -11,7 +11,7 @@ open! IStd module F = Format (** Type for ObjC accessors *) -type objc_accessor_type = Objc_getter of Typ.Struct.field | Objc_setter of Typ.Struct.field +type objc_accessor_type = Objc_getter of Struct.field | Objc_setter of Struct.field [@@deriving compare] let kind_of_objc_accessor_type accessor = diff --git a/infer/src/IR/ProcAttributes.mli b/infer/src/IR/ProcAttributes.mli index 3beb8efd5..e17d81c51 100644 --- a/infer/src/IR/ProcAttributes.mli +++ b/infer/src/IR/ProcAttributes.mli @@ -9,7 +9,7 @@ open! IStd (** Attributes of a procedure. *) -type objc_accessor_type = Objc_getter of Typ.Struct.field | Objc_setter of Typ.Struct.field +type objc_accessor_type = Objc_getter of Struct.field | Objc_setter of Struct.field val kind_of_objc_accessor_type : objc_accessor_type -> string diff --git a/infer/src/IR/Procdesc.ml b/infer/src/IR/Procdesc.ml index 63e635d43..e28fb9c06 100644 --- a/infer/src/IR/Procdesc.ml +++ b/infer/src/IR/Procdesc.ml @@ -730,9 +730,9 @@ let pp_variable_list fmt etl = let pp_objc_accessor fmt accessor = match accessor with | Some (ProcAttributes.Objc_getter field) -> - Format.fprintf fmt "Getter of %a, " (Typ.Struct.pp_field Pp.text) field + Format.fprintf fmt "Getter of %a, " (Struct.pp_field Pp.text) field | Some (ProcAttributes.Objc_setter field) -> - Format.fprintf fmt "Setter of %a, " (Typ.Struct.pp_field Pp.text) field + Format.fprintf fmt "Setter of %a, " (Struct.pp_field Pp.text) field | None -> () diff --git a/infer/src/IR/Struct.ml b/infer/src/IR/Struct.ml new file mode 100644 index 000000000..3ff8def02 --- /dev/null +++ b/infer/src/IR/Struct.ml @@ -0,0 +1,146 @@ +(* + * Copyright (c) Facebook, Inc. and its affiliates. + * + * This source code is licensed under the MIT license found in the + * LICENSE file in the root directory of this source tree. + *) + +open! IStd +module F = Format + +type field = Typ.Fieldname.t * Typ.t * Annot.Item.t [@@deriving compare] + +type fields = field list + +(** Type for a structured value. *) +type t = + { fields: fields (** non-static fields *) + ; statics: fields (** static fields *) + ; supers: Typ.Name.t list (** superclasses *) + ; methods: Typ.Procname.t list (** methods defined *) + ; exported_objc_methods: Typ.Procname.t list + (** methods in ObjC interface, subset of [methods] *) + ; annots: Annot.Item.t (** annotations *) + ; dummy: bool (** dummy struct for class including static method *) } + +type lookup = Typ.Name.t -> t option + +let pp_field pe f (field_name, typ, ann) = + F.fprintf f "@\n\t\t%a %a %a" (Typ.pp_full pe) typ Typ.Fieldname.pp field_name Annot.Item.pp ann + + +let pp pe name f {fields; supers; methods; exported_objc_methods; annots} = + if Config.debug_mode then + (* change false to true to print the details of struct *) + F.fprintf f + "%a @\n\ + \tfields: {%a@\n\ + \t}@\n\ + \tsupers: {%a@\n\ + \t}@\n\ + \tmethods: {%a@\n\ + \t}@\n\ + \texported_obj_methods: {%a@\n\ + \t}@\n\ + \tannots: {%a@\n\ + \t}" + Typ.Name.pp name + (Pp.seq (pp_field pe)) + fields + (Pp.seq (fun f n -> F.fprintf f "@\n\t\t%a" Typ.Name.pp n)) + supers + (Pp.seq (fun f m -> F.fprintf f "@\n\t\t%a" Typ.Procname.pp m)) + methods + (Pp.seq (fun f m -> F.fprintf f "@\n\t\t%a" Typ.Procname.pp m)) + exported_objc_methods Annot.Item.pp annots + else Typ.Name.pp f name + + +let internal_mk_struct ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots + ?dummy () = + let default_ = + { fields= [] + ; statics= [] + ; methods= [] + ; exported_objc_methods= [] + ; supers= [] + ; annots= Annot.Item.empty + ; dummy= false } + in + let mk_struct_ ?(default = default_) ?(fields = default.fields) ?(statics = default.statics) + ?(methods = default.methods) ?(exported_objc_methods = default.exported_objc_methods) + ?(supers = default.supers) ?(annots = default.annots) ?(dummy = default.dummy) () = + {fields; statics; methods; exported_objc_methods; supers; annots; dummy} + in + mk_struct_ ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots ?dummy () + + +(** the element typ of the final extensible array in the given typ, if any *) +let rec get_extensible_array_element_typ ~lookup (typ : Typ.t) = + match typ.desc with + | Tarray {elt} -> + Some elt + | Tstruct name -> ( + match lookup name with + | Some {fields} -> ( + match List.last fields with + | Some (_, fld_typ, _) -> + get_extensible_array_element_typ ~lookup fld_typ + | None -> + None ) + | None -> + None ) + | _ -> + None + + +(** If a struct type with field f, return the type of f. If not, return the default *) +let fld_typ ~lookup ~default fn (typ : Typ.t) = + (* Note: would be nice migrate it to get_field_info + (for that one needs to ensure adding Tptr to pattern match does not break thing) *) + match typ.desc with + | Tstruct name -> ( + match lookup name with + | Some {fields} -> + List.find ~f:(fun (f, _, _) -> Typ.Fieldname.equal f fn) fields + |> Option.value_map ~f:snd3 ~default + | None -> + default ) + | _ -> + default + + +type field_info = {typ: Typ.t; annotations: Annot.Item.t; is_static: bool} + +let find_field field_list field_name_to_lookup = + List.find_map + ~f:(fun (field_name, typ, annotations) -> + if Typ.Fieldname.equal field_name field_name_to_lookup then Some (typ, annotations) else None + ) + field_list + + +let get_field_info ~lookup field_name_to_lookup (typ : Typ.t) = + let find_field_info field_list ~is_static = + find_field field_list field_name_to_lookup + |> Option.map ~f:(fun (typ, annotations) -> {typ; annotations; is_static}) + in + match typ.desc with + | Tstruct name | Tptr ({desc= Tstruct name}, _) -> ( + match lookup name with + | Some {fields= non_statics; statics} -> + (* Search in both lists and return the first found *) + find_field_info statics ~is_static:true + |> IOption.if_none_evalopt ~f:(fun () -> find_field_info non_statics ~is_static:false) + | None -> + None ) + | _ -> + None + + +let get_field_type_and_annotation ~lookup field_name_to_lookup typ = + get_field_info ~lookup field_name_to_lookup typ + |> Option.map ~f:(fun {typ; annotations} -> (typ, annotations)) + + +let is_dummy {dummy} = dummy diff --git a/infer/src/IR/Struct.mli b/infer/src/IR/Struct.mli new file mode 100644 index 000000000..79c562574 --- /dev/null +++ b/infer/src/IR/Struct.mli @@ -0,0 +1,63 @@ +(* + * Copyright (c) 2009-2013, Monoidics ltd. + * Copyright (c) Facebook, Inc. and its affiliates. + * + * This source code is licensed under the MIT license found in the + * LICENSE file in the root directory of this source tree. + *) + +open! IStd +module F = Format + +type field = Typ.Fieldname.t * Typ.t * Annot.Item.t [@@deriving compare] + +type fields = field list + +(** Type for a structured value. *) +type t = private + { fields: fields (** non-static fields *) + ; statics: fields (** static fields *) + ; supers: Typ.Name.t list (** supers *) + ; methods: Typ.Procname.t list (** methods defined *) + ; exported_objc_methods: Typ.Procname.t list + (** methods in ObjC interface, subset of [methods] *) + ; annots: Annot.Item.t (** annotations *) + ; dummy: bool (** dummy struct for class including static method *) } + +type lookup = Typ.Name.t -> t option + +val pp_field : Pp.env -> F.formatter -> field -> unit + +val pp : Pp.env -> Typ.Name.t -> F.formatter -> t -> unit +(** Pretty print a struct type. *) + +val internal_mk_struct : + ?default:t + -> ?fields:fields + -> ?statics:fields + -> ?methods:Typ.Procname.t list + -> ?exported_objc_methods:Typ.Procname.t list + -> ?supers:Typ.Name.t list + -> ?annots:Annot.Item.t + -> ?dummy:bool + -> unit + -> t +(** Construct a struct_typ, normalizing field types *) + +val get_extensible_array_element_typ : lookup:lookup -> Typ.t -> Typ.t option +(** the element typ of the final extensible array in the given typ, if any *) + +type field_info = {typ: Typ.t; annotations: Annot.Item.t; is_static: bool} + +val get_field_info : lookup:lookup -> Typ.Fieldname.t -> Typ.t -> field_info option +(** Lookup for info associated with the field [fn]. None if [typ] has no field named [fn] *) + +val fld_typ : lookup:lookup -> default:Typ.t -> Typ.Fieldname.t -> Typ.t -> Typ.t +(** If a struct type with field f, return the type of f. If not, return the default type if given, + otherwise raise an exception *) + +val get_field_type_and_annotation : + lookup:lookup -> Typ.Fieldname.t -> Typ.t -> (Typ.t * Annot.Item.t) option +(** Return the type of the field [fn] and its annotation, None if [typ] has no field named [fn] *) + +val is_dummy : t -> bool diff --git a/infer/src/IR/Tenv.ml b/infer/src/IR/Tenv.ml index 933d60dcd..5b9b640cd 100644 --- a/infer/src/IR/Tenv.ml +++ b/infer/src/IR/Tenv.ml @@ -15,13 +15,13 @@ module TypenameHash = Caml.Hashtbl.Make (Typ.Name) module TypenameHashNormalizer = MaximumSharing.ForHashtbl (TypenameHash) (** Type for type environment. *) -type t = Typ.Struct.t TypenameHash.t +type t = Struct.t TypenameHash.t let pp fmt (tenv : t) = TypenameHash.iter (fun name typ -> Format.fprintf fmt "@[<6>NAME: %s@]@," (Typ.Name.to_string name) ; - Format.fprintf fmt "@[<6>TYPE: %a@]@," (Typ.Struct.pp Pp.text name) typ ) + Format.fprintf fmt "@[<6>TYPE: %a@]@," (Struct.pp Pp.text name) typ ) tenv @@ -32,7 +32,7 @@ let create () = TypenameHash.create 1000 let mk_struct tenv ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots ?dummy name = let struct_typ = - Typ.Struct.internal_mk_struct ?default ?fields ?statics ?methods ?exported_objc_methods ?supers + Struct.internal_mk_struct ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots ?dummy () in TypenameHash.replace tenv name struct_typ ; @@ -40,7 +40,7 @@ let mk_struct tenv ?default ?fields ?statics ?methods ?exported_objc_methods ?su (** Look up a name in the global type environment. *) -let lookup tenv name : Typ.Struct.t option = +let lookup tenv name : Struct.t option = try Some (TypenameHash.find tenv name) with Caml.Not_found -> ( (* ToDo: remove the following additional lookups once C/C++ interop is resolved *) @@ -103,7 +103,7 @@ end let merge ~src ~dst = TypenameHash.iter (fun pname cfg -> - if (not (Typ.Struct.is_dummy cfg)) || not (TypenameHash.mem dst pname) then + if (not (Struct.is_dummy cfg)) || not (TypenameHash.mem dst pname) then TypenameHash.replace dst pname cfg ) src diff --git a/infer/src/IR/Tenv.mli b/infer/src/IR/Tenv.mli index e97ebdf01..253dd9c87 100644 --- a/infer/src/IR/Tenv.mli +++ b/infer/src/IR/Tenv.mli @@ -29,24 +29,24 @@ val load_global : unit -> t option val store_global : t -> unit (** save a global type environment (Java) *) -val lookup : t -> Typ.Name.t -> Typ.Struct.t option +val lookup : t -> Typ.Name.t -> Struct.t option (** Look up a name in the global type environment. *) val mk_struct : t - -> ?default:Typ.Struct.t - -> ?fields:Typ.Struct.fields - -> ?statics:Typ.Struct.fields + -> ?default:Struct.t + -> ?fields:Struct.fields + -> ?statics:Struct.fields -> ?methods:Typ.Procname.t list -> ?exported_objc_methods:Typ.Procname.t list -> ?supers:Typ.Name.t list -> ?annots:Annot.Item.t -> ?dummy:bool -> Typ.Name.t - -> Typ.Struct.t + -> Struct.t (** Construct a struct_typ, normalizing field types *) -val add_field : t -> Typ.Name.t -> Typ.Struct.field -> unit +val add_field : t -> Typ.Name.t -> Struct.field -> unit (** Add a field to a given struct in the global type environment. *) val pp : Format.formatter -> t -> unit [@@warning "-32"] diff --git a/infer/src/IR/Typ.ml b/infer/src/IR/Typ.ml index c7c5db42f..db909e77e 100644 --- a/infer/src/IR/Typ.ml +++ b/infer/src/IR/Typ.ml @@ -1477,140 +1477,3 @@ module Fieldname = struct (last_char >= '0' && last_char <= '9') && String.is_suffix field_name ~suffix:(this ^ String.of_char last_char) end - -module Struct = struct - type field = Fieldname.t * T.t * Annot.Item.t [@@deriving compare] - - type fields = field list - - (** Type for a structured value. *) - type t = - { fields: fields (** non-static fields *) - ; statics: fields (** static fields *) - ; supers: Name.t list (** superclasses *) - ; methods: Procname.t list (** methods defined *) - ; exported_objc_methods: Procname.t list (** methods in ObjC interface, subset of [methods] *) - ; annots: Annot.Item.t (** annotations *) - ; dummy: bool (** dummy struct for class including static method *) } - - type lookup = Name.t -> t option - - let pp_field pe f (field_name, typ, ann) = - F.fprintf f "@\n\t\t%a %a %a" (pp_full pe) typ Fieldname.pp field_name Annot.Item.pp ann - - - let pp pe name f {fields; supers; methods; exported_objc_methods; annots} = - if Config.debug_mode then - (* change false to true to print the details of struct *) - F.fprintf f - "%a @\n\ - \tfields: {%a@\n\ - \t}@\n\ - \tsupers: {%a@\n\ - \t}@\n\ - \tmethods: {%a@\n\ - \t}@\n\ - \texported_obj_methods: {%a@\n\ - \t}@\n\ - \tannots: {%a@\n\ - \t}" - Name.pp name - (Pp.seq (pp_field pe)) - fields - (Pp.seq (fun f n -> F.fprintf f "@\n\t\t%a" Name.pp n)) - supers - (Pp.seq (fun f m -> F.fprintf f "@\n\t\t%a" Procname.pp m)) - methods - (Pp.seq (fun f m -> F.fprintf f "@\n\t\t%a" Procname.pp m)) - exported_objc_methods Annot.Item.pp annots - else Name.pp f name - - - let internal_mk_struct ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots - ?dummy () = - let default_ = - { fields= [] - ; statics= [] - ; methods= [] - ; exported_objc_methods= [] - ; supers= [] - ; annots= Annot.Item.empty - ; dummy= false } - in - let mk_struct_ ?(default = default_) ?(fields = default.fields) ?(statics = default.statics) - ?(methods = default.methods) ?(exported_objc_methods = default.exported_objc_methods) - ?(supers = default.supers) ?(annots = default.annots) ?(dummy = default.dummy) () = - {fields; statics; methods; exported_objc_methods; supers; annots; dummy} - in - mk_struct_ ?default ?fields ?statics ?methods ?exported_objc_methods ?supers ?annots ?dummy () - - - (** the element typ of the final extensible array in the given typ, if any *) - let rec get_extensible_array_element_typ ~lookup (typ : T.t) = - match typ.desc with - | Tarray {elt} -> - Some elt - | Tstruct name -> ( - match lookup name with - | Some {fields} -> ( - match List.last fields with - | Some (_, fld_typ, _) -> - get_extensible_array_element_typ ~lookup fld_typ - | None -> - None ) - | None -> - None ) - | _ -> - None - - - (** If a struct type with field f, return the type of f. If not, return the default *) - let fld_typ ~lookup ~default fn (typ : T.t) = - (* Note: would be nice migrate it to get_field_info - (for that one needs to ensure adding Tptr to pattern match does not break thing) *) - match typ.desc with - | Tstruct name -> ( - match lookup name with - | Some {fields} -> - List.find ~f:(fun (f, _, _) -> Fieldname.equal f fn) fields - |> Option.value_map ~f:snd3 ~default - | None -> - default ) - | _ -> - default - - - type field_info = {typ: typ; annotations: Annot.Item.t; is_static: bool} - - let find_field field_list field_name_to_lookup = - List.find_map - ~f:(fun (field_name, typ, annotations) -> - if Fieldname.equal field_name field_name_to_lookup then Some (typ, annotations) else None ) - field_list - - - let get_field_info ~lookup field_name_to_lookup (typ : T.t) = - let find_field_info field_list ~is_static = - find_field field_list field_name_to_lookup - |> Option.map ~f:(fun (typ, annotations) -> {typ; annotations; is_static}) - in - match typ.desc with - | Tstruct name | Tptr ({desc= Tstruct name}, _) -> ( - match lookup name with - | Some {fields= non_statics; statics} -> - (* Search in both lists and return the first found *) - find_field_info statics ~is_static:true - |> IOption.if_none_evalopt ~f:(fun () -> find_field_info non_statics ~is_static:false) - | None -> - None ) - | _ -> - None - - - let get_field_type_and_annotation ~lookup field_name_to_lookup typ = - get_field_info ~lookup field_name_to_lookup typ - |> Option.map ~f:(fun {typ; annotations} -> (typ, annotations)) - - - let is_dummy {dummy} = dummy -end diff --git a/infer/src/IR/Typ.mli b/infer/src/IR/Typ.mli index e6d35bef7..e2b15fbba 100644 --- a/infer/src/IR/Typ.mli +++ b/infer/src/IR/Typ.mli @@ -672,57 +672,3 @@ module Fieldname : sig val pp : Format.formatter -> t -> unit (** Pretty print a field name. *) end - -module Struct : sig - type field = Fieldname.t * typ * Annot.Item.t [@@deriving compare] - - type fields = field list - - (** Type for a structured value. *) - type t = private - { fields: fields (** non-static fields *) - ; statics: fields (** static fields *) - ; supers: Name.t list (** supers *) - ; methods: Procname.t list (** methods defined *) - ; exported_objc_methods: Procname.t list (** methods in ObjC interface, subset of [methods] *) - ; annots: Annot.Item.t (** annotations *) - ; dummy: bool (** dummy struct for class including static method *) } - - type lookup = Name.t -> t option - - val pp_field : Pp.env -> F.formatter -> field -> unit - - val pp : Pp.env -> Name.t -> F.formatter -> t -> unit - (** Pretty print a struct type. *) - - val internal_mk_struct : - ?default:t - -> ?fields:fields - -> ?statics:fields - -> ?methods:Procname.t list - -> ?exported_objc_methods:Procname.t list - -> ?supers:Name.t list - -> ?annots:Annot.Item.t - -> ?dummy:bool - -> unit - -> t - (** Construct a struct_typ, normalizing field types *) - - val get_extensible_array_element_typ : lookup:lookup -> typ -> typ option - (** the element typ of the final extensible array in the given typ, if any *) - - type field_info = {typ: typ; annotations: Annot.Item.t; is_static: bool} - - val get_field_info : lookup:lookup -> Fieldname.t -> typ -> field_info option - (** Lookup for info associated with the field [fn]. None if [typ] has no field named [fn] *) - - val fld_typ : lookup:lookup -> default:typ -> Fieldname.t -> typ -> typ - (** If a struct type with field f, return the type of f. - If not, return the default type if given, otherwise raise an exception *) - - val get_field_type_and_annotation : - lookup:lookup -> Fieldname.t -> typ -> (typ * Annot.Item.t) option - (** Return the type of the field [fn] and its annotation, None if [typ] has no field named [fn] *) - - val is_dummy : t -> bool -end diff --git a/infer/src/absint/PatternMatch.ml b/infer/src/absint/PatternMatch.ml index c2cea83ac..d35181458 100644 --- a/infer/src/absint/PatternMatch.ml +++ b/infer/src/absint/PatternMatch.ml @@ -348,7 +348,7 @@ let override_find ?(check_current_type = true) f tenv proc_name = let is_override = Staged.unstage (is_override_of proc_name) in let rec find_super_type super_class_name = Tenv.lookup tenv super_class_name - |> Option.bind ~f:(fun {Typ.Struct.methods; supers} -> + |> Option.bind ~f:(fun {Struct.methods; supers} -> match List.find ~f:(fun pname -> is_override pname && f pname) methods with | None -> List.find_map ~f:find_super_type supers @@ -422,7 +422,7 @@ let is_java_enum tenv typename = is_subtype_of_str tenv typename "java.lang.Enum for supertypes*) let check_class_attributes check tenv = function | Typ.Procname.Java java_pname -> - let check_class_annots _ {Typ.Struct.annots} = check annots in + let check_class_annots _ {Struct.annots} = check annots in supertype_exists tenv check_class_annots (Typ.Procname.Java.get_class_type_name java_pname) | _ -> false diff --git a/infer/src/absint/PatternMatch.mli b/infer/src/absint/PatternMatch.mli index d0a948a62..aabb8ccba 100644 --- a/infer/src/absint/PatternMatch.mli +++ b/infer/src/absint/PatternMatch.mli @@ -94,7 +94,7 @@ val implements_android : string -> Tenv.t -> string -> bool val implements_xmob_utils : string -> Tenv.t -> string -> bool (** Check whether class implements a class of xmod.utils *) -val supertype_exists : Tenv.t -> (Typ.Name.t -> Typ.Struct.t -> bool) -> Typ.Name.t -> bool +val supertype_exists : Tenv.t -> (Typ.Name.t -> Struct.t -> bool) -> Typ.Name.t -> bool (** Holds iff the predicate holds on a supertype of the named type, including the type itself *) val supertype_find_map_opt : Tenv.t -> (Typ.Name.t -> 'a option) -> Typ.Name.t -> 'a option diff --git a/infer/src/backend/reporting.ml b/infer/src/backend/reporting.ml index 78b5bd158..39124da19 100644 --- a/infer/src/backend/reporting.ml +++ b/infer/src/backend/reporting.ml @@ -145,7 +145,7 @@ let is_suppressed ?(field_name = None) tenv proc_desc kind = let is_field_suppressed () = match (field_name, PatternMatch.get_this_type_nonstatic_methods_only proc_attributes) with | Some field_name, Some t -> ( - match Typ.Struct.get_field_type_and_annotation ~lookup field_name t with + match Struct.get_field_type_and_annotation ~lookup field_name t with | Some (_, ia) -> Annotations.ia_has_annotation_with ia annotation_matches | None -> diff --git a/infer/src/biabduction/Absarray.ml b/infer/src/biabduction/Absarray.ml index 19763dc0d..70df17067 100644 --- a/infer/src/biabduction/Absarray.ml +++ b/infer/src/biabduction/Absarray.ml @@ -613,7 +613,7 @@ let check_after_array_abstraction tenv prop = | Predicates.Estruct (fsel, _) -> List.iter ~f:(fun (f, se) -> - let typ_f = Typ.Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f typ in + let typ_f = Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f typ in check_se root (offs @ [Predicates.Off_fld (f, typ)]) typ_f se ) fsel in diff --git a/infer/src/biabduction/Prop.ml b/infer/src/biabduction/Prop.ml index d7b752331..685334503 100644 --- a/infer/src/biabduction/Prop.ml +++ b/infer/src/biabduction/Prop.ml @@ -835,7 +835,7 @@ module Normalize = struct (* test if the extensible array at the end of [typ] has elements of type [elt] *) let extensible_array_element_typ_equal elt typ = Option.value_map ~f:(Typ.equal elt) ~default:false - (Typ.Struct.get_extensible_array_element_typ ~lookup typ) + (Struct.get_extensible_array_element_typ ~lookup typ) in match (e1', e2') with (* pattern for arrays and extensible structs: diff --git a/infer/src/biabduction/Prover.ml b/infer/src/biabduction/Prover.ml index 2a24f870f..826e44919 100644 --- a/infer/src/biabduction/Prover.ml +++ b/infer/src/biabduction/Prover.ml @@ -429,7 +429,7 @@ end = struct | Predicates.Estruct (fsel, _), t -> let get_field_type f = Option.bind t ~f:(fun t' -> - Option.map ~f:fst @@ Typ.Struct.get_field_type_and_annotation ~lookup f t' ) + Option.map ~f:fst @@ Struct.get_field_type_and_annotation ~lookup f t' ) in List.iter ~f:(fun (f, se) -> strexp_extract (se, get_field_type f)) fsel | Predicates.Earray (len, isel, _), t -> @@ -1520,8 +1520,8 @@ let rec sexp_imply tenv source calc_index_frame calc_missing subs se1 se2 typ2 : let se2' = Predicates.Earray (len, [(Exp.zero, se2)], inst) in let typ2' = Typ.mk_array typ2 in (* In the sexp_imply, struct_imply, array_imply, and sexp_imply_nolhs functions, the typ2 - argument is only used by eventually passing its value to Typ.Struct.fld, Exp.Lfield, - Typ.Struct.fld, or Typ.array_elem. None of these are sensitive to the length field + argument is only used by eventually passing its value to Struct.fld, Exp.Lfield, + Struct.fld, or Typ.array_elem. None of these are sensitive to the length field of Tarray, so forgetting the length of typ2' here is not a problem. Not one of those functions use typ.quals either *) sexp_imply tenv source true calc_missing subs se1 se2' typ2' @@ -1541,7 +1541,7 @@ and struct_imply tenv source calc_missing subs fsel1 fsel2 typ2 : | (f1, se1) :: fsel1', (f2, se2) :: fsel2' -> ( match Typ.Fieldname.compare f1 f2 with | 0 -> - let typ' = Typ.Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in + let typ' = Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in let subs', se_frame, se_missing = sexp_imply tenv (Exp.Lfield (source, f2, typ2)) false calc_missing subs se1 se2 typ' in @@ -1561,7 +1561,7 @@ and struct_imply tenv source calc_missing subs fsel1 fsel2 typ2 : in (subs', (f1, se1) :: fld_frame, fld_missing) | _ -> - let typ' = Typ.Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in + let typ' = Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in let subs' = sexp_imply_nolhs tenv (Exp.Lfield (source, f2, typ2)) calc_missing subs se2 typ' in @@ -1571,7 +1571,7 @@ and struct_imply tenv source calc_missing subs fsel1 fsel2 typ2 : let fld_missing' = (f2, se2) :: fld_missing in (subs', fld_frame, fld_missing') ) | [], (f2, se2) :: fsel2' -> - let typ' = Typ.Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in + let typ' = Struct.fld_typ ~lookup ~default:(Typ.mk Tvoid) f2 typ2 in let subs' = sexp_imply_nolhs tenv (Exp.Lfield (source, f2, typ2)) calc_missing subs se2 typ' in diff --git a/infer/src/biabduction/Rearrange.ml b/infer/src/biabduction/Rearrange.ml index 0b882524e..d20a37bd9 100644 --- a/infer/src/biabduction/Rearrange.ml +++ b/infer/src/biabduction/Rearrange.ml @@ -115,7 +115,7 @@ let rec create_struct_values pname tenv orig_prop footprint_part kind max_stamp if Typ.Fieldname.equal f f' then (f, res_t', a') else (f', t', a') in let fields' = - List.sort ~compare:Typ.Struct.compare_field (List.map ~f:replace_typ_of_f fields) + List.sort ~compare:Struct.compare_field (List.map ~f:replace_typ_of_f fields) in ignore (Tenv.mk_struct tenv ~default:struct_typ ~fields:fields' name) ; (atoms', se, t) @@ -223,7 +223,7 @@ let rec strexp_extend_values_ pname tenv orig_prop footprint_part kind max_stamp if Typ.Fieldname.equal f f1 then (f1, res_typ', a1) else fta1 in let fields' = - List.sort ~compare:Typ.Struct.compare_field (List.map ~f:replace_fta fields) + List.sort ~compare:Struct.compare_field (List.map ~f:replace_fta fields) in ignore (Tenv.mk_struct tenv ~default:struct_typ ~fields:fields' name) ; (res_atoms', Predicates.Estruct (res_fsel', inst'), typ) :: acc @@ -240,7 +240,7 @@ let rec strexp_extend_values_ pname tenv orig_prop footprint_part kind max_stamp if Typ.Fieldname.equal f' f then (f, res_typ', a') else (f', t', a') in let fields' = - List.sort ~compare:Typ.Struct.compare_field (List.map ~f:replace_fta fields) + List.sort ~compare:Struct.compare_field (List.map ~f:replace_fta fields) in ignore (Tenv.mk_struct tenv ~default:struct_typ ~fields:fields' name) ; [(atoms', Predicates.Estruct (res_fsel', inst'), typ)] ) @@ -776,7 +776,7 @@ let add_guarded_by_constraints tenv prop lexp pdesc = in (* if [fld] is annotated with @GuardedBy("mLock"), return mLock *) let get_guarded_by_fld_str fld typ = - match Typ.Struct.get_field_type_and_annotation ~lookup fld typ with + match Struct.get_field_type_and_annotation ~lookup fld typ with | Some (_, item_annot) -> ( match extract_guarded_by_str item_annot with | Some "this" -> @@ -797,7 +797,7 @@ let add_guarded_by_constraints tenv prop lexp pdesc = in let get_fld_strexp_and_typ typ f flds = let match_one (fld, strexp) = - match Typ.Struct.get_field_type_and_annotation ~lookup fld typ with + match Struct.get_field_type_and_annotation ~lookup fld typ with | Some (fld_typ, _) when f fld fld_typ -> Some (strexp, fld_typ) | _ -> @@ -1482,7 +1482,7 @@ let attr_has_annot is_annotation tenv prop exp = let is_strexp_pt_fld_with_annot tenv obj_str is_annotation typ deref_exp (fld, strexp) = let lookup = Tenv.lookup tenv in let fld_has_annot fld = - match Typ.Struct.get_field_type_and_annotation ~lookup fld typ with + match Struct.get_field_type_and_annotation ~lookup fld typ with | Some (_, annot) -> is_annotation annot | _ -> diff --git a/infer/src/biabduction/Tabulation.ml b/infer/src/biabduction/Tabulation.ml index 7a8ecbd10..c03928ad8 100644 --- a/infer/src/biabduction/Tabulation.ml +++ b/infer/src/biabduction/Tabulation.ml @@ -1088,8 +1088,7 @@ let check_uninitialize_dangling_deref caller_pname tenv callee_pname actual_pre let missing_sigma_need_adding_to_tenv tenv hpreds = let field_is_missing struc (field, _) = - not - (List.exists struc.Typ.Struct.fields ~f:(fun (fname, _, _) -> Typ.Fieldname.equal fname field)) + not (List.exists struc.Struct.fields ~f:(fun (fname, _, _) -> Typ.Fieldname.equal fname field)) in let missing_hpred_need_adding_to_tenv hpred = match hpred with diff --git a/infer/src/bufferoverrun/bufferOverrunOndemandEnv.ml b/infer/src/bufferoverrun/bufferOverrunOndemandEnv.ml index 14ecebf7f..ec101a480 100644 --- a/infer/src/bufferoverrun/bufferOverrunOndemandEnv.ml +++ b/infer/src/bufferoverrun/bufferOverrunOndemandEnv.ml @@ -57,7 +57,7 @@ let mk pdesc = match BufferOverrunField.get_type fn with | None -> let lookup = Tenv.lookup tenv in - Option.map (typ_of_param_path x) ~f:(Typ.Struct.fld_typ ~lookup ~default:Typ.void fn) + Option.map (typ_of_param_path x) ~f:(Struct.fld_typ ~lookup ~default:Typ.void fn) | some_typ -> some_typ ) | SPath.StarField {last_field} -> @@ -65,7 +65,7 @@ let mk pdesc = | SPath.Callsite {ret_typ} -> Some ret_typ in - let is_last_field fn (fields : Typ.Struct.field list) = + let is_last_field fn (fields : Struct.field list) = Option.value_map (List.last fields) ~default:false ~f:(fun (last_fn, _, _) -> Typ.Fieldname.equal fn last_fn ) in @@ -79,7 +79,7 @@ let mk pdesc = | Tstruct typename -> let opt_struct = Tenv.lookup tenv typename in Option.value_map opt_struct ~default:false ~f:(fun str -> - is_last_field fn str.Typ.Struct.fields ) + is_last_field fn str.Struct.fields ) | _ -> true ) in diff --git a/infer/src/bufferoverrun/bufferOverrunUtils.ml b/infer/src/bufferoverrun/bufferOverrunUtils.ml index e6caa6349..04f47b009 100644 --- a/infer/src/bufferoverrun/bufferOverrunUtils.ml +++ b/infer/src/bufferoverrun/bufferOverrunUtils.ml @@ -136,7 +136,7 @@ module Exec = struct match Tenv.lookup tenv typename with | Some str -> let f = init_field path locs (dimension + 1) in - IList.fold_last ~f ~f_last:(f ?dyn_length) ~init:(mem, 1) str.Typ.Struct.fields |> fst + IList.fold_last ~f ~f_last:(f ?dyn_length) ~init:(mem, 1) str.Struct.fields |> fst | None -> mem ) | _ -> diff --git a/infer/src/checkers/annotations.ml b/infer/src/checkers/annotations.ml index 05557eb8e..4f55187e6 100644 --- a/infer/src/checkers/annotations.ml +++ b/infer/src/checkers/annotations.ml @@ -162,7 +162,7 @@ let pname_has_return_annot pname ~attrs_of_pname predicate = false -let field_has_annot fieldname (struct_typ : Typ.Struct.t) predicate = +let field_has_annot fieldname (struct_typ : Struct.t) predicate = let fld_has_taint_annot (fname, _, annot) = Typ.Fieldname.equal fieldname fname && predicate annot in @@ -170,7 +170,7 @@ let field_has_annot fieldname (struct_typ : Typ.Struct.t) predicate = || List.exists ~f:fld_has_taint_annot struct_typ.statics -let struct_typ_has_annot (struct_typ : Typ.Struct.t) predicate = predicate struct_typ.annots +let struct_typ_has_annot (struct_typ : Struct.t) predicate = predicate struct_typ.annots let ia_is_not_thread_safe ia = ia_ends_with ia not_thread_safe diff --git a/infer/src/checkers/annotations.mli b/infer/src/checkers/annotations.mli index 1e43e77d7..69ca97175 100644 --- a/infer/src/checkers/annotations.mli +++ b/infer/src/checkers/annotations.mli @@ -132,7 +132,7 @@ val pdesc_return_annot_ends_with : Procdesc.t -> string -> bool val ma_has_annotation_with : Annot.Method.t -> (Annot.t -> bool) -> bool -val field_has_annot : Typ.Fieldname.t -> Typ.Struct.t -> (Annot.Item.t -> bool) -> bool +val field_has_annot : Typ.Fieldname.t -> Struct.t -> (Annot.Item.t -> bool) -> bool -val struct_typ_has_annot : Typ.Struct.t -> (Annot.Item.t -> bool) -> bool +val struct_typ_has_annot : Struct.t -> (Annot.Item.t -> bool) -> bool (** return true if the given predicate evaluates to true on some annotation of [struct_typ] *) diff --git a/infer/src/checkers/classLoads.ml b/infer/src/checkers/classLoads.ml index 062f828b9..c1ea6166a 100644 --- a/infer/src/checkers/classLoads.ml +++ b/infer/src/checkers/classLoads.ml @@ -7,13 +7,13 @@ open! IStd module L = Logging -(* Sources: Java Virtual Machine Specification +(* Sources: Java Virtual Machine Specification - Chapter 5. Loading, Linking and Initializing - Chapter 6. The Java Virtual Machine Instruction Set *) -(* TODO - - catch / throw with exception classes +(* TODO + - catch / throw with exception classes *) module Payload = SummaryPayload.Make (struct @@ -42,7 +42,7 @@ let rec load_class summary tenv loc astate class_name = in (* finally, recursively load all superclasses *) Tenv.lookup tenv class_name - |> Option.value_map ~default:[] ~f:(fun tstruct -> tstruct.Typ.Struct.supers) + |> Option.value_map ~default:[] ~f:(fun tstruct -> tstruct.Struct.supers) |> List.fold ~init:astate2 ~f:(load_class summary tenv loc) diff --git a/infer/src/clang/cGeneral_utils.mli b/infer/src/clang/cGeneral_utils.mli index d3e174ce0..0720c0b43 100644 --- a/infer/src/clang/cGeneral_utils.mli +++ b/infer/src/clang/cGeneral_utils.mli @@ -11,10 +11,9 @@ open! IStd type var_info = Clang_ast_t.decl_info * Clang_ast_t.qual_type * Clang_ast_t.var_decl_info * bool -val add_no_duplicates_fields : Typ.Struct.field -> Typ.Struct.field list -> Typ.Struct.field list +val add_no_duplicates_fields : Struct.field -> Struct.field list -> Struct.field list -val append_no_duplicates_fields : - Typ.Struct.field list -> Typ.Struct.field list -> Typ.Struct.field list +val append_no_duplicates_fields : Struct.field list -> Struct.field list -> Struct.field list val append_no_duplicates_methods : Typ.Procname.t list -> Typ.Procname.t list -> Typ.Procname.t list diff --git a/infer/src/concurrency/ConcurrencyModels.ml b/infer/src/concurrency/ConcurrencyModels.ml index d6722d795..2093dfc59 100644 --- a/infer/src/concurrency/ConcurrencyModels.ml +++ b/infer/src/concurrency/ConcurrencyModels.ml @@ -369,7 +369,7 @@ let find_override_or_superclass_annotated ~attrs_of_pname is_annot tenv proc_nam None | Some tstruct when Annotations.struct_typ_has_annot tstruct is_annot -> Some (SuperClass class_name) - | Some (tstruct : Typ.Struct.t) -> ( + | Some (tstruct : Struct.t) -> ( match List.find_map tstruct.methods ~f:(fun pn -> if is_override pn && is_annotated pn then Some (Override pn) else None ) diff --git a/infer/src/concurrency/RacerD.ml b/infer/src/concurrency/RacerD.ml index fac009a24..c16bc6699 100644 --- a/infer/src/concurrency/RacerD.ml +++ b/infer/src/concurrency/RacerD.ml @@ -862,13 +862,13 @@ let should_report_on_proc tenv procdesc = Procdesc.get_access procdesc <> PredSymb.Private | ObjCClassMethod | ObjCInstanceMethod | ObjCInternalMethod -> Tenv.lookup tenv class_name - |> Option.exists ~f:(fun {Typ.Struct.exported_objc_methods} -> + |> Option.exists ~f:(fun {Struct.exported_objc_methods} -> List.mem ~equal:Typ.Procname.equal exported_objc_methods proc_name ) ) && let matcher = ConcurrencyModels.cpp_lock_types_matcher in Option.exists (Tenv.lookup tenv class_name) ~f:(fun class_str -> (* check if the class contains a lock member *) - List.exists class_str.Typ.Struct.fields ~f:(fun (_, ft, _) -> + List.exists class_str.Struct.fields ~f:(fun (_, ft, _) -> Option.exists (Typ.name ft) ~f:(fun name -> QualifiedCppName.Match.match_qualifiers matcher (Typ.Name.qual_name name) ) ) ) | _ -> @@ -906,7 +906,7 @@ let should_report_guardedby_violation classname_str ({snapshot; tenv; procname} (* is the base class a subclass of the one containing the GuardedBy annotation? *) PatternMatch.is_subtype tenv base_name (Typ.Name.Java.from_string classname_str) && Tenv.lookup tenv base_name - |> Option.exists ~f:(fun ({fields; statics} : Typ.Struct.t) -> + |> Option.exists ~f:(fun ({fields; statics} : Struct.t) -> let f fld = field_is_annotated_guardedby field_name fld in List.exists fields ~f || List.exists statics ~f ) | _ -> diff --git a/infer/src/concurrency/StarvationModels.ml b/infer/src/concurrency/StarvationModels.ml index a5cf32228..576110cc7 100644 --- a/infer/src/concurrency/StarvationModels.ml +++ b/infer/src/concurrency/StarvationModels.ml @@ -282,7 +282,7 @@ let rec get_executor_thread_annotation_constraint tenv (receiver : HilExp.Access | FieldOffset (_, field_name) when Typ.Fieldname.is_java field_name -> Typ.Fieldname.get_class_name field_name |> Tenv.lookup tenv - |> Option.map ~f:(fun (tstruct : Typ.Struct.t) -> tstruct.fields @ tstruct.statics) + |> Option.map ~f:(fun (tstruct : Struct.t) -> tstruct.fields @ tstruct.statics) |> Option.bind ~f:(List.find ~f:(fun (fld, _, _) -> Typ.Fieldname.equal fld field_name)) |> Option.bind ~f:(fun (_, _, annot) -> if Annotations.(ia_ends_with annot for_ui_thread) then Some ForUIThread @@ -312,7 +312,7 @@ let get_run_method_from_runnable tenv runnable = |> Option.map ~f:(function Typ.{desc= Tptr (typ, _)} -> typ | typ -> typ) |> Option.bind ~f:Typ.name |> Option.bind ~f:(Tenv.lookup tenv) - |> Option.map ~f:(fun (tstruct : Typ.Struct.t) -> tstruct.methods) + |> Option.map ~f:(fun (tstruct : Struct.t) -> tstruct.methods) |> Option.bind ~f:(List.find ~f:is_run_method) diff --git a/infer/src/concurrency/starvation.ml b/infer/src/concurrency/starvation.ml index 577442c15..35702fa12 100644 --- a/infer/src/concurrency/starvation.ml +++ b/infer/src/concurrency/starvation.ml @@ -341,7 +341,7 @@ let set_constructor_attributes tenv procname (astate : Domain.t) = (* retrieve its definition *) |> Option.bind ~f:(Tenv.lookup tenv) (* get the list of methods in the class *) - |> Option.value_map ~default:[] ~f:(fun (tstruct : Typ.Struct.t) -> tstruct.methods) + |> Option.value_map ~default:[] ~f:(fun (tstruct : Struct.t) -> tstruct.methods) (* keep only the constructors *) |> List.filter ~f:Typ.Procname.(function Java jname -> Java.is_constructor jname | _ -> false) (* get the summaries of the constructors *) @@ -615,7 +615,7 @@ let should_report pdesc = let fold_reportable_summaries (tenv, current_summary) clazz ~init ~f = let methods = Tenv.lookup tenv clazz - |> Option.value_map ~default:[] ~f:(fun tstruct -> tstruct.Typ.Struct.methods) + |> Option.value_map ~default:[] ~f:(fun tstruct -> tstruct.Struct.methods) in let f acc mthd = Ondemand.get_proc_desc mthd diff --git a/infer/src/java/jTrans.ml b/infer/src/java/jTrans.ml index 091abc52a..f4b1f603c 100644 --- a/infer/src/java/jTrans.ml +++ b/infer/src/java/jTrans.ml @@ -77,7 +77,7 @@ let retrieve_fieldname fieldname = let get_field_name program static tenv cn fs = - let {Typ.Struct.fields; statics} = JTransType.get_class_struct_typ program tenv cn in + let {Struct.fields; statics} = JTransType.get_class_struct_typ program tenv cn in match List.find ~f:(fun (fieldname, _, _) -> String.equal (retrieve_fieldname fieldname) (JBasics.fs_name fs)) diff --git a/infer/src/java/jTransType.ml b/infer/src/java/jTransType.ml index a08cf8317..e566f7cf7 100644 --- a/infer/src/java/jTransType.ml +++ b/infer/src/java/jTransType.ml @@ -278,7 +278,7 @@ let add_model_fields program classpath_fields cn = let rec get_method_procname program tenv cn ms method_kind = - let (_ : Typ.Struct.t) = get_class_struct_typ program tenv cn in + let (_ : Struct.t) = get_class_struct_typ program tenv cn in let return_type_name, method_name, args_type_name = method_signature_names ms in let class_name = Typ.Name.Java.from_string (JBasics.cn_name cn) in let proc_name_java = @@ -297,7 +297,7 @@ and translate_method_name program tenv m = and get_all_fields program tenv cn = let extract_class_fields classname = - let {Typ.Struct.fields; statics} = get_class_struct_typ program tenv classname in + let {Struct.fields; statics} = get_class_struct_typ program tenv classname in (statics, fields) in let trans_fields classname = diff --git a/infer/src/java/jTransType.mli b/infer/src/java/jTransType.mli index 35273a266..8d04a2cde 100644 --- a/infer/src/java/jTransType.mli +++ b/infer/src/java/jTransType.mli @@ -28,7 +28,7 @@ val translate_method_name : JClasspath.program -> Tenv.t -> JCode.jcode Javalib.jmethod -> Typ.Procname.t (** translate the SIL procedure name of the Java method *) -val get_class_struct_typ : JClasspath.program -> Tenv.t -> JBasics.class_name -> Typ.Struct.t +val get_class_struct_typ : JClasspath.program -> Tenv.t -> JBasics.class_name -> Struct.t (** [get_class_struct_typ program tenv cn] returns the struct_typ representation of the class *) val get_class_type_no_pointer : JClasspath.program -> Tenv.t -> JBasics.class_name -> Typ.t diff --git a/infer/src/nullsafe/AnnotatedField.ml b/infer/src/nullsafe/AnnotatedField.ml index 5cebc543c..f08412951 100644 --- a/infer/src/nullsafe/AnnotatedField.ml +++ b/infer/src/nullsafe/AnnotatedField.ml @@ -25,7 +25,7 @@ let rec get_type_name {Typ.desc} = (* A heuristic to guess if the field is actually a Java enum value. *) -let is_enum_value tenv ~class_typ (field_info : Typ.Struct.field_info) = +let is_enum_value tenv ~class_typ (field_info : Struct.field_info) = (* It is tricky to get this information with 100% precision, but this works in most of practical cases. In Java, enums are special classes, and enum values are (implicitly generated) static fields in these classes, @@ -48,8 +48,8 @@ let get tenv field_name class_typ = let lookup = Tenv.lookup tenv in (* We currently don't support field-level strict mode annotation, so fetch it from class *) let is_strict_mode = is_class_in_strict_mode tenv class_typ in - Typ.Struct.get_field_info ~lookup field_name class_typ - |> Option.map ~f:(fun (Typ.Struct.{typ= field_typ; annotations} as field_info) -> + Struct.get_field_info ~lookup field_name class_typ + |> Option.map ~f:(fun (Struct.{typ= field_typ; annotations} as field_info) -> let is_enum_value = is_enum_value tenv ~class_typ field_info in let nullability = AnnotatedNullability.of_type_and_annotation field_typ annotations ~is_strict_mode