1Parsetree(3) OCaml library Parsetree(3)
2
3
4
6 Parsetree - Abstract syntax tree produced by parsing
7
9 Module Parsetree
10
12 Module Parsetree
13 : sig end
14
15
16 Abstract syntax tree produced by parsing
17
18 Warning: this module is unstable and part of Compiler_libs .
19
20
21
22
23
24 type constant =
25 | Pconst_integer of string * char option
26 (* Integer constants such as 3 3l 3L 3n .
27
28 Suffixes [g-z][G-Z] are accepted by the parser. Suffixes except 'l' ,
29 'L' and 'n' are rejected by the typechecker
30 *)
31 | Pconst_char of char
32 (* Character such as 'c' .
33 *)
34 | Pconst_string of string * Location.t * string option
35 (* Constant string such as "constant" or {delim|other constant|delim}
36 .
37
38 The location span the content of the string, without the delimiters.
39 *)
40 | Pconst_float of string * char option
41 (* Float constant such as 3.4 , 2e5 or 1.4e-4 .
42
43 Suffixes g-z G-Z are accepted by the parser. Suffixes are rejected by
44 the typechecker.
45 *)
46
47
48
49
50 type location_stack = Location.t list
51
52
53
54
55
56
57 Extension points
58 type attribute = {
59 attr_name : string Asttypes.loc ;
60 attr_payload : payload ;
61 attr_loc : Location.t ;
62 }
63
64
65 Attributes such as [@id ARG] and [@@id ARG] .
66
67 Metadata containers passed around within the AST. The compiler ignores
68 unknown attributes.
69
70
71 type extension = string Asttypes.loc * payload
72
73
74 Extension points such as [%id ARG] and [%%id ARG] .
75
76 Sub-language placeholder -- rejected by the typechecker.
77
78
79 type attributes = attribute list
80
81
82
83
84 type payload =
85 | PStr of structure
86 | PSig of signature
87 (* : SIG in an attribute or an extension point
88 *)
89 | PTyp of core_type
90 (* : T in an attribute or an extension point
91 *)
92 | PPat of pattern * expression option
93 (* ? P or ? P when E , in an attribute or an extension point
94 *)
95
96
97
98
99
100
101 Core language
102 Type expressions
103 type core_type = {
104 ptyp_desc : core_type_desc ;
105 ptyp_loc : Location.t ;
106 ptyp_loc_stack : location_stack ;
107 ptyp_attributes : attributes ; (* ... [@id1] [@id2]
108
109 *)
110 }
111
112
113
114
115 type core_type_desc =
116 | Ptyp_any (* _
117
118 *)
119 | Ptyp_var of string
120 (* A type variable such as 'a
121
122 *)
123 | Ptyp_arrow of Asttypes.arg_label * core_type * core_type
124 (* Ptyp_arrow(lbl, T1, T2) represents:
125
126 - T1 -> T2 when lbl is Asttypes.arg_label.Nolabel ,
127
128 - ~l:T1 -> T2 when lbl is Asttypes.arg_label.Labelled ,
129
130 - ?l:T1 -> T2 when lbl is Asttypes.arg_label.Optional .
131
132 *)
133 | Ptyp_tuple of core_type list
134 (* Ptyp_tuple([T1 ; ... ; Tn]) represents a product type T1 * ... *
135 Tn .
136
137 Invariant: n >= 2 .
138 *)
139 | Ptyp_constr of Longident.t Asttypes.loc * core_type list
140 (* Ptyp_constr(lident, l) represents:
141
142 - tconstr when l=[] ,
143
144 - T tconstr when l=[T] ,
145
146 - (T1, ..., Tn) tconstr when l=[T1 ; ... ; Tn] .
147
148 *)
149 | Ptyp_object of object_field list * Asttypes.closed_flag
150 (* Ptyp_object([ l1:T1; ...; ln:Tn ], flag) represents:
151
152 - < l1:T1; ...; ln:Tn > when flag is Asttypes.closed_flag.Closed ,
153
154 - < l1:T1; ...; ln:Tn; .. > when flag is Asttypes.closed_flag.Open .
155
156 *)
157 | Ptyp_class of Longident.t Asttypes.loc * core_type list
158 (* Ptyp_class(tconstr, l) represents:
159
160 - #tconstr when l=[] ,
161
162 - T #tconstr when l=[T] ,
163
164 - (T1, ..., Tn) #tconstr when l=[T1 ; ... ; Tn] .
165
166 *)
167 | Ptyp_alias of core_type * string
168 (* T as 'a .
169 *)
170 | Ptyp_variant of row_field list * Asttypes.closed_flag * Asttypes.la‐
171 bel list option
172 (* Ptyp_variant([`A;`B], flag, labels) represents:
173
174 - [ `A|`B ] when flag is Asttypes.closed_flag.Closed , and labels is
175 None ,
176
177 - [> `A|`B ] when flag is Asttypes.closed_flag.Open , and labels is
178 None ,
179
180 - [< `A|`B ] when flag is Asttypes.closed_flag.Closed , and labels is
181 Some [] ,
182
183 - [< `A|`B > `X `Y ] when flag is Asttypes.closed_flag.Closed , and la‐
184 bels is Some ["X";"Y"] .
185
186 *)
187 | Ptyp_poly of string Asttypes.loc list * core_type
188 (* 'a1 ... 'an. T
189
190 Can only appear in the following context:
191
192
193 -As the Parsetree.core_type of a Parsetree.pattern_desc.Ppat_constraint
194 node corresponding to a constraint on a let-binding:
195 let x : 'a1 ... 'an. T = e ...
196
197
198 -Under Parsetree.class_field_kind.Cfk_virtual for methods (not values).
199
200
201 -As the Parsetree.core_type of a Parse‐
202 tree.class_type_field_desc.Pctf_method node.
203
204
205 -As the Parsetree.core_type of a Parsetree.expression_desc.Pexp_poly
206 node.
207
208
209 -As the Parsetree.label_declaration.pld_type field of a Parsetree.la‐
210 bel_declaration .
211
212
213 -As a Parsetree.core_type of a Parsetree.core_type_desc.Ptyp_object
214 node.
215
216
217 -As the Parsetree.value_description.pval_type field of a Parse‐
218 tree.value_description .
219
220 *)
221 | Ptyp_package of package_type
222 (* (module S) .
223 *)
224 | Ptyp_extension of extension
225 (* [%id] .
226 *)
227
228
229
230
231 type package_type = Longident.t Asttypes.loc * (Longident.t Ast‐
232 types.loc * core_type) list
233
234
235 As Parsetree.package_type typed values:
236
237 - (S, []) represents (module S) ,
238
239 - (S, [(t1, T1) ; ... ; (tn, Tn)]) represents (module S with type t1 =
240 T1 and ... and tn = Tn) .
241
242
243
244 type row_field = {
245 prf_desc : row_field_desc ;
246 prf_loc : Location.t ;
247 prf_attributes : attributes ;
248 }
249
250
251
252
253 type row_field_desc =
254 | Rtag of Asttypes.label Asttypes.loc * bool * core_type list
255 (* Rtag(`A, b, l) represents:
256
257 - `A when b is true and l is [] ,
258
259 - `A of T when b is false and l is [T] ,
260
261 - `A of T1 & .. & Tn when b is false and l is [T1;...Tn] ,
262
263 - `A of & T1 & .. & Tn when b is true and l is [T1;...Tn] .
264
265
266 -The bool field is true if the tag contains a constant (empty) con‐
267 structor.
268
269 - & occurs when several types are used for the same constructor (see
270 4.2 in the manual)
271
272 *)
273 | Rinherit of core_type
274 (* [ | t ]
275
276 *)
277
278
279
280
281 type object_field = {
282 pof_desc : object_field_desc ;
283 pof_loc : Location.t ;
284 pof_attributes : attributes ;
285 }
286
287
288
289
290 type object_field_desc =
291 | Otag of Asttypes.label Asttypes.loc * core_type
292 | Oinherit of core_type
293
294
295
296
297
298
299 Patterns
300 type pattern = {
301 ppat_desc : pattern_desc ;
302 ppat_loc : Location.t ;
303 ppat_loc_stack : location_stack ;
304 ppat_attributes : attributes ; (* ... [@id1] [@id2]
305
306 *)
307 }
308
309
310
311
312 type pattern_desc =
313 | Ppat_any (* The pattern _ .
314 *)
315 | Ppat_var of string Asttypes.loc
316 (* A variable pattern such as x
317
318 *)
319 | Ppat_alias of pattern * string Asttypes.loc
320 (* An alias pattern such as P as 'a
321
322 *)
323 | Ppat_constant of constant
324 (* Patterns such as 1 , 'a' , "true" , 1.0 , 1l , 1L , 1n
325
326 *)
327 | Ppat_interval of constant * constant
328 (* Patterns such as 'a'..'z' .
329
330 Other forms of interval are recognized by the parser but rejected by
331 the type-checker.
332 *)
333 | Ppat_tuple of pattern list
334 (* Patterns (P1, ..., Pn) .
335
336 Invariant: n >= 2
337
338 *)
339 | Ppat_construct of Longident.t Asttypes.loc * (string Asttypes.loc
340 list * pattern) option
341 (* Ppat_construct(C, args) represents:
342
343 - C when args is None ,
344
345 - C P when args is Some ([], P)
346
347
348 - C (P1, ..., Pn) when args is Some ([], Ppat_tuple [P1; ...; Pn])
349
350
351 - C (type a b) P when args is Some ([a; b], P)
352
353
354 *)
355 | Ppat_variant of Asttypes.label * pattern option
356 (* Ppat_variant(`A, pat) represents:
357
358 - `A when pat is None ,
359
360 - `A P when pat is Some P
361
362
363 *)
364 | Ppat_record of (Longident.t Asttypes.loc * pattern) list * Ast‐
365 types.closed_flag
366 (* Ppat_record([(l1, P1) ; ... ; (ln, Pn)], flag) represents:
367
368 - { l1=P1; ...; ln=Pn } when flag is Asttypes.closed_flag.Closed
369
370
371 - { l1=P1; ...; ln=Pn; _} when flag is Asttypes.closed_flag.Open
372
373 Invariant: n > 0
374
375 *)
376 | Ppat_array of pattern list
377 (* Pattern [| P1; ...; Pn |]
378
379 *)
380 | Ppat_or of pattern * pattern
381 (* Pattern P1 | P2
382
383 *)
384 | Ppat_constraint of pattern * core_type
385 (* Pattern (P : T)
386
387 *)
388 | Ppat_type of Longident.t Asttypes.loc
389 (* Pattern #tconst
390
391 *)
392 | Ppat_lazy of pattern
393 (* Pattern lazy P
394
395 *)
396 | Ppat_unpack of string option Asttypes.loc
397 (* Ppat_unpack(s) represents:
398
399 - (module P) when s is Some "P"
400
401
402 - (module _) when s is None
403
404 Note: (module P : S) is represented as Ppat_constraint(Ppat_unpack(Some
405 "P"), Ptyp_package S)
406
407 *)
408 | Ppat_exception of pattern
409 (* Pattern exception P
410
411 *)
412 | Ppat_extension of extension
413 (* Pattern [%id]
414
415 *)
416 | Ppat_open of Longident.t Asttypes.loc * pattern
417 (* Pattern M.(P)
418
419 *)
420
421
422
423
424
425
426 Value expressions
427 type expression = {
428 pexp_desc : expression_desc ;
429 pexp_loc : Location.t ;
430 pexp_loc_stack : location_stack ;
431 pexp_attributes : attributes ; (* ... [@id1] [@id2]
432
433 *)
434 }
435
436
437
438
439 type expression_desc =
440 | Pexp_ident of Longident.t Asttypes.loc
441 (* Identifiers such as x and M.x
442
443 *)
444 | Pexp_constant of constant
445 (* Expressions constant such as 1 , 'a' , "true" , 1.0 , 1l , 1L , 1n
446
447 *)
448 | Pexp_let of Asttypes.rec_flag * value_binding list * expression
449 (* Pexp_let(flag, [(P1,E1) ; ... ; (Pn,En)], E) represents:
450
451 - let P1 = E1 and ... and Pn = EN in E when flag is Ast‐
452 types.rec_flag.Nonrecursive ,
453
454 - let rec P1 = E1 and ... and Pn = EN in E when flag is Ast‐
455 types.rec_flag.Recursive .
456
457 *)
458 | Pexp_function of case list
459 (* function P1 -> E1 | ... | Pn -> En
460
461 *)
462 | Pexp_fun of Asttypes.arg_label * expression option * pattern * ex‐
463 pression
464 (* Pexp_fun(lbl, exp0, P, E1) represents:
465
466 - fun P -> E1 when lbl is Asttypes.arg_label.Nolabel and exp0 is None
467
468
469 - fun ~l:P -> E1 when lbl is Asttypes.arg_label.Labelled and exp0 is
470 None
471
472
473 - fun ?l:P -> E1 when lbl is Asttypes.arg_label.Optional and exp0 is
474 None
475
476
477 - fun ?l:(P = E0) -> E1 when lbl is Asttypes.arg_label.Optional and
478 exp0 is Some E0
479
480 Notes:
481
482 -If E0 is provided, only Asttypes.arg_label.Optional is allowed.
483
484 - fun P1 P2 .. Pn -> E1 is represented as nested Parsetree.expres‐
485 sion_desc.Pexp_fun .
486
487 - let f P = E is represented using Parsetree.expression_desc.Pexp_fun .
488
489 *)
490 | Pexp_apply of expression * (Asttypes.arg_label * expression) list
491 (* Pexp_apply(E0, [(l1, E1) ; ... ; (ln, En)]) represents E0 ~l1:E1
492 ... ~ln:En
493
494
495 li can be Asttypes.arg_label.Nolabel (non labeled argument), Ast‐
496 types.arg_label.Labelled (labelled arguments) or Asttypes.arg_label.Op‐
497 tional (optional argument).
498
499 Invariant: n > 0
500
501 *)
502 | Pexp_match of expression * case list
503 (* match E0 with P1 -> E1 | ... | Pn -> En
504
505 *)
506 | Pexp_try of expression * case list
507 (* try E0 with P1 -> E1 | ... | Pn -> En
508
509 *)
510 | Pexp_tuple of expression list
511 (* Expressions (E1, ..., En)
512
513 Invariant: n >= 2
514
515 *)
516 | Pexp_construct of Longident.t Asttypes.loc * expression option
517 (* Pexp_construct(C, exp) represents:
518
519 - C when exp is None ,
520
521 - C E when exp is Some E ,
522
523 - C (E1, ..., En) when exp is Some (Pexp_tuple[E1;...;En])
524
525
526 *)
527 | Pexp_variant of Asttypes.label * expression option
528 (* Pexp_variant(`A, exp) represents
529
530 - `A when exp is None
531
532
533 - `A E when exp is Some E
534
535
536 *)
537 | Pexp_record of (Longident.t Asttypes.loc * expression) list * ex‐
538 pression option
539 (* Pexp_record([(l1,P1) ; ... ; (ln,Pn)], exp0) represents
540
541 - { l1=P1; ...; ln=Pn } when exp0 is None
542
543
544 - { E0 with l1=P1; ...; ln=Pn } when exp0 is Some E0
545
546 Invariant: n > 0
547
548 *)
549 | Pexp_field of expression * Longident.t Asttypes.loc
550 (* E.l
551
552 *)
553 | Pexp_setfield of expression * Longident.t Asttypes.loc * expression
554 (* E1.l <- E2
555
556 *)
557 | Pexp_array of expression list
558 (* [| E1; ...; En |]
559
560 *)
561 | Pexp_ifthenelse of expression * expression * expression option
562 (* if E1 then E2 else E3
563
564 *)
565 | Pexp_sequence of expression * expression
566 (* E1; E2
567
568 *)
569 | Pexp_while of expression * expression
570 (* while E1 do E2 done
571
572 *)
573 | Pexp_for of pattern * expression * expression * Asttypes.direc‐
574 tion_flag * expression
575 (* Pexp_for(i, E1, E2, direction, E3) represents:
576
577 - for i = E1 to E2 do E3 done when direction is Asttypes.direc‐
578 tion_flag.Upto
579
580
581 - for i = E1 downto E2 do E3 done when direction is Asttypes.direc‐
582 tion_flag.Downto
583
584
585 *)
586 | Pexp_constraint of expression * core_type
587 (* (E : T)
588
589 *)
590 | Pexp_coerce of expression * core_type option * core_type
591 (* Pexp_coerce(E, from, T) represents
592
593 - (E :> T) when from is None ,
594
595 - (E : T0 :> T) when from is Some T0 .
596
597 *)
598 | Pexp_send of expression * Asttypes.label Asttypes.loc
599 (* E # m
600
601 *)
602 | Pexp_new of Longident.t Asttypes.loc
603 (* new M.c
604
605 *)
606 | Pexp_setinstvar of Asttypes.label Asttypes.loc * expression
607 (* x <- 2
608
609 *)
610 | Pexp_override of (Asttypes.label Asttypes.loc * expression) list
611 (* {< x1 = E1; ...; xn = En >}
612
613 *)
614 | Pexp_letmodule of string option Asttypes.loc * module_expr * expres‐
615 sion
616 (* let module M = ME in E
617
618 *)
619 | Pexp_letexception of extension_constructor * expression
620 (* let exception C in E
621
622 *)
623 | Pexp_assert of expression
624 (* assert E .
625
626 Note: assert false is treated in a special way by the type-checker.
627 *)
628 | Pexp_lazy of expression
629 (* lazy E
630
631 *)
632 | Pexp_poly of expression * core_type option
633 (* Used for method bodies.
634
635 Can only be used as the expression under Parse‐
636 tree.class_field_kind.Cfk_concrete for methods (not values).
637 *)
638 | Pexp_object of class_structure
639 (* object ... end
640
641 *)
642 | Pexp_newtype of string Asttypes.loc * expression
643 (* fun (type t) -> E
644
645 *)
646 | Pexp_pack of module_expr
647 (* (module ME) .
648
649
650 (module ME : S) is represented as Pexp_constraint(Pexp_pack ME,
651 Ptyp_package S)
652
653 *)
654 | Pexp_open of open_declaration * expression
655 (* - M.(E)
656
657 - let open M in E
658
659
660 - let open! M in E
661
662
663 *)
664 | Pexp_letop of letop
665 (* - let* P = E0 in E1
666
667 - let* P0 = E00 and* P1 = E01 in E1
668
669
670 *)
671 | Pexp_extension of extension
672 (* [%id]
673
674 *)
675 | Pexp_unreachable (* .
676
677 *)
678
679
680
681
682 type case = {
683 pc_lhs : pattern ;
684 pc_guard : expression option ;
685 pc_rhs : expression ;
686 }
687
688
689 Values of type Parsetree.case represents (P -> E) or (P when E0 -> E)
690
691
692
693 type letop = {
694 let_ : binding_op ;
695 ands : binding_op list ;
696 body : expression ;
697 }
698
699
700
701
702 type binding_op = {
703 pbop_op : string Asttypes.loc ;
704 pbop_pat : pattern ;
705 pbop_exp : expression ;
706 pbop_loc : Location.t ;
707 }
708
709
710
711
712
713
714 Value descriptions
715 type value_description = {
716 pval_name : string Asttypes.loc ;
717 pval_type : core_type ;
718 pval_prim : string list ;
719 pval_attributes : attributes ; (* ... [@@id1] [@@id2]
720
721 *)
722 pval_loc : Location.t ;
723 }
724
725
726 Values of type Parsetree.value_description represents:
727
728 - val x: T , when Parsetree.value_description.pval_prim is []
729
730
731 - external x: T = "s1" ... "sn" when Parsetree.value_descrip‐
732 tion.pval_prim is ["s1";..."sn"]
733
734
735
736
737
738
739 Type declarations
740 type type_declaration = {
741 ptype_name : string Asttypes.loc ;
742 ptype_params : (core_type * (Asttypes.variance * Asttypes.injectiv‐
743 ity)) list ; (* ('a1,...'an) t
744
745 *)
746 ptype_cstrs : (core_type * core_type * Location.t) list ; (* ... con‐
747 straint T1=T1' ... constraint Tn=Tn'
748
749 *)
750 ptype_kind : type_kind ;
751 ptype_private : Asttypes.private_flag ; (* for = private ...
752
753 *)
754 ptype_manifest : core_type option ; (* represents = T
755
756 *)
757 ptype_attributes : attributes ; (* ... [@@id1] [@@id2]
758
759 *)
760 ptype_loc : Location.t ;
761 }
762
763
764 Here are type declarations and their representation, for various Parse‐
765 tree.type_declaration.ptype_kind and Parsetree.type_declara‐
766 tion.ptype_manifest values:
767
768 - type t when type_kind is Parsetree.type_kind.Ptype_abstract , and
769 manifest is None ,
770
771 - type t = T0 when type_kind is Parsetree.type_kind.Ptype_abstract ,
772 and manifest is Some T0 ,
773
774 - type t = C of T | ... when type_kind is Parse‐
775 tree.type_kind.Ptype_variant , and manifest is None ,
776
777 - type t = T0 = C of T | ... when type_kind is Parse‐
778 tree.type_kind.Ptype_variant , and manifest is Some T0 ,
779
780 - type t = {l: T; ...} when type_kind is Parse‐
781 tree.type_kind.Ptype_record , and manifest is None ,
782
783 - type t = T0 = {l : T; ...} when type_kind is Parse‐
784 tree.type_kind.Ptype_record , and manifest is Some T0 ,
785
786 - type t = .. when type_kind is Parsetree.type_kind.Ptype_open , and
787 manifest is None .
788
789
790
791 type type_kind =
792 | Ptype_abstract
793 | Ptype_variant of constructor_declaration list
794 | Ptype_record of label_declaration list
795 (* Invariant: non-empty list
796 *)
797 | Ptype_open
798
799
800
801
802 type label_declaration = {
803 pld_name : string Asttypes.loc ;
804 pld_mutable : Asttypes.mutable_flag ;
805 pld_type : core_type ;
806 pld_loc : Location.t ;
807 pld_attributes : attributes ; (* l : T [@id1] [@id2]
808
809 *)
810 }
811
812
813 - { ...; l: T; ... } when Parsetree.label_declaration.pld_mutable is
814 Asttypes.mutable_flag.Immutable ,
815
816 - { ...; mutable l: T; ... } when Parsetree.label_declaration.pld_muta‐
817 ble is Asttypes.mutable_flag.Mutable .
818
819 Note: T can be a Parsetree.core_type_desc.Ptyp_poly .
820
821
822 type constructor_declaration = {
823 pcd_name : string Asttypes.loc ;
824 pcd_vars : string Asttypes.loc list ;
825 pcd_args : constructor_arguments ;
826 pcd_res : core_type option ;
827 pcd_loc : Location.t ;
828 pcd_attributes : attributes ; (* C of ... [@id1] [@id2]
829
830 *)
831 }
832
833
834
835
836 type constructor_arguments =
837 | Pcstr_tuple of core_type list
838 | Pcstr_record of label_declaration list
839 (* Values of type Parsetree.constructor_declaration represents the
840 constructor arguments of:
841
842 - C of T1 * ... * Tn when res = None , and args = Pcstr_tuple [T1; ...
843 ; Tn] ,
844
845 - C: T0 when res = Some T0 , and args = Pcstr_tuple [] ,
846
847 - C: T1 * ... * Tn -> T0 when res = Some T0 , and args = Pcstr_tuple
848 [T1; ... ; Tn] ,
849
850 - C of {...} when res = None , and args = Pcstr_record [...] ,
851
852 - C: {...} -> T0 when res = Some T0 , and args = Pcstr_record [...] .
853
854 *)
855
856
857
858
859 type type_extension = {
860 ptyext_path : Longident.t Asttypes.loc ;
861 ptyext_params : (core_type * (Asttypes.variance * Asttypes.injectiv‐
862 ity)) list ;
863 ptyext_constructors : extension_constructor list ;
864 ptyext_private : Asttypes.private_flag ;
865 ptyext_loc : Location.t ;
866 ptyext_attributes : attributes ; (* ... @@id1 @@id2
867
868 *)
869 }
870
871
872 Definition of new extensions constructors for the extensive sum type t
873 ( type t += ... ).
874
875
876 type extension_constructor = {
877 pext_name : string Asttypes.loc ;
878 pext_kind : extension_constructor_kind ;
879 pext_loc : Location.t ;
880 pext_attributes : attributes ; (* C of ... [@id1] [@id2]
881
882 *)
883 }
884
885
886
887
888 type type_exception = {
889 ptyexn_constructor : extension_constructor ;
890 ptyexn_loc : Location.t ;
891 ptyexn_attributes : attributes ; (* ... [@@id1] [@@id2]
892
893 *)
894 }
895
896
897 Definition of a new exception ( exception E ).
898
899
900 type extension_constructor_kind =
901 | Pext_decl of string Asttypes.loc list * constructor_arguments *
902 core_type option
903 (* Pext_decl(existentials, c_args, t_opt) describes a new extension
904 constructor. It can be:
905
906 - C of T1 * ... * Tn when:
907
908 - existentials is [] ,
909
910 - c_args is [T1; ...; Tn] ,
911
912 - t_opt is None
913
914
915
916 - C: T0 when
917
918 - existentials is [] ,
919
920 - c_args is [] ,
921
922 - t_opt is Some T0 .
923
924
925 - C: T1 * ... * Tn -> T0 when
926
927 - existentials is [] ,
928
929 - c_args is [T1; ...; Tn] ,
930
931 - t_opt is Some T0 .
932
933
934 - C: 'a... . T1 * ... * Tn -> T0 when
935
936 - existentials is ['a;...] ,
937
938 - c_args is [T1; ... ; Tn] ,
939
940 - t_opt is Some T0 .
941
942
943 *)
944 | Pext_rebind of Longident.t Asttypes.loc
945 (* Pext_rebind(D) re-export the constructor D with the new name C
946
947 *)
948
949
950
951
952
953
954 Class language
955 Type expressions for the class language
956 type class_type = {
957 pcty_desc : class_type_desc ;
958 pcty_loc : Location.t ;
959 pcty_attributes : attributes ; (* ... [@id1] [@id2]
960
961 *)
962 }
963
964
965
966
967 type class_type_desc =
968 | Pcty_constr of Longident.t Asttypes.loc * core_type list
969 (* - c
970
971 - ['a1, ..., 'an] c
972
973
974 *)
975 | Pcty_signature of class_signature
976 (* object ... end
977
978 *)
979 | Pcty_arrow of Asttypes.arg_label * core_type * class_type
980 (* Pcty_arrow(lbl, T, CT) represents:
981
982 - T -> CT when lbl is Asttypes.arg_label.Nolabel ,
983
984 - ~l:T -> CT when lbl is Asttypes.arg_label.Labelled ,
985
986 - ?l:T -> CT when lbl is Asttypes.arg_label.Optional .
987
988 *)
989 | Pcty_extension of extension
990 (* %id
991
992 *)
993 | Pcty_open of open_description * class_type
994 (* let open M in CT
995
996 *)
997
998
999
1000
1001 type class_signature = {
1002 pcsig_self : core_type ;
1003 pcsig_fields : class_type_field list ;
1004 }
1005
1006
1007 Values of type class_signature represents:
1008
1009 - object('selfpat) ... end
1010
1011
1012 - object ... end when Parsetree.class_signature.pcsig_self is Parse‐
1013 tree.core_type_desc.Ptyp_any
1014
1015
1016
1017
1018 type class_type_field = {
1019 pctf_desc : class_type_field_desc ;
1020 pctf_loc : Location.t ;
1021 pctf_attributes : attributes ; (* ... [@@id1] [@@id2]
1022
1023 *)
1024 }
1025
1026
1027
1028
1029 type class_type_field_desc =
1030 | Pctf_inherit of class_type
1031 (* inherit CT
1032
1033 *)
1034 | Pctf_val of (Asttypes.label Asttypes.loc * Asttypes.mutable_flag *
1035 Asttypes.virtual_flag * core_type)
1036 (* val x: T
1037
1038 *)
1039 | Pctf_method of (Asttypes.label Asttypes.loc * Asttypes.private_flag
1040 * Asttypes.virtual_flag * core_type)
1041 (* method x: T
1042
1043 Note: T can be a Parsetree.core_type_desc.Ptyp_poly .
1044 *)
1045 | Pctf_constraint of (core_type * core_type)
1046 (* constraint T1 = T2
1047
1048 *)
1049 | Pctf_attribute of attribute
1050 (* [@@@id]
1051
1052 *)
1053 | Pctf_extension of extension
1054 (* [%%id]
1055
1056 *)
1057
1058
1059
1060
1061 type 'a class_infos = {
1062 pci_virt : Asttypes.virtual_flag ;
1063 pci_params : (core_type * (Asttypes.variance * Asttypes.injectivity))
1064 list ;
1065 pci_name : string Asttypes.loc ;
1066 pci_expr : 'a ;
1067 pci_loc : Location.t ;
1068 pci_attributes : attributes ; (* ... [@@id1] [@@id2]
1069
1070 *)
1071 }
1072
1073
1074 Values of type class_expr class_infos represents:
1075
1076 - class c = ...
1077
1078
1079 - class ['a1,...,'an] c = ...
1080
1081
1082 - class virtual c = ...
1083
1084 They are also used for "class type" declaration.
1085
1086
1087 type class_description = class_type class_infos
1088
1089
1090
1091
1092 type class_type_declaration = class_type class_infos
1093
1094
1095
1096
1097
1098
1099 Value expressions for the class language
1100 type class_expr = {
1101 pcl_desc : class_expr_desc ;
1102 pcl_loc : Location.t ;
1103 pcl_attributes : attributes ; (* ... [@id1] [@id2]
1104
1105 *)
1106 }
1107
1108
1109
1110
1111 type class_expr_desc =
1112 | Pcl_constr of Longident.t Asttypes.loc * core_type list
1113 (* c and ['a1, ..., 'an] c
1114
1115 *)
1116 | Pcl_structure of class_structure
1117 (* object ... end
1118
1119 *)
1120 | Pcl_fun of Asttypes.arg_label * expression option * pattern *
1121 class_expr
1122 (* Pcl_fun(lbl, exp0, P, CE) represents:
1123
1124 - fun P -> CE when lbl is Asttypes.arg_label.Nolabel and exp0 is None ,
1125
1126 - fun ~l:P -> CE when lbl is Asttypes.arg_label.Labelled and exp0 is
1127 None ,
1128
1129 - fun ?l:P -> CE when lbl is Asttypes.arg_label.Optional and exp0 is
1130 None ,
1131
1132 - fun ?l:(P = E0) -> CE when lbl is Asttypes.arg_label.Optional and
1133 exp0 is Some E0 .
1134
1135 *)
1136 | Pcl_apply of class_expr * (Asttypes.arg_label * expression) list
1137 (* Pcl_apply(CE, [(l1,E1) ; ... ; (ln,En)]) represents CE ~l1:E1 ...
1138 ~ln:En . li can be empty (non labeled argument) or start with ? (op‐
1139 tional argument).
1140
1141 Invariant: n > 0
1142
1143 *)
1144 | Pcl_let of Asttypes.rec_flag * value_binding list * class_expr
1145 (* Pcl_let(rec, [(P1, E1); ... ; (Pn, En)], CE) represents:
1146
1147 - let P1 = E1 and ... and Pn = EN in CE when rec is Ast‐
1148 types.rec_flag.Nonrecursive ,
1149
1150 - let rec P1 = E1 and ... and Pn = EN in CE when rec is Ast‐
1151 types.rec_flag.Recursive .
1152
1153 *)
1154 | Pcl_constraint of class_expr * class_type
1155 (* (CE : CT)
1156
1157 *)
1158 | Pcl_extension of extension
1159 (* [%id]
1160
1161 *)
1162 | Pcl_open of open_description * class_expr
1163 (* let open M in CE
1164
1165 *)
1166
1167
1168
1169
1170 type class_structure = {
1171 pcstr_self : pattern ;
1172 pcstr_fields : class_field list ;
1173 }
1174
1175
1176 Values of type Parsetree.class_structure represents:
1177
1178 - object(selfpat) ... end
1179
1180
1181 - object ... end when Parsetree.class_structure.pcstr_self is Parse‐
1182 tree.pattern_desc.Ppat_any
1183
1184
1185
1186
1187 type class_field = {
1188 pcf_desc : class_field_desc ;
1189 pcf_loc : Location.t ;
1190 pcf_attributes : attributes ; (* ... [@@id1] [@@id2]
1191
1192 *)
1193 }
1194
1195
1196
1197
1198 type class_field_desc =
1199 | Pcf_inherit of Asttypes.override_flag * class_expr * string Ast‐
1200 types.loc option
1201 (* Pcf_inherit(flag, CE, s) represents:
1202
1203 - inherit CE when flag is Asttypes.override_flag.Fresh and s is None ,
1204
1205 - inherit CE as x when flag is Asttypes.override_flag.Fresh and s is
1206 Some x ,
1207
1208 - inherit! CE when flag is Asttypes.override_flag.Override and s is
1209 None ,
1210
1211 - inherit! CE as x when flag is Asttypes.override_flag.Override and s
1212 is Some x
1213
1214
1215 *)
1216 | Pcf_val of (Asttypes.label Asttypes.loc * Asttypes.mutable_flag *
1217 class_field_kind)
1218 (* Pcf_val(x,flag, kind) represents:
1219
1220 - val x = E when flag is Asttypes.mutable_flag.Immutable and kind is
1221 Parsetree.class_field_kind.Cfk_concrete
1222
1223
1224 - val virtual x: T when flag is Asttypes.mutable_flag.Immutable and
1225 kind is Parsetree.class_field_kind.Cfk_virtual
1226
1227
1228 - val mutable x = E when flag is Asttypes.mutable_flag.Mutable and kind
1229 is Parsetree.class_field_kind.Cfk_concrete
1230
1231
1232 - val mutable virtual x: T when flag is Asttypes.mutable_flag.Mutable
1233 and kind is Parsetree.class_field_kind.Cfk_virtual
1234
1235
1236 *)
1237 | Pcf_method of (Asttypes.label Asttypes.loc * Asttypes.private_flag *
1238 class_field_kind)
1239 (* - method x = E ( E can be a Parsetree.expression_desc.Pexp_poly )
1240
1241 - method virtual x: T ( T can be a Parsetree.core_type_desc.Ptyp_poly )
1242
1243 *)
1244 | Pcf_constraint of (core_type * core_type)
1245 (* constraint T1 = T2
1246
1247 *)
1248 | Pcf_initializer of expression
1249 (* initializer E
1250
1251 *)
1252 | Pcf_attribute of attribute
1253 (* [@@@id]
1254
1255 *)
1256 | Pcf_extension of extension
1257 (* [%%id]
1258
1259 *)
1260
1261
1262
1263
1264 type class_field_kind =
1265 | Cfk_virtual of core_type
1266 | Cfk_concrete of Asttypes.override_flag * expression
1267
1268
1269
1270
1271 type class_declaration = class_expr class_infos
1272
1273
1274
1275
1276
1277
1278 Module language
1279 Type expressions for the module language
1280 type module_type = {
1281 pmty_desc : module_type_desc ;
1282 pmty_loc : Location.t ;
1283 pmty_attributes : attributes ; (* ... [@id1] [@id2]
1284
1285 *)
1286 }
1287
1288
1289
1290
1291 type module_type_desc =
1292 | Pmty_ident of Longident.t Asttypes.loc
1293 (* Pmty_ident(S) represents S
1294
1295 *)
1296 | Pmty_signature of signature
1297 (* sig ... end
1298
1299 *)
1300 | Pmty_functor of functor_parameter * module_type
1301 (* functor(X : MT1) -> MT2
1302
1303 *)
1304 | Pmty_with of module_type * with_constraint list
1305 (* MT with ...
1306
1307 *)
1308 | Pmty_typeof of module_expr
1309 (* module type of ME
1310
1311 *)
1312 | Pmty_extension of extension
1313 (* [%id]
1314
1315 *)
1316 | Pmty_alias of Longident.t Asttypes.loc
1317 (* (module M)
1318
1319 *)
1320
1321
1322
1323
1324 type functor_parameter =
1325 | Unit (* ()
1326
1327 *)
1328 | Named of string option Asttypes.loc * module_type
1329 (* Named(name, MT) represents:
1330
1331 - (X : MT) when name is Some X ,
1332
1333 - (_ : MT) when name is None
1334
1335
1336 *)
1337
1338
1339
1340
1341 type signature = signature_item list
1342
1343
1344
1345
1346 type signature_item = {
1347 psig_desc : signature_item_desc ;
1348 psig_loc : Location.t ;
1349 }
1350
1351
1352
1353
1354 type signature_item_desc =
1355 | Psig_value of value_description
1356 (* - val x: T
1357
1358 - external x: T = "s1" ... "sn"
1359
1360
1361 *)
1362 | Psig_type of Asttypes.rec_flag * type_declaration list
1363 (* type t1 = ... and ... and tn = ...
1364
1365 *)
1366 | Psig_typesubst of type_declaration list
1367 (* type t1 := ... and ... and tn := ...
1368
1369 *)
1370 | Psig_typext of type_extension
1371 (* type t1 += ...
1372
1373 *)
1374 | Psig_exception of type_exception
1375 (* exception C of T
1376
1377 *)
1378 | Psig_module of module_declaration
1379 (* module X = M and module X : MT
1380
1381 *)
1382 | Psig_modsubst of module_substitution
1383 (* module X := M
1384
1385 *)
1386 | Psig_recmodule of module_declaration list
1387 (* module rec X1 : MT1 and ... and Xn : MTn
1388
1389 *)
1390 | Psig_modtype of module_type_declaration
1391 (* module type S = MT and module type S
1392
1393 *)
1394 | Psig_modtypesubst of module_type_declaration
1395 (* module type S := ...
1396
1397 *)
1398 | Psig_open of open_description
1399 (* open X
1400
1401 *)
1402 | Psig_include of include_description
1403 (* include MT
1404
1405 *)
1406 | Psig_class of class_description list
1407 (* class c1 : ... and ... and cn : ...
1408
1409 *)
1410 | Psig_class_type of class_type_declaration list
1411 (* class type ct1 = ... and ... and ctn = ...
1412
1413 *)
1414 | Psig_attribute of attribute
1415 (* [@@@id]
1416
1417 *)
1418 | Psig_extension of extension * attributes
1419 (* [%%id]
1420
1421 *)
1422
1423
1424
1425
1426 type module_declaration = {
1427 pmd_name : string option Asttypes.loc ;
1428 pmd_type : module_type ;
1429 pmd_attributes : attributes ; (* ... [@@id1] [@@id2]
1430
1431 *)
1432 pmd_loc : Location.t ;
1433 }
1434
1435
1436 Values of type module_declaration represents S : MT
1437
1438
1439
1440 type module_substitution = {
1441 pms_name : string Asttypes.loc ;
1442 pms_manifest : Longident.t Asttypes.loc ;
1443 pms_attributes : attributes ; (* ... [@@id1] [@@id2]
1444
1445 *)
1446 pms_loc : Location.t ;
1447 }
1448
1449
1450 Values of type module_substitution represents S := M
1451
1452
1453
1454 type module_type_declaration = {
1455 pmtd_name : string Asttypes.loc ;
1456 pmtd_type : module_type option ;
1457 pmtd_attributes : attributes ; (* ... [@@id1] [@@id2]
1458
1459 *)
1460 pmtd_loc : Location.t ;
1461 }
1462
1463
1464 Values of type module_type_declaration represents:
1465
1466 - S = MT ,
1467
1468 - S for abstract module type declaration, when Parsetree.mod‐
1469 ule_type_declaration.pmtd_type is None .
1470
1471
1472
1473 type 'a open_infos = {
1474 popen_expr : 'a ;
1475 popen_override : Asttypes.override_flag ;
1476 popen_loc : Location.t ;
1477 popen_attributes : attributes ;
1478 }
1479
1480
1481 Values of type 'a open_infos represents:
1482
1483 - open! X when Parsetree.open_infos.popen_override is Asttypes.over‐
1484 ride_flag.Override (silences the "used identifier shadowing" warning)
1485
1486 - open X when Parsetree.open_infos.popen_override is Asttypes.over‐
1487 ride_flag.Fresh
1488
1489
1490
1491
1492 type open_description = Longident.t Asttypes.loc open_infos
1493
1494
1495 Values of type open_description represents:
1496
1497 - open M.N
1498
1499
1500 - open M(N).O
1501
1502
1503
1504
1505 type open_declaration = module_expr open_infos
1506
1507
1508 Values of type open_declaration represents:
1509
1510 - open M.N
1511
1512
1513 - open M(N).O
1514
1515
1516 - open struct ... end
1517
1518
1519
1520
1521 type 'a include_infos = {
1522 pincl_mod : 'a ;
1523 pincl_loc : Location.t ;
1524 pincl_attributes : attributes ;
1525 }
1526
1527
1528
1529
1530 type include_description = module_type include_infos
1531
1532
1533 Values of type include_description represents include MT
1534
1535
1536
1537 type include_declaration = module_expr include_infos
1538
1539
1540 Values of type include_declaration represents include ME
1541
1542
1543
1544 type with_constraint =
1545 | Pwith_type of Longident.t Asttypes.loc * type_declaration
1546 (* with type X.t = ...
1547
1548 Note: the last component of the longident must match the name of the
1549 type_declaration.
1550 *)
1551 | Pwith_module of Longident.t Asttypes.loc * Longident.t Asttypes.loc
1552 (* with module X.Y = Z
1553
1554 *)
1555 | Pwith_modtype of Longident.t Asttypes.loc * module_type
1556 (* with module type X.Y = Z
1557
1558 *)
1559 | Pwith_modtypesubst of Longident.t Asttypes.loc * module_type
1560 (* with module type X.Y := sig end
1561
1562 *)
1563 | Pwith_typesubst of Longident.t Asttypes.loc * type_declaration
1564 (* with type X.t := ..., same format as [Pwith_type]
1565
1566 *)
1567 | Pwith_modsubst of Longident.t Asttypes.loc * Longident.t Ast‐
1568 types.loc
1569 (* with module X.Y := Z
1570
1571 *)
1572
1573
1574
1575
1576
1577
1578 Value expressions for the module language
1579 type module_expr = {
1580 pmod_desc : module_expr_desc ;
1581 pmod_loc : Location.t ;
1582 pmod_attributes : attributes ; (* ... [@id1] [@id2]
1583
1584 *)
1585 }
1586
1587
1588
1589
1590 type module_expr_desc =
1591 | Pmod_ident of Longident.t Asttypes.loc
1592 (* X
1593
1594 *)
1595 | Pmod_structure of structure
1596 (* struct ... end
1597
1598 *)
1599 | Pmod_functor of functor_parameter * module_expr
1600 (* functor(X : MT1) -> ME
1601
1602 *)
1603 | Pmod_apply of module_expr * module_expr
1604 (* ME1(ME2)
1605
1606 *)
1607 | Pmod_constraint of module_expr * module_type
1608 (* (ME : MT)
1609
1610 *)
1611 | Pmod_unpack of expression
1612 (* (val E)
1613
1614 *)
1615 | Pmod_extension of extension
1616 (* [%id]
1617
1618 *)
1619
1620
1621
1622
1623 type structure = structure_item list
1624
1625
1626
1627
1628 type structure_item = {
1629 pstr_desc : structure_item_desc ;
1630 pstr_loc : Location.t ;
1631 }
1632
1633
1634
1635
1636 type structure_item_desc =
1637 | Pstr_eval of expression * attributes
1638 (* E
1639
1640 *)
1641 | Pstr_value of Asttypes.rec_flag * value_binding list
1642 (* Pstr_value(rec, [(P1, E1 ; ... ; (Pn, En))]) represents:
1643
1644 - let P1 = E1 and ... and Pn = EN when rec is Asttypes.rec_flag.Nonre‐
1645 cursive ,
1646
1647 - let rec P1 = E1 and ... and Pn = EN when rec is Asttypes.rec_flag.Re‐
1648 cursive .
1649
1650 *)
1651 | Pstr_primitive of value_description
1652 (* - val x: T
1653
1654 - external x: T = "s1" ... "sn"
1655
1656
1657 *)
1658 | Pstr_type of Asttypes.rec_flag * type_declaration list
1659 (* type t1 = ... and ... and tn = ...
1660
1661 *)
1662 | Pstr_typext of type_extension
1663 (* type t1 += ...
1664
1665 *)
1666 | Pstr_exception of type_exception
1667 (* - exception C of T
1668
1669 - exception C = M.X
1670
1671
1672 *)
1673 | Pstr_module of module_binding
1674 (* module X = ME
1675
1676 *)
1677 | Pstr_recmodule of module_binding list
1678 (* module rec X1 = ME1 and ... and Xn = MEn
1679
1680 *)
1681 | Pstr_modtype of module_type_declaration
1682 (* module type S = MT
1683
1684 *)
1685 | Pstr_open of open_declaration
1686 (* open X
1687
1688 *)
1689 | Pstr_class of class_declaration list
1690 (* class c1 = ... and ... and cn = ...
1691
1692 *)
1693 | Pstr_class_type of class_type_declaration list
1694 (* class type ct1 = ... and ... and ctn = ...
1695
1696 *)
1697 | Pstr_include of include_declaration
1698 (* include ME
1699
1700 *)
1701 | Pstr_attribute of attribute
1702 (* [@@@id]
1703
1704 *)
1705 | Pstr_extension of extension * attributes
1706 (* [%%id]
1707
1708 *)
1709
1710
1711
1712
1713 type value_binding = {
1714 pvb_pat : pattern ;
1715 pvb_expr : expression ;
1716 pvb_attributes : attributes ;
1717 pvb_loc : Location.t ;
1718 }
1719
1720
1721
1722
1723 type module_binding = {
1724 pmb_name : string option Asttypes.loc ;
1725 pmb_expr : module_expr ;
1726 pmb_attributes : attributes ;
1727 pmb_loc : Location.t ;
1728 }
1729
1730
1731 Values of type module_binding represents module X = ME
1732
1733
1734
1735
1736
1737 Toplevel
1738 Toplevel phrases
1739 type toplevel_phrase =
1740 | Ptop_def of structure
1741 | Ptop_dir of toplevel_directive
1742 (* #use , #load ...
1743 *)
1744
1745
1746
1747
1748 type toplevel_directive = {
1749 pdir_name : string Asttypes.loc ;
1750 pdir_arg : directive_argument option ;
1751 pdir_loc : Location.t ;
1752 }
1753
1754
1755
1756
1757 type directive_argument = {
1758 pdira_desc : directive_argument_desc ;
1759 pdira_loc : Location.t ;
1760 }
1761
1762
1763
1764
1765 type directive_argument_desc =
1766 | Pdir_string of string
1767 | Pdir_int of string * char option
1768 | Pdir_ident of Longident.t
1769 | Pdir_bool of bool
1770
1771
1772
1773
1774
1775
1776
1777OCamldoc 2023-01-23 Parsetree(3)