This file is indexed.

/usr/lib/ocaml/ocp-indent-lib/approx_lexer.mli is in libocp-indent-lib-ocaml-dev 1.4.2-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
type 'a overflow =
  'a Approx_tokens.overflow =
    InRange of 'a
  | Overflow of string
type token =
  Approx_tokens.token =
    AMPERAMPER
  | AMPERSAND
  | AND
  | AS
  | ASSERT
  | BACKQUOTE
  | BANG
  | BAR
  | BARBAR
  | BARRBRACKET
  | BEGIN
  | CHAR of char overflow
  | CLASS
  | COLON
  | COLONCOLON
  | COLONEQUAL
  | COLONGREATER
  | COMMA
  | COMMENT
  | OCAMLDOC_CODE
  | OCAMLDOC_VERB
  | COMMENTCONT
  | CONSTRAINT
  | DO
  | DONE
  | DOT
  | DOTDOT
  | DOWNTO
  | ELSE
  | END
  | EOF
  | EOF_IN_COMMENT
  | EOF_IN_STRING of int
  | EOF_IN_QUOTATION of int
  | EQUAL
  | EXCEPTION
  | EXTERNAL
  | FALSE
  | FLOAT of string
  | FOR
  | FUN
  | FUNCTION
  | FUNCTOR
  | GREATER
  | GREATERRBRACE
  | GREATERRBRACKET
  | IF
  | ILLEGAL_CHAR of char
  | IN
  | INCLUDE
  | INFIXOP0 of string
  | INFIXOP1 of string
  | INFIXOP2 of string
  | INFIXOP3 of string
  | INFIXOP4 of string
  | INHERIT
  | INITIALIZER
  | INT of int overflow
  | INT32 of int32 overflow
  | INT64 of int64 overflow
  | LABEL of string
  | LAZY
  | LBRACE
  | LBRACELESS
  | LBRACKET
  | LBRACKETBAR
  | LBRACKETLESS
  | LBRACKETGREATER
  | LBRACKETPERCENT
  | LBRACKETPERCENTPERCENT
  | LESS
  | LESSMINUS
  | LET
  | LIDENT of string
  | LINE_DIRECTIVE
  | LPAREN
  | MATCH
  | METHOD
  | MINUS
  | MINUSDOT
  | MINUSGREATER
  | MODULE
  | MUTABLE
  | NATIVEINT of nativeint overflow
  | NEW
  | OBJECT
  | OF
  | OPEN
  | OPTLABEL of string
  | OR
  | PLUS
  | PLUSDOT
  | PREFIXOP of string
  | PRIVATE
  | QUESTION
  | QUESTIONQUESTION
  | QUOTATION
  | QUOTE
  | RBRACE
  | RBRACKET
  | REC
  | RPAREN
  | SEMI
  | SEMISEMI
  | SHARP
  | SIG
  | STAR
  | STRING of string
  | STRUCT
  | THEN
  | TILDE
  | TO
  | TRUE
  | TRY
  | TYPE
  | UIDENT of string
  | UNDERSCORE
  | VAL
  | VIRTUAL
  | WHEN
  | WHILE
  | WITH
  | EOL
  | SPACES
val list_last : 'a list -> 'a
val lines_starts : (int * int) list ref
val keywords : (string * token) list
val keyword_table : (string, token) Hashtbl.t
val lexer_extensions : (Lexing.lexbuf -> token) list ref
val enable_extension : string -> unit
val disable_extensions : unit -> unit
val initial_string_buffer : string
val string_buff : string ref
val string_index : int ref
val reset_string_buffer : unit -> unit
val store_string_char : char -> unit
val get_stored_string : unit -> string
val string_start_loc : int ref
val quotation_start_loc : int ref
val quotation_kind : [ `Camlp4 | `Ppx of string ] ref
type in_comment = Comment | Code | Verbatim | CommentCont
val comment_stack : in_comment list ref
val entering_inline_code_block : bool ref
val close_comment : unit -> token
val in_comment : unit -> bool
val in_verbatim : unit -> bool
val init : unit -> unit
val char_for_backslash : char -> char
val can_overflow : (string -> 'a) -> Lexing.lexbuf -> 'a overflow
val char_for_decimal_code : int -> string -> char
val char_for_hexadecimal_code : Lexing.lexbuf -> int -> char
val cvt_int_literal : string -> int
val cvt_int32_literal : string -> int32
val cvt_int64_literal : string -> int64
val cvt_nativeint_literal : string -> nativeint
val remove_underscores : string -> string
val update_loc : Lexing.lexbuf -> string option -> int -> bool -> int -> unit
val __ocaml_lex_tables : Lexing.lex_tables
val parse_token : Lexing.lexbuf -> token
val __ocaml_lex_parse_token_rec : Lexing.lexbuf -> int -> token
val quotation : Lexing.lexbuf -> token
val __ocaml_lex_quotation_rec : Lexing.lexbuf -> int -> token
val comment : Lexing.lexbuf -> token
val __ocaml_lex_comment_rec : Lexing.lexbuf -> int -> token
val verbatim : Lexing.lexbuf -> token
val __ocaml_lex_verbatim_rec : Lexing.lexbuf -> int -> token
val string : Lexing.lexbuf -> token
val __ocaml_lex_string_rec : Lexing.lexbuf -> int -> token
val token_locs : Lexing.lexbuf -> token * (Lexing.position * Lexing.position)
val token_pos : Lexing.lexbuf -> token * (int * int)
val token_locs_and_comments :
  Lexing.lexbuf -> token * (Lexing.position * Lexing.position)
val get_token : Lexing.lexbuf -> token
val token_with_comments : Lexing.lexbuf -> token
val token : Lexing.lexbuf -> token
val tokens_of_file : string -> (token * (int * int)) list
val tokens_with_loc_of_string : string -> (token * (int * int)) list
val tokens_of_string : string -> token list
val lines : unit -> (int * int) list