This file is indexed.

/usr/lib/ocaml/galax/galax.mli is in libgalax-ocaml-dev 1.1-12.

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
(***********************************************************************)
(*                                                                     *)
(*                                 GALAX                               *)
(*                              XQuery Engine                          *)
(*                                                                     *)
(*  Copyright 2001-2007.                                               *)
(*  Distributed only by permission.                                    *)
(*                                                                     *)
(***********************************************************************)

(* $Id: galax.mli,v 1.39 2007/10/16 01:25:34 mff Exp $ *)

(* Module: Galax
   Description:
     This module contains the Galax Caml user API.
*)

open Dm_atomic
open Dm

open Physical_value


(********************)
(* External context *)
(********************)

type external_context

(***********)
(* Queries *)
(***********)

(*   A compiled program contains a processing context, extended
     with global/external variables and their values.

     A prepared program has all global variables (external and
     internal) bound to values.
*)

type compiled_program
type compiled_module
type compiled_library_module
type compiled_statement

type prepared_program

(********************************)
(* Module context accessors     *)
(********************************)

val procctxt_of_compiled_program           : compiled_program -> Processing_context.processing_context
val procctxt_of_prepared_program           : prepared_program -> Processing_context.processing_context
val compiled_program_of_prepared_program   : prepared_program -> compiled_program
val algebra_context_of_compiled_program    : compiled_program -> Execution_context.algebra_context
val main_module_of_compiled_program        : compiled_program -> compiled_module
val module_of_compiled_program             : compiled_program -> string -> compiled_library_module

val nsenv_of_main_module                   : compiled_program -> Namespace_context.nsenv
val code_selection_context_of_main_module  : compiled_program -> Code_selection_context.code_selection_context

(********************************)
(* Document I/O functions       *)
(********************************)

val load_document       : Processing_context.processing_context -> Galax_io.input_spec -> node list
    (* [load_document io] load the XML document from the
       file/string/http uri [io] *)

val serialize           : Processing_context.processing_context -> Galax_io.output_spec -> item list -> unit
    (* [serialize gout x] serializes an XML value using to the given
        galax output *)

val serialize_to_string : Processing_context.processing_context -> item list -> string
    (* [serialize_to_string x] serializes an XML value to a string *)

(*
   External context:
   Context item (optional item)
   Timezone (optional dayTimeDuration) 
   External variables and their values
   External functions 

   Redefining any symbol raises an error
*)

val default_external_context : unit -> external_context
val build_external_context : 
    Processing_context.processing_context -> 
      (item option) -> 
	(atomicDayTimeDuration option) ->
	  (string * item list) list -> external_context

(* 
   Compile a library module or a main module : includes normalization,
   typing, annotation, and logical optimization.

   When importing a main module, must specify whether a context-item
   value will be passed as an external value -- the actual value is
   passed to prepare_program.  

*)
val load_standard_library : Processing_context.processing_context -> compiled_program 

(* A prolog can only be used within the main module. *)
val import_prolog_only    : 
    compiled_program -> 
      bool (* does prolog require external context item? *) -> 
	Galax_io.input_spec ->
	  compiled_program

val import_library_module : compiled_program -> Galax_io.input_spec -> (compiled_program)
val import_main_module    :
    bool (* does module require external context item? *) -> 
      compiled_program -> 
	Galax_io.input_spec -> 
	  compiled_program * (compiled_statement list)

(* Export a DXQ server module : Namespace prefix, URI, compiled program *)
val export_server_module : compiled_program -> Galax_io.input_spec -> (Namespace_names.ncname * string * compiled_program)

(* Prepare a compiled program, so that it can be used during evaluation of a statement: *)
val prepare_program          : compiled_program -> external_context option -> prepared_program

(* Evaluation functions require a prepared program : *)
val eval_statement           : prepared_program -> Galax_io.input_spec -> item list
val eval_compiled_statement  : prepared_program -> compiled_statement -> item list
val eval_compiled_closure_statement  : 
    prepared_program -> compiled_statement -> (Xquery_physical_type_ast.physical_type * Physical_value.physical_value)

(* Compilation interfaces for external plans *)
val compile_serialized_logical_statement     : 
    compiled_program -> Galax_io.input_spec -> compiled_program * compiled_statement
val compile_serialized_logical_main_module   : 
    compiled_program -> Galax_io.input_spec -> compiled_program * compiled_statement list
val compile_serialized_optimized_main_module : 
    compiled_program -> Galax_io.input_spec -> compiled_program * compiled_statement list
val compile_serialized_closure               : 
    compiled_program -> Galax_io.input_spec -> prepared_program * compiled_statement
val compile_serialized_closure_in_module     : 
    compiled_program -> compiled_library_module -> Galax_io.input_spec -> prepared_program * compiled_statement

val serialize_logical_statement : Namespace_context.nsenv -> compiled_statement -> item list
val serialize_logical_module    : Namespace_context.nsenv -> compiled_module -> item list

(* Validation *)
val validate_document : prepared_program -> item list -> item list

(************************)
(* Streaming evaluation *)
(************************)

(* Note:
     the following are prototype operations that may return the result
     as a cursor or XML stream.
*)

val eval_statement_as_item_cursor :
    prepared_program -> Galax_io.input_spec -> item Cursor.cursor
val eval_compiled_statement_as_item_cursor  :
    prepared_program -> compiled_statement -> item Cursor.cursor

val eval_statement_as_sax :
    prepared_program -> Galax_io.input_spec -> Streaming_types.typed_xml_stream
val eval_compiled_statement_as_sax :
    prepared_program -> compiled_statement -> Streaming_types.typed_xml_stream

val serialize_as_item_cursor :
    Processing_context.processing_context -> Galax_io.output_spec -> item Cursor.cursor -> unit
val serialize_as_sax :
    Processing_context.processing_context -> Galax_io.output_spec -> Streaming_types.typed_xml_stream -> unit