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

« back to all changes in this revision

Viewing changes to ocamldoc/odoc_print.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_print.ml 6307 2004-05-18 13:28:00Z garrigue $ *)
 
12
(* $Id: odoc_print.ml 9547 2010-01-22 12:48:24Z doligez $ *)
13
13
 
14
14
open Format
15
15
 
20
20
    pp_print_flush fmt ();
21
21
    let s = Buffer.contents buf in
22
22
    Buffer.reset buf ;
23
 
    s 
 
23
    s
24
24
  in
25
25
  (fmt, flush)
26
26
 
27
27
let (type_fmt, flush_type_fmt) = new_fmt ()
28
28
let _ =
29
 
  let (out, flush, outnewline, outspace) = 
30
 
    pp_get_all_formatter_output_functions type_fmt () 
 
29
  let (out, flush, outnewline, outspace) =
 
30
    pp_get_all_formatter_output_functions type_fmt ()
31
31
  in
32
32
  pp_set_all_formatter_output_functions type_fmt
33
33
    ~out ~flush
56
56
  let rec iter t =
57
57
    match t with
58
58
      Types.Tmty_ident p -> t
59
 
    | Types.Tmty_signature _ -> 
60
 
        (
61
 
         match code with
62
 
           None -> Types.Tmty_signature []
63
 
         | Some s -> raise (Use_code s)
64
 
        )
 
59
    | Types.Tmty_signature _ ->
 
60
        (
 
61
         match code with
 
62
           None -> Types.Tmty_signature []
 
63
         | Some s -> raise (Use_code s)
 
64
        )
65
65
    | Types.Tmty_functor (id, mt1, mt2) ->
66
66
        Types.Tmty_functor (id, iter mt1, iter mt2)
67
67
  in
85
85
        (* on vire les vals et methods pour ne pas qu'elles soient imprim�es
86
86
           quand on affichera le type *)
87
87
        let tnil = { Types.desc = Types.Tnil ; Types.level = 0; Types.id = 0 } in
88
 
        Types.Tcty_signature { Types.cty_self = { cs.Types.cty_self with 
 
88
        Types.Tcty_signature { Types.cty_self = { cs.Types.cty_self with
89
89
                                                  Types.desc = Types.Tobject (tnil, ref None) };
90
90
                               Types.cty_vars = Types.Vars.empty ;
91
91
                               Types.cty_concr = Types.Concr.empty ;
97
97
  in
98
98
  iter t
99
99
 
100
 
let string_of_class_type ?(complete=false) t = 
 
100
let string_of_class_type ?(complete=false) t =
101
101
  let t2 = if complete then t else simpl_class_type t in
102
102
  (* A VOIR : ma propre version de Printtyp.class_type pour ne pas faire reset_names *)
103
103
  Printtyp.class_type modtype_fmt t2;