This file is indexed.

/usr/lib/ocaml/sexplib/macro.mli is in libsexplib-camlp4-dev 113.00.00-1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  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
(**
   Support for variable expansion and templates within s-expressions. The
   functions in this module evaluate the following constructs within
   s-expressions:

   {ul
   {- [(:include filename)] is replaced with the list of s-expressions contained
   in [filename], as if the contents of [filename] were directly inserted in
   place of [(:include filename)].  A relative [filename] is taken with respect
   to the file that contains the include macro.}

   {- [(:let v (v1 ... vn) S1 ... Sm)] defines a template [v] with arguments [v1,
   ..., vn] and body [S1 ... Sm]. The definition itself is removed from the
   input. The variables [v1, ..., vn] must be exactly the free variables of [S1,
   ..., Sm] (see below for the meaning of "free variable"). In particular, since
   a macro argument cannot be a function, a let body cannot call a macro that is
   defined elsewhere, only a macro that is defined in the body itself. However if
   you want to use the same macro inside two macros, it is still possible to define
   it in a separate file and include it in both macros. The list [S1 ... Sm] may
   not be empty.}

   {- [(:use v (v1 SS1) ... (vn SSn))] expands to the body of the template [v]
   with lists of s-expressions [SS1, ..., SSn] substituted for the arguments
   [v1, ..., vn] of [v].}

   {- [(:concat S1 ... Sn)] evaluates [S1 ... Sn] to atoms [C1, ..., Cn] when
   possible and is replaced by the string concatenation [C1 | ... | Cn].}}

   Macros other than [:include] will be called 'local'. All [:include] macros
   are resolved before all the local macros, which means that included file
   names cannot contain variables.

   The occurrence of variable [v] in [(:use v ...)] can be either free or bound, depending
   on the surrounding sexp.  The occurrence is free iff it it's not bound, and it's bound
   iff one of the following two conditions apply:

   {ol
   {- All occurrences of [v1], ..., [vn] in the body of [(:let v (v1 ... vn) S1 ... Sm)]
   are bound.}
   {- All occurrences of [v] from the appearance of [(:let v (v1 ... vn) S1 ... Sm)] to
   the end of the sexp nesting level are bound.}}

   Trying to [:use] an unbound variable is an error. Neither the top level file nor any of
   the included files may contain unbound variables.

   The [load...] functions of this module mirror the corresponding functions of
   the [Sexp] module except that they expand the macros in the loaded file and
   may throw additional exceptions.

   Example
   -------

   Assume that [input.sexp] contains
   {[
   (:include defs.sexp)
   (:include template.sexp)
   (:use f (a (:use a)) (b (:use b)))
   ]}

   the file [defs.sexp] contains
   {[
   (:let a () hello)
   (:let b () " world")
   ]}

   and the file [template.sexp] contains
   {[
   (:let f (a b) (:concat (:use a) (:use b)))
   ]}

   Then [load_sexp "input.sexp"] will return "hello world".

   Formal Evaluation Rules
   -----------------------

   In the following [v] denotes a variable (an atom), [S] denotes a sexp, and
   [SS] denotes a list of sexps. Given a map [V] we write [V(v ~> a)] to update
   the map.

   Evaluation rules are of the form [V : SS => SS'] where [V] is a set of
   bindings of the form [v ~> SSv], each binding defining a template [v] with
   body [SSv].

   First some boilerplate rules: a sexp without macros evaluates to itself:

   {[
   V : <empty sexp list> => <empty sexp list>

   V : S  => SS1
   V : SS => SS2
   -------------------
   V : S SS => SS1 SS2

   C is an atom
   ------------
   V : C => C

   V : SS => SS'
   -----------------
   V : (SS) => (SS')
   ]}

   Now the interesting rules.

   {[
   free_vars(SSv) = {v1, ..., vn}
   V(v ~> SSv) : SS => SS'
   --------------------------------------
   V : (:let v (v1 ... vn) SSv) SS => SS'

   V(v) = SS
   V : SSi => SSi' for each i
   V(v1 ~> SS1', ..., vn ~> SSn') : SS => SS'
   ------------------------------------------
   V : (:use v (v1 SS1) ... (vn SSn)) => SS'

   v not defined in V
   -----------------------
   V : (:use v ...) => _|_

   V : Si => Ci
   Each Ci is an atom
   -------------------------------------------------------
   V : (:concat S1 ... Sn) => String.concat [C1; ...; Cn]
   ]}

   As follows from the let-rule, let definitions may only refer to the variables
   explicitly mentioned in the argument list. This avoids the complexities of
   variable capture and allows us to forego closure building.
*)

type 'a conv =
  [ `Result of 'a | `Error of exn * Sexp.t ]

type 'a annot_conv = ([ `Result of 'a | `Error of exn * Sexp.Annotated.t ] as 'body)
  constraint 'body = 'a Sexp.Annotated.conv

val load_sexp : string -> Sexp.t
(** [load_sexp file] like [{!Sexp.load_sexp} file], but resolves the macros
    contained in [file]. *)

val load_sexps : string -> Sexp.t list
(** [load_sexps file] like [{!Sexp.load_sexps} file], but resolves the macros
    contained in [file]. *)

val load_sexp_conv : string -> (Sexp.t -> 'a) -> 'a annot_conv
(** [load_sexp_conv file f] uses {!load_sexp} and converts the result using
    [f]. *)

val load_sexps_conv : string -> (Sexp.t -> 'a) -> 'a annot_conv list
(** [load_sexps_conv file f] uses {!load_sexps} and converts the result using
    [f]. *)

val load_sexp_conv_exn : string -> (Sexp.t -> 'a) -> 'a
(** [load_sexp_conv_exn file f] like {!load_sexp_conv}, but raises an exception
    in case of conversion error. *)

val load_sexps_conv_exn : string -> (Sexp.t -> 'a) -> 'a list
(** [load_sexps_conv_exn file f] like {!load_sexps_conv}, but raises an
    exception in case of conversion error. *)

val expand_local_macros : Sexp.t list -> Sexp.t list conv
(** [expand_local_macros sexps] takes a list of sexps and performs macro-expansion on
    them, except that an error will be returned if an :include macro is found. *)

(** A version of [load_sexps] that is functorized with respect to the functions
    that load the sexps from files and the corresponding monad. *)
module type Sexp_loader = sig
  module Monad : sig
    type 'a t
    val return : 'a -> 'a t
    module Monad_infix : sig
      val ( >>= ) : 'a t -> ('a -> 'b t) -> 'b t
    end
    module List : sig
      val iter : 'a list -> f:('a -> unit t) -> unit t
      val map : 'a list -> f:('a -> 'b t) -> 'b list t
    end
  end
  val load_sexps           : string -> Sexp.t           list Monad.t
  val load_annotated_sexps : string -> Sexp.Annotated.t list Monad.t
end

module Loader (S : Sexp_loader) : sig
  val load_sexp_conv  : string -> (Sexp.t -> 'a) -> 'a annot_conv      S.Monad.t
  val load_sexps_conv : string -> (Sexp.t -> 'a) -> 'a annot_conv list S.Monad.t
end

val add_error_location : string -> exn -> exn