This file is indexed.

/usr/lib/ocaml/cf/cf_dfa.mli is in libcf-ocaml-dev 0.10-4build1.

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
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
(*---------------------------------------------------------------------------*
  INTERFACE  cf_xdfa.mli

  Copyright (c) 2004-2006, James H. Woodyatt
  All rights reserved.

  Redistribution and use in source and binary forms, with or without
  modification, are permitted provided that the following conditions
  are met:

    Redistributions of source code must retain the above copyright
    notice, this list of conditions and the following disclaimer.

    Redistributions in binary form must reproduce the above copyright
    notice, this list of conditions and the following disclaimer in
    the documentation and/or other materials provided with the
    distribution

  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
  FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
  COPYRIGHT HOLDERS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT,
  INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
  (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
  SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
  HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
  STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
  ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
  OF THE POSSIBILITY OF SUCH DAMAGE. 
 *---------------------------------------------------------------------------*)

(** Functional composition of lazy deterministic finite automata. *)

(** {6 Overview}

    This module implements operators for functional composition of lazy
    deterministic finite automata (DFA).  A lazy DFA is more efficient at
    recognizing regular grammars than a non-deterministic finite automaton,
    and the lazy evaluation amortizes the cost of compiling the state table
    so that it compares well to that of the NFA.
    
    The interface defined here is used as the underlying algorithm for the
    {!Cf_lex} module.  It uses a functor that operates on a module defining
    the type of a symbol, the type of parser input tokens that contain such
    symbols, and a map of symbols to some polymorphic type.  The result of the
    functor is a module that contains operator functions for composing
    expressions and rules for automata that operate on streams of the input
    symbol type.
    
    {b Note}: a DFA can be remarkably inefficient compared to an NFA for
    certain classes of unusual grammars and unusual input.
*)

(** {6 Module Types} *)

(** The type of the input module for [Create(S: Symbol_T)] functor defined
    below.
*)
module type Symbol_T = sig
    (** The symbol type *)
    type t
        
    (** The type of maps from symbols to polymorphic types. *)
    type 'a map
        
    (** The engine uses [map f] to construct a map from symbols to state
        transitions.
    *)
    val map: (t -> 'a) -> 'a map
    
    (** The engine uses [get m s] to get the state transition from map [m] for
        the symbol [s].
    *)
    val get: 'a map -> t -> 'a
end

(** The output of the [Create(S: Symbol_T)] functor, which is a module that
    can be used to compose deterministic finite automata which operate on
    symbols of the type specified.
*)
module type T = sig

    (** The module used as the input to the [Create(S: Symbol_T)] functor. *)
    module S: Symbol_T

    (** The type of an expression in the regular grammar of an automaton. *)
    type x

    (** The type of a rule for recognizing a sequence of symbols according to
        the regular grammar of an automaton and producing an output token.
    *)
    type 'a r

    (** A parser that works on the symbols used in the automaton. *)
    type 'a t = (S.t, 'a) Cf_parser.t

    (** The expression that matches the empty symbol sequence. *)
    val nil: x
    
    (** The signature of modules containing operators for composing DFA
        expressions.
    *)
    module type Expr_Op_T = sig
    
        (** Use [a $| b] to compose an expression that matches either [a] or
            [b] in the symbol stream.
        *)
        val ( $| ): x -> x -> x
        
        (** Use [a $& b] to compose an expression that matches [a] followed by
            [b] in the symbol stream.
        *)
        val ( $& ): x -> x -> x

        (** Use [!*a] to compose an expression that matches zero or more
            occurances of [a] in the symbol stream.
        *)
        val ( !* ): x -> x
        
        (** Use [!+a] to compose an expression that matches one or more
            occurances of [a] in the symbol stream.
        *)
        val ( !+ ): x -> x

        (** Use [!?a] to compose an expression that matches zero or one
            occurance of [a] in the symbol stream.
        *)
        val ( !? ): x -> x

        (** Use [!:sym] to compose an expression that matches the symbol [sym]
            in the symbol stream.
        *)
        val ( !: ): S.t -> x
        
        (** Use [!^f] to compose an expression that matches any symbol in the
            symbol stream for which applying the function [f] returns [true].
        *)
        val ( !^ ): (S.t -> bool) -> x
        
        (** Use [!~z] to compose an expression that matches the sequence of
            symbols [z] in the symbol stream.
        *)
        val ( !~ ): S.t Cf_seq.t -> x
    end
    
    (** The module containing the expression operators. *)
    module Expr_Op: Expr_Op_T

    (** The signature of the [Op] module, which contains the composition
        operators.
    *)
    module type Op_T = sig
        include Expr_Op_T

        (** Use [e $= x] to compose a rule that produces [x] when the symbols
            in the symbol stream match the expression [e].
        *)
        val ( $= ): x -> 'a -> 'a r
        
        (** Use [e $> f] to compose a rule that applies the tokenizer function
            [f] to the sequence of input symbols in the stream recognized by
            the expression [e] to produce an output token.
        *)
        val ( $> ): x -> (S.t Cf_seq.t -> 'a) -> 'a r

        (** Use [e $@ f] to compose a rule that applies the scanning function
            [f] to the input stream when it is recognized by the expression
            [e].  The scanning function is passed the length of the recognized
            sequence of symbols and receives a parser in return that produces
            the output of the rule and makes any advanced manipulations of the
            input stream necessary to continue parsing for the next token.
            If the parser returned from the scanning function does not
            recognize the input stream, then the rule is not matched and the
            next best matching rule is selected.
        *)
        val ( $@ ): x -> (int -> 'a t) -> 'a r
        
        (** Use this operator to combine a list of rules into a single rule. *)
        val ( !@ ): 'a r list -> 'a r
    end
    
    (** Open this module to bring the composition operators into the current
        scope.
    *)
    module Op: Op_T

    (** Use [create r] to construct a parser that recognizes the longest
        sequence that matches the rule [r].
    *)
    val create: 'a r -> 'a t
    
    (** A module of extensions for working with input sequences that
        require position information in the parse function.
    *)
    module X: sig

        (** The type of a rule for recognizing a sequence of symbols in a
            stream woven with a cursor stream and according to the regular
            grammar of an automaton and producing an output token.
        *)
        type ('c, 'a) r constraint 'c = S.t #Cf_parser.cursor

        (** An extended parser that works on pairs of symbols and cursor
            objects and used in the automaton.
        *)
        type ('c, 'a) t = ('c, S.t, 'a) Cf_parser.X.t
            constraint 'c = S.t #Cf_parser.cursor

        (** The signature of the [Op] module, which contains the composition
            operators.
        *)
        module type Op_T = sig
            include Expr_Op_T

            (** Use [e $= x] to compose a rule that produces [x] when the
                symbols in the symbol stream match the expression [e].
            *)
            val ( $= ): x -> 'a -> ('c, 'a) r
            
            (** Use [e $> f] to compose a rule that applies the tokenizer
                function [f] to the sequence of input symbols in the
                symbol/cursor stream recognized by the expression [e] to
                produce an output token.
            *)
            val ( $> ): x -> (S.t Cf_seq.t -> 'a) -> ('c, 'a) r

            (** Use [e $@ f] to compose a rule that applies the scanning
                function [f] to the symbol/cursor input stream when the symbol
                sequence is recognized by the expression [e].  This operator
                performs the same function as the [( $@ )] operator, but it
                works on a stream of symbols woven with a corresponding cursor
                stream.
            *)
            val ( $@ ): x -> (int -> ('c, 'a) t) -> ('c, 'a) r

            (** Use this operator to combine a list of "cursor woven" rules
                into a single rule.
            *)
            val ( !@ ): ('c, 'a) r list -> ('c, 'a) r
        end
        
        (** Open this module to bring the composition operators into the
            current scope.
        *)
        module Op: Op_T

        (** Use [create r] to construct a parser that recognizes the longest
            sequence that matches the rule [r].
        *)
        val create: ('c, 'a) r -> ('c, 'a) t
    end
end

(** The functor that creates a DFA module. *)
module Create(S: Symbol_T): T with module S = S

(*--- End of File [ cf_xdfa.mli ] ---*)