This file is indexed.

/usr/lib/ocaml/ocamlbricks/ipv4.mli is in libocamlbricks-ocaml-dev 0.90+bzr367-1build1.

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
(* This file is part of Marionnet, a virtual network laboratory
   Copyright (C) 2009 Jean-Vincent Loddo

   This program is free software: you can redistribute it and/or modify
   it under the terms of the GNU General Public License as published by
   the Free Software Foundation, either version 2 of the License, or
   (at your option) any later version.

   This program 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
   GNU General Public License for more details.

   You should have received a copy of the GNU General Public License
   along with this program.  If not, see <http://www.gnu.org/licenses/>. *)

(** IPv4 parsing and printing. *)

(** The internal representation of an ipv4 address. *)
type t = int * int * int * int

(** The integer implicitely representing the netmask.
    Admissible values are in the range [0..32]. *)
type cidr = int
type netmask = t

(** The internal representation of an ipv4 configuration,
    i.e. a pair [<address>/<cidr>]. *)
type config          = t * cidr
type verbose_config  = t * netmask

(** {2 Netmask <-> CIDR} *)

val netmask_of_cidr   : cidr -> netmask
val cidr_of_netmask   : netmask -> cidr
val netmask_of_string : string -> netmask

(** {2 Parsing} *)

val of_string : string -> t
val to_string : t -> string

val config_of_string  : string -> config
val string_of_config  : config -> string

type ipcalc_result =
< ip        : t;
  cidr      : int;
  config    : t * int;
  netmask   : t;
  network   : t;
  broadcast : t;
  hostmin   : t;
  hostmax   : t;
  hosts     : int;
  print     : unit;

  to_string : <
      ip        : string;
      cidr      : string;
      config    : string;
      netmask   : string;
      network   : string;
      broadcast : string;
      hostmax   : string;
      hostmin   : string;
      >;

  contains : t -> bool;
  >

val ipcalc : t -> cidr -> ipcalc_result

(** {2 String checking} *)

module String : sig

 val is_valid_ipv4    : string -> bool
 val is_valid_netmask : string -> bool
 val is_valid_config  : string -> bool

 val ipcalc : config:string ->
  < ip        : string;
    cidr      : string;
    netmask   : string;
    network   : string;
    broadcast : string;
    hostmax   : string;
    hostmin   : string;
    contains  : ip:string -> bool;
    print     : unit;
    >

end