Summary: Just a bunch of minor changes. - The mutable field doesn't need to be mutable: it's only mutated once in the code somewhere that doesn't even need to mutate - Hence the type can be public - All the `ms_get_*` functions are replaced by field accesses - `CMethod_signature` -> `CMethodSignature` while I'm at it, although maybe that's bad since other files in clang/ follow the former convention - `type method_signature` -> `type t` - `pp` function instead of `to_string`, since it's used with `fprintf`. This gets rid of the only caller of `IList.to_string`. Reviewed By: dulmarod Differential Revision: D7123795 fbshipit-source-id: fdfae42master
parent
d773dedb4b
commit
fa6a798451
@ -0,0 +1,76 @@
|
|||||||
|
(*
|
||||||
|
* Copyright (c) 2013 - present Facebook, Inc.
|
||||||
|
* All rights reserved.
|
||||||
|
*
|
||||||
|
* This source code is licensed under the BSD style license found in the
|
||||||
|
* LICENSE file in the root directory of this source tree. An additional grant
|
||||||
|
* of patent rights can be found in the PATENTS file in the same directory.
|
||||||
|
*)
|
||||||
|
|
||||||
|
open! IStd
|
||||||
|
|
||||||
|
(** Define the signature of a method consisting of its name, its arguments, return type, location
|
||||||
|
and whether its an instance method. *)
|
||||||
|
|
||||||
|
module F = Format
|
||||||
|
|
||||||
|
type t =
|
||||||
|
{ name: Typ.Procname.t
|
||||||
|
; access: Clang_ast_t.access_specifier
|
||||||
|
; args: (Mangled.t * Clang_ast_t.qual_type) list
|
||||||
|
; ret_type: Clang_ast_t.qual_type
|
||||||
|
; attributes: Clang_ast_t.attribute list
|
||||||
|
; loc: Clang_ast_t.source_range
|
||||||
|
; method_kind: ProcAttributes.clang_method_kind
|
||||||
|
; is_cpp_virtual: bool
|
||||||
|
; is_cpp_nothrow: bool
|
||||||
|
; lang: CFrontend_config.clang_lang
|
||||||
|
; pointer_to_parent: Clang_ast_t.pointer option
|
||||||
|
; pointer_to_property_opt: Clang_ast_t.pointer option
|
||||||
|
; (* If set then method is a getter/setter *)
|
||||||
|
return_param_typ: Typ.t option }
|
||||||
|
|
||||||
|
(* A method is a getter if it has a link to a property and *)
|
||||||
|
(* it has 1 argument (this includes self) *)
|
||||||
|
let is_getter {pointer_to_property_opt; args} =
|
||||||
|
Option.is_some pointer_to_property_opt && Int.equal (List.length args) 1
|
||||||
|
|
||||||
|
|
||||||
|
(* A method is a setter if it has a link to a property and *)
|
||||||
|
(* it has 2 argument (this includes self) *)
|
||||||
|
let is_setter {pointer_to_property_opt; args} =
|
||||||
|
Option.is_some pointer_to_property_opt && Int.equal (List.length args) 2
|
||||||
|
|
||||||
|
|
||||||
|
let mk name args ret_type attributes loc method_kind ?is_cpp_virtual ?is_cpp_nothrow lang
|
||||||
|
pointer_to_parent pointer_to_property_opt return_param_typ access =
|
||||||
|
let is_cpp_virtual = Option.value is_cpp_virtual ~default:false in
|
||||||
|
let is_cpp_nothrow = Option.value is_cpp_nothrow ~default:false in
|
||||||
|
{ name
|
||||||
|
; access
|
||||||
|
; args
|
||||||
|
; ret_type
|
||||||
|
; attributes
|
||||||
|
; loc
|
||||||
|
; method_kind
|
||||||
|
; is_cpp_virtual
|
||||||
|
; is_cpp_nothrow
|
||||||
|
; lang
|
||||||
|
; pointer_to_parent
|
||||||
|
; pointer_to_property_opt
|
||||||
|
; return_param_typ }
|
||||||
|
|
||||||
|
|
||||||
|
let pp fmt ms =
|
||||||
|
let pp_arg fmt (mangled, qual_type) =
|
||||||
|
F.fprintf fmt "%a, %a" Mangled.pp mangled
|
||||||
|
(Pp.to_string ~f:CAst_utils.string_of_qual_type)
|
||||||
|
qual_type
|
||||||
|
in
|
||||||
|
Format.fprintf fmt "Method %a [%a]->%a %a"
|
||||||
|
(Pp.to_string ~f:Typ.Procname.to_string)
|
||||||
|
ms.name (Pp.comma_seq pp_arg) ms.args
|
||||||
|
(Pp.to_string ~f:Clang_ast_extend.type_ptr_to_string)
|
||||||
|
ms.ret_type.Clang_ast_t.qt_type_ptr
|
||||||
|
(Pp.to_string ~f:Clang_ast_j.string_of_source_range)
|
||||||
|
ms.loc
|
@ -0,0 +1,42 @@
|
|||||||
|
(*
|
||||||
|
* Copyright (c) 2013 - present Facebook, Inc.
|
||||||
|
* All rights reserved.
|
||||||
|
*
|
||||||
|
* This source code is licensed under the BSD style license found in the
|
||||||
|
* LICENSE file in the root directory of this source tree. An additional grant
|
||||||
|
* of patent rights can be found in the PATENTS file in the same directory.
|
||||||
|
*)
|
||||||
|
|
||||||
|
open! IStd
|
||||||
|
|
||||||
|
(** Define the signature of a method consisting of its name, its arguments, return type, location
|
||||||
|
and whether its an instance method. *)
|
||||||
|
|
||||||
|
type t =
|
||||||
|
{ name: Typ.Procname.t
|
||||||
|
; access: Clang_ast_t.access_specifier
|
||||||
|
; args: (Mangled.t * Clang_ast_t.qual_type) list
|
||||||
|
; ret_type: Clang_ast_t.qual_type
|
||||||
|
; attributes: Clang_ast_t.attribute list
|
||||||
|
; loc: Clang_ast_t.source_range
|
||||||
|
; method_kind: ProcAttributes.clang_method_kind
|
||||||
|
; is_cpp_virtual: bool
|
||||||
|
; is_cpp_nothrow: bool
|
||||||
|
; lang: CFrontend_config.clang_lang
|
||||||
|
; pointer_to_parent: Clang_ast_t.pointer option
|
||||||
|
; pointer_to_property_opt: Clang_ast_t.pointer option
|
||||||
|
; (* If set then method is a getter/setter *)
|
||||||
|
return_param_typ: Typ.t option }
|
||||||
|
|
||||||
|
val is_getter : t -> bool
|
||||||
|
|
||||||
|
val is_setter : t -> bool
|
||||||
|
|
||||||
|
val mk :
|
||||||
|
Typ.Procname.t -> (Mangled.t * Clang_ast_t.qual_type) list -> Clang_ast_t.qual_type
|
||||||
|
-> Clang_ast_t.attribute list -> Clang_ast_t.source_range -> ProcAttributes.clang_method_kind
|
||||||
|
-> ?is_cpp_virtual:bool -> ?is_cpp_nothrow:bool -> CFrontend_config.clang_lang
|
||||||
|
-> Clang_ast_t.pointer option -> Clang_ast_t.pointer option -> Typ.t option
|
||||||
|
-> Clang_ast_t.access_specifier -> t
|
||||||
|
|
||||||
|
val pp : Format.formatter -> t -> unit
|
@ -1,100 +0,0 @@
|
|||||||
(*
|
|
||||||
* Copyright (c) 2013 - present Facebook, Inc.
|
|
||||||
* All rights reserved.
|
|
||||||
*
|
|
||||||
* This source code is licensed under the BSD style license found in the
|
|
||||||
* LICENSE file in the root directory of this source tree. An additional grant
|
|
||||||
* of patent rights can be found in the PATENTS file in the same directory.
|
|
||||||
*)
|
|
||||||
|
|
||||||
open! IStd
|
|
||||||
|
|
||||||
(** Define the signature of a method consisting of its name, its arguments, *)
|
|
||||||
|
|
||||||
(** return type, location and whether its an instance method. *)
|
|
||||||
|
|
||||||
type method_signature =
|
|
||||||
{ mutable name: Typ.Procname.t
|
|
||||||
; access: Clang_ast_t.access_specifier
|
|
||||||
; args: (Mangled.t * Clang_ast_t.qual_type) list
|
|
||||||
; ret_type: Clang_ast_t.qual_type
|
|
||||||
; attributes: Clang_ast_t.attribute list
|
|
||||||
; loc: Clang_ast_t.source_range
|
|
||||||
; method_kind: ProcAttributes.clang_method_kind
|
|
||||||
; is_cpp_virtual: bool
|
|
||||||
; is_cpp_nothrow: bool
|
|
||||||
; language: CFrontend_config.clang_lang
|
|
||||||
; pointer_to_parent: Clang_ast_t.pointer option
|
|
||||||
; pointer_to_property_opt: Clang_ast_t.pointer option
|
|
||||||
; (* If set then method is a getter/setter *)
|
|
||||||
return_param_typ: Typ.t option }
|
|
||||||
|
|
||||||
let ms_get_name {name} = name
|
|
||||||
|
|
||||||
let ms_set_name ms name = ms.name <- name
|
|
||||||
|
|
||||||
let ms_get_access {access} = access
|
|
||||||
|
|
||||||
let ms_get_args {args} = args
|
|
||||||
|
|
||||||
let ms_get_ret_type {ret_type} = ret_type
|
|
||||||
|
|
||||||
let ms_get_attributes {attributes} = attributes
|
|
||||||
|
|
||||||
let ms_get_loc {loc} = loc
|
|
||||||
|
|
||||||
let ms_get_method_kind {method_kind} = method_kind
|
|
||||||
|
|
||||||
let ms_is_cpp_virtual {is_cpp_virtual} = is_cpp_virtual
|
|
||||||
|
|
||||||
let ms_is_cpp_nothrow {is_cpp_nothrow} = is_cpp_nothrow
|
|
||||||
|
|
||||||
let ms_get_lang {language} = language
|
|
||||||
|
|
||||||
let ms_get_pointer_to_parent {pointer_to_parent} = pointer_to_parent
|
|
||||||
|
|
||||||
let ms_get_pointer_to_property_opt {pointer_to_property_opt} = pointer_to_property_opt
|
|
||||||
|
|
||||||
let ms_get_return_param_typ {return_param_typ} = return_param_typ
|
|
||||||
|
|
||||||
(* A method is a getter if it has a link to a property and *)
|
|
||||||
(* it has 1 argument (this includes self) *)
|
|
||||||
let ms_is_getter {pointer_to_property_opt; args} =
|
|
||||||
Option.is_some pointer_to_property_opt && Int.equal (List.length args) 1
|
|
||||||
|
|
||||||
|
|
||||||
(* A method is a setter if it has a link to a property and *)
|
|
||||||
(* it has 2 argument (this includes self) *)
|
|
||||||
let ms_is_setter {pointer_to_property_opt; args} =
|
|
||||||
Option.is_some pointer_to_property_opt && Int.equal (List.length args) 2
|
|
||||||
|
|
||||||
|
|
||||||
let make_ms name args ret_type attributes loc method_kind ?is_cpp_virtual ?is_cpp_nothrow language
|
|
||||||
pointer_to_parent pointer_to_property_opt return_param_typ access =
|
|
||||||
let booloption_to_bool = function Some b -> b | None -> false in
|
|
||||||
let is_cpp_virtual = booloption_to_bool is_cpp_virtual in
|
|
||||||
let is_cpp_nothrow = booloption_to_bool is_cpp_nothrow in
|
|
||||||
{ name
|
|
||||||
; access
|
|
||||||
; args
|
|
||||||
; ret_type
|
|
||||||
; attributes
|
|
||||||
; loc
|
|
||||||
; method_kind
|
|
||||||
; is_cpp_virtual
|
|
||||||
; is_cpp_nothrow
|
|
||||||
; language
|
|
||||||
; pointer_to_parent
|
|
||||||
; pointer_to_property_opt
|
|
||||||
; return_param_typ }
|
|
||||||
|
|
||||||
|
|
||||||
let replace_name_ms ms name = {ms with name}
|
|
||||||
|
|
||||||
let ms_to_string ms =
|
|
||||||
"Method " ^ Typ.Procname.to_string ms.name ^ " "
|
|
||||||
^ IList.to_string
|
|
||||||
(fun (s1, s2) -> Mangled.to_string s1 ^ ", " ^ CAst_utils.string_of_qual_type s2)
|
|
||||||
ms.args
|
|
||||||
^ "->" ^ Clang_ast_extend.type_ptr_to_string ms.ret_type.Clang_ast_t.qt_type_ptr ^ " "
|
|
||||||
^ Clang_ast_j.string_of_source_range ms.loc
|
|
@ -1,59 +0,0 @@
|
|||||||
(*
|
|
||||||
* Copyright (c) 2013 - present Facebook, Inc.
|
|
||||||
* All rights reserved.
|
|
||||||
*
|
|
||||||
* This source code is licensed under the BSD style license found in the
|
|
||||||
* LICENSE file in the root directory of this source tree. An additional grant
|
|
||||||
* of patent rights can be found in the PATENTS file in the same directory.
|
|
||||||
*)
|
|
||||||
|
|
||||||
open! IStd
|
|
||||||
|
|
||||||
(** Define the signature of a method consisting of its name, its arguments, *)
|
|
||||||
|
|
||||||
(** return type, location and whether its an instance method. *)
|
|
||||||
|
|
||||||
type method_signature
|
|
||||||
|
|
||||||
val ms_get_name : method_signature -> Typ.Procname.t
|
|
||||||
|
|
||||||
val ms_set_name : method_signature -> Typ.Procname.t -> unit
|
|
||||||
|
|
||||||
val ms_get_access : method_signature -> Clang_ast_t.access_specifier
|
|
||||||
|
|
||||||
val ms_get_args : method_signature -> (Mangled.t * Clang_ast_t.qual_type) list
|
|
||||||
|
|
||||||
val ms_get_ret_type : method_signature -> Clang_ast_t.qual_type
|
|
||||||
|
|
||||||
val ms_get_attributes : method_signature -> Clang_ast_t.attribute list
|
|
||||||
|
|
||||||
val ms_get_loc : method_signature -> Clang_ast_t.source_range
|
|
||||||
|
|
||||||
val ms_get_method_kind : method_signature -> ProcAttributes.clang_method_kind
|
|
||||||
|
|
||||||
val ms_is_cpp_virtual : method_signature -> bool
|
|
||||||
|
|
||||||
val ms_is_cpp_nothrow : method_signature -> bool
|
|
||||||
|
|
||||||
val ms_get_lang : method_signature -> CFrontend_config.clang_lang
|
|
||||||
|
|
||||||
val ms_get_pointer_to_parent : method_signature -> Clang_ast_t.pointer option
|
|
||||||
|
|
||||||
val ms_get_pointer_to_property_opt : method_signature -> Clang_ast_t.pointer option
|
|
||||||
|
|
||||||
val ms_get_return_param_typ : method_signature -> Typ.t option
|
|
||||||
|
|
||||||
val ms_is_getter : method_signature -> bool
|
|
||||||
|
|
||||||
val ms_is_setter : method_signature -> bool
|
|
||||||
|
|
||||||
val make_ms :
|
|
||||||
Typ.Procname.t -> (Mangled.t * Clang_ast_t.qual_type) list -> Clang_ast_t.qual_type
|
|
||||||
-> Clang_ast_t.attribute list -> Clang_ast_t.source_range -> ProcAttributes.clang_method_kind
|
|
||||||
-> ?is_cpp_virtual:bool -> ?is_cpp_nothrow:bool -> CFrontend_config.clang_lang
|
|
||||||
-> Clang_ast_t.pointer option -> Clang_ast_t.pointer option -> Typ.t option
|
|
||||||
-> Clang_ast_t.access_specifier -> method_signature
|
|
||||||
|
|
||||||
val replace_name_ms : method_signature -> Typ.Procname.t -> method_signature
|
|
||||||
|
|
||||||
val ms_to_string : method_signature -> string
|
|
Loading…
Reference in new issue