This file is indexed.

/usr/lib/ocaml/oasis/OASISFileTemplate.mli is in liboasis-ocaml-dev 0.4.5-1build3.

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
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
(******************************************************************************)
(* OASIS: architecture for building OCaml libraries and applications          *)
(*                                                                            *)
(* Copyright (C) 2011-2013, Sylvain Le Gall                                   *)
(* Copyright (C) 2008-2011, OCamlCore SARL                                    *)
(*                                                                            *)
(* This library is free software; you can redistribute it and/or modify it    *)
(* under the terms of the GNU Lesser General Public License as published by   *)
(* the Free Software Foundation; either version 2.1 of the License, or (at    *)
(* your option) any later version, with the OCaml static compilation          *)
(* exception.                                                                 *)
(*                                                                            *)
(* This library is distributed in the hope that it will be useful, but        *)
(* WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *)
(* or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more         *)
(* details.                                                                   *)
(*                                                                            *)
(* You should have received a copy of the GNU Lesser General Public License   *)
(* along with this library; if not, write to the Free Software Foundation,    *)
(* Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA              *)
(******************************************************************************)


(** Generate files replacing parts of it

    This module allow to generate files using template. Each template files
    is split into three parts: an header, a body and a footer. We target at
    changing the body part. If target file already exists, we load the header
    and the footer from it. We merge the three parts and repalce the target
    files.

    There are some safety limits:
    - embed a digest to check nothing has changed in the body
    - if digest of the body has changed, create a backup
    - if we cannot find OASIS_START/OASIS_STOP body section, leave the
      file untouched

    The whole module is {b not exported}.

    @author Sylvain Le Gall
  *)


open OASISUnixPath


(** {2 Comments} *)


(** Comment definition. *)
type comment


(** .ml comments.  *)
val comment_ml: comment


(** Shell comments.  *)
val comment_sh: comment


(** Makefile comments.  *)
val comment_makefile: comment


(** OCamlbuild comments.  *)
val comment_ocamlbuild: comment


(** .bat file comments.  *)
val comment_bat: comment


(** META file comments.  *)
val comment_meta: comment


(** Markdown comments. *)
val comment_markdown: comment


(** {2 Template} *)


type line = string


type body =
    NoBody
  | Body of line list
  | BodyWithDigest of Digest.t * line list


type template =
    {
      fn: host_filename;
      comment: comment;
      header: line list;
      body: body;
      footer: line list;
      perm: int;
      important: bool; (** Determine if should be kept in dynamic mode. *)
      disable_oasis_section: bool;
      (** Determine if OASIS section comments and digest should be omitted. *)
    }


(** [template_make fn cmt header body footer] Create a template for which
    target file is [fn].  *)
val template_make:
  host_filename ->
  comment -> line list -> line list -> line list -> template


(** [template_of_string_list ~ctxt ~template ~pure fn cmt lst] Split the list
    [lst] into a header, body and footer, using comment [cmt] to determine each
    part. Set [~template] if this is an embedded template (i.e. not a file
    loaded from disk). If [~disable_oasis_section] is set, then the list is
    processed on the assumption that there is no header and footer. See
    {!template_make} for other options.  *)
val template_of_string_list:
  ctxt:OASISContext.t -> template:bool ->
  ?disable_oasis_section:bool -> host_filename -> comment -> line list -> template


(** [template_of_ml_file fn] Create an OCaml file template taking into account
    subtleties, like line modifier. See {!template_make} for other options.
*)
val template_of_mlfile:
  host_filename -> line list -> line list -> line list -> template


(** {2 File generation} *)

(** Create a list representation of the file. *)
val to_string_list: template -> line list

(** Describe what has been done to generate a file out of a template.
  *)
type file_generate_change =
    Create of host_filename
  (** [Create fn], [fn] is the target file, nothing exists before *)
  | Change of host_filename * host_filename option
  (** [Change (fn, bak)], [bak] is the backup file, an existing file
      has been changed. *)
  | NoChange
  (** Nothing done, the file doesn't need to be updated *)


(** Reset to pristine a generated file.
  *)
val file_rollback: ctxt:OASISContext.t -> file_generate_change -> unit


(** Generate a file using a template. Only the part between OASIS_START and
    OASIS_STOP will be really replaced if the file exists. If the file doesn't
    exist use the whole template. If [~remove] is [true], then an existing file
    will be deleted iff the template body is [[]] and the header and footer of
    the file match the template's (used by the -remove option for setup-clean).
 *)
val file_generate:
  ctxt:OASISContext.t ->
  ?remove:bool -> backup:bool -> template -> file_generate_change


(** {2 Multiple templates management } *)


(** Try to add a file that is already in the set
  *)
exception AlreadyExists of host_filename


(** Set of templates.
  *)
type templates


(** No generated template files with the given set of files with the OASIS
    section disabled. *)
val create: disable_oasis_section:unix_filename list -> unit -> templates


(** Find a generated template file.
  *)
val find: host_filename -> templates -> template


(** Add a generated template file.
  *)
val add: template -> templates -> templates


(** Remove a generated template file.
  *)
val remove: host_filename -> templates -> templates


(** Add or replace a generated template file.
  *)
val replace: template -> templates -> templates


(** Fold over generated template files.
  *)
val fold: (template -> 'b -> 'b) -> templates -> 'b -> 'b