summaryrefslogtreecommitdiff
path: root/camlp4/Camlp4/Printers/OCamlr.ml
blob: 33a85f3d0fd1870ba9f93f0df96cb121271f63f2 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
(****************************************************************************)
(*                                                                          *)
(*                                   OCaml                                  *)
(*                                                                          *)
(*                            INRIA Rocquencourt                            *)
(*                                                                          *)
(*  Copyright  2006   Institut National de Recherche  en  Informatique et   *)
(*  en Automatique.  All rights reserved.  This file is distributed under   *)
(*  the terms of the GNU Library General Public License, with the special   *)
(*  exception on linking described in LICENSE at the top of the OCaml       *)
(*  source tree.                                                            *)
(*                                                                          *)
(****************************************************************************)

(* Authors:
 * - Nicolas Pouillard: initial version
 *)

open Format;

module Id = struct
  value name = "Camlp4.Printers.OCamlr";
  value version = Sys.ocaml_version;
end;

module Make (Syntax : Sig.Camlp4Syntax) = struct
  include Syntax;
  open Sig;

  module PP_o = OCaml.Make Syntax;

  open PP_o;

  value pp = fprintf;

  value is_keyword =
    let keywords = ["where"]
    and not_keywords = ["false"; "function"; "true"; "val"]
    in fun s -> not (List.mem s not_keywords)
             && (is_keyword s || List.mem s keywords);

  class printer ?curry_constr:(init_curry_constr = True) ?(comments = True) () =
  object (o)
    inherit PP_o.printer ~curry_constr:init_curry_constr ~comments () as super;

    value! semisep : sep = ";";
    value! no_semisep : sep = ";";
    value mode = if comments then `comments else `no_comments;
    value curry_constr = init_curry_constr;
    value first_match_case = True;

    method andsep : sep = "@]@ @[<2>and@ ";
    method value_val = "value";
    method value_let = "value";
    method under_pipe = o;
    method under_semi = o;
    method reset_semi = o;
    method reset = o;
    method private unset_first_match_case = {< first_match_case = False >};
    method private set_first_match_case = {< first_match_case = True >};

    method seq f e =
      let rec self right f e =
        let go_right = self right and go_left = self False in
        match e with
        [ <:expr< let $rec:r$ $bi$ in $e1$ >> ->
            if right then
              pp f "@[<2>let %a%a@];@ %a"
                o#rec_flag r o#binding bi go_right e1
            else
              pp f "(%a)" o#expr e
        | <:expr< do { $e$ } >> -> go_right f e
        | <:expr< $e1$; $e2$ >> -> do {
            pp f "%a;@ " go_left e1;
            match (right, e2) with
            [ (True, <:expr< let $rec:r$ $bi$ in $e3$ >>) ->
                pp f "@[<2>let %a%a@];@ %a"
                  o#rec_flag r o#binding bi go_right e3
            | _ -> go_right f e2 ] }
        | e -> o#expr f e ]
      in self True f e;

    method var f =
      fun
      [ "" -> pp f "$lid:\"\"$"
      | "[]" -> pp f "[]"
      | "()" -> pp f "()"
      | " True"  -> pp f "True"
      | " False" -> pp f "False"
      | v ->
          match lex_string v with
          [ (LIDENT s | UIDENT s | ESCAPED_IDENT s) when is_keyword s ->
              pp f "%s__" s
          | SYMBOL s ->
              pp f "( %s )" s
          | LIDENT s | UIDENT s | ESCAPED_IDENT s ->
              pp_print_string f s
          | tok -> failwith (sprintf
                    "Bad token used as an identifier: %s"
                    (Token.to_string tok)) ] ];

    method type_params f =
      fun
      [ [] -> ()
      | [x] -> pp f "@ %a" o#ctyp x
      | l -> pp f "@ @[<1>%a@]" (list o#ctyp "@ ") l ];

    method match_case f =
      fun
      [ <:match_case<>> -> pp f "@ []"
      | m -> pp f "@ [ %a ]" o#set_first_match_case#match_case_aux m ];

    method match_case_aux f =
      fun
      [ <:match_case<>> -> ()
      | <:match_case< $anti:s$ >> -> o#anti f s
      | <:match_case< $a1$ | $a2$ >> ->
          pp f "%a%a" o#match_case_aux a1 o#unset_first_match_case#match_case_aux a2
      | <:match_case< $p$ -> $e$ >> ->
          let () = if first_match_case then () else pp f "@ | " in
          pp f "@[<2>%a@ ->@ %a@]" o#patt p o#under_pipe#expr e
      | <:match_case< $p$ when $w$ -> $e$ >> ->
          let () = if first_match_case then () else pp f "@ | " in
          pp f "@[<2>%a@ when@ %a@ ->@ %a@]"
            o#patt p o#under_pipe#expr w o#under_pipe#expr e ];

    method sum_type f =
      fun
      [ <:ctyp<>> -> pp f "[]"
      | t -> pp f "@[<hv0>[ %a ]@]" o#ctyp t
      ];

    method ident f i =
    let () = o#node f i Ast.loc_of_ident in
    match i with
    [ <:ident< $i1$ $i2$ >> -> pp f "%a@ %a" o#dot_ident i1 o#dot_ident i2
    | i -> o#dot_ident f i ];

    method private dot_ident f i =
    let () = o#node f i Ast.loc_of_ident in
    match i with
    [ <:ident< $i1$.$i2$ >> -> pp f "%a.@,%a" o#dot_ident i1 o#dot_ident i2
    | <:ident< $anti:s$ >> -> o#anti f s
    | <:ident< $lid:s$ >> | <:ident< $uid:s$ >> -> o#var f s
    | i -> pp f "(%a)" o#ident i ];

    method patt4 f = fun
    [ <:patt< [$_$ :: $_$] >> as p ->
        let (pl, c) = o#mk_patt_list p in
        match c with
        [ None -> pp f "@[<2>[@ %a@]@ ]" (list o#patt ";@ ") pl
        | Some x -> pp f "@[<2>[ %a ::@ %a ]@]" (list o#patt ";@ ") pl o#patt x ]
    | p -> super#patt4 f p ];

    method expr_list_cons _ f e =
      let (el, c) = o#mk_expr_list e in
      match c with
      [ None -> o#expr_list f el
      | Some x -> pp f "@[<2>[ %a ::@ %a ]@]" (list o#expr ";@ ") el o#expr x ];

    method expr f e =
    let () = o#node f e Ast.loc_of_expr in
    match e with
    [ <:expr< $e1$ := $e2$ >> ->
        pp f "@[<2>%a@ :=@ %a@]" o#dot_expr e1 o#expr e2
    | <:expr< fun $p$ -> $e$ >> when Ast.is_irrefut_patt p ->
        pp f "@[<2>fun@ %a@]" o#patt_expr_fun_args (`patt p, e)
    | <:expr< fun (type $i$) -> $e$ >> ->
        pp f "@[<2>fun@ %a@]" o#patt_expr_fun_args (`newtype i, e)
    | <:expr< fun [ $a$ ] >> ->
        pp f "@[<hv0>fun%a@]" o#match_case a
    | <:expr< assert False >> -> pp f "@[<2>assert@ False@]"
    | e -> super#expr f e ];

    method dot_expr f e =
    let () = o#node f e Ast.loc_of_expr in
    match e with
    [ <:expr< $e$.val >> -> pp f "@[<2>%a.@,val@]" o#simple_expr e
    | e -> super#dot_expr f e ];

    method ctyp f t =
    let () = o#node f t Ast.loc_of_ctyp in
    match t with
    [ Ast.TyDcl _ tn tp te cl -> do {
        pp f "@[<2>%a%a@]" o#var tn o#type_params tp;
        match te with
        [ <:ctyp<>> -> ()
        | _ -> pp f " =@ %a" o#ctyp te ];
        if cl <> [] then pp f "@ %a" (list o#constrain "@ ") cl else ();
      }
    | <:ctyp< $t1$ : mutable $t2$ >> ->
        pp f "@[%a :@ mutable %a@]" o#ctyp t1 o#ctyp t2
    | <:ctyp< $t1$ == $t2$ >> ->
        pp f "@[<2>%a ==@ %a@]" o#simple_ctyp t1 o#ctyp t2
    | t -> super#ctyp f t ];

    method simple_ctyp f t =
    let () = o#node f t Ast.loc_of_ctyp in
    match t with
    [ <:ctyp< [ = $t$ ] >> -> pp f "@[<2>[ =@ %a@]@ ]" o#ctyp t
    | <:ctyp< [ < $t$ ] >> -> pp f "@[<2>[ <@ %a@]@,]" o#ctyp t
    | <:ctyp< [ < $t1$ > $t2$ ] >> ->
        pp f "@[<2>[ <@ %a@ >@ %a@]@ ]" o#ctyp t1 o#ctyp t2
    | <:ctyp< [ > $t$ ] >> -> pp f "@[<2>[ >@ %a@]@,]" o#ctyp t
    | <:ctyp< $t1$ == $t2$ >> ->
        pp f "@[<2>%a@ ==@ %a@]" o#simple_ctyp t1 o#simple_ctyp t2
    | <:ctyp< ~ $s$ : $t$ >> -> pp f "@[<2>~%s:@ %a@]" s o#simple_ctyp t
    | t -> super#simple_ctyp f t ];

    method ctyp1 f = fun
    [ <:ctyp< $t1$ $t2$ >> ->
        match get_ctyp_args t1 [t2] with
        [ (_, [_]) -> pp f "@[<2>%a@ %a@]" o#simple_ctyp t1 o#simple_ctyp t2
        | (a, al) -> pp f "@[<2>%a@]" (list o#simple_ctyp "@ ") [a::al] ]
    | <:ctyp< ! $t1$ . $t2$ >> ->
        let (a, al) = get_ctyp_args t1 [] in
        pp f "@[<2>! %a.@ %a@]" (list o#ctyp "@ ") [a::al] o#ctyp t2
    | t -> super#ctyp1 f t ];

    method constructor_type f t =
    match t with
    [ <:ctyp@loc< $t1$ and $t2$ >> ->
        let () = o#node f t (fun _ -> loc) in
        pp f "%a@ and %a" o#constructor_type t1 o#constructor_type t2
    | t -> o#ctyp f t ];

    method str_item f st =
    match st with
    [ <:str_item< $exp:e$ >> -> pp f "@[<2>%a%(%)@]" o#expr e semisep
    | st -> super#str_item f st ];

    method module_expr f me =
    let () = o#node f me Ast.loc_of_module_expr in
    match me with
    [ <:module_expr< $me1$ $me2$ >> ->
          pp f "@[<2>%a@ %a@]" o#module_expr me1 o#simple_module_expr me2
    | me -> super#module_expr f me ];

    method simple_module_expr f me =
    let () = o#node f me Ast.loc_of_module_expr in
    match me with
    [ <:module_expr< $_$ $_$ >> ->
          pp f "(%a)" o#module_expr me
    | _ -> super#simple_module_expr f me ];

    method implem f st = pp f "@[<v0>%a@]@." o#str_item st;

    method class_type f ct =
    let () = o#node f ct Ast.loc_of_class_type in
    match ct with
    [ <:class_type< [ $t$ ] -> $ct$ >> ->
          pp f "@[<2>[ %a ] ->@ %a@]" o#simple_ctyp t o#class_type ct
    | <:class_type< $id:i$ >> ->
          pp f "@[<2>%a@]" o#ident i
    | <:class_type< $id:i$ [ $t$ ] >> ->
          pp f "@[<2>%a [@,%a@]@,]" o#ident i o#class_params t
    | <:class_type< virtual $lid:i$ >> ->
          pp f "@[<2>virtual@ %a@]" o#var i
    | <:class_type< virtual $lid:i$ [ $t$ ] >> ->
          pp f "@[<2>virtual@ %a@ [@,%a@]@,]" o#var i o#class_params t
    | ct -> super#class_type f ct ];

    method class_expr f ce =
    let () = o#node f ce Ast.loc_of_class_expr in
    match ce with
    [ <:class_expr< $id:i$ >> ->
          pp f "@[<2>%a@]" o#ident i
    | <:class_expr< $id:i$ [ $t$ ] >> ->
          pp f "@[<2>%a@ @[<1>[%a]@]@]" o#ident i o#class_params t
    | <:class_expr< virtual $lid:i$ >> ->
          pp f "@[<2>virtual@ %a@]" o#var i
    | <:class_expr< virtual $lid:i$ [ $t$ ] >> ->
          pp f "@[<2>virtual@ %a@ @[<1>[%a]@]@]" o#var i o#class_params t
    | ce -> super#class_expr f ce ];
  end;

  value with_outfile = with_outfile;

  value print output_file fct =
    let o = new printer () in
    with_outfile output_file (fct o);

  value print_interf ?input_file:(_) ?output_file sg =
    print output_file (fun o -> o#interf) sg;

  value print_implem ?input_file:(_) ?output_file st =
    print output_file (fun o -> o#implem) st;

end;

module MakeMore (Syntax : Sig.Camlp4Syntax)
: (Sig.Printer Syntax.Ast).S
= struct

  include Make Syntax;

  value margin = ref 78;
  value comments = ref True;
  value locations = ref False;
  value curry_constr = ref True;

  value print output_file fct =
    let o = new printer ~comments:comments.val
                        ~curry_constr:curry_constr.val () in
    let o = if locations.val then o#set_loc_and_comments else o in
    with_outfile output_file
      (fun f ->
        let () = Format.pp_set_margin f margin.val in
        Format.fprintf f "@[<v0>%a@]@." (fct o));

  value print_interf ?input_file:(_) ?output_file sg =
    print output_file (fun o -> o#interf) sg;

  value print_implem ?input_file:(_) ?output_file st =
    print output_file (fun o -> o#implem) st;

  Options.add "-l" (Arg.Int (fun i -> margin.val := i))
    "<length> line length for pretty printing.";

  Options.add "-no_comments" (Arg.Clear comments) "Do not add comments.";

  Options.add "-add_locations" (Arg.Set locations) "Add locations as comment.";

end;