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

« back to all changes in this revision

Viewing changes to ocamldoc/odoc_to_text.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_to_text.ml 8927 2008-07-23 08:55:36Z guesdon $ *)
 
12
(* $Id: odoc_to_text.ml 10480 2010-05-31 11:52:13Z guesdon $ *)
13
13
 
14
14
(** Text generation.
15
15
 
61
61
                    Newline
62
62
                  ]
63
63
 
 
64
    (** @return [text] value to represent the list of "before" information. *)
 
65
    method text_of_before = function
 
66
      [] -> []
 
67
    | l ->
 
68
        let f (v, text) =
 
69
          (Bold [Raw (Printf.sprintf "%s %s " Odoc_messages.before v) ]) ::
 
70
            text @
 
71
            [Newline]
 
72
        in
 
73
        List.flatten (List.map f l)
 
74
 
64
75
    (** @return [text] value for the given list of raised exceptions.*)
65
76
    method text_of_raised_exceptions l =
66
77
      match l with
153
164
            ) @
154
165
            (self#text_of_author_list info.i_authors) @
155
166
            (self#text_of_version_opt info.i_version) @
 
167
            (self#text_of_before info.i_before) @
156
168
            (self#text_of_since_opt info.i_since) @
157
169
            (self#text_of_raised_exceptions info.i_raised_exceptions) @
158
170
            (self#text_of_return_opt info.i_return_value) @
229
241
    method normal_class_params m_name c =
230
242
      let s = Odoc_info.string_of_class_params c in
231
243
      self#relative_idents m_name
232
 
        (Odoc_info.remove_ending_newline s)
 
244
        (Odoc_info.remove_ending_newline s)
233
245
 
234
246
    (** @return [text] value to represent a [Types.type_expr].*)
235
247
    method text_of_type_expr module_name t =
259
271
    (** @return [text] value to represent parameters of a class (with arraows).*)
260
272
    method text_of_class_params module_name c =
261
273
      let t = Odoc_info.text_concat
262
 
          [Newline]
 
274
          [Newline]
263
275
          (List.map
264
276
             (fun s -> [Code s])
265
 
             (Str.split (Str.regexp "\n")
 
277
             (Str.split (Str.regexp "\n")
266
278
                (self#normal_class_params module_name c))
267
 
          )
 
279
          )
268
280
      in
269
281
      t
270
282
 
280
292
      let name = v.val_name in
281
293
      let s_name = Name.simple name in
282
294
      let s =
283
 
        Format.fprintf Format.str_formatter "@[<hov 2>val %s :@ %s"
 
295
        Format.fprintf Format.str_formatter "@[<hov 2>val %s :@ %s"
284
296
          s_name
285
297
          (self#normal_type (Name.father v.val_name) v.val_type);
286
 
        Format.flush_str_formatter ()
 
298
        Format.flush_str_formatter ()
287
299
      in
288
300
      [ CodePre s ] @
289
301
      [Latex ("\\index{"^(self#label s_name)^"@\\verb`"^(self#label ~no_:false s_name)^"`}\n")] @
294
306
      let s_name = Name.simple a.att_value.val_name in
295
307
      let mod_name = Name.father a.att_value.val_name in
296
308
      let s =
297
 
        Format.fprintf Format.str_formatter "@[<hov 2>val %s%s%s :@ %s"
 
309
        Format.fprintf Format.str_formatter "@[<hov 2>val %s%s%s :@ %s"
298
310
          (if a.att_virtual then "virtual " else "")
299
311
          (if a.att_mutable then "mutable " else "")
300
312
          s_name
301
 
          (self#normal_type mod_name a.att_value.val_type);
302
 
        Format.flush_str_formatter ()
 
313
          (self#normal_type mod_name a.att_value.val_type);
 
314
        Format.flush_str_formatter ()
303
315
      in
304
316
      (CodePre s) ::
305
317
      [Latex ("\\index{"^(self#label s_name)^"@\\verb`"^(self#label ~no_:false s_name)^"`}\n")] @
310
322
      let s_name = Name.simple m.met_value.val_name in
311
323
      let mod_name = Name.father m.met_value.val_name in
312
324
      let s =
313
 
        Format.fprintf Format.str_formatter "@[<hov 2>method %s%s%s :@ %s"
 
325
        Format.fprintf Format.str_formatter "@[<hov 2>method %s%s%s :@ %s"
314
326
          (if m.met_private then "private " else "")
315
327
          (if m.met_virtual then "virtual " else "")
316
328
          s_name
317
 
          (self#normal_type mod_name m.met_value.val_type);
318
 
        Format.flush_str_formatter ()
 
329
          (self#normal_type mod_name m.met_value.val_type);
 
330
        Format.flush_str_formatter ()
319
331
      in
320
332
      (CodePre s) ::
321
333
      [Latex ("\\index{"^(self#label s_name)^"@\\verb`"^(self#label ~no_:false s_name)^"`}\n")] @
332
344
            Format.fprintf Format.str_formatter "@ of "
333
345
        );
334
346
      let s = self#normal_type_list
335
 
          ~par: false (Name.father e.ex_name) " * " e.ex_args
 
347
          ~par: false (Name.father e.ex_name) " * " e.ex_args
336
348
      in
337
349
      let s2 =
338
350
        Format.fprintf Format.str_formatter "%s" s ;
543
555
          [Code " -> "] @
544
556
          (self#text_of_module_kind ~with_def_syntax: false k)
545
557
 
 
558
      | Module_typeof s ->
 
559
          let code = Printf.sprintf "%smodule type of %s"
 
560
            (if with_def_syntax then " : " else "")
 
561
            s
 
562
          in
 
563
          [Code code]
 
564
      | Module_unpack (code, _) ->
 
565
          let code = Printf.sprintf "%s%s"
 
566
            (if with_def_syntax then " : " else "")
 
567
            code
 
568
          in
 
569
          [Code code]
 
570
 
546
571
    (** Return html code for a [module_type_kind].*)
547
572
    method text_of_module_type_kind ?(with_def_syntax=true) tk =
548
573
      match tk with
551
576
 
552
577
      | Module_type_functor (p, k) ->
553
578
          let t1 =
554
 
            [Code ("("^p.mp_name^" : ")] @
 
579
            [Code ("("^p.mp_name^" : ")] @
555
580
            (self#text_of_module_type_kind p.mp_kind) @
556
581
            [Code ") -> "]
557
582
          in
570
595
                 | Some mt -> mt.mt_name))
571
596
          ]
572
597
 
573
 
 
 
598
      | Odoc_module.Module_type_typeof s ->
 
599
          let code = Printf.sprintf "%smodule type of %s"
 
600
            (if with_def_syntax then " = " else "") s
 
601
          in
 
602
          [ Code code ]
574
603
  end