~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to ocamldoc/odoc_class.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
9
9
(*                                                                     *)
10
10
(***********************************************************************)
11
11
 
12
 
(* $Id: odoc_class.ml 6174 2004-03-26 15:57:03Z guesdon $ *)
 
12
(* $Id: odoc_class.ml 9547 2010-01-22 12:48:24Z doligez $ *)
13
13
 
14
14
(** Representation and manipulation of classes and class types.*)
15
15
 
22
22
  | Class_comment of Odoc_types.text
23
23
 
24
24
(** Used when we can reference t_class or t_class_type. *)
25
 
type cct = 
 
25
type cct =
26
26
    Cl of t_class
27
27
  | Cltype of t_class_type * Types.type_expr list (** class type and type parameters *)
28
28
 
30
30
    ic_name : Name.t ; (** Complete name of the inherited class *)
31
31
    mutable ic_class : cct option ; (** The associated t_class or t_class_type *)
32
32
    ic_text : Odoc_types.text option ; (** The inheritance comment, if any *)
33
 
  } 
 
33
  }
34
34
 
35
35
and class_apply = {
36
36
    capp_name : Name.t ; (** The complete name of the applied class *)
37
37
    mutable capp_class : t_class option;  (** The associated t_class if we found it *)
38
38
    capp_params : Types.type_expr list; (** The type of expressions the class is applied to *)
39
39
    capp_params_code : string list ; (** The code of these expressions *)
40
 
  } 
 
40
  }
41
41
 
42
42
and class_constr = {
43
43
    cco_name : Name.t ; (** The complete name of the applied class *)
44
44
    mutable cco_class : cct option;  (** The associated class ot class type if we found it *)
45
45
    cco_type_parameters : Types.type_expr list; (** The type parameters of the class, if needed *)
46
 
  } 
 
46
  }
47
47
 
48
48
 
49
49
and class_kind =
52
52
  | Class_apply of class_apply (** application/alias of a class, used in implementation only *)
53
53
  | Class_constr of class_constr (** a class used to give the type of the defined class,
54
54
                                    instead of a structure, used in interface only.
55
 
                                    For example, it will be used with the name "M1.M2....tutu" 
 
55
                                    For example, it will be used with the name "M1.M2....tutu"
56
56
                                    when the class to is defined like this :
57
57
                                    class toto : int -> tutu *)
58
58
  | Class_constraint of class_kind * class_type_kind
68
68
    mutable cl_kind : class_kind ;
69
69
    mutable cl_parameters : Odoc_parameter.parameter list ;
70
70
    mutable cl_loc : Odoc_types.location ;
71
 
  } 
 
71
  }
72
72
 
73
73
and class_type_alias = {
74
74
    cta_name : Name.t ;
75
75
    mutable cta_class : cct option ; (** we can have a t_class or a t_class_type *)
76
76
    cta_type_parameters : Types.type_expr list ; (** the type parameters *)
77
 
  } 
 
77
  }
78
78
 
79
 
and class_type_kind = 
 
79
and class_type_kind =
80
80
    Class_signature of inherited_class list * class_element list
81
81
  | Class_type of class_type_alias (** a class type eventually applied to type args *)
82
82
 
83
83
(** Representation of a class type. *)
84
84
and t_class_type = {
85
 
    clt_name : Name.t ; 
 
85
    clt_name : Name.t ;
86
86
    mutable clt_info : Odoc_types.info option ; (** The optional associated user information *)
87
87
    clt_type : Types.class_type ;
88
88
    clt_type_parameters : Types.type_expr list ; (** type parameters *)
89
89
    clt_virtual : bool ; (** true = virtual *)
90
90
    mutable clt_kind : class_type_kind ;
91
91
    mutable clt_loc : Odoc_types.location ;
92
 
  } 
 
92
  }
93
93
 
94
94
 
95
95
(** {2 Functions} *)
108
108
          None
109
109
 
110
110
(** Returns the list of elements of a t_class. *)
111
 
let rec class_elements ?(trans=true) cl = 
112
 
  let rec iter_kind k = 
 
111
let rec class_elements ?(trans=true) cl =
 
112
  let rec iter_kind k =
113
113
    match k with
114
114
      Class_structure (_, elements) -> elements
115
115
    | Class_constraint (c_kind, ct_kind) ->
117
117
      (* A VOIR : utiliser le c_kind ou le ct_kind ?
118
118
         Pour l'instant, comme le ct_kind n'est pas analys�,
119
119
         on cherche dans le c_kind
120
 
         class_type_elements ~trans: trans 
 
120
         class_type_elements ~trans: trans
121
121
         { clt_name = "" ; clt_info = None ;
122
122
          clt_type_parameters = [] ;
123
123
         clt_virtual = false ;
137
137
         | _ -> []
138
138
        )
139
139
  in
140
 
  iter_kind cl.cl_kind 
141
 
  
 
140
  iter_kind cl.cl_kind
 
141
 
142
142
(** Returns the list of elements of a t_class_type. *)
143
 
and class_type_elements ?(trans=true) clt = 
 
143
and class_type_elements ?(trans=true) clt =
144
144
  match clt.clt_kind with
145
145
    Class_signature (_, elements) -> elements
146
146
  | Class_type { cta_class = Some (Cltype (ct, _)) } when trans ->
192
192
 
193
193
(** Update the parameters text of a t_class, according to the cl_info field. *)
194
194
let class_update_parameters_text cl =
195
 
  let f p = 
196
 
    Odoc_parameter.update_parameter_text (class_parameter_text_by_name cl) p 
 
195
  let f p =
 
196
    Odoc_parameter.update_parameter_text (class_parameter_text_by_name cl) p
197
197
  in
198
198
  List.iter f cl.cl_parameters
199
199
 
249
249
        Not_found ->
250
250
          None
251
251
 
252
 
        
253
 
(* eof $Id: odoc_class.ml 6174 2004-03-26 15:57:03Z guesdon $ *)
 
252
 
 
253
(* eof $Id: odoc_class.ml 9547 2010-01-22 12:48:24Z doligez $ *)