File: path.mli

package info (click to toggle)
ocaml 5.4.0-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 44,384 kB
  • sloc: ml: 370,196; ansic: 52,820; sh: 27,419; asm: 5,462; makefile: 3,684; python: 974; awk: 278; javascript: 273; perl: 59; fortran: 21; cs: 9
file content (83 lines) | stat: -rw-r--r-- 3,035 bytes parent folder | download | duplicates (3)
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
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           *)
(*                                                                        *)
(*   Copyright 1996 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(* Access paths *)

type t =
  | Pident of Ident.t
  (** Examples: x, List, int *)
  | Pdot of t * string
  (** Examples: List.map, Float.Array *)
  | Papply of t * t
  (** Examples: Set.Make(Int), Map.Make(Set.Make(Int)) *)
  | Pextra_ty of t * extra_ty
  (** [Pextra_ty (p, extra)] are additional paths of types
      introduced by specific OCaml constructs. See below.
  *)
and extra_ty =
  | Pcstr_ty of string
  (** [Pextra_ty (p, Pcstr_ty c)] is the type of the inline record for
      constructor [c] inside type [p].

      For example, in
      {[
        type 'a t = Nil | Cons of {hd : 'a; tl : 'a t}
      ]}

      The inline record type [{hd : 'a; tl : 'a t}] cannot
      be named by the user in the surface syntax, but internally
      it has the path
        [Pextra_ty (Pident `t`, Pcstr_ty "Cons")].
  *)
  | Pext_ty
  (** [Pextra_ty (p, Pext_ty)] is the type of the inline record for
      the extension constructor [p].

      For example, in
      {[
        type exn += Error of {loc : loc; msg : string}
      ]}

      The inline record type [{loc : loc; msg : string}] cannot
      be named by the user in the surface syntax, but internally
      it has the path
        [Pextra_ty (Pident `Error`, Pext_ty)].
  *)

val same: t -> t -> bool
val compare: t -> t -> int
val compare_extra: extra_ty -> extra_ty -> int
val find_free_opt: Ident.t list -> t -> Ident.t option
val exists_free: Ident.t list -> t -> bool
val scope: t -> int
val flatten : t -> [ `Contains_apply | `Ok of Ident.t * string list ]

val scrape_extra_ty: t -> t
(** Removes surrounding `Pext_ty` constructors from a path *)

val name: ?paren:(string -> bool) -> t -> string
    (* [paren] tells whether a path suffix needs parentheses *)
val head: t -> Ident.t

val print: t Format_doc.printer

val heads: t -> Ident.t list

val last: t -> string

val is_constructor_typath: t -> bool

module Map : Map.S with type key = t
module Set : Set.S with type elt = t