This file is indexed.

/usr/lib/ocaml/galax/procmod_compiler.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
(***********************************************************************)
(*                                                                     *)
(*                                 GALAX                               *)
(*                              XQuery Engine                          *)
(*                                                                     *)
(*  Copyright 2001-2007.                                               *)
(*  Distributed only by permission.                                    *)
(*                                                                     *)
(***********************************************************************)

(* $Id: procmod_compiler.mli,v 1.26 2007/10/16 01:25:35 mff Exp $ *)

(* Module: Procmod_compiler
   Description:
     This module contains top-level operations over the processing
     model. This notably supports various levels of compilations for
     queries.
*)

open Xquery_common_ast
open Xquery_ast
open Xquery_core_ast
open Xquery_algebra_ast
open Logical_algebra_types
open Algebra_type

open Dm_atomic
open Physical_value

open Processing_context
open Namespace_context
open Parse_context
open Norm_context
open Typing_context
open Compile_context
open Code_selection_context
open Execution_context
open Monitoring_context

open Compiled_program_units

(*******************************************)
(* Type for intermediate compilation steps *)
(*******************************************)

type ginput =
  | IOStatement of Galax_io.input_spec
  | IOProlog of Galax_io.input_spec
  | IOLibraryModule of Galax_io.input_spec
  | IOMainModule of Galax_io.input_spec

type ast =
  | ASTStatement of statement
  | ASTProlog of prolog
  | ASTLibraryModule of library_module
  | ASTMainModule of main_module

type core_ast =
  | CoreASTStatement of acstatement
  | CoreASTProlog of acprolog
  | CoreASTLibraryModule of acxmodule
  | CoreASTMainModule of acxmodule


type logical_plan =
  | LogicalPlanStatement of logical_algop_expr
  | LogicalPlanProlog of logical_algop_prolog
  | LogicalPlanLibraryModule of logical_algop_xmodule
  | LogicalPlanMainModule of logical_algop_xmodule

type logical_plan_statement = logical_algop_expr
type logical_plan_main_module = logical_algop_xmodule

type physical_plan =
  | PhysicalPlanStatement of algop_expr
  | PhysicalPlanProlog of algop_prolog
  | PhysicalPlanLibraryModule of algop_xmodule
  | PhysicalPlanMainModule of algop_xmodule


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

type external_context =
    { external_context_item : item option;
      external_timezone     : atomicDayTimeDuration option;
      external_variables    : (cvname * item list) list }

val create_external_context :
    processing_context ->
      (item option) ->
	(atomicDayTimeDuration option) ->
	  (string * item list) list ->
	    external_context

val default_external_context : unit -> external_context

(*************************)
(* Statement compilation *)
(*************************)

val logical_compile_statement :
    compiled_program -> Galax_io.input_spec -> (compiled_program * logical_compiled_statement)

val compile_statement :
    compiled_program -> Galax_io.input_spec -> (compiled_program * compiled_statement)
val compile_statement_from_logical_plan :
    compiled_program -> compiled_prolog  -> (logical_plan_statement) -> (compiled_program * compiled_statement)
val compile_statement_from_optimized_logical_plan :
    compiled_program -> (logical_plan_statement) -> (compiled_program * compiled_statement)

(**********************)
(* Prolog compilation *)
(**********************)

(* A compiled prolog is installed as the prolog of the program's main module *)
val compile_prolog :
    bool (* external context item *) -> compiled_program -> Galax_io.input_spec -> compiled_program

(**********************)
(* Module compilation *)
(**********************)

val logical_compile_main_module : 
    bool (* external context item *) -> compiled_program -> Galax_io.input_spec -> (compiled_program * (logical_compile_context * logical_plan_main_module))

val compile_library_module :
    compiled_program -> Galax_io.input_spec -> (Namespace_names.ncname * string * compiled_program)

val compile_main_module :
    bool (* external context item *) -> compiled_program -> Galax_io.input_spec -> (compiled_program * compiled_statement list)
val compile_main_module_from_logical_plan :
    compiled_program -> (logical_compile_context * logical_plan_main_module) -> (compiled_program * compiled_statement list)
val compile_main_module_from_optimized_logical_plan :
    compiled_program -> (logical_compile_context * logical_plan_main_module) -> (compiled_program * compiled_statement list)

(***************************************)
(* Standard library module compilation *)
(***************************************)

val compile_standard_library_module : processing_context -> compiled_program

(*****************************)
(* Prepare a compiled prolog *)
(*****************************)

val prepare_compiled_program : external_context option -> compiled_program -> prepared_program

(********************************)
(* Execute a compiled statement *)
(********************************)

val execute_compiled_statement : prepared_program -> compiled_statement -> physical_value