[m-rev.] diff: remove the rest of the aditi backend

Julien Fischer juliensf at cs.mu.OZ.AU
Fri Feb 24 17:18:55 AEDT 2006


Estimated hours taken: 1.5
Branches: main

Remove residual parts of the Aditi backend that weren't deleted the other day.

configure.in:
Mmake.common.in:
	Remove support for enabling the Aditi backend.

runtime/mercury_aditi.h:
	Remove this file.

runtime/Mmakefile:
runtime/mercury.h:
runtime/mercury_imp.h:
runtime/mercury_ho_call.[ch]:
runtime/mercury_wrapper.[ch]:
	Delete support for Aditi in the runtime.

scripts/Mmake.rules:
scripts/Mmake.vars.in:
scripts/c2init.in:
scripts/parse_ml_options.sh-subr.in:
	Remove mmake support for building .rlo files, etc.

util/mkinit.c:
	Remove Aditi specific code.

compiler/bytecode_data.m:
compiler/closure_analysis.m:
compiler/code_model.m:
compiler/compile_target_code.m:
compiler/det_analysis.m:
compiler/handle_options.m:
compiler/hlds_goal.m:
compiler/hlds_module.m:
compiler/make.dependencies.m:
compiler/make.m:
compiler/make.module_target.m:
compiler/make.program_target.m:
compiler/make.util.m:
compiler/make_hlds_error.m:
compiler/make_hlds_passes.m:
compiler/mercury_to_mercury.m:
compiler/mlds_to_gcc.m:
compiler/modecheck_call.m:
compiler/modules.m:
compiler/opt_debug.m:
compiler/options.m:
compiler/prog_data.m:
compiler/prog_foreign.m:
compiler/prog_mode.m:
compiler/prog_type.m:
compiler/rtti.m:
compiler/rtti_out.m:
compiler/rtti_to_mlds.m:
compiler/term_errors.m:
compiler/unify_proc.m:
mdbcomp/prim_data.m:
	Remove residual support for Aditi.

library/ops.m:
	Remove the 'aditi_bottom_up' and 'aditi_top_down' operators from the
	ops table.

doc/reference_manual.texi:
doc/user_guide.texi:
	Delete the sections on the Aditi interface.

extras/aditi/*:
	Delete this.

Julien.

Index: Mmake.common.in
===================================================================
RCS file: /home/mercury1/repository/mercury/Mmake.common.in,v
retrieving revision 1.86
diff -u -r1.86 Mmake.common.in
--- Mmake.common.in	13 Feb 2006 07:14:32 -0000	1.86
+++ Mmake.common.in	24 Feb 2006 04:52:12 -0000
@@ -181,21 +181,6 @@
 # `tree.c', `tree.h', etc.
 GCC_SRC_DIR = @GCC_SRC_DIR@

-# Do we want to include the support for Aditi compilation in the compiler?
-# This can be set using the `--enable-aditi-back-end' or
-# `--disable-aditi-back-end' options to configure.
-# It is not practical to include the code to output Aditi-RL in the alias
-# branch compiler - it currently takes more than an hour to compile
-# compiler/rl_code.m, due to performance problems compiling large disjunctions
-# with the new mode checker.
-# To disable the Aditi support, put `INCLUDE_ADITI_OUTPUT = no'
-# in Mmake.stage.params. Do not put this into Mmake.params - we still
-# want to check that the Aditi code compiles after any changes.
-# `mmake depend' must be run in any compiler directories affected by
-# the changed value (tools/bootcheck will do this automatically for
-# the stage2 and stage3 directories).
-INCLUDE_ADITI_OUTPUT = @ENABLE_ADITI_BACK_END@
-
 # Enable building of the deep profiler?
 # The value of ENABLE_DEEP_PROFILER is either yes or no.
 ENABLE_DEEP_PROFILER=@ENABLE_DEEP_PROFILER@
Index: configure.in
===================================================================
RCS file: /home/mercury1/repository/mercury/configure.in,v
retrieving revision 1.445
diff -u -r1.445 configure.in
--- configure.in	14 Feb 2006 03:12:49 -0000	1.445
+++ configure.in	24 Feb 2006 04:42:26 -0000
@@ -524,33 +524,7 @@
 GCC_SRC_DIR=$gcc_src_dir
 AC_SUBST(ENABLE_GCC_BACK_END)
 AC_SUBST(GCC_SRC_DIR)
-#-----------------------------------------------------------------------------#
-#
-# Determine whether or not to enable the Aditi back-end.
-#
-AC_ARG_ENABLE(aditi-back-end,
-[  --disable-aditi-back-end
-                          disable the Mercury compiler's Aditi back-end],
-enable_aditi_back_end="$enableval",enable_aditi_back_end=yes)
-AC_MSG_CHECKING(whether to enable the Aditi back-end)
-case $enable_aditi_back_end in
-	no)
-		if test "$BOOTSTRAP_MC" = ""; then
-			enable_aditi_back_end=yes
-			AC_MSG_RESULT(yes)
-			AC_MSG_WARN(
-[--disable-aditi-back-end requires an already
-	installed Mercury compiler])
-		else
-			# This will regenerate compiler/rl_out.m and
-			# compiler/rl_file.m.
-			AC_MSG_RESULT($enable_aditi_back_end)
-			remake_dependencies=true
-		fi
-		;;
-esac
-ENABLE_ADITI_BACK_END=$enable_aditi_back_end
-AC_SUBST(ENABLE_ADITI_BACK_END)
+
 #-----------------------------------------------------------------------------#
 MERCURY_MSG("looking for GNU Make...")
 AC_PROGRAMS_CHECK(GNU_MAKE,gmake make)
@@ -4392,8 +4366,7 @@

 case "$remake_dependencies.$reconfiguring" in "true.no")
 	MERCURY_MSG(
-"regenerating dependencies to enable GCC backend
-	and/or disable Aditi backend.")
+"regenerating dependencies to enable GCC backend.")

 	MMAKE_DIR=`pwd`/scripts scripts/mmake depend || exit 1
 	;;
Index: compiler/bytecode_data.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/bytecode_data.m,v
retrieving revision 1.19
diff -u -r1.19 bytecode_data.m
--- compiler/bytecode_data.m	17 Nov 2005 15:57:03 -0000	1.19
+++ compiler/bytecode_data.m	24 Feb 2006 04:39:42 -0000
@@ -10,10 +10,7 @@
 % Authors: zs, aet, stayl.
 %
 % This module defines the representation of basic types used by the bytecode
-% interpreter and by the Aditi bytecodes.
-%
-% NOTE: this file is included in both the Mercury compiler and the Aditi
-% bytecode assembler.
+% interpreter.
 %
 %---------------------------------------------------------------------------%

Index: compiler/closure_analysis.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/closure_analysis.m,v
retrieving revision 1.6
diff -u -r1.6 closure_analysis.m
--- compiler/closure_analysis.m	24 Feb 2006 05:49:25 -0000	1.6
+++ compiler/closure_analysis.m	24 Feb 2006 05:55:28 -0000
@@ -231,10 +231,6 @@
     Goal = GoalExpr - GoalInfo.
 process_goal(VarTypes, ModuleInfo, Goal0, Goal, !ClosureInfo) :-
     Goal0 = GoalExpr - GoalInfo0,
-    %
-    % XXX We should probably just ignore Aditi stuff and unsafe_casts
-    % but annotating them with closure_infos won't hurt.
-    %
     GoalExpr = generic_call(Details, GCallArgs, GCallModes, _),
     partition_arguments(ModuleInfo, VarTypes, GCallArgs, GCallModes,
         set.init, InputArgs0, set.init, OutputArgs),
@@ -292,8 +288,6 @@
     (
         Unification = construct(LHS, RHS, _, _, _, _, _),
         (
-            % NOTE: we don't bother worrying about features
-            % that relate to Aditi, i.e. when EvalMethod = (aditi_bottom_up)
             RHS = pred_const(ShroudedPPId, EvalMethod),
             EvalMethod = lambda_normal
         ->
Index: compiler/code_model.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_model.m,v
retrieving revision 1.9
diff -u -r1.9 code_model.m
--- compiler/code_model.m	28 Oct 2005 02:10:00 -0000	1.9
+++ compiler/code_model.m	24 Feb 2006 04:34:09 -0000
@@ -14,8 +14,7 @@
 %
 % We define this in a different module than the `determinism' type because
 % it is only used by some of the different back-ends, not all of them.
-% It is used by the MLDS, LLDS, and bytecode back-ends, but not by the
-% Aditi-RL back-end.
+% It is used by the MLDS, LLDS, and bytecode back-ends.
 %
 %-----------------------------------------------------------------------------%

Index: compiler/compile_target_code.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/compile_target_code.m,v
retrieving revision 1.82
diff -u -r1.82 compile_target_code.m
--- compiler/compile_target_code.m	13 Feb 2006 03:04:35 -0000	1.82
+++ compiler/compile_target_code.m	24 Feb 2006 05:09:41 -0000
@@ -865,9 +865,7 @@
     io__open_output(TmpInitFileName, InitFileRes, !IO),
     (
         InitFileRes = ok(InitFileStream),
-        globals__io_lookup_bool_option(aditi, Aditi, !IO),
-        list__foldl(make_init_file_aditi(InitFileStream, Aditi), AllModules,
-            !IO),
+        list__foldl(make_init_file(InitFileStream), AllModules, !IO),
         globals__io_lookup_maybe_string_option(extra_init_command,
             MaybeInitFileCommand, !IO),
         (
@@ -899,24 +897,15 @@
         Succeeded = no
     ).

-:- pred make_init_file_aditi(io__output_stream::in, bool::in, module_name::in,
+:- pred make_init_file(io.output_stream::in, module_name::in,
     io::di, io::uo) is det.

-make_init_file_aditi(InitFileStream, Aditi, ModuleName, !IO) :-
+make_init_file(InitFileStream, ModuleName, !IO) :-
     InitFuncName0 = make_init_name(ModuleName),
     InitFuncName = InitFuncName0 ++ "init",
     io__write_string(InitFileStream, "INIT ", !IO),
     io__write_string(InitFileStream, InitFuncName, !IO),
-    io__nl(InitFileStream, !IO),
-    (
-        Aditi = yes,
-        RLName = make_rl_data_name(ModuleName),
-        io__write_string(InitFileStream, "ADITI_DATA ", !IO),
-        io__write_string(InitFileStream, RLName, !IO),
-        io__nl(InitFileStream, !IO)
-    ;
-        Aditi = no
-    ).
+    io__nl(InitFileStream, !IO).

 %-----------------------------------------------------------------------------%

@@ -1067,9 +1056,6 @@
     globals__io_lookup_bool_option(main, Main, !IO),
     NoMainOpt = ( Main = no -> "-l" ; "" ),

-    globals__io_lookup_bool_option(aditi, Aditi, !IO),
-    AditiOpt = ( Aditi = yes -> "-a" ; "" ),
-
     globals__io_lookup_string_option(experimental_complexity,
         ExperimentalComplexity, !IO),
     ( ExperimentalComplexity = "" ->
@@ -1081,11 +1067,18 @@
     globals__io_lookup_string_option(mkinit_command, Mkinit, !IO),
     TmpInitCFileName = InitCFileName ++ ".tmp",
     MkInitCmd = string__append_list(
-        [Mkinit, " -g ", Grade, " ", TraceOpt, " ", ExtraInitsOpt,
-        " ", NoMainOpt, " ", AditiOpt,
-        " ", ExperimentalComplexityOpt, " ", RuntimeFlags,
-        " -o ", quote_arg(TmpInitCFileName), " ", InitFileDirs,
-        " ", InitFileNames, " ", CFileNames]),
+        [   Mkinit,
+            " -g ", Grade,
+            " ", TraceOpt,
+            " ", ExtraInitsOpt,
+            " ", NoMainOpt,
+            " ", ExperimentalComplexityOpt,
+            " ", RuntimeFlags,
+            " -o ", quote_arg(TmpInitCFileName),
+            " ", InitFileDirs,
+            " ", InitFileNames,
+            " ", CFileNames
+        ]),
     invoke_system_command(ErrorStream, verbose, MkInitCmd, MkInitOK0, !IO),
     maybe_report_stats(Stats, !IO),
     (
Index: compiler/det_analysis.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/det_analysis.m,v
retrieving revision 1.187
diff -u -r1.187 det_analysis.m
--- compiler/det_analysis.m	24 Feb 2006 05:49:27 -0000	1.187
+++ compiler/det_analysis.m	24 Feb 2006 05:55:29 -0000
@@ -887,9 +887,7 @@
         SolnContext = all_solns
     ->
         % This error can only occur for higher-order calls.
-        % Class method calls are only introduced by polymorphism,
-        % and the aditi_builtins are all det (for the updates)
-        % or introduced later (for calls).
+        % Class method calls are only introduced by polymorphism.
         det_get_proc_info(DetInfo, ProcInfo),
         proc_info_varset(ProcInfo, VarSet),
         Msg = higher_order_cc_pred_in_wrong_context(GoalInfo, CallDetism,
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.257
diff -u -r1.257 handle_options.m
--- compiler/handle_options.m	24 Feb 2006 01:41:46 -0000	1.257
+++ compiler/handle_options.m	24 Feb 2006 02:16:04 -0000
@@ -132,13 +132,11 @@
         globals__io_get_target(Target, !IO),
         GenerateIL = (if Target = il then yes else no),
         globals__io_lookup_bool_option(compile_only, CompileOnly, !IO),
-        globals__io_lookup_bool_option(aditi_only, AditiOnly, !IO),
         bool__or_list([GenerateDependencies, GenerateDependencyFile,
             MakeInterface, MakePrivateInterface, MakeShortInterface,
             MakeOptimizationInt, MakeTransOptInt, MakeAnalysisRegistry,
-            ConvertToMercury, TypecheckOnly,
-            ErrorcheckOnly, TargetCodeOnly,
-            GenerateIL, CompileOnly, AditiOnly],
+            ConvertToMercury, TypecheckOnly, ErrorcheckOnly, TargetCodeOnly,
+            GenerateIL, CompileOnly],
             NotLink),
         bool__not(NotLink, Link),
         globals__io_lookup_bool_option(smart_recompilation, Smart, !IO),
@@ -802,13 +800,6 @@
         option_implies(make_transitive_opt_interface,   line_numbers, bool(no),
             !Globals),

-        % `--aditi-only' is only used by the Aditi query shell,
-        % for queries which should only be compiled once.
-        % recompilation_check.m currently doesn't check whether
-        % the `.rlo' file is up to date (with `--no-aditi-only' the
-        % Aditi-RL bytecode is embedded in the `.c' file).
-        option_implies(aditi_only, smart_recompilation, bool(no), !Globals),
-
         % We never use version number information in `.int3',
         % `.opt' or `.trans_opt' files.
         option_implies(make_short_interface, generate_item_version_numbers,
@@ -1423,25 +1414,6 @@
         option_implies(generate_source_file_mapping, warn_wrong_module_name,
             bool(no), !Globals),

-        % --aditi-only implies --aditi.
-        option_implies(aditi_only, aditi, bool(yes), !Globals),
-
-        % Set --aditi-user to the value of $USER if it is not set already.
-        % If $USER is not set, use the string "guest".
-        globals__lookup_string_option(!.Globals, aditi_user, User0),
-        ( User0 = "" ->
-            io__get_environment_var("USER", MaybeUser, !IO),
-            (
-                MaybeUser = yes(User)
-            ;
-                MaybeUser = no,
-                User = "guest"
-            ),
-            globals__set_option(aditi_user, string(User), !Globals)
-        ;
-            true
-        ),
-
         globals__lookup_string_option(!.Globals, fullarch, FullArch),

         %
Index: compiler/hlds_goal.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_goal.m,v
retrieving revision 1.150
diff -u -r1.150 hlds_goal.m
--- compiler/hlds_goal.m	24 Feb 2006 05:49:30 -0000	1.150
+++ compiler/hlds_goal.m	24 Feb 2006 05:55:29 -0000
@@ -102,8 +102,8 @@
                 % polymorphic to be written as ordinary predicates in Mercury
                 % and require special casing, either because their arity is
                 % variable, or they take higher-order arguments of variable
-                % arity. This currently includes higher-order calls,
-                % class-method calls, Aditi calls and the Aditi update goals.
+                % arity. This currently includes higher-order calls and
+                % class-method calls.
                 %
                 gcall_details       :: generic_call,

@@ -285,10 +285,6 @@
             % A non-removable explicit quantification may be introduced
             % to keep related goals together where optimizations that
             % separate the goals can only result in worse behaviour.
-            % An example is the closures for the builtin Aditi update
-            % predicates - they should be kept close to the update call
-            % where possible to make it easier to use indexes for the
-            % update.
             %
             % A barrier says nothing about the determinism of either
             % the inner or the outer goal, or about pruning.
@@ -447,8 +443,8 @@
                 rhs_purity          :: purity,
                 rhs_p_or_f          :: pred_or_func,
                 rhs_eval_method     :: lambda_eval_method,
-                                    % Should be `normal' except for
-                                    % closures executed by Aditi.
+                                    % Currently, we don't support any other
+                                    % value than `normal'.
                 rhs_nonlocals       :: list(prog_var),
                                     % Non-locals of the goal excluding
                                     % the lambda quantified variables.
@@ -1296,89 +1292,6 @@

 %-----------------------------------------------------------------------------%
 %
-% Stuff specific to Aditi.
-%
-
-    % Builtin Aditi operations.
-    % These are transformed into ordinary Mercury calls
-    % by aditi_builtin_ops.m before code generation.
-    %
-:- type aditi_builtin
-
-    --->    aditi_tuple_update(
-                % Insert or delete a single tuple into/from a base relation.
-                % Arguments:
-                %   the arguments of tuple to insert
-                %   aditi__state::di, aditi__state::uo
-
-                aditi_tuple_update,
-                pred_id             % base relation to insert into
-            )
-
-    ;       aditi_bulk_update(
-                % Insert/delete/modify operations which take
-                % an input closure.
-                % Arguments:
-                %   the closure producing the tuples to insert/delete/modify
-                %   aditi__state::di, aditi__state::uo
-                % These operations all have two variants.
-                %
-                % A pretty syntax:
-                %
-                % aditi_bulk_insert(p(DB, X, Y) :- q(DB, X, Y)).
-                % aditi_bulk_delete(p(DB, X, Y) :- q(DB, X, Y)).
-                % aditi_bulk_modify(
-                %   (p(DB, X0, Y0) ==> p(_, X, Y) :-
-                %       X = X0 + 1,
-                %       Y = Y0 + 3
-                %   )).
-                %
-                % An ugly syntax:
-                %
-                % InsertPred = (aditi_bottom_up
-                %   pred(DB::aditi_mui, X::out, Y::out) :-
-                %       q(DB, X, Y)
-                % ),
-                % aditi_bulk_insert(pred p/3, InsertPred).
-                %
-                % DeletePred = (aditi_bottom_up
-                %   pred(DB::aditi_mui, X::out, Y::out) :-
-                %       p(DB, X, Y),
-                %       q(DB, X, Y)
-                % ),
-                % aditi_bulk_delete(pred p/3, DeletePred).
-
-                aditi_bulk_update,
-                pred_id,
-                aditi_builtin_syntax
-            ).
-
-:- type aditi_tuple_update
-    --->    delete          % `aditi_delete'
-    ;       insert.         % `aditi_insert'
-
-:- type aditi_bulk_update
-    --->    bulk_delete     % `aditi_bulk_delete'
-    ;       bulk_insert     % `aditi_bulk_insert'
-    ;       bulk_modify.    % `aditi_bulk_modify'
-
-    % Which syntax was used for an `aditi_delete' or `aditi_modify'
-    % call. The first syntax is prettier, the second is used
-    % where the closure to be passed in is not known at the call site.
-    % (See the "Aditi update syntax" section of the Mercury Language
-    % Reference Manual).
-    %
-:- type aditi_builtin_syntax
-    --->    pred_term       % e.g. aditi_bulk_insert(p(_, X) :- X = 1).
-    ;       sym_name_and_closure.
-                            % e.g.
-                            % aditi_insert(p/2,
-                            %    (pred(_::in, X::out) is nondet:-
-                            %       X = 1)
-                            %    )
-
-%-----------------------------------------------------------------------------%
-%
 % Stuff specific to a back-end. At the moment, only the LLDS back-end
 % annotates the HLDS.
 %
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_module.m,v
retrieving revision 1.129
diff -u -r1.129 hlds_module.m
--- compiler/hlds_module.m	1 Feb 2006 04:02:45 -0000	1.129
+++ compiler/hlds_module.m	24 Feb 2006 04:29:08 -0000
@@ -153,12 +153,6 @@
                                     % becomes exported.
             ).

-    % This field should be set to `do_aditi_compilation' if there
-    % are local Aditi predicates.
-:- type do_aditi_compilation
-    --->    do_aditi_compilation
-    ;       no_aditi_compilation.
-
     % Maps the full names of procedures (in the sense of
     % complexity_proc_name in complexity.m) to the number of their slot
     % in MR_complexity_proc_table.
@@ -189,20 +183,10 @@
     ;       complexity_input_fixed_size
     ;       complexity_output.

-    % Mercury procedures which can be called from Aditi join conditions.
-    % Each procedure has one input and one output argument.
-    % The compiler generates a constant structure containing
-    % the address and other information for each procedure,
-    % which Aditi will find using dlsym().
-:- type aditi_top_down_proc
-    --->    aditi_top_down_proc(
-                pred_proc_id,
-                string      % name of the constant.
-            ).
-
 %-----------------------------------------------------------------------------%
-
-    % Various predicates for manipulating the module_info data structure
+%
+% Various predicates for manipulating the module_info data structure
+%

     % Create an empty module_info for a given module name (and the
     % global options).  The item_list is passed so that we can
@@ -420,12 +404,6 @@
 :- pred module_info_set_stratified_preds(set(pred_id)::in,
     module_info::in, module_info::out) is det.

-:- pred module_info_get_do_aditi_compilation(module_info::in,
-    do_aditi_compilation::out) is det.
-
-:- pred module_info_set_do_aditi_compilation(module_info::in, module_info::out)
-    is det.
-
 :- pred module_info_get_type_spec_info(module_info::in, type_spec_info::out)
     is det.

@@ -457,15 +435,6 @@
 :- pred module_info_set_complexity_proc_infos(list(complexity_proc_info)::in,
     module_info::in, module_info::out) is det.

-:- pred module_info_get_aditi_top_down_procs(module_info::in,
-    list(aditi_top_down_proc)::out) is det.
-
-:- pred module_info_set_aditi_top_down_procs(module_info::in,
-    list(aditi_top_down_proc)::in, module_info::out) is det.
-
-:- pred module_info_next_aditi_top_down_proc(module_info::in, int::out,
-    module_info::out) is det.
-
 :- pred module_info_new_user_init_pred(sym_name::in, string::out,
     module_info::in, module_info::out) is det.

@@ -561,9 +530,6 @@
 :- pred module_info_dependency_info(module_info::in, dependency_info::out)
     is det.

-:- pred module_info_aditi_dependency_ordering(module_info::in,
-    aditi_dependency_ordering::out) is det.
-
     % Please see module_info_ensure_dependency_info for the
     % constraints on this dependency_info.
     %
@@ -697,10 +663,6 @@
                 % back-end).
                 indirectly_imported_module_specifiers :: set(module_specifier),

-                % Are there any local Aditi predicates for which Aditi-RL
-                % must be produced?
-                do_aditi_compilation        :: do_aditi_compilation,
-
                 % Data used for user-guided type specialization.
                 type_spec_info              :: type_spec_info,

@@ -718,12 +680,6 @@
                 % Information for the inter-module analysis framework.
                 analysis_info               :: analysis_info,

-                % List of top-down procedures which could be called from
-                % bottom-up Aditi procedures.
-                aditi_top_down_procs        :: list(aditi_top_down_proc),
-
-                aditi_proc_counter          :: counter,
-
                 % Exported C names for preds appearing in `:- initialise
                 % initpred' directives in this module, in order of appearance.
                 user_init_pred_c_names      :: assoc_list(sym_name, string),
@@ -772,17 +728,17 @@
     ModuleSubInfo = module_sub_info(Name, Globals, no, [], [], [], [], no, 0,
         [], [], StratPreds, UnusedArgInfo, ExceptionInfo, TrailingInfo,
         map.init, counter__init(1), ImportedModules,
-        IndirectlyImportedModules, no_aditi_compilation, TypeSpecInfo,
-        NoTagTypes, no, [], init_analysis_info(mmc),
-        [], counter__init(1), [], []),
+        IndirectlyImportedModules, TypeSpecInfo, NoTagTypes, no, [],
+        init_analysis_info(mmc), [], []),
     ModuleInfo = module_info(ModuleSubInfo, PredicateTable, Requests,
         UnifyPredMap, QualifierInfo, Types, Insts, Modes, Ctors,
         ClassTable, SuperClassTable, InstanceTable, AssertionTable,
         ExclusiveTable, FieldNameTable, RecompInfo).

 %-----------------------------------------------------------------------------%
-
-    % Various predicates which access the module_info data structure.
+%
+% Various predicates which access the module_info data structure
+%

 module_info_get_predicate_table(MI, MI ^ predicate_table).
 module_info_get_proc_requests(MI, MI ^ proc_requests).
@@ -852,8 +808,6 @@
     MI ^ sub_info ^ imported_module_specifiers).
 module_info_get_indirectly_imported_module_specifiers(MI,
     MI ^ sub_info ^ indirectly_imported_module_specifiers).
-module_info_get_do_aditi_compilation(MI,
-    MI ^ sub_info ^ do_aditi_compilation).
 module_info_get_type_spec_info(MI, MI ^ sub_info ^ type_spec_info).
 module_info_get_no_tag_types(MI, MI ^ sub_info ^ no_tag_type_table).
 module_info_get_analysis_info(MI, MI ^ sub_info ^ analysis_info).
@@ -861,12 +815,6 @@
     MI ^ sub_info ^ maybe_complexity_proc_map).
 module_info_get_complexity_proc_infos(MI,
     MI ^ sub_info ^ complexity_proc_infos).
-module_info_get_aditi_top_down_procs(MI, MI ^ sub_info ^ aditi_top_down_procs).
-
-module_info_next_aditi_top_down_proc(MI0, Proc, MI) :-
-    Counter0 = MI0 ^ sub_info ^ aditi_proc_counter,
-    counter__allocate(Proc, Counter0, Counter),
-    MI = MI0 ^ sub_info ^ aditi_proc_counter := Counter.

     % XXX There is some debate as to whether duplicate initialise directives
     % in the same module should constitute an error. Currently it is not, but
@@ -966,8 +914,6 @@
     MI ^ sub_info ^ indirectly_imported_module_specifiers :=
         set__insert_list(MI ^ sub_info ^ indirectly_imported_module_specifiers,
             Modules)).
-module_info_set_do_aditi_compilation(MI,
-    MI ^ sub_info ^ do_aditi_compilation := do_aditi_compilation).
 module_info_set_type_spec_info(NewVal, MI,
     MI ^ sub_info ^ type_spec_info := NewVal).
 module_info_set_no_tag_types(NewVal, MI,
@@ -978,8 +924,6 @@
     MI ^ sub_info ^ maybe_complexity_proc_map := NewVal).
 module_info_set_complexity_proc_infos(NewVal, MI,
     MI ^ sub_info ^ complexity_proc_infos := NewVal).
-module_info_set_aditi_top_down_procs(MI, NewVal,
-    MI ^ sub_info ^ aditi_top_down_procs := NewVal).

 %-----------------------------------------------------------------------------%

@@ -1082,19 +1026,6 @@
         unexpected(this_file, "Attempted to access invalid dependency_info")
     ).

-module_info_aditi_dependency_ordering(MI, AditiOrdering) :-
-    module_info_dependency_info(MI, DepInfo),
-    hlds_dependency_info_get_maybe_aditi_dependency_ordering(DepInfo,
-        MaybeOrdering),
-    (
-        MaybeOrdering = yes(OrderingPrime),
-        AditiOrdering = OrderingPrime
-    ;
-        MaybeOrdering = no,
-        unexpected(this_file,
-            "Attempted to access invalid aditi_dependency_ordering")
-    ).
-
 module_info_set_dependency_info(DependencyInfo, !MI) :-
     module_info_set_maybe_dependency_info(yes(DependencyInfo), !MI).

@@ -1210,16 +1141,6 @@
 :- type dependency_ordering(T)  == list(list(T)).
 :- type dependency_ordering     == dependency_ordering(pred_proc_id).

-:- type aditi_dependency_ordering   == list(aditi_scc).
-
-    % Each Aditi SCC contains one or more SCCs from the original dependency
-    % ordering and the entry points of the SCC. SCCs which are only called from
-    % one other SCC and are not called through negation or aggregation are
-    % merged into the parent SCC. This makes the low-level RL optimizations
-    % more effective while maintaining stratification.
-:- type aditi_scc
-    --->    aditi_scc(dependency_ordering, list(pred_proc_id)).
-
 :- type dependency_graph(T)     == relation(T).
 :- type dependency_graph        == dependency_graph(pred_proc_id).
 :- type dependency_info(T).
@@ -1233,9 +1154,6 @@
 :- pred hlds_dependency_info_get_dependency_ordering(dependency_info(T)::in,
     dependency_ordering(T)::out) is det.

-:- pred hlds_dependency_info_get_maybe_aditi_dependency_ordering(
-    dependency_info::in, maybe(aditi_dependency_ordering)::out) is det.
-
 :- pred hlds_dependency_info_set_dependency_graph(dependency_graph(T)::in,
     dependency_info(T)::in, dependency_info(T)::out) is det.

@@ -1243,10 +1161,6 @@
     dependency_ordering(T)::in,
     dependency_info(T)::in, dependency_info(T)::out) is det.

-:- pred hlds_dependency_info_set_aditi_dependency_ordering(
-    aditi_dependency_ordering::in,
-    dependency_info::in, dependency_info::out) is det.
-
 %-----------------------------------------------------------------------------%

 :- implementation.
@@ -1254,27 +1168,21 @@
 :- type dependency_info(T)
     --->    dependency_info(
                 dep_graph       :: dependency_graph(T),
-                dep_ord         :: dependency_ordering(T),
-                dep_aditi_ord   :: maybe(aditi_dependency_ordering)
-                                % Dependency ordering of Aditi SCCs
+                dep_ord         :: dependency_ordering(T)
             ).

 hlds_dependency_info_init(DepInfo) :-
     relation__init(DepRel),
     DepOrd = [],
-    DepInfo = dependency_info(DepRel, DepOrd, no).
+    DepInfo = dependency_info(DepRel, DepOrd).

 hlds_dependency_info_get_dependency_graph(DepInfo, DepInfo ^ dep_graph).
 hlds_dependency_info_get_dependency_ordering(DepInfo, DepInfo ^ dep_ord).
-hlds_dependency_info_get_maybe_aditi_dependency_ordering(DepInfo,
-    DepInfo ^ dep_aditi_ord).

 hlds_dependency_info_set_dependency_graph(DepGraph, DepInfo,
     DepInfo ^ dep_graph := DepGraph).
 hlds_dependency_info_set_dependency_ordering(DepOrd, DepInfo,
     DepInfo ^ dep_ord := DepOrd).
-hlds_dependency_info_set_aditi_dependency_ordering(DepOrd, DepInfo,
-    DepInfo ^ dep_aditi_ord := yes(DepOrd)).

 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/make.dependencies.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.dependencies.m,v
retrieving revision 1.25
diff -u -r1.25 make.dependencies.m
--- compiler/make.dependencies.m	13 Feb 2006 03:47:42 -0000	1.25
+++ compiler/make.dependencies.m	24 Feb 2006 04:26:31 -0000
@@ -179,7 +179,6 @@
 target_dependencies(_, long_interface) = interface_file_dependencies.
 target_dependencies(_, short_interface) = interface_file_dependencies.
 target_dependencies(_, unqualified_short_interface) = source `of` self.
-target_dependencies(Globals, aditi_code) = compiled_code_dependencies(Globals).
 target_dependencies(Globals, c_header(_)) =
         target_dependencies(Globals, c_code).
 target_dependencies(Globals, c_code) = compiled_code_dependencies(Globals).
Index: compiler/make.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.m,v
retrieving revision 1.34
diff -u -r1.34 make.m
--- compiler/make.m	13 Feb 2006 07:57:21 -0000	1.34
+++ compiler/make.m	24 Feb 2006 04:26:19 -0000
@@ -185,7 +185,6 @@
     ;       unqualified_short_interface
     ;       intermodule_interface
     ;       analysis_registry
-    ;       aditi_code
     ;       c_header(c_header_type)
     ;       c_code
     ;       il_code
Index: compiler/make.module_target.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.module_target.m,v
retrieving revision 1.37
diff -u -r1.37 make.module_target.m
--- compiler/make.module_target.m	13 Feb 2006 03:47:42 -0000	1.37
+++ compiler/make.module_target.m	24 Feb 2006 04:26:15 -0000
@@ -672,8 +672,6 @@
         ["--make-optimization-interface"].
 compilation_task(_, analysis_registry) =
     process_module(make_analysis_registry) - ["--make-analysis-registry"].
-compilation_task(_, aditi_code) =
-    process_module(compile_to_target_code) - ["--aditi-only"].
 compilation_task(Globals, c_header(_)) = compilation_task(Globals, c_code).
 compilation_task(_, c_code) =
     process_module(compile_to_target_code) - ["--compile-to-c"].
Index: compiler/make.program_target.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.program_target.m,v
retrieving revision 1.45
diff -u -r1.45 make.program_target.m
--- compiler/make.program_target.m	22 Feb 2006 00:32:14 -0000	1.45
+++ compiler/make.program_target.m	24 Feb 2006 05:41:52 -0000
@@ -1260,9 +1260,7 @@
         [errors, c_code, c_header(mih), il_code, java_code],
         !Info, !IO),

-    list__foldl2(remove_file(ModuleName),
-        [".used", ".prof", ".derived_schema", ".base_schema"],
-        !Info, !IO),
+    list__foldl2(remove_file(ModuleName), [".used", ".prof"], !Info, !IO),

     get_module_dependencies(ModuleName, MaybeImports, !Info, !IO),
     (
@@ -1317,9 +1315,14 @@
 make_module_realclean(ModuleName, !Info, !IO) :-
     make_module_clean(ModuleName, !Info, !IO),
     list__foldl2(remove_target_file(ModuleName),
-        [private_interface, long_interface, short_interface,
-        unqualified_short_interface, intermodule_interface, analysis_registry,
-        aditi_code, c_header(mh)
+        [
+            private_interface,
+            long_interface,
+            short_interface,
+            unqualified_short_interface,
+            intermodule_interface,
+            analysis_registry,
+            c_header(mh)
         ],
         !Info, !IO),
     remove_file(ModuleName, module_dep_file_extension, !Info, !IO),
Index: compiler/make.util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make.util.m,v
retrieving revision 1.32
diff -u -r1.32 make.util.m
--- compiler/make.util.m	13 Feb 2006 07:57:21 -0000	1.32
+++ compiler/make.util.m	24 Feb 2006 04:25:26 -0000
@@ -803,7 +803,6 @@
 target_extension(_, unqualified_short_interface) = yes(".int3").
 target_extension(_, intermodule_interface) = yes(".opt").
 target_extension(_, analysis_registry) = yes(".analysis").
-target_extension(_, aditi_code) = yes(".rlo").
 target_extension(_, c_header(mih)) = yes(".mih").
 target_extension(_, c_header(mh)) = yes(".mh").
 target_extension(_, c_code) = yes(".c").
@@ -931,7 +930,6 @@
 search_for_file_type(unqualified_short_interface) = yes(search_directories).
 search_for_file_type(intermodule_interface) = yes(intermod_directories).
 search_for_file_type(analysis_registry) = yes(intermod_directories).
-search_for_file_type(aditi_code) = no.
 search_for_file_type(c_header(_)) = yes(c_include_directory).
 search_for_file_type(c_code) = no.
 search_for_file_type(il_code) = no.
@@ -957,7 +955,6 @@
 target_is_grade_or_arch_dependent(unqualified_short_interface, no).
 target_is_grade_or_arch_dependent(intermodule_interface, yes).
 target_is_grade_or_arch_dependent(analysis_registry, yes).
-target_is_grade_or_arch_dependent(aditi_code, no).
 target_is_grade_or_arch_dependent(c_header(mh), no).
 target_is_grade_or_arch_dependent(c_header(mih), yes).
 target_is_grade_or_arch_dependent(c_code, yes).
Index: compiler/make_hlds_error.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make_hlds_error.m,v
retrieving revision 1.5
diff -u -r1.5 make_hlds_error.m
--- compiler/make_hlds_error.m	28 Oct 2005 02:10:17 -0000	1.5
+++ compiler/make_hlds_error.m	24 Feb 2006 04:25:02 -0000
@@ -181,30 +181,16 @@
     % then we just add an implicit declaration for that predicate or
     % function, marking it as one whose type will be inferred.
     %
-    % If this module is for a query generated by the Aditi dbsh
-    % (--aditi-only is set), allow mode declarations for exported
-    % predicates with no `:- pred' or `:- func' declaration.
-    % The predicate will never be called from a compiled Mercury
-    % procedure. The RL bytecode for the predicate will be called
-    % directly using information from the generated
-    % `<module>.derived_schema' file to work out the argument
-    % types of the output relation.
-    %
 maybe_undefined_pred_error(Name, Arity, PredOrFunc, Status, IsClassMethod,
         Context, Description, !IO) :-
     status_defined_in_this_module(Status, DefinedInThisModule),
     status_is_exported(Status, IsExported),
     globals__io_lookup_bool_option(infer_types, InferTypes, !IO),
-    globals__io_lookup_bool_option(aditi_only, AditiOnly, !IO),
     (
-        (
-            DefinedInThisModule = yes,
-            IsExported = no,
-            IsClassMethod = no,
-            InferTypes = yes
-        ;
-            AditiOnly = yes
-        )
+        DefinedInThisModule = yes,
+        IsExported = no,
+        IsClassMethod = no,
+        InferTypes = yes
     ->
         true
     ;
Index: compiler/make_hlds_passes.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/make_hlds_passes.m,v
retrieving revision 1.28
diff -u -r1.28 make_hlds_passes.m
--- compiler/make_hlds_passes.m	24 Feb 2006 05:44:46 -0000	1.28
+++ compiler/make_hlds_passes.m	24 Feb 2006 05:55:29 -0000
@@ -48,15 +48,6 @@
     prog_context::in, module_info::in, module_info::out,
     qual_info::in, qual_info::out, io::di, io::uo) is det.

-    % If there are any Aditi procedures enable Aditi compilation.
-    % If there are only imported Aditi procedures, magic.m still
-    % needs to remove the `aditi' and `base_relation' markers
-    % so that the procedures are not ignored by the code
-    % generation annotation passes (e.g. arg_info.m).
-    %
-:- pred maybe_enable_aditi_compilation(item_status::in, term__context::in,
-    module_info::in, module_info::out, io::di, io::uo) is det.
-
 :- pred add_stratified_pred(string::in, sym_name::in, arity::in,
     term__context::in, module_info::in, module_info::out, io::di, io::uo)
     is det.
@@ -1377,22 +1368,6 @@

 %-----------------------------------------------------------------------------%

-maybe_enable_aditi_compilation(_Status, Context, !ModuleInfo, !IO) :-
-    globals__io_lookup_bool_option(aditi, Aditi, !IO),
-    (
-        Aditi = no,
-        prog_out__write_context(Context, !IO),
-        io__write_string("Error: compilation of Aditi procedures\n", !IO),
-        prog_out__write_context(Context, !IO),
-        io__write_string("  requires the `--aditi' option.\n", !IO),
-        io__set_exit_status(1, !IO),
-        module_info_incr_errors(!ModuleInfo)
-    ;
-        Aditi = yes,
-        % There are Aditi procedures - enable Aditi code generation.
-        module_info_set_do_aditi_compilation(!ModuleInfo)
-    ).
-
 :- pred add_promise_clause(promise_type::in, list(term(prog_var_type))::in,
     prog_varset::in, goal::in, prog_context::in, import_status::in,
     module_info::in, module_info::out, qual_info::in, qual_info::out,
Index: compiler/mercury_to_mercury.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
retrieving revision 1.282
diff -u -r1.282 mercury_to_mercury.m
--- compiler/mercury_to_mercury.m	24 Feb 2006 01:41:49 -0000	1.282
+++ compiler/mercury_to_mercury.m	24 Feb 2006 05:25:41 -0000
@@ -161,10 +161,6 @@
 :- pred mercury_output_pragma_trailing_info(pred_or_func::in, sym_name::in,
     arity::in, mode_num::in, trailing_status::in, io::di, io::uo) is det.

-    % Write an Aditi index specifier.
-    %
-:- pred mercury_output_index_spec(index_spec::in, io::di, io::uo) is det.
-
     % Output the given foreign_decl declaration.
     %
 :- pred mercury_output_pragma_foreign_decl(foreign_language::in,
@@ -350,7 +346,6 @@
     pred add_class_id(class_id::in, U::di, U::uo) is det,
     pred add_eval_method(eval_method::in, U::di, U::uo) is det,
     pred add_lambda_eval_method(lambda_eval_method::in, U::di, U::uo) is det,
-    pred add_index_type(index_type::in, U::di, U::uo) is det,
     pred add_escaped_string(string::in, U::di, U::uo) is det,
     pred add_format(string::in, list(io__poly_type)::in, U::di, U::uo) is det,
     pred add_list(list(T)::in, string::in,
@@ -3431,45 +3426,6 @@

 %-----------------------------------------------------------------------------%

-:- pred mercury_format_pragma_owner(sym_name::in, arity::in, string::in,
-    U::di, U::uo) is det <= output(U).
-
-mercury_format_pragma_owner(Pred, Arity, Owner, !U) :-
-    add_string(":- pragma owner(", !U),
-    mercury_format_bracketed_sym_name(Pred, next_to_graphic_token, !U),
-    add_string("/", !U),
-    add_int(Arity, !U),
-    add_string(", ", !U),
-    add_quoted_atom(Owner, !U),
-    add_string(").\n", !U).
-
-:- pred mercury_format_pragma_index(sym_name::in, arity::in, index_spec::in,
-    U::di, U::uo) is det <= output(U).
-
-mercury_format_pragma_index(PredName, Arity, IndexSpec, !U) :-
-    add_string(":- pragma aditi_index(", !U),
-    mercury_format_bracketed_sym_name(PredName, next_to_graphic_token, !U),
-    add_string("/", !U),
-    add_int(Arity, !U),
-    add_string(", ", !U),
-    mercury_format_index_spec(IndexSpec, !U),
-    add_string(").\n", !U).
-
-mercury_output_index_spec(IndexSpec, !IO) :-
-    mercury_format_index_spec(IndexSpec, !IO).
-
-:- pred mercury_format_index_spec(index_spec::in,
-    U::di, U::uo) is det <= output(U).
-
-mercury_format_index_spec(IndexSpec, !IO) :-
-    IndexSpec = index_spec(IndexType, Attrs),
-    add_index_type(IndexType, !IO),
-    add_string(", [", !IO),
-    mercury_format_int_list(Attrs, !IO),
-    add_string("]", !IO).
-
-%-----------------------------------------------------------------------------%
-
 mercury_output_newline(Indent, !IO) :-
     io__write_char('\n', !IO),
     mercury_format_tabs(Indent, !IO).
@@ -3991,7 +3947,6 @@
     pred(add_class_id/3) is io__write,
     pred(add_eval_method/3) is io__write,
     pred(add_lambda_eval_method/3) is io__write,
-    pred(add_index_type/3) is io__write,
     pred(add_escaped_string/3) is term_io__write_escaped_string,
     pred(add_format/4) is io__format,
     pred(add_list/5) is io__write_list
@@ -4010,7 +3965,6 @@
     pred(add_class_id/3) is output_class_id,
     pred(add_eval_method/3) is output_eval_method,
     pred(add_lambda_eval_method/3) is output_lambda_eval_method,
-    pred(add_index_type/3) is output_index_type,
     pred(add_escaped_string/3) is output_escaped_string,
     pred(add_format/4) is output_format,
     pred(add_list/5) is output_list
@@ -4095,13 +4049,6 @@
 output_lambda_eval_method(lambda_normal, !Str) :-
     output_string("normal", !Str).

-:- pred output_index_type(index_type::in, string::di, string::uo) is det.
-
-output_index_type(unique_B_tree, !Str) :-
-    output_string("unique_B_tree", !Str).
-output_index_type(non_unique_B_tree, !Str) :-
-    output_string("non_unique_B_tree", !Str).
-
 :- pred output_format(string::in, list(io__poly_type)::in,
     string::di, string::uo) is det.

Index: compiler/mlds_to_gcc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_gcc.m,v
retrieving revision 1.113
diff -u -r1.113 mlds_to_gcc.m
--- compiler/mlds_to_gcc.m	23 Feb 2006 09:36:58 -0000	1.113
+++ compiler/mlds_to_gcc.m	24 Feb 2006 04:19:28 -0000
@@ -1991,9 +1991,6 @@
 	;
 		RttiId = tc_rtti_id(_, TCRttiName),
 		build_rtti_type_tc_name(TCRttiName, BaseType, !IO)
-	;
-		RttiId = aditi_rtti_id(_),
-		build_rtti_type_aditi_name(BaseType, !IO)
 	),
 	IsArray = rtti_id_has_array_type(RttiId),
 	(
@@ -2218,25 +2215,6 @@
 	sorry(this_file,
 		"build_rtti_type_tc_name: type_class_instance_methods").

-:- pred build_rtti_type_aditi_name(gcc__type::out,
-		io__state::di, io__state::uo) is det.
-
-build_rtti_type_aditi_name(GCC_Type, !IO) :-
-	% typedef struct {
-	%	MR_ProcAddr	MR_aditi_proc_addr;
-	%	MR_String	MR_aditi_proc_name;
-	%	MR_TypeInfo	MR_aditi_input_type_info;
-	%	MR_TypeInfo	MR_aditi_output_type_info;
-	%	MR_Determinism	MR_aditi_proc_detism;
-	% } MR_Aditi_Proc_Info;
-	build_struct_type("MR_Aditi_Proc_Info",
-		['MR_ProcAddr'		- "MR_aditi_proc_addr",
-		 'MR_String'		- "MR_aditi_proc_name",
-		 'MR_TypeInfo'		- "MR_aditi_input_type_info",
-		 'MR_TypeInfo'		- "MR_aditi_output_type_info",
-		 'MR_Determinism'	- "MR_aditi_proc_detism"],
-		GCC_Type, !IO).
-
 :- pred build_type_info_type(rtti_type_info::in,
 	gcc__type::out, io__state::di, io__state::uo) is det.

@@ -2629,7 +2607,6 @@
 	RttiTypeCtor = fixup_rtti_type_ctor(RttiTypeCtor0),
 	RttiName = fixup_rtti_name(RttiName0).
 fixup_rtti_id(tc_rtti_id(TCName, TCRttiName)) = tc_rtti_id(TCName, TCRttiName).
-fixup_rtti_id(aditi_rtti_id(ProcLabel)) = aditi_rtti_id(ProcLabel).

 	% XXX sometimes earlier stages of the compiler forget to add
 	% the appropriate qualifiers for stuff in the `builtin' module;
Index: compiler/modecheck_call.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/modecheck_call.m,v
retrieving revision 1.66
diff -u -r1.66 modecheck_call.m
--- compiler/modecheck_call.m	16 Jan 2006 03:08:13 -0000	1.66
+++ compiler/modecheck_call.m	24 Feb 2006 02:20:30 -0000
@@ -46,11 +46,6 @@
     determinism::out, extra_goals::out,
     mode_info::in, mode_info::out) is det.

-:- pred modecheck_aditi_builtin(aditi_builtin::in, simple_call_id::in,
-    list(mer_mode)::in, list(prog_var)::in, list(prog_var)::out,
-    determinism::out, extra_goals::out,
-    mode_info::in, mode_info::out) is det.
-
 :- pred modecheck_builtin_cast(list(mer_mode)::in,
     list(prog_var)::in, list(prog_var)::out, determinism::out,
     extra_goals::out, mode_info::in, mode_info::out) is det.
@@ -272,21 +267,6 @@
         ExtraGoals = no_extra_goals
     ).

-modecheck_aditi_builtin(AditiBuiltin, _, Modes, Args0, Args, Det, ExtraGoals,
-        !ModeInfo) :-
-    aditi_builtin_determinism(AditiBuiltin, Det),
-
-    % The argument modes are set by post_typecheck.m, so all
-    % that needs to be done here is to check that they match.
-    ArgOffset = 0,
-    modecheck_arg_list(ArgOffset, Modes, ExtraGoals, Args0, Args,
-        !ModeInfo).
-
-:- pred aditi_builtin_determinism(aditi_builtin::in, determinism::out) is det.
-
-aditi_builtin_determinism(aditi_tuple_update(_, _), det).
-aditi_builtin_determinism(aditi_bulk_update(_, _, _), det).
-
 modecheck_builtin_cast(Modes, Args0, Args, Det, ExtraGoals, !ModeInfo) :-
     Det = det,
     % These should always be mode correct.
Index: compiler/modules.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/modules.m,v
retrieving revision 1.376
diff -u -r1.376 modules.m
--- compiler/modules.m	23 Feb 2006 09:37:00 -0000	1.376
+++ compiler/modules.m	24 Feb 2006 05:29:05 -0000
@@ -973,7 +973,6 @@
             ; Ext = ".check"
             ; Ext = ".ints"
             ; Ext = ".int3s"
-            ; Ext = ".rlos"
             ; Ext = ".ss"
             ; Ext = ".pic_ss"
             ; Ext = ".ils"
@@ -981,11 +980,6 @@
             ; Ext = ".classes"
             ; Ext = ".opts"
             ; Ext = ".trans_opts"
-            % The following files are only used by the Aditi
-            % query shell which doesn't know about --use-subdirs.
-            ; Ext = ".base_schema"
-            ; Ext = ".derived_schema"
-            ; Ext = ".rlo"
             )
         ;
             % output files intended for use by the user
@@ -3055,7 +3049,6 @@
         module_name_to_file_name(ModuleName, ".pic_s_date", no,
             PicAsmDateFileName, !IO),
         module_name_to_file_name(ModuleName, ".$O", no, ObjFileName, !IO),
-        module_name_to_file_name(ModuleName, ".rlo", no, RLOFileName, !IO),
         module_name_to_file_name(ModuleName, ".il_date", no, ILDateFileName,
             !IO),
         module_name_to_file_name(ModuleName, ".java_date", no,
@@ -3070,7 +3063,6 @@
             CDateFileName, " ",
             AsmDateFileName, " ",
             PicAsmDateFileName, " ",
-            RLOFileName, " ",
             ILDateFileName, " ",
             JavaDateFileName
         ] , !IO),
@@ -3094,7 +3086,6 @@
                 ".s_date",
                 ".pic_s_date",
                 ".dir/*.$O",
-                ".rlo",
                 ".il_date",
                 ".java_date"],

@@ -3150,7 +3141,6 @@
                 CDateFileName, " ",
                 AsmDateFileName, " ",
                 PicAsmDateFileName, " ",
-                RLOFileName, " ",
                 ILDateFileName, " ",
                 JavaDateFileName, " : "
             ], !IO),
@@ -3185,7 +3175,6 @@
                     CDateFileName, " ",
                     AsmDateFileName, " ",
                     PicAsmDateFileName, " ",
-                    RLOFileName, " ",
                     ILDateFileName, " ",
                     JavaDateFileName, " : "
                 ], !IO),
@@ -4762,12 +4751,6 @@
     ], !IO),

     io__write_string(DepStream, MakeVarName, !IO),
-    io__write_string(DepStream, ".rlos = ", !IO),
-    write_compact_dependencies_list(Modules, "$(rlos_subdir)", ".rlo",
-        Basis, DepStream, !IO),
-    io__write_string(DepStream, "\n", !IO),
-
-    io__write_string(DepStream, MakeVarName, !IO),
     io__write_string(DepStream, ".useds = ", !IO),
     write_compact_dependencies_list(Modules, "$(useds_subdir)", ".used",
         Basis, DepStream, !IO),
@@ -5009,15 +4992,6 @@
     io__write_string(DepStream, "\n", !IO),

     io__write_string(DepStream, MakeVarName, !IO),
-    io__write_string(DepStream, ".schemas = ", !IO),
-    write_compact_dependencies_list(Modules, "", ".base_schema",
-        Basis, DepStream, !IO),
-    io__write_string(DepStream, " ", !IO),
-    write_compact_dependencies_list(Modules, "", ".derived_schema",
-        Basis, DepStream, !IO),
-    io__write_string(DepStream, "\n", !IO),
-
-    io__write_string(DepStream, MakeVarName, !IO),
     io__write_string(DepStream, ".profs = ", !IO),
     write_compact_dependencies_list(Modules, "", ".prof", Basis, DepStream,
         !IO),
@@ -5483,7 +5457,6 @@
         TransOptsTargetName, !IO),
     module_name_to_file_name(ModuleName, ".ss", no, SsTargetName, !IO),
     module_name_to_file_name(ModuleName, ".pic_ss", no, PicSsTargetName, !IO),
-    module_name_to_file_name(ModuleName, ".rlos", no, RLOsTargetName, !IO),
     module_name_to_file_name(ModuleName, ".ils", no, ILsTargetName, !IO),
     module_name_to_file_name(ModuleName, ".javas", no, JavasTargetName, !IO),
     module_name_to_file_name(ModuleName, ".classes", no, ClassesTargetName,
@@ -5512,8 +5485,6 @@
         SsTargetName, " : $(", MakeVarName, ".ss)\n\n",
         ".PHONY : ", PicSsTargetName, "\n",
         PicSsTargetName, " : $(", MakeVarName, ".pic_ss)\n\n",
-        ".PHONY : ", RLOsTargetName, "\n",
-        RLOsTargetName, " : $(", MakeVarName, ".rlos)\n\n",
         ".PHONY : ", ILsTargetName, "\n",
         ILsTargetName, " : $(", MakeVarName, ".ils)\n\n",
         ".PHONY : ", JavasTargetName, "\n",
@@ -5562,8 +5533,7 @@
         "\t-echo $(", MakeVarName, ".javas) | xargs rm -f\n",
         "\t-echo $(", MakeVarName, ".profs) | xargs rm -f\n",
         "\t-echo $(", MakeVarName, ".errs) | xargs rm -f\n",
-        "\t-echo $(", MakeVarName, ".foreign_cs) | xargs rm -f\n",
-        "\t-echo $(", MakeVarName, ".schemas) | xargs rm -f\n"
+        "\t-echo $(", MakeVarName, ".foreign_cs) | xargs rm -f\n"
     ], !IO),

     io__write_string(DepStream, "\n", !IO),
@@ -5595,8 +5565,7 @@
         "\t-echo $(", MakeVarName, ".all_mihs) | xargs rm -f\n",
         "\t-echo $(", MakeVarName, ".dlls) | xargs rm -f\n",
         "\t-echo $(", MakeVarName, ".foreign_dlls) | xargs rm -f\n",
-        "\t-echo $(", MakeVarName, ".classes) | xargs rm -f\n",
-        "\t-echo $(", MakeVarName, ".rlos) | xargs rm -f\n"
+        "\t-echo $(", MakeVarName, ".classes) | xargs rm -f\n"
     ], !IO),
     io__write_strings(DepStream, [
         "\t-rm -f ",
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.160
diff -u -r1.160 opt_debug.m
--- compiler/opt_debug.m	28 Oct 2005 02:10:26 -0000	1.160
+++ compiler/opt_debug.m	24 Feb 2006 02:19:55 -0000
@@ -339,11 +339,6 @@
 dump_data_addr(rtti_addr(tc_rtti_id(TCName, TCDataName))) =
     "tc_rtti_addr(" ++ dump_rtti_type_class_name(TCName) ++ ", "
         ++ dump_tc_rtti_name(TCDataName) ++ ")".
-dump_data_addr(rtti_addr(aditi_rtti_id(ProcLabel))) =
-    "aditi_rtti_addr("
-        ++ sym_name_to_string(
-            qualified(ProcLabel ^ proc_module, ProcLabel ^ proc_name))
-        ++ ")".
 dump_data_addr(layout_addr(LayoutName)) =
     "layout_addr(" ++ dump_layout_name(LayoutName) ++ ")".

Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.500
diff -u -r1.500 options.m
--- compiler/options.m	24 Feb 2006 01:41:51 -0000	1.500
+++ compiler/options.m	24 Feb 2006 05:45:43 -0000
@@ -132,8 +132,6 @@
     ;       debug_term          % term = constraint termination analysis
     ;       debug_opt_pred_id
     ;       debug_pd            % pd = partial deduction/deforestation
-    ;       debug_rl_gen
-    ;       debug_rl_opt
     ;       debug_il_asm        % il_asm = IL generation via asm
     ;       debug_liveness
     ;       debug_stack_opt
@@ -160,7 +158,6 @@
     ;       target_code_only
     ;       compile_only
     ;       compile_to_shared_lib
-    ;       aditi_only
     ;       output_grade_string
     ;       output_link_command
     ;       output_shared_lib_link_command
@@ -205,9 +202,6 @@
     ;       dump_hlds_options
     ;       dump_mlds
     ;       verbose_dump_mlds
-    ;       generate_schemas
-    ;       dump_rl
-    ;       dump_rl_bytecode
     ;       mode_constraints
     ;       simple_mode_constraints
     ;       prop_mode_constraints
@@ -274,11 +268,7 @@
     ;       record_term_sizes_as_cells
     ;       experimental_complexity

-    % (c) Aditi
-    ;       aditi
-    ;       aditi_calls_mercury
-
-    % (d) Miscellaneous
+    % (c) Miscellaneous
     ;       gc
     ;       parallel
     ;       use_trail
@@ -760,7 +750,6 @@
     ;       intermod_directories
     ;       use_search_directories_for_intermod
     ;       filenames_from_stdin
-    ;       aditi_user
     ;       help
     ;       version
     ;       fullarch
@@ -890,8 +879,6 @@
     debug_opt                           -   bool(no),
     debug_opt_pred_id                   -   int(-1),
     debug_pd                            -   bool(no),
-    debug_rl_gen                        -   bool(no),
-    debug_rl_opt                        -   bool(no),
     debug_il_asm                        -   bool(no),
     debug_liveness                      -   int(-1),
     debug_stack_opt                     -   int(-1),
@@ -919,7 +906,6 @@
     target_code_only                    -   bool(no),
     compile_only                        -   bool(no),
     compile_to_shared_lib               -   bool(no),
-    aditi_only                          -   bool(no),
     output_grade_string                 -   bool(no),
     output_link_command                 -   bool(no),
     output_shared_lib_link_command      -   bool(no)
@@ -956,8 +942,6 @@
     dump_hlds_options                   -   string(""),
     dump_mlds                           -   accumulating([]),
     verbose_dump_mlds                   -   accumulating([]),
-    dump_rl                             -   bool(no),
-    dump_rl_bytecode                    -   bool(no),
     mode_constraints                    -   bool(no),
     simple_mode_constraints             -   bool(no),
     prop_mode_constraints               -   bool(no),
@@ -965,8 +949,7 @@
     benchmark_modes_repeat              -   int(1),
     sign_assembly                       -   bool(no),
     % XXX should default to no but currently broken
-    separate_assemblies                 -   bool(yes),
-    generate_schemas                    -   bool(no)
+    separate_assemblies                 -   bool(yes)
 ]).
 option_defaults_2(language_semantics_option, [
     strict_sequential                   -   special,
@@ -1025,8 +1008,6 @@
     use_minimal_model_own_stacks        -   bool(no),
     minimal_model_debug                 -   bool(no),
     type_layout                         -   bool(yes),
-    aditi                               -   bool(no),
-    aditi_calls_mercury                 -   bool(no), % XXX eventually yes

     % Data representation compilation model options
     reserve_tag                         -   bool(no),
@@ -1497,7 +1478,6 @@
 option_defaults_2(miscellaneous_option, [
     % Miscellaneous Options
     filenames_from_stdin                -   bool(no),
-    aditi_user                          -   string(""),
     help                                -   bool(no),
     version                             -   bool(no),
     fullarch                            -   string(""),
@@ -1600,8 +1580,6 @@
 long_option("debug-opt",            debug_opt).
 long_option("debug-opt-pred-id",    debug_opt_pred_id).
 long_option("debug-pd",             debug_pd).
-long_option("debug-rl-gen",         debug_rl_gen).
-long_option("debug-rl-opt",         debug_rl_opt).
     % debug-il-asm does very low-level printf style debugging of
     % IL assembler.  Each instruction is written on stdout before it
     % is executed.  It is a temporary measure until the IL debugging
@@ -1644,7 +1622,6 @@
 long_option("target-code-only",     target_code_only).
 long_option("compile-only",         compile_only).
 long_option("compile-to-shared-lib",    compile_to_shared_lib).
-long_option("aditi-only",           aditi_only).
 long_option("output-grade-string",  output_grade_string).
 long_option("output-link-command",  output_link_command).
 long_option("output-shared-lib-link-command", output_shared_lib_link_command).
@@ -1684,11 +1661,8 @@
 long_option("mlds-dump",            dump_mlds).
 long_option("verbose-dump-mlds",    verbose_dump_mlds).
 long_option("verbose-mlds-dump",    verbose_dump_mlds).
-long_option("dump-rl",              dump_rl).
-long_option("dump-rl-bytecode",     dump_rl_bytecode).
 long_option("sign-assembly",        sign_assembly).
 long_option("separate-assemblies",  separate_assemblies).
-long_option("generate-schemas",     generate_schemas).
 long_option("mode-constraints",     mode_constraints).
 long_option("simple-mode-constraints",  simple_mode_constraints).
 long_option("prop-mode-constraints",    prop_mode_constraints).
@@ -1754,8 +1728,6 @@
 long_option("type-layout",          type_layout).
 long_option("maybe-thread-safe",    maybe_thread_safe).
 long_option("extend-stacks-when-needed",    extend_stacks_when_needed).
-long_option("aditi",                aditi).
-long_option("aditi-calls-mercury",  aditi_calls_mercury).
 % Data representation options
 long_option("reserve-tag",          reserve_tag).
 long_option("use-minimal-model-stack_copy", use_minimal_model_stack_copy).
@@ -2252,7 +2224,6 @@
 long_option("help",                 help).
 long_option("version",              version).
 long_option("filenames-from-stdin", filenames_from_stdin).
-long_option("aditi-user",           aditi_user).
 long_option("fullarch",             fullarch).
 long_option("local-module-id",      local_module_id).
 long_option("bug-intermod-2002-06-13",  compiler_sufficiently_recent).
@@ -2756,7 +2727,6 @@
     options_help_hlds_llds_optimization,
     options_help_llds_llds_optimization,
     options_help_mlds_mlds_optimization,
-    options_help_rl_rl_optimization,
     options_help_output_optimization,
     options_help_target_code_compilation,
     options_help_link,
@@ -2933,10 +2903,6 @@
         "--debug-pd",
         "\tOutput detailed debugging traces of the partial",
         "\tdeduction and deforestation process.",
-        "--debug-rl-gen",
-        "\tOutput detailed debugging traces of Aditi-RL code generation.",
-        "--debug-rl-opt",
-        "\tOutput detailed debugging traces of Aditi-RL optimization.",
         "--debug-liveness <pred_id>",
         "\tOutput detailed debugging traces of the liveness analysis",
         "\tof the predicate with the given predicate id.",
@@ -3025,9 +2991,6 @@
         % --compile-to-shared-lib is intended only for use
         % by the debugger's interactive query facility,
         % so it isn't documented.
-        "--aditi-only",
-        "\tWrite Aditi-RL bytecode to `<module>.rlo' and",
-        "\tdo not compile to C.",
         "--output-grade-string",
         "\tCompute the grade of the library to link with based on",
         "\tthe command line options, and print it to the standard",
@@ -3170,20 +3133,6 @@
         "--verbose-dump-mlds <stage number or name>",
         "\tDump the internal compiler representation of the MLDS, after",
         "\tthe specified stage, to `<module>.mlds_dump.<num>-<name>'.",
-        "--dump-rl",
-        "\tOutput a human readable form of the compiler's internal",
-        "\trepresentation of the generated Aditi-RL code to",
-        "\t`<module>.rl_dump'.",
-        "--dump-rl-bytecode",
-        "\tOutput a human readable representation of the generated",
-        "\tAditi-RL bytecodes to `<module>.rla'.",
-        "\tAditi-RL bytecodes are directly executed by the Aditi system.",
-        "--generate-schemas",
-        "\tOutput schema strings for Aditi base relations",
-        "\tto `<module>.base_schema' and for Aditi derived",
-        "\trelations to `<module>.derived_schema'.",
-        "\tA schema string is a representation of the types",
-        "\tof a relation.",
 % The mode constraints code is still experimental so these options are
 % currently commented out.
 %       "--mode-constraints"
@@ -3483,16 +3432,6 @@
         "\tThis option is supported for the C back-end, with",
         "\t--no-highlevel-code."
     ]),
-    io__write_string("      Aditi\n"),
-    write_tabbed_lines([
-        "--aditi",
-        "\tEnable Aditi compilation. You need to enable this",
-        "\toption if you are making use of the Aditi deductive",
-        "\tdatabase interface."
-        % XXX --aditi-calls-mercury is not fully implemented.
-        % "--aditi-calls-mercury",
-        % "\tEnable calling ordinary Mercury code from Aditi."
-    ]),

     io__write_string("      Miscellaneous optional features\n"),
     write_tabbed_lines([
@@ -4236,30 +4175,6 @@
         "\tin the standard library."
 ]).

-
-:- pred options_help_rl_rl_optimization(io::di, io::uo) is det.
-
-options_help_rl_rl_optimization -->
-    io__write_string("\n    Aditi-RL optimizations:\n"),
-    write_tabbed_lines([
-        "--optimize-rl",
-        "\tEnable the optimizations of Aditi-RL procedures",
-        "\tdescribed below.",
-        "\t--optimize-rl-invariants",
-        "\tOptimize loop invariants in Aditi-RL procedures.",
-        "\t--optimize-rl-index",
-        "\tUse indexing to optimize access to relations in Aditi-RL",
-        "\tprocedures.",
-        "\t--detect-rl-streams",
-        "\tDetect cases where intermediate results in Aditi-RL",
-        "\tprocedures do not need to be materialised."
-        /*
-        % This option is not yet used.
-        "--optimize-rl-cse",
-        "\tOptimize common subexpressions in Aditi-RL procedures.",
-        */
-    ]).
-
 :- pred options_help_output_optimization(io::di, io::uo) is det.

 options_help_output_optimization -->
@@ -4618,14 +4533,6 @@
         "\tis reached. (This allows a program or user to interactively",
         "\tcompile several modules without the overhead of process",
         "\tcreation for each one.)",
-        "--aditi-user",
-        "\tSpecify the Aditi login of the owner of the predicates",
-        "\tin any Aditi RL files produced. The owner field is",
-        "\tused along with module, name and arity to identify",
-        "\tpredicates, and is also used for security checks.",
-        "\tDefaults to the value of the `USER' environment",
-        "\tvariable. If `$USER' is not set, `--aditi-user'",
-        "\tdefaults to the string ""guest"".",
         "--version",
         "\tDisplay the compiler version."

Index: compiler/prog_data.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_data.m,v
retrieving revision 1.154
diff -u -r1.154 prog_data.m
--- compiler/prog_data.m	24 Feb 2006 01:41:53 -0000	1.154
+++ compiler/prog_data.m	24 Feb 2006 04:34:35 -0000
@@ -206,7 +206,6 @@
     ;       own_stacks.     % Each generator has its own stacks.

     % The evaluation method that should be used for a procedure.
-    % Ignored for Aditi procedures.
     %
 :- type eval_method
     --->    eval_normal                 % normal mercury evaluation
@@ -253,26 +252,6 @@

 %-----------------------------------------------------------------------------%
 %
-% Stuff for the `aditi_index' pragma
-%
-
-    % For Aditi base relations, an index_spec specifies how the base
-    % relation is indexed.
-    %
-:- type index_spec
-    --->    index_spec(
-                index_type,
-                list(int)   % Which attributes are being indexed on
-                            % (attribute numbers start at 1)
-            ).
-
-    % Hash indexes?
-:- type index_type
-    --->    unique_B_tree
-    ;       non_unique_B_tree.
-
-%-----------------------------------------------------------------------------%
-%
 % Stuff for the `termination_info' pragma.
 % See term_util.m.
 %
Index: compiler/prog_foreign.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_foreign.m,v
retrieving revision 1.4
diff -u -r1.4 prog_foreign.m
--- compiler/prog_foreign.m	23 Nov 2005 04:44:06 -0000	1.4
+++ compiler/prog_foreign.m	24 Feb 2006 04:34:56 -0000
@@ -170,10 +170,6 @@
     %
 :- func make_init_name(module_name) = string.

-    % Returns the name of the Aditi-RL code constant for a given module.
-    %
-:- func make_rl_data_name(module_name) = string.
-
     % Mangle a possibly module-qualified Mercury symbol name
     % into a C identifier.
     %
@@ -352,10 +348,6 @@
     MangledModuleName = sym_name_mangle(ModuleName),
     InitName = "mercury__" ++ MangledModuleName ++ "__".

-make_rl_data_name(ModuleName) = RLDataConstName :-
-    MangledModuleName = sym_name_mangle(ModuleName),
-    RLDataConstName = "mercury__aditi_rl_data__" ++ MangledModuleName.
-
 sym_name_mangle(unqualified(Name)) =
     name_mangle(Name).
 sym_name_mangle(qualified(ModuleName, PlainName)) = MangledName :-
Index: compiler/prog_mode.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_mode.m,v
retrieving revision 1.11
diff -u -r1.11 prog_mode.m
--- compiler/prog_mode.m	28 Nov 2005 04:11:52 -0000	1.11
+++ compiler/prog_mode.m	24 Feb 2006 02:19:13 -0000
@@ -43,15 +43,6 @@
 :- func free_inst = mer_inst.
 :- func any_inst = mer_inst.

-    % Construct the modes used for `aditi__state' arguments.
-    % XXX These should be unique, but are not yet because that
-    % would require alias tracking.
-    %
-:- func aditi_mui_mode = mer_mode.
-:- func aditi_ui_mode = mer_mode.
-:- func aditi_di_mode = mer_mode.
-:- func aditi_uo_mode = mer_mode.
-
 :- pred make_std_mode(string::in, list(mer_inst)::in, mer_mode::out) is det.
 :- func make_std_mode(string, list(mer_inst)) = mer_mode.

@@ -161,11 +152,6 @@
 in_any_mode = make_std_mode("in", [any_inst]).
 out_any_mode = make_std_mode("out", [any_inst]).

-aditi_mui_mode = Mode :- in_mode(Mode).
-aditi_ui_mode = Mode :- in_mode(Mode).
-aditi_di_mode = Mode :- in_mode(Mode).
-aditi_uo_mode = Mode :- out_mode(Mode).
-
 ground_inst = ground(shared, none).
 free_inst = free.
 any_inst = any(shared).
Index: compiler/prog_type.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_type.m,v
retrieving revision 1.17
diff -u -r1.17 prog_type.m
--- compiler/prog_type.m	24 Feb 2006 01:41:53 -0000	1.17
+++ compiler/prog_type.m	24 Feb 2006 02:19:01 -0000
@@ -209,15 +209,8 @@

 :- pred type_is_io_state(mer_type::in) is semidet.

-:- pred type_is_aditi_state(mer_type::in) is semidet.
-
 :- pred type_ctor_is_array(type_ctor::in) is semidet.

-    % Remove an `aditi:state' from the given list if one is present.
-    %
-:- pred remove_aditi_state(list(mer_type)::in, list(T)::in, list(T)::out)
-    is det.
-
     % A test for type_info-related types that are introduced by
     % polymorphism.m.  These need to be handled specially in certain
     % places.  For example, mode inference never infers unique modes
@@ -278,7 +271,6 @@
 :- func sample_type_info_type = mer_type.
 :- func sample_typeclass_info_type = mer_type.
 :- func comparison_result_type = mer_type.
-:- func aditi_state_type = mer_type.
 :- func io_state_type = mer_type.

     % Construct the types of type_infos and type_ctor_infos.
@@ -728,7 +720,6 @@

 is_builtin_dummy_argument_type("io", "state", 0).    % io.state/0
 is_builtin_dummy_argument_type("store", "store", 1). % store.store/1.
-% XXX should we include aditi.state/0 in this list?

 constructor_list_represents_dummy_argument_type([Ctor], no) :-
     Ctor = ctor([], [], _, []).
@@ -738,25 +729,8 @@
     mercury_std_lib_module_name("io", ModuleName),
     TypeCtor = qualified(ModuleName, "state") - 0.

-type_is_aditi_state(Type) :-
-    type_to_ctor_and_args(Type, TypeCtor, []),
-    TypeCtor = qualified(unqualified("aditi"), "state") - 0.
-
 type_ctor_is_array(qualified(unqualified("array"), "array") - 1).

-remove_aditi_state([], [], []).
-remove_aditi_state([], [_ | _], _) :-
-    unexpected(this_file, "gremove_aditi_state").
-remove_aditi_state([_ | _], [], _) :-
-    unexpected(this_file, "gremove_aditi_state").
-remove_aditi_state([Type | Types], [Arg | Args0], Args) :-
-    ( type_is_aditi_state(Type) ->
-        remove_aditi_state(Types, Args0, Args)
-    ;
-        remove_aditi_state(Types, Args0, Args1),
-        Args = [Arg | Args1]
-    ).
-
 is_introduced_type_info_type(Type) :-
     type_to_ctor_and_args(Type, TypeCtor, _),
     is_introduced_type_info_type_ctor(TypeCtor).
@@ -840,10 +814,6 @@
     mercury_private_builtin_module(BuiltinModule),
     Name = qualified(BuiltinModule, "type_ctor_info").

-aditi_state_type = defined(Name, [], star) :-
-    aditi_public_builtin_module(BuiltinModule),
-    Name = qualified(BuiltinModule, "state").
-
 io_state_type = defined(Name, [], star) :-
     mercury_std_lib_module_name("io", Module),
     Name = qualified(Module, "state").
Index: compiler/rtti.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/rtti.m,v
retrieving revision 1.65
diff -u -r1.65 rtti.m
--- compiler/rtti.m	28 Nov 2005 04:11:53 -0000	1.65
+++ compiler/rtti.m	24 Feb 2006 02:18:00 -0000
@@ -571,14 +571,6 @@
             )
     ;       type_class_instance(
                 tc_instance
-            )
-            % A procedure to be called top-down by Aditi when evaluating
-            % a join condition. These procedures only have one input and one
-            % output argument, both of which must have a ground {}/N type.
-    ;       aditi_proc_info(
-                rtti_proc_label,    % The procedure to call.
-                rtti_type_info,     % Type of the input argument.
-                rtti_type_info      % Type of the output argument.
             ).

 % All rtti_data data structures and all their components are identified
@@ -591,8 +583,7 @@

 :- type rtti_id
     --->    ctor_rtti_id(rtti_type_ctor, ctor_rtti_name)
-    ;       tc_rtti_id(tc_name, tc_rtti_name)
-    ;       aditi_rtti_id(rtti_proc_label).
+    ;       tc_rtti_id(tc_name, tc_rtti_name).

 :- type ctor_rtti_name
     --->    exist_locns(int)                % functor ordinal
@@ -701,10 +692,6 @@
 :- pred proc_label_pred_proc_id(rtti_proc_label::in,
     pred_id::out, proc_id::out) is det.

-    % Construct an aditi_proc_info for a given procedure.
-    %
-:- func make_aditi_proc_info(module_info, pred_id, proc_id) = rtti_data.
-
     % Return the C variable name of the RTTI data structure identified
     % by the input argument.
     %
@@ -893,7 +880,6 @@
     TCId = tc_id(TCName, _, _).
 rtti_data_to_id(type_class_instance(tc_instance(TCName, TCTypes, _, _, _)),
         tc_rtti_id(TCName, type_class_instance(TCTypes))).
-rtti_data_to_id(aditi_proc_info(ProcLabel, _, _), aditi_rtti_id(ProcLabel)).

 tcd_get_rtti_type_ctor(TypeCtorData) = RttiTypeCtor :-
     ModuleName = TypeCtorData ^ tcr_module_name,
@@ -950,7 +936,6 @@
     ctor_rtti_name_has_array_type(RttiName).
 rtti_id_has_array_type(tc_rtti_id(_, TCRttiName)) =
     tc_rtti_name_has_array_type(TCRttiName).
-rtti_id_has_array_type(aditi_rtti_id(_)) = no.

 ctor_rtti_name_has_array_type(RttiName) = IsArray :-
     ctor_rtti_name_type(RttiName, _, IsArray).
@@ -962,8 +947,6 @@
     ctor_rtti_name_is_exported(RttiName).
 rtti_id_is_exported(tc_rtti_id(_, TCRttiName)) =
     tc_rtti_name_is_exported(TCRttiName).
-% MR_AditiProcInfos must be exported to be visible to dlsym().
-rtti_id_is_exported(aditi_rtti_id(_)) = yes.

 ctor_rtti_name_is_exported(exist_locns(_))              = no.
 ctor_rtti_name_is_exported(exist_locn)                  = no.
@@ -1065,26 +1048,10 @@
     PredId = ProcLabel ^ pred_id,
     ProcId = ProcLabel ^ proc_id.

-make_aditi_proc_info(ModuleInfo, PredId, ProcId) =
-        aditi_proc_info(ProcLabel, InputTypeInfo, OutputTypeInfo) :-
-    ProcLabel = make_rtti_proc_label(ModuleInfo, PredId, ProcId),
-
-    % The types of the arguments must be ground.
-    ( ProcLabel ^ proc_arg_types = [InputArgType, OutputArgType] ->
-        pseudo_type_info__construct_type_info(InputArgType, InputTypeInfo),
-        pseudo_type_info__construct_type_info(OutputArgType, OutputTypeInfo)
-    ;
-        unexpected(this_file,
-            "make_aditi_proc_info: incorrect number of arguments")
-    ).
-
 id_to_c_identifier(ctor_rtti_id(RttiTypeCtor, RttiName), Str) :-
     Str = name_to_string(RttiTypeCtor, RttiName).
 id_to_c_identifier(tc_rtti_id(TCName, TCRttiName), Str) :-
     tc_name_to_string(TCName, TCRttiName, Str).
-id_to_c_identifier(aditi_rtti_id(RttiProcLabel), Str) :-
-    Str = "AditiProcInfo_For_" ++
-        proc_label_to_c_string(make_proc_label_from_rtti(RttiProcLabel), no).

 :- func name_to_string(rtti_type_ctor, ctor_rtti_name) = string.

@@ -1657,7 +1624,6 @@
     ctor_rtti_name_would_include_code_addr(RttiName).
 rtti_id_would_include_code_addr(tc_rtti_id(_, TCRttiName)) =
     tc_rtti_name_would_include_code_addr(TCRttiName).
-rtti_id_would_include_code_addr(aditi_rtti_id(_)) = yes.

 ctor_rtti_name_would_include_code_addr(exist_locns(_)) =                no.
 ctor_rtti_name_would_include_code_addr(exist_locn)  =                   no.
@@ -1732,7 +1698,6 @@
     ctor_rtti_name_c_type(RttiName, CTypeName, IsArray).
 rtti_id_c_type(tc_rtti_id(_, TCRttiName), CTypeName, IsArray) :-
     tc_rtti_name_c_type(TCRttiName, CTypeName, IsArray).
-rtti_id_c_type(aditi_rtti_id(_), "MR_Aditi_Proc_Info", no).

 ctor_rtti_name_c_type(RttiName, CTypeName, IsArray) :-
     ctor_rtti_name_type(RttiName, GenTypeName, IsArray),
@@ -1759,8 +1724,6 @@
     ctor_rtti_name_java_type(RttiName, JavaTypeName, IsArray).
 rtti_id_java_type(tc_rtti_id(_, TCRttiName), JavaTypeName, IsArray) :-
     tc_rtti_name_java_type(TCRttiName, JavaTypeName, IsArray).
-rtti_id_java_type(aditi_rtti_id(_), _, _) :-
-    unexpected(this_file, "Aditi not supported for the Java back-end").

 ctor_rtti_name_java_type(RttiName, JavaTypeName, IsArray) :-
     ctor_rtti_name_type(RttiName, GenTypeName0, IsArray),
@@ -1927,9 +1890,6 @@
         RttiId = tc_rtti_id(_, TCRttiName),
         ShouldModuleQualify =
             module_qualify_name_of_tc_rtti_name(TCRttiName)
-    ;
-        RttiId = aditi_rtti_id(_),
-        ShouldModuleQualify = yes
     ).

 module_qualify_name_of_ctor_rtti_name(_) = yes.
Index: compiler/rtti_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/rtti_out.m,v
retrieving revision 1.60
diff -u -r1.60 rtti_out.m
--- compiler/rtti_out.m	11 Jan 2006 02:33:41 -0000	1.60
+++ compiler/rtti_out.m	24 Feb 2006 02:18:25 -0000
@@ -140,42 +140,6 @@
     output_type_class_decl_defn(TCDecl, !DeclSet, !IO).
 output_rtti_data_defn(type_class_instance(InstanceDecl), !DeclSet, !IO) :-
     output_type_class_instance_defn(InstanceDecl, !DeclSet, !IO).
-output_rtti_data_defn(aditi_proc_info(ProcLabel, InputTypeInfo,
-        OutputTypeInfo), !DeclSet, !IO) :-
-    output_aditi_proc_info_defn(ProcLabel, InputTypeInfo, OutputTypeInfo,
-        !DeclSet, !IO).
-
-%-----------------------------------------------------------------------------%
-
-:- pred output_aditi_proc_info_defn(rtti_proc_label::in,
-    rtti_type_info::in, rtti_type_info::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_aditi_proc_info_defn(ProcLabel, InputTypeInfo, OutputTypeInfo,
-        !DeclSet, !IO) :-
-    output_type_info_defn(InputTypeInfo, !DeclSet, !IO),
-    output_type_info_defn(OutputTypeInfo, !DeclSet, !IO),
-    CodeAddr = make_code_addr(ProcLabel),
-    output_code_addr_decls(CodeAddr, !DeclSet, !IO),
-
-    output_rtti_id_storage_type_name(aditi_rtti_id(ProcLabel), yes,
-        !DeclSet, !IO),
-    io__write_string(" = {\n\t(MR_Code *) ", !IO),
-    output_static_code_addr(CodeAddr, !IO),
-    io__write_string(",\n\t", !IO),
-    io__write_string("""", !IO),
-    c_util__output_quoted_string(
-        proc_label_to_c_string(make_proc_label_from_rtti(ProcLabel), no), !IO),
-    io__write_string(""",\n\t", !IO),
-    output_cast_addr_of_rtti_data("(MR_TypeInfo) ", type_info(InputTypeInfo),
-        !IO),
-    io__write_string(",\n\t", !IO),
-    output_cast_addr_of_rtti_data("(MR_TypeInfo) ", type_info(OutputTypeInfo),
-        !IO),
-    io__write_string(",\n\t", !IO),
-    io__write_int(represent_determinism(ProcLabel ^ proc_interface_detism),
-        !IO),
-    io__write_string("\n};\n", !IO).

 %-----------------------------------------------------------------------------%

@@ -1538,16 +1502,6 @@
             "not yet supported without static code addresses""\n", !IO),
         io__write_string("#endif /* MR_STATIC_CODE_ADDRESSES */\n", !IO)
     ;
-        Data = aditi_proc_info(ProcLabel, _, _)
-    ->
-        io__write_string("\tMR_INIT_ADITI_PROC_INFO(", !IO),
-        rtti_data_to_id(Data, DataId),
-        rtti__id_to_c_identifier(DataId, CId),
-        io__write_string(CId, !IO),
-        io__write_string(", ", !IO),
-        output_code_addr(make_code_addr(ProcLabel), !IO),
-        io__write_string(");\n", !IO)
-    ;
         true
     ).

Index: compiler/rtti_to_mlds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/rtti_to_mlds.m,v
retrieving revision 1.66
diff -u -r1.66 rtti_to_mlds.m
--- compiler/rtti_to_mlds.m	28 Nov 2005 04:11:54 -0000	1.66
+++ compiler/rtti_to_mlds.m	24 Feb 2006 02:16:46 -0000
@@ -272,38 +272,6 @@
         % gen_init_proc_id_from_univ(ModuleInfo, PrettyprinterProc)
     ]).

-gen_init_rtti_data_defn(RttiData, RttiId, ModuleInfo, Init, SubDefns) :-
-    RttiData = aditi_proc_info(ProcLabel, InputTypeInfo, OutputTypeInfo),
-    ( real_rtti_data(type_info(InputTypeInfo)) ->
-        InputTypeInfoDefns = rtti_data_to_mlds(ModuleInfo,
-            type_info(InputTypeInfo))
-    ;
-        InputTypeInfoDefns = []
-    ),
-    ( real_rtti_data(type_info(OutputTypeInfo)) ->
-        OutputTypeInfoDefns = rtti_data_to_mlds(ModuleInfo,
-            type_info(OutputTypeInfo))
-    ;
-        OutputTypeInfoDefns = []
-    ),
-    prog_out__sym_name_and_arity_to_string(
-        qualified(ProcLabel ^ proc_module, ProcLabel ^ proc_name)/
-            ProcLabel ^ proc_arity,
-        ProcNameStr),
-    module_info_get_name(ModuleInfo, ModuleName),
-
-    Init = init_struct(mlds__rtti_type(item_type(RttiId)), [
-        gen_init_proc_id(ModuleInfo, ProcLabel),
-        gen_init_string(ProcNameStr),
-        gen_init_cast_rtti_data(mlds__type_info_type,
-            ModuleName, type_info(InputTypeInfo)),
-        gen_init_cast_rtti_data(mlds__type_info_type,
-            ModuleName, type_info(OutputTypeInfo)),
-        gen_init_int(code_model__represent_determinism(
-            ProcLabel ^ proc_interface_detism))
-    ]),
-    SubDefns = InputTypeInfoDefns ++ OutputTypeInfoDefns.
-
 %-----------------------------------------------------------------------------%

 :- pred gen_type_class_decl_defn(tc_decl::in, rtti_id::in, module_info::in,
@@ -1176,8 +1144,6 @@
     gen_init_rtti_name(ModuleName, RttiTypeCtor, RttiName).
 gen_init_rtti_id(ModuleName, tc_rtti_id(TCName, TCRttiName)) =
     gen_init_tc_rtti_name(ModuleName, TCName, TCRttiName).
-gen_init_rtti_id(ModuleName, aditi_rtti_id(ProcLabel)) =
-    gen_init_aditi_rtti_name(ModuleName, ProcLabel).

     % Generate an MLDS initializer comprising just the
     % the rval for a given rtti_name.
@@ -1197,15 +1163,6 @@
 gen_init_tc_rtti_name(ModuleName, TCName, TCRttiName) =
     init_obj(gen_tc_rtti_name(ModuleName, TCName, TCRttiName)).

-    % Generate an MLDS initializer comprising just the
-    % the rval for a given aditi_rtti_name.
-    %
-:- func gen_init_aditi_rtti_name(module_name, rtti_proc_label) =
-    mlds__initializer.
-
-gen_init_aditi_rtti_name(ModuleName, ProcLabel) =
-    init_obj(gen_aditi_rtti_name(ModuleName, ProcLabel)).
-
     % Generate the MLDS initializer comprising the rtti_name
     % for a given rtti_name, converted to the given type.
     %
@@ -1225,8 +1182,6 @@
     gen_rtti_name(ThisModuleName, RttiTypeCtor, RttiName).
 gen_rtti_id(ThisModuleName, tc_rtti_id(TCName, TCRttiName)) =
     gen_tc_rtti_name(ThisModuleName, TCName, TCRttiName).
-gen_rtti_id(ThisModuleName, aditi_rtti_id(ProcLabel)) =
-    gen_aditi_rtti_name(ThisModuleName, ProcLabel).

 :- func gen_rtti_name(module_name, rtti_type_ctor, ctor_rtti_name)
     = mlds_rval.
@@ -1316,14 +1271,6 @@
     DataAddr = data_addr(MLDS_ModuleName, MLDS_DataName),
     Rval = const(data_addr_const(DataAddr)).

-:- func gen_aditi_rtti_name(module_name, rtti_proc_label) = mlds_rval.
-
-gen_aditi_rtti_name(ThisModuleName, ProcLabel) = Rval :-
-    MLDS_ModuleName = mercury_module_name_to_mlds(ThisModuleName),
-    MLDS_DataName = rtti(aditi_rtti_id(ProcLabel)),
-    DataAddr = data_addr(MLDS_ModuleName, MLDS_DataName),
-    Rval = const(data_addr_const(DataAddr)).
-
 :- func mlds_module_name_from_tc_name(tc_name) = mlds_module_name.

 mlds_module_name_from_tc_name(TCName) = MLDS_ModuleName :-
Index: compiler/term_errors.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/term_errors.m,v
retrieving revision 1.35
diff -u -r1.35 term_errors.m
--- compiler/term_errors.m	1 Feb 2006 05:10:35 -0000	1.35
+++ compiler/term_errors.m	24 Feb 2006 02:11:37 -0000
@@ -68,10 +68,6 @@
             % There is a call to a typeclass method at the associated
             % context.  Valid in both passes.

-    ;       aditi_call
-            % There is a call to an Aditi builtin at the associated
-            % context. Valid in both passes.
-
     ;       inf_termination_const(pred_proc_id, pred_proc_id)
             % inf_termination_const(Caller, Callee)
             % The call from Caller to Callee at the associated
@@ -186,7 +182,6 @@

 indirect_error(horder_call).
 indirect_error(method_call).
-indirect_error(aditi_call).
 indirect_error(pragma_foreign_code).
 indirect_error(imported_pred).
 indirect_error(can_loop_proc_called(_, _)).
@@ -307,9 +302,6 @@
 description(method_call, _, _, Pieces, no) :-
     Pieces = [words("It contains a typeclass method call.")].

-description(aditi_call, _, _, Pieces, no) :-
-    Pieces = [words("It contains an Aditi builtin call.")].
-
 description(pragma_foreign_code, _, _, Pieces, no) :-
     Pieces = [
         words("It depends on the properties of"),
Index: compiler/unify_proc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unify_proc.m,v
retrieving revision 1.159
diff -u -r1.159 unify_proc.m
--- compiler/unify_proc.m	24 Feb 2006 05:49:42 -0000	1.159
+++ compiler/unify_proc.m	24 Feb 2006 05:55:30 -0000
@@ -1238,19 +1238,18 @@
     %           X3 = Y3
     %       ).
     %
-    % Note that in the disjuncts handling constants, we want to unify Y with X,
-    % not with the constant. Doing this allows dupelim to take the code
-    % fragments implementing the switch arms for constants and eliminate
-    % all but one of them. This can be a significant code size saving
-    % for types with lots of constants, such as the one representing Aditi
-    % bytecodes, which can lead to significant reductions in C compilation
-    % time. The keep_constant_binding feature on the cast goals is there to ask
-    % mode analysis to copy any known bound inst on the cast-from variable
-    % to the cast-to variable. This is necessary to keep determinism analysis
-    % working for modes in which the inputs of the unify predicate are known
-    % to be bound to the same constant, modes whose determinism should
-    % therefore be inferred to be det. (tests/general/det_complicated_unify2.m
-    % tests this case.)
+    % Note that in the disjuncts handling constants, we want to unify Y with
+    % X, not with the constant. Doing this allows dupelim to take the code
+    % fragments implementing the switch arms for constants and eliminate all
+    % but one of them. This can be a significant code size saving for types
+    % with lots of constants which can lead to significant reductions in C
+    % compilation time. The keep_constant_binding feature on the cast goals is
+    % there to ask mode analysis to copy any known bound inst on the cast-from
+    % variable to the cast-to variable. This is necessary to keep determinism
+    % analysis working for modes in which the inputs of the unify predicate
+    % are known to be bound to the same constant, modes whose determinism
+    % should therefore be inferred to be det.
+    % (tests/general/det_complicated_unify2.m tests this case.)
     %
 :- pred generate_du_unify_clauses(list(constructor)::in,
     prog_var::in, prog_var::in, prog_context::in,
Index: doc/reference_manual.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
retrieving revision 1.343
diff -u -r1.343 reference_manual.texi
--- doc/reference_manual.texi	3 Jan 2006 04:03:06 -0000	1.343
+++ doc/reference_manual.texi	23 Feb 2006 13:44:22 -0000
@@ -7,9 +7,6 @@
 * Mercury Language: (mercury_ref).  The Mercury Language Reference Manual.
 @end direntry

- at c Uncomment the line below to enable documentation of the Aditi interface.
- at set aditi
-
 @c @smallbook
 @c @cropmarks
 @finalout
@@ -444,8 +441,6 @@
 --                              yfx               500
 /\\                             yfx               500
 \\/                             yfx               500
-aditi_bottom_up                 fx                500
-aditi_top_down                  fx                500
 ..                              xfx               550
 :=                              xfx               650
 =^                              xfx               650
@@ -782,20 +777,6 @@
 higher-order call using the @code{call/N} syntax, i.e.@:
 @samp{call(Var)}, @samp{call(Var, Arg1)}, etc.

- at ifset aditi
-
- at item @code{aditi_bulk_delete(@dots{})}
- at itemx @code{aditi_bulk_insert(@dots{})}
- at itemx @code{aditi_bulk_modify(@dots{})}
- at itemx @code{aditi_delete(@dots{})}
- at itemx @code{aditi_insert(@dots{})}
-
-These goal forms are used for the Aditi database interface.
- at xref{Aditi update syntax}.
-
- at end ifset
- at c aditi
-
 @item @code{@var{Call}}
 Any goal which does not match any of the above forms
 must be a predicate call.
@@ -9035,9 +9016,7 @@
                                 calculated results and detecting or avoiding
                                 certain kinds of infinite loops.
 * Termination analysis::        Support for automatic proofs of termination.
-* Aditi deductive database interface::
-                                Support for bottom-up evaluation of Mercury
-                                predicates.
+
 @end menu
 @c XXX The `reserved tag' pragma is not documented because it is intended to
 @c     be used with `any' insts, which are themselves not yet documented.
@@ -9352,750 +9331,6 @@
 If it cannot prove the termination of the specified predicate or
 function then the compiler will quit with an error message.

- at ifset aditi
- at node Aditi deductive database interface
- at section Aditi deductive database interface
-
- at menu
-* Aditi overview::
-* Aditi pragma declarations::   Controlling Aditi compilation.
-* Aditi update syntax::         Changing the contents of Aditi relations.
-* Aditi glossary::              Glossary of Aditi terms.
- at end menu
-
- at node Aditi overview
- at subsection Aditi overview
-
-The University of Melbourne Mercury implementation includes support for
-compiling Mercury predicates for bottom-up evaluation using the Aditi2
-deductive database system. The Aditi system is not yet publicly available,
-so this is currently not very useful to anyone other than the Mercury and
-Aditi developers. For more information see the Aditi web site
-at <http://www.cs.mu.oz.au/aditi>.
-
-Evaluation by a deductive database system is useful for predicates which
-use large amounts of data, since the database system can use efficient join
-algorithms instead of backtracking. Also, some predicates which loop when
-executed top-down may terminate when executed bottom-up by the database (this
-effect can also be achieved using tabling (@pxref{Tabled evaluation})).
-Bottom-up evaluation computes the answers to a predicate a set at a time,
-rather than a tuple at a time as in the normal top-down execution of a
-Mercury program.
-
-There are several restrictions on predicates to be evaluated using Aditi.
-Argument types may not include polymorphic, higher-order or abstract types.
-Type classes are not supported within database predicates. The argument
-modes must not contain partially instantiated insts. Aditi predicates must
-be stratified (@pxref{Aditi glossary}) and must not be mutually recursive
-with predicates in other modules.
-
-Every predicate with a @samp{pragma aditi} or
- at samp{pragma base_relation} declaration must have an input
-argument of type @samp{aditi.state}. This ensures that Aditi predicates
-are only called from within transactions and that updates and database
-calls are ordered correctly, in the same way that @samp{io.state} arguments
-are used to ensure ordering of I/O operations. Within the clauses for
-predicates with a @samp{pragma aditi} declaration variables with
-type @samp{aditi.state} may only be passed to other database predicates ---
-they may not be packaged into terms or passed to top-down Mercury predicates.
-This allows the compiler to remove all instances of @samp{aditi.state}
-variables from database predicates, and enforces the restriction that
-top-down Mercury code called from within the database cannot call bottom-up
-code, which is currently impossible for Aditi to handle.
-
-Some useful predicates are defined in @file{$ADITI_HOME/doc/aditi.m}
-in the Aditi distribution.
-
-The Aditi interface currently has the major restriction that recursive or
-imported top-down Mercury predicates or functions cannot be called from
-predicates with @samp{pragma aditi} declarations.
-The following predicates and functions from the standard library
-can be called from Aditi:
-
- at samp{builtin.compare/3},
-
- at samp{int.'<'/2},
- at samp{int.'>'/2},
- at samp{int.'=<'/2},
- at samp{int.'>='/2},
- at samp{int.abs/2},
- at samp{int.max/3},
- at samp{int.min/3},
- at samp{int.to_float/2},
- at samp{int.pow/2},
- at samp{int.log2/2},
- at samp{int.'+'/2},
- at samp{int.'+'/1},
- at samp{int.'-'/2},
- at samp{int.'-'/1},
- at samp{int.'*'/2},
- at samp{int.'//'/2},
- at samp{int.rem/2},
-
- at samp{float.'<'/2},
- at samp{float.'>'/2},
- at samp{float.'>='/2},
- at samp{float.'=<'/2},
- at samp{float.abs/1},
- at samp{float.abs/2},
- at samp{float.max/2},
- at samp{float.max/3},
- at samp{float.min/2},
- at samp{float.min/3},
- at samp{float.pow/2},
- at samp{float.log2/2},
- at samp{float.float/1},
- at samp{float.truncate_to_int/1},
- at samp{float.truncate_to_int/2},
- at samp{float.'+'/2},
- at samp{float.'+'/1},
- at samp{float.'-'/2},
- at samp{float.'-'/1},
- at samp{float.'*'/2},
- at samp{float.'/'/2},
-
- at samp{math.ceiling/1},
- at samp{math.round/1},
- at samp{math.floor/1},
- at samp{math.sqrt/1},
- at samp{math.pow/2},
- at samp{math.exp/1},
- at samp{math.ln/1},
- at samp{math.log10/1},
- at samp{math.log2/1},
- at samp{math.sin/1},
- at samp{math.cos/1},
- at samp{math.tan/1},
- at samp{math.asin/1},
- at samp{math.acos/1},
- at samp{math.atan/1},
- at samp{math.sinh/1},
- at samp{math.cosh/1},
- at samp{math.tanh/1},
-
- at samp{string.length/2}.
-
- at node Aditi pragma declarations
- at subsection Aditi pragma declarations
-
-The following pragma declarations control compilation of Aditi predicates.
-
- at example
-:- pragma aditi(@var{Name}/@var{Arity}).
- at end example
-
-This predicate should be evaluated using the Aditi deductive database.
-
- at c `pragma base_relation' is intended to be used only in files automatically
- at c generated by the Aditi system, so this documentation should disappear
- at c eventually.
- at example
-:- pragma base_relation(@var{Name}/@var{Arity}).
- at end example
-
-This predicate is an Aditi base relation.
-
- at example
-:- pragma supp_magic(@var{Name}/@var{Arity}).
-:- pragma context(@var{Name}/@var{Arity}).
- at end example
-
-Perform either the supplementary magic sets or context transformations.
-One of these transformations must be performed on every Aditi predicate.
- at samp{supp_magic} is the default.
-There are restrictions on predicates to which the context transformation
-can be applied; these are described in @cite{Right-, left-, and multi-linear
-rule transformations that maintain context information.} @xref{[6]}.
-
- at example
-:- pragma naive(@var{Name}/@var{Arity}).
-:- pragma psn(@var{Name}/@var{Arity}).
- at end example
-
-Specify naive or predicate semi-naive evaluation (@pxref{Aditi glossary})
-for the predicate.
- at samp{psn} is the default.
-
- at example
-:- pragma aditi_memo(@var{Name}/@var{Arity}).
-:- pragma aditi_no_memo(@var{Name}/@var{Arity}).
- at end example
-
-The Aditi deductive database can store the results of procedures within
-a transaction to avoid unnecessary recomputations. This is unrelated to
-the type of memoing described in @ref{Tabled evaluation}.
- at samp{aditi_no_memo} is the default.
-Memoing is not yet implemented, so any @samp{pragma aditi_memo}
-declarations will be ignored.
-
- at example
-:- pragma owner(@var{Name}/@var{Arity}, @var{UserName}).
- at end example
-
-The predicate is owned by the named user. A predicate in the database
-is identified by owner, module name, predicate name and arity. The owner
-field is used for security checks. If no @samp{pragma owner}
-declaration is given, the owner is taken from the @samp{--aditi-user}
-option, which defaults to the value of the environment variable @samp{USER},
-or ``guest'' if that is not set.
-
- at c `pragma aditi_index' is intended to be used only in files automatically
- at c generated by the Aditi system, so this documentation should disappear
- at c eventually.
- at example
-:- pragma aditi_index(@var{Name}/@var{Arity}, @var{IndexType}, @var{Attributes}).
- at end example
-
-The base relation has the given B-tree index. B-tree indexes allow efficient
-retrieval of a tuple or range of tuples from a base relation.
- at samp{@var{IndexType}} must be one of @samp{unique_B_tree} or
- at samp{non_unique_B_tree}. @samp{@var{Attributes}} is a list of argument
-numbers (argument numbers are counted from one).
-
- at node Aditi update syntax
- at subsection Aditi update syntax
-
-The Melbourne Mercury compiler provides special syntax to specify updates
-of Aditi base relations.
-
-Note: Only error checking is implemented for Aditi updates --- no code is
-generated yet.
-
- at menu
-* Aditi update notes::
-* Insertion and deletion::
-* Bulk insertion and deletion::
-* Modification::
- at end menu
-
- at node Aditi update notes
- at subsubsection Aditi update notes
-
-All Aditi update goals have determinism @samp{det}.
-
-There must be a @w{@samp{pragma base_relation}} declaration for
-any relation to be updated.
-
-It is currently up to the application to ensure that any modifications
-do not violate the determinism of a base relation. If any modification
-does violate the determinism of a base relation, then the behaviour
-is undefined. However, updates of relations with unique B-tree indexes
-are checked to ensure that a key is not given multiple values. The transaction
-will abort if this occurs.
-
-Predicate and function names in Aditi update goals may be module qualified.
-
-The examples make use of the following declarations:
-
- at example
-:- pred p(aditi.state::aditi_mui, int::out, int::out) is nondet.
-:- pragma base_relation(p/3).
-
-:- func f(aditi.state::aditi_mui, int::out) = (int::out) is nondet.
-:- pragma base_relation(f/2).
-
-:- pred ancestor(aditi.state::aditi_mui, int::out, int::out) is nondet.
-:- pragma aditi(ancestor/3).
- at end example
-
- at node Insertion and deletion
- at subsubsection Insertion and deletion
-
- at example
-aditi_insert(@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{}), @var{DB0}, @var{DB}).
-
-aditi_insert(@var{FuncName}(@var{Arg1}, @var{Arg2}, @dots{}) = @var{RetVal}, @var{DB0}, @var{DB}).
- at end example
-
- at sp 1
-
-Insert the specified tuple into a relation.
-
- at sp 1
-
- at example
-aditi_delete(@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{}), @var{DB0}, @var{DB}).
-
-aditi_delete(@var{FuncName}(@var{Arg1}, @var{Arg2}, @dots{}) = @var{RetVal}, @var{DB0}, @var{DB}).
- at end example
-
- at sp 1
-
-Delete the specified tuple from a relation.
-
- at sp 1
-
- at itemize @bullet
- at item
- at samp{@var{PredName}} must be the name of a predicate.
-
- at item
- at samp{@var{FuncName}} must be the name of a function.
-
- at item
- at samp{@var{Arg1}}, @samp{@var{Arg2}}, @dots{} and @samp{@var{RetVal}}
-must be data-terms.
-
-The tuple to be inserted must have the same type signature as the relation
-being inserted into. All the arguments of the tuple (including the return value
-of a function) have mode @samp{in}, except the @samp{aditi.state} argument
-which has mode @samp{unused}.
-
- at item
- at samp{@var{DB0}} and @samp{@var{DB}} must be data-terms of type
- at samp{aditi.state}. They have mode @w{@samp{aditi_di, aditi_uo}}.
- at end itemize
-
- at sp 1
-
-Note that @w{@samp{@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{})}}
-in an @samp{aditi_insert} or @samp{aditi_delete} goal is not a
-higher-order term.
- at w{@samp{Pred = p(DB0, X, Y), aditi_insert(Pred, DB0, DB)}}
-is a syntax error.
-
- at sp 1
-
-Examples:
-
- at example
-insert_example_1(DB0, DB) :-
-        aditi_insert(p(_, 1, 2), DB0, DB).
-
-insert_example_2(DB0, DB) :-
-        aditi_insert(f(_, 1) = 2, DB0, DB).
-
-delete_example_1(DB0, DB) :-
-        aditi_delete(p(_, 1, 2), DB0, DB).
-
-delete_example_2(DB0, DB) :-
-        aditi_delete(f(_, 1) = 2, DB0, DB).
-
- at end example
-
- at node Bulk insertion and deletion
- at subsubsection Bulk insertion and deletion
-
- at example
-aditi_bulk_insert((@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{}) :- @var{Goal}), @var{DB0}, @var{DB}).
-
-aditi_bulk_insert((@var{FuncName}(@var{Arg1}, @var{Arg2}, @dots{}) = @var{RetVal} :- @var{Goal}), @var{DB0}, @var{DB}).
-
-aditi_bulk_insert(@var{PredOrFunc} @var{Name}/@var{Arity}, @var{Closure}, @var{DB0}, @var{DB}).
- at end example
-
- at sp 1
-
-Insert all solutions of @samp{@var{Goal}} or @samp{@var{Closure}} into
-the named relation.
-
- at sp 1
-
- at example
-aditi_bulk_delete((@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{}) :- @var{Goal}), @var{DB0}, @var{DB}).
-
-aditi_bulk_delete((@var{FuncName}(@var{Arg1}, @var{Arg2}, @dots{}) = @var{RetVal} :- @var{Goal}), @var{DB0}, @var{DB}).
-
-aditi_bulk_delete(@var{PredOrFunc} @var{Name}/@var{Arity}, @var{Closure}, @var{DB0}, @var{DB}).
- at end example
-
- at sp 1
-
-Delete all solutions of @samp{@var{Goal}} or @samp{@var{Closure}}
-from the named relation.
-
- at sp 1
-
- at itemize @bullet
- at item
- at samp{@var{PredOrFunc}} must be either @samp{pred} or @samp{func}.
-If it is @samp{pred}, then @samp{@var{Name}} must be the name of
-a predicate, and if it is @samp{func}, then @samp{@var{Name}}
-must be the name of a function.
-
- at item
- at samp{@var{Arity}} must be the arity of the predicate or function
-being updated.
-
- at item
- at samp{@var{Goal}} must be a Mercury goal.
-
- at item
- at samp{@var{Closure}} must be a data-term which has a higher-order type with
-the same type signature as the base relation being updated.
-
-The @samp{aditi.state} argument of @samp{@var{Closure}} must have
-mode @samp{aditi_mui}. All other arguments must have mode @samp{out}.
-The determinism of @samp{@var{Closure}} must be @samp{nondet}.
-
- at samp{@var{Closure}} must be evaluable bottom-up by the Aditi
-system --- the predicate or function passed must have a
- at w{@samp{pragma aditi}} declaration. Lambda expressions can be
-marked as evaluable by Aditi using an @samp{aditi_bottom_up} annotation
-on the lambda expression.
-
- at item
- at samp{@var{DB0}} and @samp{@var{DB}} must be data-terms of type
- at samp{aditi.state}. They have mode @w{@samp{aditi_di, aditi_uo}}.
- at end itemize
-
- at sp 1
-
-The form
-
- at example
-aditi_bulk_insert((@var{PredName}(@var{DB1}, @var{Arg2}, @dots{}) :- @var{Goal}), @var{DB0}, @var{DB}).
- at end example
-
- at noindent
-is equivalent to
-
- at example
-Closure = (aditi_bottom_up
-        pred(@var{DB1}::aditi_mui, @var{Arg2}::out, @dots{}) is nondet :- @var{Goal}),
-aditi_bulk_insert(@var{PredOrFunc} @var{Name}/@var{Arity}, @var{Closure}, @var{DB0}, @var{DB}).
- at end example
-
- at noindent
-and likewise for the function version.  For instance, the examples
-bulk_insert_example_1, bulk_insert_example_2 and bulk_insert_example_3
-below are all equivalent.
-
-Similarly, the form
-
- at example
-aditi_bulk_delete((@var{PredName}(@var{Arg1}, @var{Arg2}, @dots{}) :- @var{Goal}), @var{DB0}, @var{DB}).
- at end example
-
- at noindent
-is equivalent to
-
- at example
-DeleteClosure = (aditi_bottom_up
-        pred(@var{DB1}::aditi_mui, @var{Arg2}::out, @dots{}) is nondet :-
-        @var{PredName}(@var{DB1}, @var{Arg2}, @dots{}),
-        @var{Goal}
-),
-aditi_bulk_delete(@var{PredOrFunc} @var{Name}/@var{Arity}, @var{Closure}, @var{DB0}, @var{DB}).
- at end example
-
- at noindent
-and likewise for the function version.  For instance
-bulk_delete_example_1 and bulk_delete_example_2 below are equivalent.
-
- at sp 2
-
-Examples:
-
- at example
-bulk_insert_example_1(DB0, DB) :-
-        aditi_bulk_insert(p(DB1, X, Y) :- ancestor(DB1, X, Y), DB0, DB).
-
-bulk_insert_example_2(DB0, DB) :-
-        aditi_bulk_insert(pred p/3, ancestor, DB0, DB).
-
-bulk_insert_example_3(DB0, DB) :-
-        InsertP = (aditi_bottom_up
-                pred(DB1::aditi_mui, X::out, Y::out) is nondet :-
-                        ancestor(DB1, X, Y)
-                ),
-        aditi_bulk_insert(pred p/3, InsertP, DB0, DB).
-
-bulk_delete_example_1 -->
-        aditi_bulk_delete(
-                (p(DB1, X, _) :-
-                        X > 1,
-                        X < 5
-                )).
-
-bulk_delete_example_2(DB0, DB) :-
-        DeleteP = (aditi_bottom_up
-                pred(DB1::aditi_mui, X::out, Y::out) is nondet :-
-                        p(DB1, X, Y),
-                        X > 1,
-                        X < 5
-                ),
-        aditi_bulk_delete(DeleteP, DB0, DB).
-
-bulk_delete_example_3(DB0, DB) :-
-        aditi_bulk_delete(f(DB1, X) = _Y :- X = 1, DB0, DB).
-
-bulk_delete_example_4(DB0, DB) :-
-        DeleteQ = (aditi_bottom_up
-                func(DB1::aditi_mui, X::out) = (Y::out) is nondet :-
-                        q(DB1, X) = Y,
-                        X > 1,
-                        X < 5
-                ),
-        aditi_bulk_delete(func f/2, DeleteQ, DB0, DB).
- at end example
-
-The type of @samp{InsertP} is
- at w{@samp{aditi_bottom_up pred(aditi.state, int, int)}}.
-Its inst is @w{@samp{pred(aditi_mui, out, out) is nondet}},
-as for a normal lambda expression.
-
-Note that in @samp{bulk_delete_example_1} the extra set of parentheses around
-the goal are needed, otherwise the second goal in the conjunction in the
-deletion goal would be parsed as an extra argument
-of the @samp{aditi_bulk_delete} call, resulting in a syntax error.
-
- at node Modification
- at subsubsection Modification
-
- at example
-aditi_bulk_modify(
-        (@var{PredName}(@var{OldArg1}, @var{OldArg2}, @dots{}) ==>
-        @var{PredName}(@var{NewArg1}, @var{NewArg2}, @dots{}) :-
-                @var{Goal}
-        ),
-        @var{DB0}, @var{DB}).
-
-aditi_bulk_modify(
-        ((@var{FuncName}(@var{OldArg1}, @var{OldArg2}, @dots{}) = @var{OldRetVal}) ==>
-        (@var{FuncName}(@var{NewArg1}, @var{NewArg2}, @dots{}) = @var{NewRetVal}) :-
-                @var{Goal}
-        ),
-        @var{DB0}, @var{DB}).
-
-aditi_bulk_modify(@var{PredOrFunc} @var{PredName}/@var{Arity}, @var{Closure}, @var{DB0}, @var{DB}).
- at end example
-
- at sp 1
-
-Modify tuples for which @samp{@var{Goal}} or @samp{@var{Closure}} succeeds,
-leaving any other tuples unchanged.
-
- at sp 1
-
- at itemize @bullet
- at item
- at samp{@var{PredName}} must be the name of a predicate.
-
- at item
- at samp{@var{FuncName}} must be the name of a function.
-
- at item
- at samp{@var{PredOrFunc}} must be either @samp{pred} or @samp{func}.
-If it is @samp{pred}, then @samp{@var{Name}} must be the name of
-a predicate, and if it is @samp{func}, then @samp{@var{Name}}
-must be the name of a function.
-
- at item
- at samp{@var{Arity}} must be the arity of the predicate or function
-being updated.
-
- at item
- at samp{@var{OldArg1}}, @samp{@var{OldArg2}}, @dots{}, @samp{@var{OldRetVal}},
- at samp{@var{NewArg1}}, @samp{@var{NewArg2}}, @dots{}, and @samp{@var{NewRetVal}}
-must be data-terms.
-
-The original tuple is given by the first set of arguments, which
-have mode @samp{out}. The updated tuple is given by the second set
-of arguments, which have mode @samp{out}. The @samp{aditi.state}
-argument for the original tuple has mode @samp{aditi_mui}.
-The @samp{aditi.state} argument for the updated tuple has mode
- at samp{unused}.
-
-The argument types of each tuple must match the argument types
-of the base relation being modified.
-
- at item
- at samp{@var{Goal}} must be a Mercury goal.
-
- at item
- at samp{@var{Closure}} must be a data-term which has a higher-order type.
-
-When modifying a predicate with type declaration
- at w{@samp{:- pred p(aditi.state, @var{Type1}, @dots{})}}, @samp{@var{Closure}}
-must have type
- at samp{aditi_bottom_up pred(aditi.state, @var{Type1}, @dots{}, aditi.state, @var{Type1}, @dots{})},
-and inst
- at w{@samp{pred(aditi_mui, out, @dots{}, unused, out, @dots{}) is nondet}}.
-
-When modifying a function with type declaration
- at w{@samp{:- func p(aditi.state, @var{Type1}, @dots{}) = @var{Type2}}},
- at samp{@var{Closure}} must have type
- at samp{aditi_bottom_up pred(aditi.state, @var{Type1}, @dots{}, @var{Type2}, aditi.state, @var{Type1}, @dots{}, @var{Type2})},
-and inst
- at w{@samp{pred(aditi_mui, out, @dots{}, out, unused, out, @dots{}, out) is nondet}}.
-
-It is an error for the closure to return a solution for which the arguments
-corresponding to the original tuple do not match a tuple in the relation
-being modified.
-
- at item
- at samp{@var{DB0}} and @samp{@var{DB}} must be data-terms of type
- at samp{aditi.state}. They have mode @w{@samp{aditi_di, aditi_uo}}.
- at end itemize
-
- at sp 2
-
-The forms using @samp{==>} can be considered as syntactic sugar for the
-form using @var{PredOrFunc} @var{PredName}/@var{Arity}:
-
- at example
-aditi_bulk_modify(
-        (@var{PredName}(@var{DB1}, @var{OldArg1}, @var{OldArg2}, @dots{}) ==>
-        @var{PredName}(@var{_DB}, @var{NewArg1}, @var{NewArg2}, @dots{}) :-
-                @var{Goal}
-        ),
-        @var{DB0}, @var{DB}).
- at end example
-
- at noindent
-is equivalent to
-
- at example
-ModifyClosure =
-        (aditi_bottom_up pred(@var{DB1}::aditi_mui, @var{OldArg1}::out, @var{OldArg2}::out, @dots{},
-                @var{_DB}::unused, @var{NewArg1}::out, @var{NewArg2}::out, @dots{}) is nondet :-
-                @var{PredName}(@var{DB1}, @var{OldArg1}, @var{OldArg2}, @dots{}),
-                @var{Goal}
-        ),
-aditi_bulk_modify(pred @var{PredName}/@var{PredArity}, ModifyClosure, DB0, DB).
- at end example
-
- at noindent
-and likewise for the function version.
-
-The bulk modify operation
-
- at example
-aditi_bulk_modify(pred p/3, Closure, DB0, DB).
- at end example
-
- at noindent
-is almost equivalent to a bulk delete followed by a bulk insert:
-
- at example
-DeleteClosure =
-        (aditi_bottom_up pred(DB1::aditi_mui, X1::out, Y1::out) is nondet :-
-                Closure(DB1, X1, Y1, _, _)
-        ),
-InsertClosure =
-        (aditi_bottom_up pred(DB1::aditi_mui, X2::out, Y2::out) is nondet :-
-                Closure(DB1, _, _, X2, Y2)
-        ),
-aditi_bulk_delete(pred p/3, DeleteClosure, DB0, DB1),
-aditi_bulk_insert(pred p/3, InsertClosure, DB1, DB).
- at end example
-
- at noindent
-However, they are not quite equivalent,
-because in the bulk modify operation @var{InsertClosure}
-is executed using the contents of @samp{p/3} before the deletion
-is applied.
-
- at sp 2
-
-Examples:
-
- at example
-bulk_modify_example_1(DB0, DB) :-
-        aditi_bulk_modify(
-                (p(DB1, X, Y0) ==> p(_DB, X, Y) :-
-                        X > 2,
-                        X < 5,
-                        Y = Y0 + 1
-                ), DB0, DB).
-
-bulk_modify_example_2(DB0, DB) :-
-        aditi_bulk_modify(
-                (f(_DB0, X) = Y0 ==> f(_DB, X) = Y :-
-                        X > 2, X < 5, Y = Y0 + 1
-                ), DB0, DB).
-
-bulk_modify_example_3(DB0, DB) :-
-        ModifyP = (aditi_bottom_up pred(DB1::aditi_mui, X::in, Y0::in,
-                        _::unused, X::out, Y::out) is nondet :-
-                    p(DB1, X, Y0),
-                    X > 2,
-                    X < 5,
-                    Y = Y0 + 1
-                 ),
-        aditi_bulk_modify(pred p/3, ModifyP, DB0, DB).
-
-bulk_modify_example_4(DB0, DB) :-
-        ModifyF = (aditi_bottom_up pred(DB1::aditi_mui, X::in, Y0::in,
-                        _::unused, X::out, Y::out) is nondet :-
-                    f(DB1, X) = Y0,
-                    X > 2, X < 5, Y = Y0 + 1
-                 ),
-        aditi_bulk_modify(func f/2, ModifyQ, DB0, DB).
-
-bulk_modify_example_5 -->
-        aditi_bulk_modify(
-                (p(_DB0, X, Y0) ==> p(_DB, X, Y) :-
-                        X > 2, X < 5, Y = Y0 + 1
-                )).
- at end example
-
-Note that in @samp{bulk_modify_example_5} the extra set of parentheses around
-the goal are needed, otherwise the second and third goals in
-the conjunction in the modification goal would be parsed as extra arguments
-of the @samp{aditi_bulk_modify} call, resulting in a syntax error.
-
-The type of @samp{ModifyP} is
- at w{@samp{aditi_bottom_up pred(aditi.state, int, int, aditi.state, int, int)}}.
-Its inst is @w{@samp{pred(aditi_mui, out, out, unused, out, out) is nondet}},
-as for a normal lambda expression.
-
- at node Aditi glossary
- at subsection Aditi glossary
-
- at table @asis
-
- at item Aditi-RL
-Aditi Relational Language is used by the Aditi system to execute queries.
-The basic instructions in Aditi-RL are relational database operations such as
- at samp{join}, @samp{select} and @samp{project}.
-
- at item aggregate
-Aggregates are used to compute a value such as a sum over all the solutions
-for a predicate. Aggregates can be computed over Aditi predicates using
- at samp{aditi.aggregate_compute_initial} defined in
- at file{$ADITI_HOME/doc/aditi.m} in the Aditi distribution.
-
- at item base relation
-A base relation is a predicate consisting of a set of facts
-stored in a database. There must be no clauses for a base relation.
-
- at item derived relation
-A derived relation is an Aditi predicate for which there are clauses.
-Derived relations are compiled to Aditi-RL for execution by an Aditi database.
-
- at item predicate semi-naive evaluation
-When a recursive predicate is called, the Aditi system produces the set of all
-solutions using fixed point iteration. The set of solutions is initialised
-to those tuples which can be derived using the non-recursive rules of the
-predicate. In each iteration, new tuples are derived for the predicate using
-the recursive rules for the predicate and the tuples derived in previous
-iterations. Evaluation finishes when no new tuples are generated.
-Predicate semi-naive evaluation (@pxref{[8]}) is a method of evaluating
-recursive predicates which uses just the new tuples in each iteration
-where possible. This improves efficiency by reducing the size of joins.
-
- at item schema
-A schema is a representation of the types of the attributes of a relation.
-
- at item stratification
-A program is stratified if no predicate can call itself through a negation
-or an aggregate.
-
- at item transaction
-A transaction is a database operation which is executed atomically. If
-part of a transaction fails, the database reverts to its original state
-before the transaction. For details on how transactions are implemented
-in Mercury, see @cite{Database transactions in a purely declarative logic
-programming language} @ref{[7]} and @file{$ADITI_HOME/doc/aditi.m} in the
-Aditi distribution.
-
- at end table
-
- at end ifset
- at c aditi
-
 @c XXX The `reserved tag' pragma is not documented because it is intended to
 @c     be used with `any' insts, which are themselves not yet documented.
 @c     Also, it is a quite low-level facility, and very
@@ -10152,17 +9387,6 @@
 * [4]::         Sagonas, @cite{The SLG-WAM: A Search-Efficient Engine
                 for Well-Founded Evaluation of Normal Logic Programs}.
 * [5]::         Demoen and Sagonas, @cite{CAT: the copying approach to tabling}.
- at ifset aditi
-* [6]::         Kemp, Ramamohanarao and Somogyi,
-                @cite{Right-, left-, and multi-linear rule transformations
-                that maintain context information}.
-* [7]::         Kemp, Conway, Harris, Henderson, Ramamohanarao and Somogyi
-                @cite{Database transactions in a purely declarative
-                logic programming language}.
-* [8]::         Ramakrishnan, Srivistava and Sudarshan,
-                @cite{Rule ordering in bottom-up fixpoint evaluation
-                of logic programs}.
- at end ifset
 @end menu

 @node [1]
@@ -10201,36 +9425,4 @@
 submitted for publication,
 Katholieke Universiteit Leuven, 1998.

- at ifset aditi
- at node [6]
- at unnumberedsec [6]
-David B. Kemp and Kotagiri Ramamohanarao and Zoltan Somogyi.
- at cite{Right-, left-, and multi-linear rule transformations that maintain
-context information},
-The Proceedings of the Sixteenth Conference on Very Large Databases, pages
-380--391, August 1990.
-Available from <http://www.cs.mu.oz.au/mercury/papers/tr90-2.ps.gz>.
-
- at node [7]
- at unnumberedsec [7]
-
-David B. Kemp, Thomas Conway, Evan Harris, Fergus Henderson,
-Kotagiri Ramamohanarao and Zoltan Somogyi,
- at cite{Database transactions in a purely declarative
-logic programming language},
-Technical Report 96/45, Department of Computer Science,
-University of Melbourne, December 1996,
-Available from <http://www.cs.mu.OZ.AU/publications/tr_db/mu_96_45.ps.gz>.
-
- at node [8]
- at unnumberedsec [8]
-
-R. Ramakrishnan, D. Srivistava and S. Sudarshan,
- at cite{Rule ordering in bottom-up fixpoint evaluation of logic programs}.
-In @cite{Proceedings of the Sixteenth International Conference on
-Very Large Data Bases}, page 359--371, August 1990.
-
- at end ifset
- at c aditi
-
 @bye
Index: doc/user_guide.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/user_guide.texi,v
retrieving revision 1.467
diff -u -r1.467 user_guide.texi
--- doc/user_guide.texi	6 Feb 2006 05:39:45 -0000	1.467
+++ doc/user_guide.texi	24 Feb 2006 05:47:14 -0000
@@ -7,9 +7,6 @@
 * Mercury User's Guide: (mercury_user_guide).  The Mercury User's Guide.
 @end direntry

- at c Uncomment the line below to enable documentation of the Aditi interface.
- at set aditi
-
 @c @smallbook
 @c @cropmarks
 @finalout
@@ -114,8 +111,6 @@
 * Running::         Execution of programs built with the Mercury compiler.
 * Using Mmake::     ``Mercury Make'', a tool for building Mercury programs.
 * Libraries::       Creating and using libraries of Mercury modules.
-* Using Aditi::     Executing Mercury predicates using the Aditi
-                    deductive database.
 * Debugging::       The Mercury debugger @samp{mdb}.
 * Profiling::       Analyzing the performance of Mercury programs.
 * Invocation::      List of options for the Mercury compiler.
@@ -241,11 +236,6 @@
 for the .NET Common Language Runtime.
 @c XXX mention .dll and .exe?

- at ifset aditi
-Files ending in @file{.rlo} are Aditi-RL bytecode files, which are
-executed by the Aditi deductive database system (@pxref{Using Aditi}).
- at end ifset
-
 @c ----------------------------------------------------------------------------

 @node Using mmc
@@ -577,9 +567,6 @@
 Specifically, this will remove all the @samp{.c}, @samp{.s}, @samp{.o},
 @samp{.pic_o}, @samp{.prof}, @samp{.no}, @samp{.ql}, @samp{.used},
 @samp{.mih},
- at ifset aditi
- at samp{.derived_schema}, @samp{.base_schema}
- at end ifset
 and @samp{.err} files
 belonging to the named @var{main-module} or its imported modules.
 Use this target whenever you wish to change compilation model
@@ -595,9 +582,6 @@
 @samp{.int3}, @samp{.opt}, @samp{.trans_opt},
 @samp{.date}, @samp{.date0}, @samp{.date3}, @samp{.optdate},
 @samp{.trans_opt_date},
- at ifset aditi
- at samp{.rlo},
- at end ifset
 @samp{.mh} and @samp{.d} files
 belonging to one of the modules of the program,
 and also the various possible executables, libraries and dependency files
@@ -4568,42 +4552,6 @@

 @c ----------------------------------------------------------------------------

- at ifset aditi
- at node Using Aditi
- at chapter Using Aditi
- at cindex Aditi
- at cindex database, deductive
- at cindex deductive database
-
-The Mercury compiler allows compilation of predicates for execution
-using the Aditi2 deductive database system. There are several sources
-of useful information:
-
- at itemize @bullet
- at item
-the ``Aditi deductive database interface'' section of the
-``Implementation-dependent extensions'' chapter in the
-Mercury Language Reference Manual
- at item
-the Aditi web site at <http://www.cs.mu.oz.au/aditi>
- at item
-the documentation supplied with Aditi, especially the file
- at file{$ADITI_HOME/doc/aditi.m}
- at item
-the samples provided with the Aditi distribution in @file{$ADITI_HOME/demos}
- at end itemize
-
-As an alternative to compiling stand-alone programs, you can execute
-queries using the Aditi query shell.
-
-The Aditi interface library is installed as part of the Aditi
-installation process. To use the Aditi library in your programs, use
-the Mmakefile in @file{$ADITI_HOME/demos/transactions} as a template.
-
- at end ifset
-
- at c ----------------------------------------------------------------------------
-
 @node Profiling
 @chapter Profiling
 @pindex mprof
@@ -5429,21 +5377,6 @@
 Output detailed debugging traces of the partial
 deduction and deforestation process.

- at ifset aditi
- at sp 1
- at item --debug-rl-gen
- at findex --debug-rl-gen
-Output detailed debugging traces of Aditi-RL code generation
-(@pxref{Using Aditi}).
-
- at sp 1
- at item --debug-rl-opt
- at findex --debug-rl-opt
-Output detailed debugging traces of Aditi-RL optimization
-(@pxref{Using Aditi}).
- at end ifset
- at c aditi
-
 @sp 1
 @item --debug-liveness <n>
 @findex --debug-liveness
@@ -5617,15 +5550,6 @@
 and object code in @file{@var{module}.o}
 but do not attempt to link the named modules.

- at ifset aditi
- at sp 1
- at item --aditi-only
- at findex --aditi-only
-Write Aditi-RL bytecode to @file{@var{module}.rlo} and do not compile to C
-(@pxref{Using Aditi}).
- at end ifset
- at c aditi
-
 @sp 1
 @item --output-grade-string
 @findex --output-grade-string
@@ -5850,33 +5774,6 @@
 due to background load or clock granularity.
 This option is ignored unless --benchmark-modes is also given.

- at ifset aditi
- at sp 1
- at item --dump-rl
- at findex --dump-rl
-Output a human readable form of the internal compiler representation
-of the generated Aditi-RL code to @file{@var{module}.rl_dump}
-(@pxref{Using Aditi}).
-
- at sp 1
- at item --dump-rl-bytecode
- at findex --dump-rl-bytecode
-Output a human readable representation of the generated Aditi-RL
-bytecodes @file{@var{module}.rla}. Aditi-RL bytecodes are directly
-executed by the Aditi system (@pxref{Using Aditi}).
-
- at sp 1
- at item --generate-schemas
- at findex --generate-schemas
-Output schema strings for Aditi base relations to
- at file{@var{module}.base_schema} and for Aditi derived
-relations to @file{@var{module}.derived_schema}. A schema
-string is a representation of the types of the attributes
-of a relation (@pxref{Using Aditi}).
-
- at end ifset
- at c aditi
-
 @end table

 @node Language semantics options
@@ -6553,24 +6450,6 @@
 procedure is treated as though it has a @samp{not_thread_safe}
 attribute.  The default is @samp{no}.

- at ifset aditi
- at sp 1
- at item --aditi
- at findex --aditi
-Enable Aditi compilation.  You need to enable this option if you
-are making use of the Aditi deductive database interface (@pxref{Using Aditi}).
-
- at c --aditi-calls-mercury is not fully implemented.
- at ignore
- at sp 1
- at item --aditi-calls-mercury
- at findex --aditi-calls-mercury
-Enable calling ordinary Mercury code from Aditi.
- at end ignore
-
- at end ifset
- at c aditi
-
 @end table

 @node Developer compilation model options
@@ -6798,9 +6677,6 @@
 * Medium-level (HLDS -> LLDS) optimization options::
 * Low-level (LLDS -> LLDS) optimization options::
 * Output-level (LLDS -> C) optimization options::
- at ifset aditi
-* Aditi-RL optimization options::
- at end ifset
 @end menu

 @node Overall optimization options
@@ -7497,43 +7373,6 @@

 @end table

- at ifset aditi
- at node Aditi-RL optimization options
- at subsection Aditi-RL optimization options
-
-These optimizations are applied to the Aditi-RL code produced
-for predicates with @samp{:- pragma aditi(@dots{})} declarations
-(@pxref{Using Aditi}).
-
- at table @code
- at item --optimize-rl
- at findex --optimize-rl
-Enable the optimizations of Aditi-RL procedures described below.
-
- at sp 1
- at item --optimize-rl-cse
- at findex --optimize-rl-cse
-Optimize common subexpressions in Aditi-RL procedures.
-
- at sp 1
- at item --optimize-rl-invariants
- at findex --optimize-rl-invariants
-Optimize loop invariants in Aditi-RL procedures.
-
- at sp 1
- at item --optimize-rl-index
- at findex --optimize-rl-index
-Use indexing to optimize access to relations in Aditi-RL procedures.
-
- at sp 1
- at item --detect-rl-streams
- at findex --detect-rl-streams
-Detect cases where intermediate results in Aditi-RL procedures
-do not need to be materialised.
- at end table
- at end ifset
- at c aditi
-
 @node Build system options
 @section Build system options
 @table @code
@@ -7730,19 +7569,6 @@
 or user to interactively compile several modules without the overhead of
 process creation for each one.)

- at ifset aditi
- at sp 1
- at item --aditi-user
- at findex --aditi-user
-Specify the Aditi login of the owner of the predicates in any Aditi RL
-files produced if no @samp{:- pragma owner(@dots{})} declaration is given.
-The owner field is used along with module, name and arity to identify
-predicates, and is also used for security checks. Defaults to the value
-of the @samp{USER} environment variable. If @samp{USER} is not set,
- at samp{--aditi-user} defaults to the string ``guest''.
-
- at end ifset
- at c aditi
 @end table

 @node Target code compilation options
Index: extras/aditi/LIMITATIONS
===================================================================
RCS file: extras/aditi/LIMITATIONS
diff -N extras/aditi/LIMITATIONS
--- extras/aditi/LIMITATIONS	26 May 2000 08:38:14 -0000	1.3
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,18 +0,0 @@
-The Aditi interface and Aditi itself are still in development.
-
-* aditi__state arguments must currently be ground, not unique. This will
-  be fixed when the alias tracking mode analyser is released. Use the
-  mode aditi_mui defined in aditi.m instead for now.
-
-* Only calls to local, non-recursive Mercury predicates are allowed
-  from Aditi procedures (they are generated inline). The code
-  generator aborts if recursive predicates are called. Stick
-  to builtins in join conditions for now.
-  Non-deterministic predicates will probably not work.
-
-* Abstract data types are not supported.
-
-* Existential types are not supported.
-
-* Types with user-defined equality predicates are not supported.
-
Index: extras/aditi/Mmakefile
===================================================================
RCS file: extras/aditi/Mmakefile
diff -N extras/aditi/Mmakefile
--- extras/aditi/Mmakefile	18 Mar 2003 02:43:49 -0000	1.8
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,67 +0,0 @@
-#-----------------------------------------------------------------------------#
-# Copyright (C) 1998-2000, 2003 The University of Melbourne.
-# This file may only be copied under the terms of the GNU Library General
-# Public License - see the file COPYING.LIB in the Mercury distribution.
-#-----------------------------------------------------------------------------#
-# Mmakefile for the Mercury->Aditi interface.
-#
-# Environment variables (must be set externally):
-# MAKEFILE_ADITI - makefile containing variables used when compiling
-# 		a program for Aditi.
-#
-#-----------------------------------------------------------------------------#
-#
-# Defines $(ADITI_API_EXTRA_CFLAGS), $(ADITI_API_EXTRA_LIBS) and
-# $(ADITI_API_EXTRA_LDFLAGS).
-include $(MAKEFILE_ADITI)
-
-# The Aditi interface only works with conservative garbage collection.
-# This is equivalent to
-# LIBGRADES-aditi = $(filter %.gc%,$(LIBGRADES))
-# but gmake patterns can't include multiple wildcards.
-LIBGRADES-aditi = \
-	$(shell echo $(LIBGRADES) | tr ' ' '\n' | grep '.gc')
-
-#----------------------------------------------------------------------------#
-
-# The --Wno-strict-prototypes is to shut up warnings about prototypes
-# without argument types in a header file generated by rpcgen.
-# To get more debugging messages, add "-DMR_DEBUG_ON" to CFLAGS.
-CFLAGS = $(ADITI_API_EXTRA_CFLAGS) -Wno-strict-prototypes
-
-# The RPC headers on Linux don't like it when `-ansi' is passed to gcc.
-MGNUCFLAGS = --no-ansi
-
-MLFLAGS = $(ADITI_API_EXTRA_LDFLAGS) --aditi
-MLLIBS = $(ADITI_API_EXTRA_LIBS)
-
-MCFLAGS = --no-infer-all --aditi --aditi-user guest
-
-#-----------------------------------------------------------------------------%
-
-MAIN_TARGET = libaditi
-
-.PHONY: depend
-depend: aditi.depend
-	cd tests && $(MMAKE) depend
-
-.PHONY: clean
-clean:
-	cd tests && $(MMAKE) clean
-
-.PHONY: realclean
-realclean:
-	cd tests && $(MMAKE) realclean
-
-.PHONY: tests
-tests:
-	cd tests && $(MMAKE)
-
-.PHONY: check
-check:
-	cd tests && $(MMAKE)
-
-.PHONY: install
-install: libaditi.install
-
-#-----------------------------------------------------------------------------#
Index: extras/aditi/NOBOOTTEST
===================================================================
RCS file: extras/aditi/NOBOOTTEST
diff -N extras/aditi/NOBOOTTEST
Index: extras/aditi/aditi.m
===================================================================
RCS file: extras/aditi/aditi.m
diff -N extras/aditi/aditi.m
--- extras/aditi/aditi.m	9 Feb 2005 12:31:14 -0000	1.19
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,322 +0,0 @@
-%-----------------------------------------------------------------------------%
-% Copyright (C) 1998-2000,2003, 2005 The University of Melbourne.
-% This file may only be copied under the terms of the GNU Library General
-% Public License - see the file COPYING.LIB in the Mercury distribution.
-%-----------------------------------------------------------------------------%
-% File: aditi.m
-% Main author: stayl
-%
-% This module provides an interface to the Aditi deductive database
-% system developed at the University of Melbourne. See the
-% "Aditi deductive database interface" section of the Mercury
-% Language Reference Manual (listed under "Implementation defined pragmas"
-% in the "Pragmas" chapter) for details on how to compile database queries.
-%
-% For information on how to build programs which use this interface,
-% see the example Mmakefile in $ADITI_HOME/demos/transactions.
-%
-%
-% Compilation grade notes (see the section "Compilation model options"
-% in the Mercury User's Guide for more information):
-%
-%	This module requires a compilation grade with conservative garbage
-%	collection. Any grade containing `.gc' in its name, such as
-%	`asm_fast.gc' or `asm_fast.gc.tr', will do.
-%
-% 	When trailing is not being used (the compilation grade does not
-% 	contain `.tr'), resources will sometimes not be cleaned up until
-%	the end of a transaction.
-%	If there is a commit across a nondet database call, or an exception
-%	is thrown, or a database call is retried in the debugger, the output
-%	relation from the call and its cursor will not be cleaned up until the
-%	transaction ends.
-%	It is up to the programmer to decide whether imposing the overhead
-%	of trailing on the rest of the program is worthwhile.
-%
-%	Compilation of this module in a high level C code grade (e.g. `hlc.gc')
-%	is not yet supported.
-%
-%
-% The transaction interface used here is described in
-%	Kemp, Conway, Harris, Henderson, Ramamohanarao and Somogyi,
-% 	"Database transactions in a purely declarative
-%		logic programming language",
-%	In Proceedings of the Fifth International Conference on Database
-%	Systems for Advanced Applications, pp. 283-292.
-%	Melbourne, Australia, 1-4 April, 1997.
-%
-%	This paper is also available as
-%	Technical Report 96/45, Department of Computer Science,
-%	University of Melbourne, December 1996,
-%	<http://www.cs.mu.OZ.AU/publications/tr_db/mu_96_45_cover.ps.gz>
-%	and <http://www.cs.mu.OZ.AU/publications/tr_db/mu_96_45.ps.gz>.
-%
-%-----------------------------------------------------------------------------%
-:- module aditi.
-
-:- interface.
-
-:- import_module io.
-
-:- type aditi__state.
-
-% XXX This will change to unique when the mode system is fully implemented.
-:- inst aditi_unique == ground.
-:- mode aditi_di  == in(aditi_unique).
-:- mode aditi_uo  == out(aditi_unique).
-:- mode aditi_ui  == in(aditi_unique).
-:- mode aditi_mui == in(aditi_unique).
-
-:- type aditi__result(T)
-	--->	ok(T)
-	;	error(aditi__error, string).
-
-:- type aditi__result
-	--->	ok
-	;	error(aditi__error, string).
-
-:- type aditi__error
-	--->	error_creating_client
-	;	invalid_passwd
-	;	too_many_connections
-	;	invalid_ticket
-	;	general_failure
-	;	already_logged_in
-	;	not_logged_in
-	;	not_connected
-	;	not_implemented
-	;	abort
-	;	bad_value
-	;	bad_rl_code
-	;	error_opening_relation
-	;	security_violation
-	;	unique_key_violation
-	;	relation_or_cursor_not_open
-	;	timeout
-	;	determinism_error	% The number of solutions returned
-					% for a procedure did not match
-					% its determinism declaration.
-	;	parse_error_in_tuple	% Aditi returned a tuple
-					% which the Mercury interface
-					% code could not understand.
-	.
-
-:- type aditi__exception
-	--->	aditi__exception(aditi__error, string).
-
-:- type aditi__connection.
-
-	% aditi__connect(Host, User, Passwd, Result).
-	%
-	% Only one connection is allowed per process.
-:- pred aditi__connect(string, string, string,
-		aditi__result(aditi__connection), io__state, io__state).
-:- mode aditi__connect(in, in, in, out, di, uo) is det.
-
-:- pred aditi__disconnect(aditi__connection, aditi__result,
-		io__state, io__state).
-:- mode aditi__disconnect(in, out, di, uo) is det.
-
-:- type aditi__transaction(T) == pred(T, aditi__state, aditi__state).
-:- inst aditi__transaction == (pred(out, aditi_di, aditi_uo) is det).
-
-	% aditi__transaction(Connection, Transaction, Result).
-	%
-	% Start a transaction with the Aditi database referred to by
-	% Connection, call Transaction, returning ok(Result) if the
-	% transaction is not aborted, or error(Error, Msg) if
-	% the transaction fails.
-	%
-	% If Transaction throws an exception, the transaction will
-	% be aborted and the exception will be rethrown to the caller.
-	%
-	% Predicates with `:- pragma aditi' or `:- pragma base_relation'
-	% markers can only be called from within a transaction -- there
-	% is no other way to get an `aditi__state' to pass to them.
-:- pred aditi__transaction(aditi__connection, aditi__transaction(T),
-		aditi__result(T), io__state, io__state).
-:- mode aditi__transaction(in, in(aditi__transaction), out, di, uo) is det.
-
-	% As above, except that it throws an exception if the
-	% transaction is aborted.
-:- pred aditi__transaction_exception(aditi__connection, aditi__transaction(T),
-		T, io__state, io__state).
-:- mode aditi__transaction_exception(in, in(aditi__transaction),
-		out, di, uo) is det.
-
-	% aditi__aggregate_compute_initial(Closure, UpdateAcc,
-	% 		ComputeInitial, Results)
-	%
-	% When called, the query Closure returns the relation to be
-	% aggregated over. This relation must have two attributes,
-	% the first being the attribute to group by. The closure
-	% ComputeInitial computes an initial accumulator for each
-	% group given the first tuple in the group. The closure
-	% UpdateAcc is called for each tuple in each group to
-	% update the accumulator. The outputs are the group-by element
-	% and final accumulator for each group.
-	%
-	% For example, to compute a sum over relation `p/3' where
-	% the first non-aditi__state attribute of `p' is the group-by
-	% attribute:
-	% 	aditi__aggregate_compute_initial(p(DB),
-	%		(pred(_::in, Attr::in, Acc0::in, Acc::out) is det :-
-	%			Acc = Acc0 + Attr),
-	%		(pred(_::in, _::in, 0::out) is det :- true),
-	%		GrpBy, Sum).
-:- pred aditi__aggregate_compute_initial(pred(GrpBy, NonGrpBy),
-		pred(GrpBy, NonGrpBy, Acc, Acc),
-		pred(GrpBy, NonGrpBy, Acc), GrpBy, Acc).
-:- mode aditi__aggregate_compute_initial(pred(out, out) is nondet,
-		pred(in, in, in, out) is det,
-		pred(in, in, out) is det, out, out) is nondet.
-:- mode aditi__aggregate_compute_initial(pred(out, out) is multi,
-		pred(in, in, in, out) is det,
-		pred(in, in, out) is det, out, out) is multi.
-
-/*
-	This should be translated into the equivalent
-	aggregate_compute_initial, but that hasn't been
-	done yet. The main problem is collecting the initial
-	value - it may not be constant.
-
-	Also, it would be nice to provide versions of aditi__aggregate
-	which work over one attribute relations, as in std_util__aggregate.
-
-	% aditi_aggregate_given_initial(Closure, UpdateAcc,
-	% 		InitialAcc, Results)
-	%
-	% Same as aditi__aggregate_compute_initial except the initial
-	% accumulator is supplied, rather than computed from the first
-	% element.
-:- pred aditi__aggregate_given_initial(pred(GrpBy, NonGrpBy),
-		pred(GrpBy, NonGrpBy, Acc, Acc), Acc, GrpBy, Acc).
-:- mode aditi__aggregate_given_initial(pred(out, out) is nondet,
-		pred(in, in, in, out) is det,
-		in, out, out) is nondet.
-*/
-
-%-----------------------------------------------------------------------------%
-:- implementation.
-
-:- interface.
-
-% These are used by aditi_private_builtin.m, but otherwise
-% shouldn't be in the interface.
-:- pragma foreign_type("C", aditi__connection, "MADITI_Connection").
-:- pragma foreign_type("C", aditi__state, "MADITI_State").
-
-:- implementation.
-
-:- import_module bool, char, exception, list, require, std_util, string.
-:- import_module aditi_private_builtin.
-
-%-----------------------------------------------------------------------------%
-
-:- pragma foreign_decl("C",
-"
-#include ""v2_api_without_engine.h""
-
-typedef struct {
-	apiID		connection;
-	apiID		bytecode_transaction;
-} MADITI_Connection;
-
-typedef struct {
-	apiID		connection;
-	apiID		bytecode_transaction;
-	apiID		transaction;
-} MADITI_State;
-").
-
-%-----------------------------------------------------------------------------%
-
-	% These are handled by the RL code generator.
-:- external(aditi__aggregate_compute_initial/5).
-%:- external(aditi__aggregate_given_initial/5).
-
-%-----------------------------------------------------------------------------%
-
-aditi__connect(Host, User, Passwd, Result) -->
-	aditi_private_builtin__connect(Host,
-		User, Passwd, Status, Connection),
-	{ Status = 0 ->
-		Result = ok(Connection)
-	;
-		aditi_private_builtin__error_code(Status, Error, String),
-		Result = error(Error, String)
-	}.
-
-%-----------------------------------------------------------------------------%
-
-aditi__disconnect(Connection, Result) -->
-	aditi_private_builtin__disconnect(Connection, Status),
-	{ Status = 0 ->
-		Result = ok
-	;
-		aditi_private_builtin__error_code(Status, Error, Msg),
-		Result = error(Error, Msg)
-	}.
-
-%-----------------------------------------------------------------------------%
-
-aditi__transaction(Connection, Transaction, TransResult, IO0, IO) :-
-	%
-	% aditi__transaction_2 is cc_multi because of the call to
-	% try_io, but if an Aditi exception occurs, it really
-	% doesn't matter which one we get.
-	%
-	RunTransaction =
-		(pred(ResultAndIO0::out) is cc_multi :-
-			unsafe_promise_unique(IO0, IO1),
-			aditi__transaction_2(Connection, Transaction,
-				Result, IO1, IO2),
-			ResultAndIO0 = Result - IO2
-		),
-	ResultAndIO = promise_only_solution(RunTransaction),
-	ResultAndIO = TransResult - IO3,
-	unsafe_promise_unique(IO3, IO).
-
-:- pred aditi__transaction_2(aditi__connection, aditi__transaction(T),
-		aditi__result(T), io__state, io__state).
-:- mode aditi__transaction_2(in, in(aditi__transaction),
-		out, di, uo) is cc_multi.
-
-aditi__transaction_2(Connection, Transaction, TransResult) -->
-	aditi_private_builtin__start_transaction(Connection, StartResult),
-	(
-		{ StartResult = ok(DB0) },
-		try_io((pred(Result::out, di, uo) is det -->
-			{ Transaction(Result, DB0, DB) },
-			aditi_private_builtin__commit_transaction(DB)
-		    ), TransExceptionResult),
-		(
-			{ TransExceptionResult = succeeded(Results) },
-			{ TransResult = ok(Results) }
-		;
-			{ TransExceptionResult = exception(Exception) },
-			aditi_private_builtin__abort_transaction(DB0),
-			( { univ_to_type(Exception, AditiException) } ->
-				{ AditiException =
-					aditi__exception(ErrorCode, String) },
-				{ TransResult = error(ErrorCode, String) }
-			;
-				{ rethrow(TransExceptionResult) }
-			)
-		)
-	;
-		{ StartResult = error(StartErrorCode, StartMsg) },
-		{ TransResult = error(StartErrorCode, StartMsg) }
-	).
-
-aditi__transaction_exception(Connection, Transaction, Result) -->
-	aditi__transaction(Connection, Transaction, TransResult),
-	{
-		TransResult = ok(Result)
-	;
-		TransResult = error(ErrorCode, String),
-		throw(aditi__exception(ErrorCode, String))
-	}.
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
Index: extras/aditi/aditi_private_builtin.m
===================================================================
RCS file: extras/aditi/aditi_private_builtin.m
diff -N extras/aditi/aditi_private_builtin.m
--- extras/aditi/aditi_private_builtin.m	23 Aug 2003 13:31:04 -0000	1.2
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,1336 +0,0 @@
-%-----------------------------------------------------------------------------%
-% Copyright (C) 2003 University of Melbourne.
-% This file may only be copied under the terms of the GNU Library General
-% Public License - see the file COPYING.LIB in the Mercury distribution.
-%-----------------------------------------------------------------------------%
-% File: aditi_private_builtin.m
-% Author: stayl
-%
-% Internals of the Mercury->Aditi interface.
-%
-% This module is automatically imported when `--aditi' is passed to
-% the compiler.
-%
-% Calls to some of these predicates are generated by the compiler,
-% and some are called from aditi.m.
-%
-% None of these predicates should appear in user programs.
-%
-%-----------------------------------------------------------------------------%
-:- module aditi_private_builtin.
-
-:- interface.
-
-:- import_module io.
-:- import_module aditi.
-
-:- type aditi_private_builtin__relation.
-
-:- pred connect(string, string, string, int, aditi__connection,
-		io__state, io__state).
-:- mode connect(in, in, in, out, out, di, uo) is det.
-
-:- pred disconnect(aditi__connection, int, io__state, io__state).
-:- mode disconnect(in, out, di, uo) is det.
-
-:- pred start_transaction(aditi__connection, aditi__result(aditi__state),
-		io__state, io__state).
-:- mode start_transaction(in, out, di, uo) is det.
-
-:- pred commit_transaction(aditi__state, io__state, io__state).
-:- mode commit_transaction(in, di, uo) is det.
-
-:- pred abort_transaction(aditi__state, io__state, io__state).
-:- mode abort_transaction(in, di, uo) is det.
-
-	% do_call_returning_relation(ProcName, InputSchema, InputTuple,
-	%		OutputRel).
-	%
-	% Call an Aditi procedure, returning a reference to the output
-	% relation. InputTuple is a tuple containing the
-	% input arguments. InputSchema is an Aditi schema string
-	% describing the tuple of input arguments.
-:- impure pred do_call_returning_relation(aditi__state, string, string,
-		T, relation).
-:- mode do_call_returning_relation(aditi_mui, in, in, in, out) is det.
-
-	% Find the single solution for a deterministic database call.
-	% Abort the transaction if the call does not succeed at
-	% least once.
-	% InputTuple and OutputTuple must have type '{}/N' (the arity
-	% depends on the relation being called).
-:- impure pred do_det_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_det_call(aditi_mui, in, in, in, out) is det.
-
-:- impure pred do_semidet_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_semidet_call(aditi_mui, in, in, in, out) is semidet.
-
-:- impure pred do_nondet_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_nondet_call(aditi_mui, in, in, in, out) is nondet.
-
-:- impure pred do_multi_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_multi_call(aditi_mui, in, in, in, out) is multi.
-
-	% XXX I'm not sure whether it makes sense to have
-	% committed choice Aditi predicates.
-:- impure pred do_cc_nondet_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_cc_nondet_call(aditi_mui, in, in, in, out) is cc_nondet.
-
-:- impure pred do_cc_multi_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_cc_multi_call(aditi_mui, in, in, in, out) is cc_multi.
-
-:- impure pred do_erroneous_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_erroneous_call(aditi_mui, in, in, in, out) is erroneous.
-
-:- impure pred do_failure_call(aditi__state, string, string,
-		InputTuple, OutputTuple).
-:- mode do_failure_call(aditi_mui, in, in, in, out) is failure.
-
-	% do_insert_tuple(BaseRelationName, Tuple).
-	%
-	% TypeInfos is an array containing the type-infos for
-	% the tuple to insert. TupleArgs contains the attribute
-	% values of the tuple to insert.
-:- pred do_insert_tuple(string, InputTuple, aditi__state, aditi__state).
-:- mode do_insert_tuple(in, in, aditi_di, aditi_uo) is det.
-
-	% do_delete_tuple(BaseRelationName, DeleteProcName,
-	%	DeleteProcInputSchema, Tuple).
-:- pred do_delete_tuple(string, string, string, Tuple,
-		aditi__state, aditi__state).
-:- mode do_delete_tuple(in, in, in, in, aditi_di, aditi_uo) is det.
-
-:- type update_closure == pred(aditi__state, relation).
-:- inst update_closure == (pred(aditi_ui, out) is det).
-
-	% do_bulk_insert(BaseRelationName, UpdateProcName, Closure).
-:- pred do_bulk_insert(string, string, update_closure,
-		aditi__state, aditi__state).
-:- mode do_bulk_insert(in, in, in(update_closure), aditi_di, aditi_uo) is det.
-
-	% do_bulk_delete(BaseRelationName, UpdateProcName, Closure).
-:- pred do_bulk_delete(string, string, update_closure,
-		aditi__state, aditi__state).
-:- mode do_bulk_delete(in, in, in(update_closure), aditi_di, aditi_uo) is det.
-
-	% do_bulk_modify(BaseRelationName, UpdateProcName, Closure).
-:- pred do_bulk_modify(string, string, update_closure,
-		aditi__state, aditi__state).
-:- mode do_bulk_modify(in, in, in(update_closure), aditi_di, aditi_uo) is det.
-
-	% Try to classify an error code returned by Aditi.
-:- pred error_code(int, aditi__error, string).
-:- mode error_code(in, out, out) is det.
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-:- implementation.
-
-:- import_module bool, char, exception, int, list, require, std_util, string.
-
-:- pragma foreign_type("C", relation, "apiID").
-
-:- type cursor.
-:- pragma foreign_type("C", cursor, "MADITI_Output_Info *").
-
-:- pragma foreign_import_module("C", aditi).
-
-:- pragma foreign_decl("C",
-"
-#include ""mercury_wrapper.h""
-#include ""mercury_string.h""
-#include ""mercury_reg_workarounds.h""
-
-#include ""v2_api_without_engine.h""
-#include ""AditiStatus.h""
-
-#define MADITI_OK ADITI_ENUM(AditiStatus_OK)
-
-	/*
-	** MADITI_check can only be used within functions which return
-	** an Aditi error code.
-	*/
-#define MADITI_check(status)						\\
-    do {	int MADITI_line_xxx = __LINE__;				\\
-		int MADITI_check_status_xxx;				\\
-		MADITI_check_status_xxx = status;			\\
-		MADITI_do_debug_status(MADITI_check_status_xxx,		\\
-			MADITI_line_xxx);				\\
-		if (MADITI_check_status_xxx != MADITI_OK) {		\\
-			MADITI_status = MADITI_check_status_xxx;	\\
-    			return MADITI_check_status_xxx;			\\
-		}							\\
-    } while(0)
-
-#define MADITI_debug_status(status)					\\
-    do {	int MADITI_line_xxx_2 = __LINE__;			\\
-		int MADITI_check_status_xxx_2;				\\
-		MADITI_check_status_xxx_2 = status;			\\
-	    	MADITI_do_debug_status(MADITI_check_status_xxx_2,	\\
-			MADITI_line_xxx_2);				\\
-    } while(0)
-
-#define MADITI_do_debug_status(status, line)				\\
-    do {	int MADITI_do_debug_status_xxx;				\\
-		MADITI_do_debug_status_xxx = status;			\\
-		if (MADITI_do_debug_status_xxx != MADITI_OK) {		\\
-			MR_DEBUG(fprintf(stderr, ""\\naditi_private_builtin.m:%d: API call failed, returned %d\\n"", \\
-			line, MADITI_do_debug_status_xxx));		\\
-	}								\\
-    } while(0)
-
-typedef enum { MADITI_INSERT_TUPLE, MADITI_DELETE_TUPLE } MADITI_Insert_Delete;
-typedef enum { MADITI_INSERT, MADITI_DELETE, MADITI_MODIFY } MADITI_Bulk_Op;
-
-/*
-** Information used to clean up a call result if there is a commit
-** or an exception across a database call.
-*/
-typedef struct {
-	MADITI_State	state;
-	apiID		relation;
-	apiID		cursor;
-	bool		cleaned_up;
-} MADITI_Output_Info;
-
-static apiID MADITI_session;		/* Current connection ticket. */
-static int MADITI_status;		/* Return code of the last
-					** Aditi API call.
-					*/
-
-static int MADITI_run_procedure(MADITI_State *DB, MR_String proc_name,
-		MR_String input_schema, MR_String input_tuple,
-		apiID *output_relation);
-static int MADITI_create_cursor(MADITI_State *DB, apiID relation,
-		MADITI_Output_Info **output_info_ptr);
-static int MADITI_do_insert_delete_tuple(MADITI_State *DB,
-		MADITI_Insert_Delete operation,
-		MR_String relation_name, MR_String update_proc,
-		MR_String update_schema, MR_String tuple);
-static int MADITI_do_bulk_operation(MADITI_State *DB, MADITI_Bulk_Op operation,
-		MR_String relation_name, MR_String update_proc,
-		apiID closure_result);
-static int MADITI_cleanup_call_output(MADITI_Output_Info *);
-
-#ifdef MR_USE_TRAIL
-static void MADITI_trail_cleanup_call_output(void *cleanup_data,
-		MR_untrail_reason reason);
-#endif
-
-static int MADITI_list_rel(MADITI_State DB, apiID rel);
-").
-
-:- pragma c_code("
-
-	/*
-	** No effort is made to ensure that MR_hp is valid where
-	** memory is allocated. Given that it is likely that a better
-	** way of allocating memory from C code is will be implemented
-	** when the accurate garbage collector is finished, I don't
-	** see much point in cluttering the code here with
-	** save_transient_registers()/restore_transient_registers() calls.
-	*/
-#ifndef CONSERVATIVE_GC
-#error ""The Aditi interface requires conservative garbage collection. \\
-                Use a compilation grade containing .gc.""
-#endif
-").
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-	%
-	% Code to handle connections.
-	%
-:- pragma foreign_proc("C",
-	connect(_XXXHost::in, User::in, Passwd::in,
-		Stat::out, Connection::out, IO0::di, IO::uo),
-	[will_not_call_mercury, promise_pure, tabled_for_io],
-"
-{
-    apiID transport_id;
-    char *challenge = NULL;
-    MR_Box boxed_connection;
-    MR_Box boxed_bytecode_transaction;
-
-    Stat = ADITI_FUNC(api_init)((apiString) ""D"", 0,
-    		NULL, NULL, &transport_id);
-    if (Stat == MADITI_OK) {
-        /*
-        ** Log in.
-        ** XXX handle extra authentication using
-        ** ADITI_FUNC(session_authenticate)
-        */
-        Stat = ADITI_FUNC(session_create)(User, Passwd, 0,
-                &(Connection.connection), &challenge);
-        if (Stat == MADITI_OK) {
-
-            MR_DEBUG(fprintf(stderr, ""connected\\n""));
-
-            /*
-            ** Create a transaction which will run as long as the connection.
-            ** The bytecode will be stored in this transaction.
-            */
-            Stat = ADITI_FUNC(transaction_begin)(Connection.connection,
-                                    &(Connection.bytecode_transaction));
-            if (Stat == MADITI_OK) {
-                /*
-                ** Upload all the RL code for the program to
-                ** the database.
-                */
-
-                /* XXX The new API doesn't provide any way to do this */
-                /* MR_DEBUG(ADITI_FUNC(set_debug)()); */
-
-                MR_DEBUG(fprintf(stderr, ""logged in\\n""));
-
-                /*
-                ** The casts to `void *' are to avoid the Mercury runtime
-                ** depending on Aditi headers.
-                */
-		MR_MAYBE_BOX_FOREIGN_TYPE(apiID, Connection.connection,
-			boxed_connection);
-		MR_MAYBE_BOX_FOREIGN_TYPE(apiID,
-			Connection.bytecode_transaction,
-			boxed_bytecode_transaction);
-                Stat = MR_load_aditi_rl_code(boxed_connection,
-                        boxed_bytecode_transaction);
-                if (Stat == MADITI_OK) {
-                    MR_DEBUG(fprintf(stderr, ""code loaded\\n""));
-                } else {
-                    ADITI_FUNC(transaction_abort)(Connection.connection,
-                            Connection.bytecode_transaction);
-                    ADITI_FUNC(session_disconnect)(Connection.connection);
-                    ADITI_FUNC(api_close)();
-                }
-            } else {
-                ADITI_FUNC(session_disconnect)(Connection.connection);
-                ADITI_FUNC(api_close)();
-            }
-        } else {
-            ADITI_FUNC(api_close)();
-        }
-    }
-    MADITI_debug_status(Stat);
-    IO = IO0;
-}
-").
-
-:- pragma foreign_proc("C",
-	disconnect(Connection::in, Stat::out, IO0::di, IO::uo),
-	[will_not_call_mercury, promise_pure, tabled_for_io],
-"{
-	ADITI_TYPE(AditiStatus) status;
-        Stat = ADITI_FUNC(transaction_abort)(Connection.connection,
-                Connection.bytecode_transaction);
-        status = ADITI_FUNC(session_disconnect)(Connection.connection);
-	if (Stat == MADITI_OK) {
-		Stat = status;
-	}
-        status = ADITI_FUNC(api_close)();
-	if (Stat == MADITI_OK) {
-		Stat = status;
-	}
-        MADITI_debug_status(Stat);
-        IO = IO0;
-}").
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-	%
-	% This section handles starting, committing and aborting transactions.
-	%
-
-start_transaction(Connection, Result) -->
-	start_transaction_2(Connection, Status, DB),
-	{ Status = 0 ->
-		Result = ok(DB)
-	;
-		error_code(Status, Error, String),
-		Result = error(Error, String)
-	}.
-
-:- pred start_transaction_2(aditi__connection, int,
-		aditi__state, io__state, io__state).
-:- mode start_transaction_2(in, out, out, di, uo) is det.
-
-:- pragma foreign_proc("C",
-	start_transaction_2(Connection::in, Stat::out,
-		DB::out, IO0::di, IO::uo),
-	[will_not_call_mercury, promise_pure, tabled_for_io],
-"{
-	IO = IO0;
-	MR_DEBUG(fprintf(stderr, ""starting transaction...""));
-	DB.connection = Connection.connection;
-	DB.bytecode_transaction = Connection.bytecode_transaction;
-	Stat = ADITI_FUNC(transaction_begin)(Connection.connection,
-		&(DB.transaction));
-	MADITI_debug_status(Stat);
-	MADITI_status = Stat;
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-}").
-
-:- pragma foreign_proc("C",
-	abort_transaction(DB::in, IO0::di, IO::uo),
-	[will_not_call_mercury, promise_pure, tabled_for_io],
-"{
-	/*
-	** Ignore the return code -- we're more interested
-	** in the error which caused the abort.
-	*/
-	ADITI_FUNC(transaction_abort)(DB.connection, DB.transaction);
-	IO = IO0;
-}").
-
-:- pragma promise_pure(commit_transaction/3).
-commit_transaction(DB) -->
-	{ semipure check_for_old_error },
-	commit_transaction_2(DB, Status),
-	{ semipure maybe_throw_aditi_exception(Status) }.
-
-:- pred commit_transaction_2(aditi__state, int, io__state, io__state).
-:- mode commit_transaction_2(in, out, di, uo) is det.
-
-:- pragma c_code(commit_transaction_2(DB::in, Stat::out, IO0::di, IO::uo),
-		will_not_call_mercury,
-"{
-	Stat = ADITI_FUNC(transaction_commit)(DB.connection, DB.transaction);
-	MADITI_debug_status(Stat);
-	IO = IO0;
-}").
-
-	% Throw an exception to abort the transaction if the status
-	% is not MADITI_OK.
-	% This needs to be impure to stop it being reordered with
-	% other calls.
-:- semipure pred maybe_throw_aditi_exception(int).
-:- mode maybe_throw_aditi_exception(in) is det.
-
-maybe_throw_aditi_exception(Status) :-
-	semipure get_aditi_status(_),
-	( Status = 0 ->
-		true
-	;
-		error_code(Status, Error, String),
-		throw(aditi__exception(Error, String))
-	).
-
-:- pred maybe_throw_aditi_exception(int, aditi__state, aditi__state).
-:- mode maybe_throw_aditi_exception(in, aditi_di, aditi_uo) is det.
-:- pragma promise_pure(maybe_throw_aditi_exception/3).
-
-maybe_throw_aditi_exception(Status) -->
-	{ semipure maybe_throw_aditi_exception(Status) }.
-
-	% If a call result is cleaned up by untrailing, any errors
-	% will not result in the transaction being aborted immediately
-	% because there is no way to throw an exception from a trail
-	% function. Instead, a global variable is set to indicate that
-	% an error has occurred, and the next database call will
-	% check for the error and abort the transaction.
-	% This needs to be semipure to stop it being reordered with
-	% other calls.
-:- semipure pred check_for_old_error is det.
-
-check_for_old_error :-
-	semipure get_aditi_status(Status),
-	semipure maybe_throw_aditi_exception(Status).
-
-:- pred check_for_old_error(aditi__state, aditi__state).
-:- mode check_for_old_error(aditi_di, aditi_uo) is det.
-:- pragma promise_pure(check_for_old_error/2).
-
-check_for_old_error -->
-	{ semipure check_for_old_error }.
-
-:- semipure pred get_aditi_status(int).
-:- mode get_aditi_status(out) is det.
-
-:- pragma c_code(get_aditi_status(Stat::out), will_not_call_mercury,
-		"Stat = MADITI_status;").
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-	%
-	% This section handles calls to Aditi predicates and functions.
-	%
-
-do_det_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_call_returning_relation(DB, ProcName,
-		InputSchema, InputTuple, OutputRel),
-	impure create_cursor(DB, OutputRel, CursorStatus, Cursor0),
-	semipure maybe_throw_aditi_exception(CursorStatus),
-	( get_next_tuple(OutputTuple0, Cursor0, Cursor) ->
-		OutputTuple = OutputTuple0,
-		impure destroy_cursor(DB, Cursor, DestroyStatus),
-		semipure maybe_throw_aditi_exception(DestroyStatus)
-	;
-		impure destroy_cursor(DB, Cursor0, DestroyStatus),
-		semipure maybe_throw_aditi_exception(DestroyStatus),
-		determinism_error("no solution", "det", ProcName)
-	).
-
-do_semidet_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_call_returning_relation(DB, ProcName,
-		InputSchema, InputTuple, OutputRel),
-	impure create_cursor(DB, OutputRel, CursorStatus, Cursor0),
-	semipure maybe_throw_aditi_exception(CursorStatus),
-	( get_next_tuple(OutputTuple0, Cursor0, Cursor) ->
-		%
-		% Assume that if a call succeeds multiple times,
-		% the other solutions are just duplicates.
-		%
-		OutputTuple = OutputTuple0,
-		impure destroy_cursor(DB, Cursor, DestroyStatus),
-		semipure maybe_throw_aditi_exception(DestroyStatus)
-	;
-		impure destroy_cursor(DB, Cursor0, DestroyStatus),
-		semipure maybe_throw_aditi_exception(DestroyStatus),
-		fail
-	).
-
-do_nondet_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_call_returning_relation(DB, ProcName, InputSchema,
-		InputTuple, OutputRel),
-	impure create_cursor(DB, OutputRel, CursorStatus, Cursor),
-	semipure maybe_throw_aditi_exception(CursorStatus),
-	impure collect_nondet_output_tuples(DB, Cursor, OutputTuple).
-
-do_multi_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	(
-		impure do_nondet_call(DB, ProcName, InputSchema,
-			InputTuple, OutputTuple0)
-	->
-		OutputTuple = OutputTuple0
-	;
-		determinism_error("no solution", "multi", ProcName)
-	).
-
-do_cc_nondet_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_nondet_call(DB, ProcName, InputSchema,
-		InputTuple, OutputTuple).
-
-do_cc_multi_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_multi_call(DB, ProcName, InputSchema,
-		InputTuple, OutputTuple).
-
-do_erroneous_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	impure do_det_call(DB, ProcName, InputSchema, InputTuple, OutputTuple),
-	determinism_error("solution", "erroneous", ProcName).
-
-do_failure_call(DB, ProcName, InputSchema, InputTuple, OutputTuple) :-
-	(
-		impure do_semidet_call(DB, ProcName, InputSchema,
-			InputTuple, OutputTuple0)
-	->
-		OutputTuple = OutputTuple0,
-		determinism_error("solution", "failure", ProcName)
-	;
-		fail
-	).
-
-:- pred determinism_error(string, string, string).
-:- mode determinism_error(in, in, in) is erroneous.
-
-determinism_error(Solution, Det, ProcName) :-
-	string__format(
-		"Error in Aditi call: %s for procedure with determinism %s\n",
-		[s(Solution), s(Det), s(ProcName)], Msg),
-	throw(aditi__exception(determinism_error, Msg)).
-
-:- impure pred collect_nondet_output_tuples(aditi__state, cursor, T).
-:- mode collect_nondet_output_tuples(in, in, out) is nondet.
-
-collect_nondet_output_tuples(DB, Cursor0, OutputTuple) :-
-	semipure check_for_old_error,
-	(
-		get_next_tuple(OutputTuple0, Cursor0, Cursor)
-	->
-		(
-			OutputTuple = OutputTuple0
-		;
-			impure collect_nondet_output_tuples(DB, Cursor,
-				OutputTuple)
-		)
-	;
-		impure destroy_cursor(DB, Cursor0, DestroyStatus),
-		semipure maybe_throw_aditi_exception(DestroyStatus),
-		fail
-	).
-
-% XXX Work around GCC register bug.
-:- pragma no_inline(do_call_returning_relation/5).
-
-do_call_returning_relation(DB, ProcName, InputSchema, InputTuple, OutputRel) :-
-	construct_input_tuple(InputTuple, InputTupleStr),
-	impure do_call_returning_relation_2(DB, ProcName, InputSchema,
-		InputTupleStr, Status, OutputRel),
-	semipure maybe_throw_aditi_exception(Status).
-
-:- impure pred do_call_returning_relation_2(aditi__state, string, string,
-		string, int, relation).
-:- mode do_call_returning_relation_2(aditi_mui, in, in, in, out, out) is det.
-
-:- pragma foreign_proc("C",
-	do_call_returning_relation_2(DB::aditi_mui, ProcName::in,
-		InputSchema::in, InputTuple::in, Stat::out, OutputRel::out),
-	[will_not_call_mercury],
-"{
-	Stat = MADITI_run_procedure(&DB, ProcName, InputSchema,
-			InputTuple, &OutputRel);
-}").
-
-	% Create a cursor, adding an entry to the trail if possible
-	% to make sure that it is cleaned up.
-:- impure pred create_cursor(aditi__state, relation, int, cursor).
-:- mode create_cursor(aditi_mui, in, out, out) is det.
-
-:- pragma foreign_proc("C",
-	create_cursor(DB::aditi_mui, Relation::in, Stat::out, Cursor::out),
-	[will_not_call_mercury],
-"{
-	Stat = MADITI_create_cursor(&DB, Relation, &Cursor);
-}").
-
-:- impure pred destroy_cursor(aditi__state, cursor, int).
-:- mode destroy_cursor(aditi_mui, in, out) is det.
-
-:- pragma foreign_proc("C",
-	destroy_cursor(_DB::aditi_mui, Cursor::in, Stat::out),
-	[will_not_call_mercury],
-"
-	Stat = MADITI_cleanup_call_output(Cursor);
-").
-
-:- pred get_next_tuple(T, cursor, cursor).
-:- mode get_next_tuple(out, in, out) is semidet.
-
-get_next_tuple(OutputTuple, Cursor0, Cursor) :-
-	cursor_next(TupleStr, Cursor0, Cursor),
-	ArgTypeDescs = type_args(type_of(OutputTuple)),
-	Posn0 = posn(1, 0, 0),
-	string__length(TupleStr, TupleLength),
-	parse_output_tuple(ArgTypeDescs, TupleStr, TupleLength, Posn0,
-		OutputArgUnivs),
-	OutputTuple0 = univ_value(construct_tuple(OutputArgUnivs)),
-	OutputTuple = cast(OutputTuple0).
-
-	% The arguments of the output tuple were constructed using
-	% the argument types passed in -- we don't need to check
-	% that they match again.
-:- func cast(T) = U.
-:- pragma c_code(cast(T::in) = (U::out), will_not_call_mercury, "U = T;").
-
-:- pred cursor_next(string, cursor, cursor).
-:- mode cursor_next(out, in, out) is semidet.
-
-:- pragma foreign_proc("C",
-	cursor_next(Tuple::out, Cursor0::in, Cursor::out),
-	[will_not_call_mercury, promise_pure],
-"{
-	int rc;
-	char *tuple_str;
-#ifdef MR_INT_LEAST64_TYPE
-	MR_uint_least64_t file_page_slot;
-#else
-	#error ""The Aditi interface needs a 64 bit integer type""
-#endif
-
-	Cursor = Cursor0;
-	rc = ADITI_FUNC(cursor_get_next)((Cursor->state).connection,
-		(Cursor->state).transaction, Cursor->relation,
-		Cursor->cursor, &file_page_slot);
-	MADITI_debug_status(rc);
-
-	/*
-	** XXX This check should be more specific, but there is no
-	** Aditi return code for no more tuples.
-	*/
-	if (rc == MADITI_OK) {
-		rc = ADITI_FUNC(cursor_get_current)((Cursor->state).connection,
-			(Cursor->state).transaction, Cursor->relation,
-			Cursor->cursor, &tuple_str);
-		MADITI_debug_status(rc);
-		if (rc == MADITI_OK) {
-			MR_DEBUG(fprintf(stderr,
-				""received tuple: %s\\n"", tuple_str));
-			MR_make_aligned_string_copy(Tuple, tuple_str);
-			free(tuple_str);
-			SUCCESS_INDICATOR = TRUE;
-		} else {
-			SUCCESS_INDICATOR = FALSE;
-		}
-	} else {
-		SUCCESS_INDICATOR = FALSE;
-	}
-}").
-
-:- pred parse_output_tuple(list(type_desc), string, int,
-		io__posn, list(univ)).
-:- mode parse_output_tuple(in, in, in, in, out) is det.
-
-parse_output_tuple([], _, _, _, []).
-parse_output_tuple([TypeDesc | TypeDescs], Tuple, TupleLength, Posn0,
-		[Arg | Args]) :-
-	has_read_result_type(Result, TypeDesc),
-	io__read_from_string_with_int_instead_of_char("Aditi result tuple",
-		Tuple, TupleLength, Result, Posn0, Posn),
-	(
-		Result = ok(Field),
-		Arg = univ(Field)
-	;
-		Result = eof,
-		string__format("Aditi: unexpected end of tuple: %s",
-			[s(Tuple)], ErrorMsg),
-		throw(aditi__exception(parse_error_in_tuple, ErrorMsg))
-	;
-		Result = error(Msg, _),
-		string__format("Aditi: invalid tuple returned: %s",
-			[s(Msg)], ErrorMsg),
-		throw(aditi__exception(parse_error_in_tuple, ErrorMsg))
-	),
-	parse_output_tuple(TypeDescs, Tuple, TupleLength, Posn, Args).
-
-	% Use existential types to set up the type of the output argument
-	% using the type-info passed for the output tuple.
-:- some [T] pred has_read_result_type(io__read_result(T), type_desc).
-:- mode has_read_result_type(unused, in) is det.
-
-has_read_result_type(Result, TypeDesc) :-
-	has_type(Var, TypeDesc),
-	read_result_type(Var, Result).
-
-:- pred read_result_type(T, io__read_result(T)).
-:- mode read_result_type(unused, unused) is det.
-
-read_result_type(_, _).
-
-:- pragma foreign_decl("C",
-"
-/*
-** Given an RL procedure name, the schema of the input relation and a tuple
-** to insert into the input relation, run the procedure, returning a ticket
-** for the output relation.
-*/
-static int
-MADITI_run_procedure(MADITI_State *DB, MR_String proc_name,
-	MR_String input_schema, MR_String input_tuple, apiID *output_relation)
-{
-	apiID input_relation;
-
-	/*
-	** Create a temporary relation to hold the input tuple.
-	*/
-	MR_DEBUG(fprintf(stderr, ""creating input temporary (schema %s)..."",
-		input_schema));
-	MADITI_check(ADITI_FUNC(relation_create)(DB->connection,
-		DB->transaction, input_schema,
-		(apiString) """", /* unnamed */
-		0, /* temporary relation */
-		&input_relation));
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-
-	/*
-	** Insert the input tuple into the relation.
-	*/
-	MR_DEBUG(fprintf(stderr, ""adding input tuple...%s"", input_tuple));
-	MADITI_check(ADITI_FUNC(relation_tuple_add)(DB->connection,
-		DB->transaction, input_relation, input_tuple,
-		0 /* !use_internal_save_point */));
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-
-	/*
-	** Run the procedure.
-	*/
-	MR_DEBUG(fprintf(stderr, ""running procedure... ""));
-	MADITI_check(ADITI_FUNC(procedure_run)(DB->connection, DB->transaction,
-		proc_name, input_relation, DB->bytecode_transaction,
-		1 /* output is used */,
-		output_relation));
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-
-	/*
-	** Drop the input relation.
-	*/
-	MR_DEBUG(fprintf(stderr, ""dropping input temporary...""));
-	MADITI_check(ADITI_FUNC(relation_destroy)(DB->connection,
-		DB->transaction, input_relation));
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-
-	MR_DEBUG(fprintf(stderr, ""output tuples\\n""));
-	MR_DEBUG(MADITI_check(MADITI_list_rel(DB, *output_relation)));
-	MR_DEBUG(fprintf(stderr, ""\\n\\n""));
-
-	return MADITI_OK;
-}
-
-static int
-MADITI_create_cursor(MADITI_State *DB, apiID relation,
-		MADITI_Output_Info **output_info_ptr)
-{
-	apiID cursor;
-	MADITI_Output_Info *output_info;
-
-	/* create cursor on the output relation */
-	MR_DEBUG(fprintf(stderr, ""opening output cursor...""));
-	MADITI_check(ADITI_FUNC(cursor_create)(DB->connection,
-		DB->transaction, relation,
-		(apiString) """" /* no index */,
-		&cursor));
-	MADITI_check(ADITI_FUNC(cursor_open)(DB->connection,
-		DB->transaction, relation, cursor,
-		0 /* forwards */,
-		(apiString) """", 0, (apiString) """", 0 /* not used */));
-	MR_DEBUG(fprintf(stderr, ""done\\n""));
-
-	output_info = MR_GC_NEW(MADITI_Output_Info);
-	MR_assign_structure(output_info->state, DB);
-	output_info->relation = relation;
-	output_info->cursor = cursor;
-	output_info->cleaned_up = FALSE;
-#ifdef MR_USE_TRAIL
-	MR_trail_function(MADITI_trail_cleanup_call_output,
-		(void *) output_info);
-#endif
-	*output_info_ptr = output_info;
-	return MADITI_OK;
-}
-
-static int
-MADITI_list_rel(MADITI_State DB, apiID relation)
-{
-	size_t len;
-	apiID cursor;
-	char *tuple_str;
-	int rc;
-#ifdef MR_INT_LEAST64_TYPE
-	MR_uint_least64_t file_page_slot;
-#else
-	#error ""The Aditi interface needs a 64 bit integer type""
-#endif
-
-
-	MADITI_check(ADITI_FUNC(cursor_create)(DB.connection,
-		DB.transaction, relation,
-		(apiString) """" /* no index */,
-		&cursor));
-	MADITI_check(ADITI_FUNC(cursor_open)(DB.connection,
-		DB.transaction, relation, cursor,
-		0 /* forwards */,
-		(apiString) """", 0, (apiString) """", 0 /* not used */));
-
-	len = 0;
-	fflush(stdout);
-
-	/*
-	** XXX This check should be more specific, but there is no
-	** Aditi return code for no more tuples.
-	*/
-	while (ADITI_FUNC(cursor_get_next)(DB.connection, DB.transaction,
-			relation, cursor, &file_page_slot) == MADITI_OK)
-	{
-		rc = ADITI_FUNC(cursor_get_current)(DB.connection,
-			DB.transaction, relation, cursor, &tuple_str);
-		if (rc == MADITI_OK) {
-			fprintf(stderr, ""tuple: %s\\n"", tuple_str);
-			free(tuple_str);
-			len = 0;
-			tuple_str = NULL;
-		}
-	}
-
-	MADITI_check(ADITI_FUNC(cursor_close)(DB.connection,
-		DB.transaction, relation, cursor));
-	MADITI_check(ADITI_FUNC(cursor_destroy)(DB.connection,
-		DB.transaction, relation, cursor));
-	return MADITI_OK;
-}
-
-/*---------------------------------------------------------------------------*/
-
-/*
-** Free all resources used by a database call.
-*/
-
-#ifdef MR_USE_TRAIL
-static void
-MADITI_trail_cleanup_call_output(void *data, MR_untrail_reason reason)
-{
-    switch (reason) {
-	case MR_commit:
-	case MR_exception:
-	case MR_retry:
-	    /*
-	    ** Clean up the output relation. If the transaction
-	    ** status is not MADITI_OK, the transaction is about
-	    ** to be aborted, so it's best not to try to clean up.
-	    ** The database will do any cleaning up that is required.
-	    */
-	    if (MADITI_status == MADITI_OK) {
-		MR_DEBUG(fprintf(stderr,
-		    ""MADITI_trail_cleanup_call_output: cleaning up %d\\n"",
-		    reason));
-		/*
-		** We shouldn't throw exceptions during an untrail operation,
-		** so we just set the status so that the next Aditi operation
-		** called will abort the transaction if there were any errors.
-		*/
-		MADITI_status = MADITI_cleanup_call_output(
-			(MADITI_Output_Info *)data);
-	    }
-	    break;
-	case MR_solve:
-	case MR_undo:
-	    /*
-	    ** Undo on backtracking will be handled by
-	    ** do_*_call, so that the  cleanup will happen
-	    ** even if trailing is not being used.
-	    */
-	    break;
-
-	case MR_gc:
-	default:
-	    MR_fatal_error(""MADITI_trail_cleanup_call_output"");
-    }
-}
-#endif /* MR_USE_TRAIL */
-
-static int
-MADITI_cleanup_call_output(MADITI_Output_Info *output_info)
-{
-	if (output_info->cleaned_up) {
-
-		/*
-		** This can happen if there is a commit followed
-		** by an exception -- the commit will not reset
-		** the trail.
-		*/
-		MR_DEBUG(fprintf(stderr,
-			""MADITI_cleanup_call_output: already cleaned up\\n""
-		));
-
-	} else {
-
-		MR_DEBUG(fprintf(stderr,
-			""MADITI_cleanup_call_output: cleaning up\\n""
-		));
-
-		/* close cursor */
-		MR_DEBUG(fprintf(stderr, ""closing cursor\\n""));
-		MADITI_check(
-			ADITI_FUNC(cursor_close)(
-				(output_info->state).connection,
-				(output_info->state).transaction,
-				output_info->relation,
-				output_info->cursor)
-		);
-
-		/* destroy cursor */
-		MR_DEBUG(fprintf(stderr, ""destroying cursor\\n""));
-		MADITI_check(
-			ADITI_FUNC(cursor_destroy)(
-				(output_info->state).connection,
-				(output_info->state).transaction,
-				output_info->relation,
-				output_info->cursor)
-		);
-
-		/* close output temporary */
-		MR_DEBUG(fprintf(stderr,
-			""closing output temporary relation\\n""));
-		MADITI_check(ADITI_FUNC(relation_close)(
-			(output_info->state).connection,
-			(output_info->state).transaction,
-			output_info->relation));
-
-		/* Make sure we don't do this again. */
-		output_info->cleaned_up = TRUE;
-	}
-
-	return MADITI_OK;
-}
-").
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-	%
-	% This section handles updates.
-	%
-
-do_insert_tuple(RelationName, Args) -->
-	% There are no compiler-generated procedures for inserting
-	% a single tuple into a relation.
-	{ UpdateProc = "" },
-	{ UpdateSchema = "" },
-
-	do_insert_delete_tuple(insert_tuple, RelationName,
-		UpdateProc, UpdateSchema, Args).
-
-do_delete_tuple(RelationName, DeleteProc, DeleteProcInputSchema, Args) -->
-	do_insert_delete_tuple(delete_tuple, RelationName,
-		DeleteProc, DeleteProcInputSchema, Args).
-
-:- pred do_insert_delete_tuple(int, string, string, string,
-		T, aditi__state, aditi__state).
-:- mode do_insert_delete_tuple(in, in, in, in, in, aditi_di, aditi_uo) is det.
-
-do_insert_delete_tuple(InsertDelete, RelationName,
-		UpdateProc, UpdateSchema, Args) -->
-	check_for_old_error,
-	{ construct_input_tuple(Args, Tuple) },
-	do_insert_delete_tuple_2(InsertDelete, RelationName,
-		UpdateProc, UpdateSchema, Tuple, Status),
-	maybe_throw_aditi_exception(Status).
-
-:- pred do_insert_delete_tuple_2(int, string, string, string, string, int,
-		aditi__state, aditi__state).
-:- mode do_insert_delete_tuple_2(in, in, in, in, in, out,
-		aditi_di, aditi_uo) is det.
-
-:- pragma foreign_proc("C",
-	do_insert_delete_tuple_2(InsertDelete::in, RelationName::in,
-		UpdateProc::in, UpdateSchema::in, Tuple::in, Stat::out,
-		DB0::aditi_di, DB::aditi_uo),
-	[will_not_call_mercury, promise_pure],
-"{
-	MR_assign_structure(DB, DB0);
-	Stat = MADITI_do_insert_delete_tuple(&DB,
-			(MADITI_Insert_Delete) InsertDelete,
-			RelationName, UpdateProc, UpdateSchema, Tuple);
-}").
-
-:- func insert_tuple = int.
-:- pragma foreign_proc("C",
-	insert_tuple = (InsertTuple::out),
-	[will_not_call_mercury, promise_pure, thread_safe],
-"{
-	InsertTuple = MADITI_INSERT_TUPLE;
-}").
-
-:- func delete_tuple = int.
-:- pragma foreign_proc("C",
-	delete_tuple = (DeleteTuple::out),
-	[will_not_call_mercury, promise_pure, thread_safe],
-"{
-	DeleteTuple = MADITI_DELETE_TUPLE;
-}").
-
-do_bulk_insert(RelationName, InsertProcName, Closure) -->
-	do_bulk_operation(bulk_insert, RelationName, InsertProcName, Closure).
-
-do_bulk_delete(RelationName, DeleteProcName, Closure) -->
-	do_bulk_operation(bulk_delete, RelationName, DeleteProcName, Closure).
-
-do_bulk_modify(RelationName, ModifyProcName, Closure) -->
-	do_bulk_operation(bulk_delete, RelationName, ModifyProcName, Closure).
-
-:- pred do_bulk_operation(int, string, string, update_closure,
-		aditi__state, aditi__state).
-:- mode do_bulk_operation(in, in, in, in(update_closure),
-		aditi_di, aditi_uo) is det.
-
-do_bulk_operation(Op, RelationName, UpdateProc, Closure) -->
-	check_for_old_error,
-	=(DB),
-	{ Closure(DB, ResultRelation) },
-	do_bulk_operation_2(Op, RelationName, UpdateProc,
-		ResultRelation, Status),
-	maybe_throw_aditi_exception(Status).
-
-:- pred do_bulk_operation_2(int, string, string, relation, int,
-		aditi__state, aditi__state).
-:- mode do_bulk_operation_2(in, in, in, in, out,
-		aditi_di, aditi_uo) is det.
-
-:- pragma c_code(do_bulk_operation_2(Op::in, RelationName::in, UpdateProc::in,
-		ResultRelation::in, Stat::out, DB0::aditi_di, DB::aditi_uo),
-		will_not_call_mercury,
-"{
-	MR_assign_structure(DB, DB0);
-	Stat = MADITI_do_bulk_operation(&DB, (MADITI_Bulk_Op) Op,
-			RelationName, UpdateProc, ResultRelation);
-}").
-
-:- func bulk_insert = int.
-:- pragma foreign_proc("C",
-	bulk_insert = (Insert::out),
-	[will_not_call_mercury, promise_pure, thread_safe],
-"{
-	Insert = MADITI_INSERT;
-}").
-
-:- func bulk_delete = int.
-:- pragma foreign_proc("C",
-	bulk_delete = (Delete::out),
-	[will_not_call_mercury, promise_pure, thread_safe],
-"{
-	Delete = MADITI_DELETE;
-}").
-
-:- func bulk_modify = int.
-:- pragma foreign_proc("C",
-	bulk_modify = (Modify::out),
-	[will_not_call_mercury, promise_pure, thread_safe],
-"{
-	Modify = MADITI_MODIFY;
-}").
-
-%-----------------------------------------------------------------------------%
-
-:- pragma foreign_code("C",
-"
-static int
-MADITI_do_insert_delete_tuple(MADITI_State *DB, MADITI_Insert_Delete operation,
-		MR_String relation_name, MR_String update_proc,
-		MR_String update_schema, MR_String tuple)
-{
-	apiID delete_output_rel;
-	apiID relation;
-
-	switch (operation) {
-		case MADITI_INSERT_TUPLE:
-			MR_DEBUG(fprintf(stderr,
-				""inserting tuple %s into relation %s\\n"",
-				tuple, relation_name));
-			MADITI_check(ADITI_FUNC(relation_open)(DB->connection,
-				DB->transaction, relation_name, &relation));
-			MADITI_check(ADITI_FUNC(relation_tuple_add)(
-				DB->connection, DB->transaction,
-				relation, tuple,
-				0 /* !use_internal_save_point */));
-			MADITI_check(ADITI_FUNC(relation_close)(DB->connection,
-				DB->transaction, relation));
-			MR_DEBUG(fprintf(stderr, ""finished insertion\\n""));
-			break;
-
-		case MADITI_DELETE_TUPLE:
-			MR_DEBUG(fprintf(stderr,
-				""deleting tuple %s from relation %s\\n"",
-				tuple , relation_name));
-			MADITI_check(MADITI_run_procedure(DB,
-				update_proc, update_schema, tuple,
-				&delete_output_rel));
-			MADITI_check(ADITI_FUNC(relation_close)(DB->connection,
-				DB->transaction, delete_output_rel));
-			MR_DEBUG(fprintf(stderr, ""finished deletion\\n""));
-			break;
-	}
-	return MADITI_OK;
-}
-
-static int
-MADITI_do_bulk_operation(MADITI_State *DB, MADITI_Bulk_Op operation,
-		MR_String relation_name, MR_String update_proc,
-		apiID closure_result)
-{
-	apiID output_relation;
-
-	MR_DEBUG(
-	    switch (operation) {
-		case MADITI_INSERT:
-			fprintf(stderr,
-				""aditi_bulk_insert(%s)\\n"", relation_name);
-			break;
-		case MADITI_DELETE:
-			fprintf(stderr,
-				""aditi_bulk_delete(%s)\\n"", relation_name);
-			break;
-		case MADITI_MODIFY:
-			fprintf(stderr,
-				""aditi_bulk_delete(%s)\\n"", relation_name);
-			break;
-	    }
-	)
-
-	/*
-	** Call the procedure generated by the compiler to apply the update.
-	*/
-	MR_DEBUG(fprintf(stderr, ""Calling update procedure %s\\n"",
-		update_proc));
-	MADITI_check(ADITI_FUNC(procedure_run)(DB->connection,
-		DB->transaction, update_proc, closure_result,
-		DB->bytecode_transaction,
-		0 /* output is not used */,
-		&output_relation));
-
-	/*
-	** Clean up.
-	*/
-	MADITI_check(ADITI_FUNC(relation_close)(DB->connection,
-		DB->transaction, closure_result));
-	return MADITI_OK;
-}
-
-").
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-	%
-	% Data conversion.
-	%
-
-:- pred construct_input_tuple(T, string).
-:- mode construct_input_tuple(in, out) is det.
-
-construct_input_tuple(Tuple, TupleStr) :-
-	NumArgs = type_ctor_arity(type_ctor(type_of(Tuple))),
-	construct_input_tuple_2(0, NumArgs, Tuple, ["("], RevStrings),
-
-	% XXX deforest this to reduce memory usage.
-	list__reverse([")\n" | RevStrings], Strings),
-	string__append_list(Strings, TupleStr).
-
-:- pred construct_input_tuple_2(int, int, T, list(string), list(string)).
-:- mode construct_input_tuple_2(in, in, in, in, out) is det.
-
-construct_input_tuple_2(Index, NumArgs, Tuple, Strings0, Strings) :-
-	( Index < NumArgs ->
-		univ_to_string(det_argument(Tuple, Index), String),
-		( Index = 0 ->
-			Strings1 = [String | Strings0]
-		;
-			Strings1 = [String, ", " | Strings0]
-		),
-		construct_input_tuple_2(Index + 1, NumArgs, Tuple,
-			Strings1, Strings)
-	;
-		Strings = Strings0
-	).
-
-	% This is very similar to io__write except
-	% a) it writes to a string
-	% b) everything is written in prefix form.
-	% c) arrays, c_pointers, type_infos and univs result in an abort.
-:- pred univ_to_string(univ, string).
-:- mode univ_to_string(in, out) is det.
-
-univ_to_string(Univ, String) :-
-	%
-	% we need to special-case the builtin types:
-	%	int, char, float, string
-	%	type_info, univ, c_pointer, array
-	%
-	( univ_to_type(Univ, String1) ->
-		string__append_list(["\"", String1, "\""], String)
-	; univ_to_type(Univ, Char) ->
-		char__to_int(Char, CharInt),
-		string__int_to_string(CharInt, String)
-	; univ_to_type(Univ, Int) ->
-		string__int_to_string(Int, String)
-	; univ_to_type(Univ, Float) ->
-		string__float_to_string(Float, String)
-	;
-		ordinary_term_to_string(Univ, String)
-	).
-
-:- pred ordinary_term_to_string(univ, string).
-:- mode ordinary_term_to_string(in, out) is det.
-
-ordinary_term_to_string(Term, String) :-
-	deconstruct(univ_value(Term), Functor, _Arity, Args),
-	quote_atom(Functor, FunctorStr),
-	term_args_to_strings(yes, Args, ["(" | FunctorStr],
-		Strings0),
-	list__reverse([")" | Strings0], Strings),
-	string__append_list(Strings, String).
-
-:- pred term_args_to_strings(bool, list(univ),
-		list(string), list(string)).
-:- mode term_args_to_strings(in, in, in, out) is det.
-
-term_args_to_strings(_, [], Strings, Strings).
-term_args_to_strings(IsFirst, [X | Xs], Strings0, Strings) :-
-	univ_to_string(X, XStr),
-	( IsFirst = yes ->
-		Comma = ""
-	;
-		Comma = ", "
-	),
-	term_args_to_strings(no, Xs, [XStr, Comma | Strings0], Strings).
-
-:- pred quote_atom(string::in, list(string)::out) is det.
-
-quote_atom(String0, Quoted) :-
-	( string__is_alnum_or_underscore(String0) ->
-		Quoted = [String0]
-	;
-		Quoted = ["'", String0, "'"]
-	).
-
-%-----------------------------------------------------------------------------%
-	%
-	% Attempt to make sense of the Aditi return code.
-	% XXX Aditi needs some way to return more descriptive
-	% error messages.
-	%
-
-error_code(Status, Error, String) :-
-	( error_code_2(Status, Error0) ->
-		Error = Error0,
-		error_message(Status, String)
-	;
-		Error = general_failure,
-		string__format("invalid Aditi error code %i",
-			[i(Status)], String)
-	).
-
-:- pred error_code_2(int::in, aditi__error::out) is semidet.
-
-error_code_2(-1, invalid_passwd).
-error_code_2(-2, invalid_passwd).
-error_code_2(-3, general_failure).
-error_code_2(-4, general_failure).
-error_code_2(-5, too_many_connections).
-error_code_2(-6, general_failure).
-error_code_2(-7, general_failure).
-error_code_2(-8, already_logged_in).
-error_code_2(-9, not_logged_in).
-error_code_2(-10, general_failure).
-error_code_2(-11, general_failure).
-error_code_2(-12, general_failure).
-error_code_2(-13, general_failure).
-error_code_2(-14, error_creating_client).
-error_code_2(-15, general_failure).
-error_code_2(-16, not_implemented).
-error_code_2(-17, abort).
-error_code_2(-18, general_failure).
-error_code_2(-19, general_failure).
-error_code_2(-20, general_failure).
-error_code_2(-21, bad_value).
-error_code_2(-22, not_connected).
-error_code_2(-23, bad_rl_code).
-error_code_2(-24, bad_rl_code).
-error_code_2(-25, bad_rl_code).
-error_code_2(-26, error_opening_relation).
-error_code_2(-27, bad_rl_code).
-error_code_2(-28, bad_rl_code).
-error_code_2(-29, security_violation).
-error_code_2(-30, bad_rl_code).
-error_code_2(-31, bad_rl_code).
-error_code_2(-32, bad_rl_code).
-error_code_2(-33, unique_key_violation).
-error_code_2(-34, relation_or_cursor_not_open).
-error_code_2(-35, general_failure).
-error_code_2(-36, bad_value).
-error_code_2(-37, timeout).
-
-:- pred error_message(int::in, string::out) is det.
-
-:- pragma c_code(error_message(Stat::in, Msg::out),
-		will_not_call_mercury,
-"
-	MR_make_aligned_string_copy(Msg,
-		ADITI_FUNC(AditiError_as_string)(
-			(ADITI_TYPE(AditiStatus)) Stat));
-").
-
Index: library/ops.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/ops.m,v
retrieving revision 1.57
diff -u -r1.57 ops.m
--- library/ops.m	15 Nov 2005 04:59:23 -0000	1.57
+++ library/ops.m	23 Feb 2006 13:44:50 -0000
@@ -310,8 +310,6 @@
                                             % Mercury (record syntax)
 ops__op_table("^", before, fx, 100).        % Mercury extension
                                             % (record syntax)
-ops__op_table("aditi_bottom_up", before, fx, 500). % Mercury extension
-ops__op_table("aditi_top_down", before, fx, 500). % Mercury extension
 ops__op_table("all", before, fxy, 950).     % Mercury/NU-Prolog extension
 ops__op_table("and", after, xfy, 720).      % NU-Prolog extension
 ops__op_table("div", after, yfx, 400).      % standard ISO Prolog
Index: mdbcomp/prim_data.m
===================================================================
RCS file: /home/mercury1/repository/mercury/mdbcomp/prim_data.m,v
retrieving revision 1.9
diff -u -r1.9 prim_data.m
--- mdbcomp/prim_data.m	27 Jan 2006 05:52:17 -0000	1.9
+++ mdbcomp/prim_data.m	24 Feb 2006 05:07:20 -0000
@@ -204,20 +204,6 @@
 :- pred mercury_term_size_prof_builtin_module(sym_name::out) is det.
 :- func mercury_term_size_prof_builtin_module = sym_name.

-    % Returns the name of the module containing the public builtins
-    % used by the Aditi transaction interface, currently "aditi".
-    % This module is not automatically imported (XXX should it be?).
-    %
-:- pred aditi_public_builtin_module(sym_name::out) is det.
-:- func aditi_public_builtin_module = sym_name.
-
-    % Returns the name of the module containing the private builtins used by
-    % the Aditi transaction interface, currently "aditi_private_builtin".
-    % This module is automatically imported iff the Aditi interface is enabled.
-    %
-:- pred aditi_private_builtin_module(sym_name::out) is det.
-:- func aditi_private_builtin_module = sym_name.
-
     % Returns the sym_name of the module with the given name in the
     % Mercury standard library.
     %
@@ -313,10 +299,6 @@
 mercury_profiling_builtin_module(mercury_profiling_builtin_module).
 mercury_term_size_prof_builtin_module = unqualified("term_size_prof_builtin").
 mercury_term_size_prof_builtin_module(mercury_term_size_prof_builtin_module).
-aditi_public_builtin_module = unqualified("aditi").
-aditi_public_builtin_module(aditi_public_builtin_module).
-aditi_private_builtin_module = unqualified("aditi_private_builtin").
-aditi_private_builtin_module(aditi_private_builtin_module).
 mercury_std_lib_module_name(Name) = unqualified(Name).
 mercury_std_lib_module_name(Name, unqualified(Name)).

@@ -326,12 +308,10 @@
     ; mercury_table_builtin_module(Module)
     ; mercury_profiling_builtin_module(Module)
     ; mercury_term_size_prof_builtin_module(Module)
-    ; aditi_private_builtin_module(Module)
     ).

 non_traced_mercury_builtin_module(Module) :-
     ( mercury_table_builtin_module(Module)
     ; mercury_profiling_builtin_module(Module)
     ; mercury_term_size_prof_builtin_module(Module)
-    ; aditi_private_builtin_module(Module)
     ).
Index: runtime/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/Mmakefile,v
retrieving revision 1.130
diff -u -r1.130 Mmakefile
--- runtime/Mmakefile	2 Dec 2005 06:53:18 -0000	1.130
+++ runtime/Mmakefile	24 Feb 2006 04:54:28 -0000
@@ -23,7 +23,6 @@
 HDRS		=	\
 			mercury.h		\
 			mercury_accurate_gc.h	\
-			mercury_aditi.h		\
 			mercury_agc_debug.h	\
 			mercury_array_macros.h	\
 			mercury_bootstrap.h	\
Index: runtime/mercury.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury.h,v
retrieving revision 1.71
diff -u -r1.71 mercury.h
--- runtime/mercury.h	11 Oct 2005 04:45:52 -0000	1.71
+++ runtime/mercury.h	24 Feb 2006 04:43:07 -0000
@@ -34,7 +34,6 @@
 				   /* the type in io.m whose foreign_type is */
 				   /* MercuryFilePtr XXX */
 #include "mercury_ho_call.h"	/* for the `MR_Closure' type */
-#include "mercury_aditi.h"	/* for the `MR_Aditi_Proc_Info' type */
 #include "mercury_bootstrap.h"
 #include "mercury_memory.h"	/* for memory allocation routines */
 #include "mercury_type_tables.h"	/* for MR_register_type_ctor_info */
Index: runtime/mercury_aditi.h
===================================================================
RCS file: runtime/mercury_aditi.h
diff -N runtime/mercury_aditi.h
--- runtime/mercury_aditi.h	20 Oct 2004 09:45:10 -0000	1.1
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,43 +0,0 @@
-/*
-** Copyright (C) 2003-2004 The University of Melbourne.
-** This file may only be copied under the terms of the GNU Library General
-** Public License - see the file COPYING.LIB in the Mercury distribution.
-*/
-
-/*
-** mercury_aditi.h - definitions for interfacing with Aditi.
-*/
-
-#ifndef	MERCURY_ADITI_H
-#define	MERCURY_ADITI_H
-
-#include "mercury_stack_layout.h"	/* for MR_Determinism */
-#include "mercury_type_info.h"		/* for MR_TypeInfo */
-
-/*
-** MR_Aditi_Proc_Info_Struct describes the top-down procedures created
-** for complex join conditions in bottom-up Aditi procedures.
-** These procedures will only ever have two arguments -- an
-** input and an output, both of which will be tuples.
-*/
-typedef struct MR_Aditi_Proc_Info_Struct {
-	MR_ProcAddr	MR_aditi_proc_addr;
-	MR_String	MR_aditi_proc_name;
-	MR_TypeInfo	MR_aditi_input_type_info;
-	MR_TypeInfo	MR_aditi_output_type_info;
-	MR_Determinism	MR_aditi_proc_detism;
-} MR_Aditi_Proc_Info;
-
-#ifndef MR_STATIC_CODE_ADDRESSES
-
-  #define MR_INIT_ADITI_PROC_INFO(api, addr) \
-		do { (api).MR_aditi_proc_addr = (addr); } while (0)
-
-#else /* MR_STATIC_CODE_ADDRESSES */
-
-  #define MR_INIT_ADITI_PROC_INFO(api, addr) \
-  		do { } while (0)
-
-#endif /* MR_STATIC_CODE_ADDRESSES */
-
-#endif	/* not MERCURY_ADITI_H */
Index: runtime/mercury_ho_call.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_ho_call.c,v
retrieving revision 1.77
diff -u -r1.77 mercury_ho_call.c
--- runtime/mercury_ho_call.c	12 Sep 2005 03:03:04 -0000	1.77
+++ runtime/mercury_ho_call.c	24 Feb 2006 04:45:06 -0000
@@ -907,7 +907,7 @@

 /*---------------------------------------------------------------------------*/
 /*
-** Code to construct closures, for use by browser/dl.m and Aditi.
+** Code to construct closures, for use by browser/dl.m.
 */

 #ifdef MR_HIGHLEVEL_CODE
Index: runtime/mercury_ho_call.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_ho_call.h,v
retrieving revision 1.12
diff -u -r1.12 mercury_ho_call.h
--- runtime/mercury_ho_call.h	29 Aug 2005 15:44:28 -0000	1.12
+++ runtime/mercury_ho_call.h	24 Feb 2006 04:45:18 -0000
@@ -133,7 +133,7 @@

 /*
 ** Build a closure for the given procedure address.
-** This is used by browser/dl.m and Aditi.
+** This is used by browser/dl.m.
 ** MR_make_closure allocates heap, so call MR_{save,restore}_transient_hp()
 ** around calls to it.
 */
Index: runtime/mercury_imp.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_imp.h,v
retrieving revision 1.25
diff -u -r1.25 mercury_imp.h
--- runtime/mercury_imp.h	15 Feb 2005 05:22:32 -0000	1.25
+++ runtime/mercury_imp.h	24 Feb 2006 04:43:40 -0000
@@ -59,7 +59,6 @@
 #include	"mercury_goto.h"
 #include	"mercury_calls.h"
 #include	"mercury_ho_call.h"
-#include	"mercury_aditi.h"
 #include	"mercury_engine.h"

 #include	"mercury_memory.h"
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.158
diff -u -r1.158 mercury_wrapper.c
--- runtime/mercury_wrapper.c	25 Oct 2005 04:00:50 -0000	1.158
+++ runtime/mercury_wrapper.c	24 Feb 2006 04:44:17 -0000
@@ -318,9 +318,6 @@
 **   calls main/2 in the user's program.
 ** - The Mercury runtime finalization, namely mercury_runtime_terminate(),
 **   calls io__finalize_state/2 in the Mercury library.
-** - `aditi__connect/6' in extras/aditi/aditi.m calls
-**   MR_do_load_aditi_rl_code() in the automatically
-**   generated C init file.
 **
 ** But, to enable Quickstart of shared libraries on Irix 5,
 ** and in general to avoid various other complications
@@ -358,8 +355,6 @@
 MR_TypeInfo     MR_type_info_for_list_of_type_info;
 MR_TypeInfo     MR_type_info_for_list_of_pseudo_type_info;

-MR_Box  (*MR_address_of_do_load_aditi_rl_code)(MR_Box, MR_Box);
-
 char        *(*MR_address_of_trace_getline)(const char *, FILE *, FILE *);
 char        *(*MR_address_of_trace_get_command)(const char *, FILE *, FILE *);
 const char  *(*MR_address_of_trace_browse_all_on_level)(FILE *,
@@ -2345,23 +2340,6 @@

 /*---------------------------------------------------------------------------*/

-MR_Box
-MR_load_aditi_rl_code(MR_Box connection, MR_Box bytecode_transaction)
-{
-    if (MR_address_of_do_load_aditi_rl_code != NULL) {
-        return (*MR_address_of_do_load_aditi_rl_code)(connection,
-            bytecode_transaction);
-    } else {
-        MR_fatal_error(
-            "attempt to load Aditi-RL code from an executable\n"
-            "not compiled for Aditi execution.\n"
-            "Add `--aditi' to C2INITFLAGS.\n"
-        );
-    }
-}
-
-/*---------------------------------------------------------------------------*/
-
 /* forward decls to suppress gcc warnings */
 void mercury_sys_init_wrapper_init(void);
 void mercury_sys_init_wrapper_init_type_tables(void);
Index: runtime/mercury_wrapper.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.h,v
retrieving revision 1.72
diff -u -r1.72 mercury_wrapper.h
--- runtime/mercury_wrapper.h	28 Sep 2005 06:00:58 -0000	1.72
+++ runtime/mercury_wrapper.h	24 Feb 2006 04:44:47 -0000
@@ -46,20 +46,6 @@
 extern	int	mercury_runtime_terminate(void);

 /*
-** MR_load_aditi_rl_code() uploads all the Aditi-RL code for
-** the program to a database specified by connection. The code
-** will be stored in the context of the given transaction.
-** The return value is described by aditi2/src/AditiStatus/AditiStatus.h
-** in the Aditi sources.
-** Aborts if the executable was not compiled for Aditi execution.
-** The return value is an Aditi error code.
-** We use MR_Box here rather than the actual argument types to
-** avoid dependencies on the Aditi headers.
-*/
-
-extern	MR_Box	MR_load_aditi_rl_code(MR_Box connection, MR_Box transaction);
-
-/*
 ** MR_init_conservative_GC() initializes the conservative collector.
 ** The conservative collector can be either the Boehm et al collector,
 ** or the MPS (Memory Pool System) kit collector.  This function is normally
@@ -124,8 +110,6 @@
 extern	void		(*MR_address_of_init_gc)(void);
 #endif

-extern	MR_Box		(*MR_address_of_do_load_aditi_rl_code)(MR_Box, MR_Box);
-
 /*
 ** MR_trace_getline(const char *, FILE *, FILE *) and
 ** MR_trace_get_command(const char *, FILE *, FILE *) are defined in
Index: scripts/Mmake.rules
===================================================================
RCS file: /home/mercury1/repository/mercury/scripts/Mmake.rules,v
retrieving revision 1.149
diff -u -r1.149 Mmake.rules
--- scripts/Mmake.rules	28 Nov 2005 02:30:31 -0000	1.149
+++ scripts/Mmake.rules	24 Feb 2006 04:49:46 -0000
@@ -25,7 +25,6 @@
 		.date0 .date .date3 .optdate .trans_opt_date \
 		.c .$O .pic_o \
 		.i .s .pic_s \
-		.rlo \
 		.java .class \
 		.il .dll .exe .cpp .cs \
 		.c_date .il_date .java_date .s_date .pic_s_date
@@ -239,11 +238,6 @@
 $(c_dates_subdir)%.c_date : %.m
 	$(MCG) $(ALL_GRADEFLAGS) $(ALL_MCGFLAGS) $(*F) $(ERR_REDIRECT)

-# Aditi-RL back-end
-$(rlos_subdir)%.rlo : %.m
-	$(MCG) $(ALL_GRADEFLAGS) $(ALL_MCGFLAGS) \
-		--aditi-only $(*F) $(ERR_REDIRECT)
-
 # Java back-end

 ifeq ($(MMAKE_USE_SUBDIRS),yes)
Index: scripts/Mmake.vars.in
===================================================================
RCS file: /home/mercury1/repository/mercury/scripts/Mmake.vars.in,v
retrieving revision 1.101
diff -u -r1.101 Mmake.vars.in
--- scripts/Mmake.vars.in	1 Feb 2006 12:10:17 -0000	1.101
+++ scripts/Mmake.vars.in	24 Feb 2006 04:50:00 -0000
@@ -607,9 +607,6 @@
 ss_subdir=$(SUBDIR)ss/
 pic_ss_subdir=$(SUBDIR)pic_ss/
 os_subdir=$(SUBDIR)os/
-# `.rlo' files are used by the Aditi query shell, which
-# doesn't know about `--use-subdirs'.
-rlos_subdir=
 ils_subdir=$(SUBDIR)ils/
 javas_subdir=$(SUBDIR)javas/
 dirs_subdir=$(SUBDIR)dirs/
Index: scripts/c2init.in
===================================================================
RCS file: /home/mercury1/repository/mercury/scripts/c2init.in,v
retrieving revision 1.46
diff -u -r1.46 c2init.in
--- scripts/c2init.in	9 May 2005 08:10:22 -0000	1.46
+++ scripts/c2init.in	24 Feb 2006 04:49:11 -0000
@@ -98,13 +98,13 @@
 esac

 case $# in
-	0) exec $MKINIT $aditi_opt -c"$maxcalls" $init_opt $trace_opt \
+	0) exec $MKINIT -c"$maxcalls" $init_opt $trace_opt \
 		$library_opt $defentry_opt $extra_inits_opt \
 		-g "$GRADE" -o "$init_c_file" $experimental_complexity_opt \
 		$extra_init_dirs $always_exec_init_opts \
 		$EXTRA_INIT_FILES $TRACE_INIT_FILES $MERCURY_ALL_LIB_MODS
 	   ;;
-	*) exec $MKINIT $aditi_opt -c"$maxcalls" $init_opt $trace_opt \
+	*) exec $MKINIT -c"$maxcalls" $init_opt $trace_opt \
 		$library_opt $defentry_opt $extra_inits_opt \
 		-g "$GRADE" -o "$init_c_file" $experimental_complexity_opt \
 		-r "$runtime_flags" \
Index: scripts/parse_ml_options.sh-subr.in
===================================================================
RCS file: /home/mercury1/repository/mercury/scripts/parse_ml_options.sh-subr.in,v
retrieving revision 1.11
diff -u -r1.11 parse_ml_options.sh-subr.in
--- scripts/parse_ml_options.sh-subr.in	3 Aug 2005 18:52:18 -0000	1.11
+++ scripts/parse_ml_options.sh-subr.in	24 Feb 2006 04:48:19 -0000
@@ -59,7 +59,6 @@
 trace_opt=""
 library_opt=""
 extra_inits_opt=""
-aditi_opt=""
 always_exec_init_opts=""
 extra_init_dirs=""
 trace_init_files=""
@@ -192,10 +191,6 @@
 		Output the generated C initialization program to the
 		specified file, rather than sending it to the standard
 		output.
-	-a, --aditi
-		Generate a function to upload Aditi-RL data to a database.
-		This option is needed when interfacing with the Aditi
-		deductive database system.
 	-A <funcname>
 		Always execute the named void function (which must take no
 		arguments) when the Mercury runtime is initialized.
@@ -419,11 +414,6 @@
 	#
 	# c2init options.
 	#
-	-a|--aditi)
-		aditi_opt="-a";;
-	-a-|--no-aditi)
-		aditi_opt="";;
-
 	-A)
 		always_exec_init_opts="$always_exec_init_opts -A $2"; shift;;

Index: util/mkinit.c
===================================================================
RCS file: /home/mercury1/repository/mercury/util/mkinit.c,v
retrieving revision 1.107
diff -u -r1.107 mkinit.c
--- util/mkinit.c	11 Oct 2005 04:45:51 -0000	1.107
+++ util/mkinit.c	24 Feb 2006 04:59:22 -0000
@@ -55,7 +55,7 @@
 #define MAXLINE     256 /* maximum number of characters per line */
                         /* (characters after this limit are ignored) */

-/* --- used to collect a list of strings, e.g. Aditi data constant names --- */
+/* --- used to collect a list of strings --- */

 typedef struct String_List_struct {
     char                        *data;
@@ -245,9 +245,6 @@
 static int          req_final_module_next = 0;
 #define MR_FINAL_REQ_MODULE_SIZE    10

-/* List of names of Aditi-RL code constants. */
-static String_List  *rl_data = NULL;
-
 /* options and arguments, set by parse_options() */
 static const char   *output_file_name = NULL;
 static const char   *entry_point = "mercury__main_2_0";
@@ -257,7 +254,6 @@
 static int          num_files;
 static char         **files;
 static MR_bool      output_main_func = MR_TRUE;
-static MR_bool      aditi = MR_FALSE;
 static MR_bool      need_initialization_code = MR_FALSE;
 static MR_bool      need_tracing = MR_FALSE;
 static const char   *experimental_complexity = NULL;
@@ -319,18 +315,6 @@
     "#endif\n"
     ;

-static const char aditi_header[] =
-    "\n"
-    "/*\n"
-    "** MR_do_load_aditi_rl_code() uploads all the Aditi-RL code\n"
-    "** for the program to a database to which the program currently\n"
-    "** has a connection, returning a status value as described in\n"
-    "** aditi2/src/api/aditi_err.h in the Aditi sources.\n"
-    "*/\n"
-    "static MR_Box MR_do_load_aditi_rl_code(MR_Box connection,\n"
-    "           MR_Box transaction);\n"
-    ;
-
 static const char mercury_funcs1[] =
     "\n"
     "#ifdef MR_HIGHLEVEL_CODE\n"
@@ -416,7 +400,6 @@
     "       &ML_type_info_for_list_of_type_info;\n"
     "   MR_type_info_for_list_of_pseudo_type_info = (MR_TypeInfo)\n"
     "       &ML_type_info_for_list_of_pseudo_type_info;\n"
-    "   MR_address_of_do_load_aditi_rl_code = %s;\n"
     "#ifdef MR_CONSERVATIVE_GC\n"
     "   MR_address_of_init_gc = init_gc;\n"
     "#endif\n"
@@ -512,8 +495,6 @@
     "}\n"
     ;

-static const char aditi_rl_data_str[] = "mercury__aditi_rl_data__";
-
 /* --- function prototypes --- */
 static  void    parse_options(int argc, char *argv[]);
 static  void    usage(void);
@@ -528,7 +509,6 @@
 static  int     output_sub_init_functions(Purpose purpose,
                     const char **func_names, int num_func_names);
 static  void    output_main_init_function(Purpose purpose, int num_bunches);
-static  void    output_aditi_load_function(void);
 static  void    output_main(void);
 static  void    process_file(const char *filename);
 static  void    process_init_file(const char *filename);
@@ -644,11 +624,6 @@
         req_final_modules, req_final_module_next);
     output_main_init_function(PURPOSE_REQ_FINAL, num_bunches);

-
-    if (aditi) {
-        output_aditi_load_function();
-    }
-
     output_main();

     if (num_errors > 0) {
@@ -674,12 +649,8 @@
     int         i;
     String_List *tmp_slist;

-    while ((c = getopt(argc, argv, "aA:c:g:iI:lo:r:tw:xX:")) != EOF) {
+    while ((c = getopt(argc, argv, "A:c:g:iI:lo:r:tw:xX:")) != EOF) {
         switch (c) {
-        case 'a':
-            aditi = MR_TRUE;
-            break;
-
         case 'A':
             /*
             ** Add the argument to the end of the list of always executed
@@ -786,7 +757,6 @@
 {
     fputs("Usage: mkinit [options] files...\n", stderr);
     fputs("Options:\n", stderr);
-    fputs("  -a:\t\tenable Aditi\n", stderr);
     fputs("  -c maxcalls:\tset the max size of an init function\n", stderr);
     fputs("  -g grade:\tset the grade of the executable\n", stderr);
     fputs("  -i:\t\tenable initialization code\n", stderr);
@@ -1010,9 +980,6 @@

     printf(header2, need_tracing);

-    if (aditi) {
-        fputs(aditi_header, stdout);
-    }
 }

 static int
@@ -1086,16 +1053,9 @@
 static void
 output_main(void)
 {
-    const char  *aditi_load_func;
     String_List *list;
     char        *options_str;

-    if (aditi) {
-        aditi_load_func = "MR_do_load_aditi_rl_code";
-    } else {
-        aditi_load_func = "NULL";
-    }
-
     if (experimental_complexity != NULL) {
         output_complexity_experiment_table(experimental_complexity);
     } else {
@@ -1106,7 +1066,7 @@

     printf(mercury_funcs1, hl_entry_point, entry_point);
     printf(mercury_funcs2, num_experimental_complexity_procs,
-        aditi_load_func, hl_entry_point, entry_point);
+        hl_entry_point, entry_point);

     printf("   MR_runtime_flags = \"");
     for (list = runtime_flags; list != NULL; list = list->next) {
@@ -1178,12 +1138,10 @@
     const char * const  reqinit_str = "REQUIRED_INIT ";
     const char * const  reqfinal_str = "REQUIRED_FINAL ";
     const char * const  endinit_str = "ENDINIT";
-    const char * const  aditi_init_str = "ADITI_DATA ";
     const int           init_strlen = strlen(init_str);
     const int           reqinit_strlen = strlen(reqinit_str);
     const int           reqfinal_strlen = strlen(reqfinal_str);
     const int           endinit_strlen = strlen(endinit_str);
-    const int           aditi_init_strlen = strlen(aditi_init_str);
     char                line[MAXLINE];
     char                *rl_data_name;
     FILE                *cfile;
@@ -1252,21 +1210,6 @@
             req_final_modules[req_final_module_next] =
                 checked_strdup(func_name);
             req_final_module_next++;
-        } else if (aditi &&
-            strncmp(line, aditi_init_str, aditi_init_strlen) == 0)
-        {
-            int j;
-
-            for (j = aditi_init_strlen; MR_isalnumunder(line[j]); j++) {
-                /* VOID */
-            }
-            line[j] = '\0';
-
-            rl_data_name = checked_malloc(
-                strlen(line + aditi_init_strlen) + 1);
-            strcpy(rl_data_name, line + aditi_init_strlen);
-            add_rl_data(rl_data_name);
-
         } else if (strncmp(line, endinit_str, endinit_strlen) == 0) {
             break;
         }
@@ -1311,114 +1254,6 @@

 /*---------------------------------------------------------------------------*/

-/*
-** Load the Aditi-RL for each module into the database.
-** MR_do_load_aditi_rl_code() is called by MR_load_aditi_rl_code()
-** in runtime/mercury_wrapper.c, which is called by
-** `aditi__connect/6' in extras/aditi/aditi.m.
-*/
-
-static void
-output_aditi_load_function(void)
-{
-    int         len;
-    int         filenum;
-    char        filename[1000];
-    int         num_rl_modules;
-    String_List *node;
-
-    printf("\n/*\n** Load the Aditi-RL code for the program into the\n");
-    printf("** currently connected database.\n*/\n");
-    printf("#include \"mercury_heap.h\"\n");
-    printf("#include \"netapi.h\"\n");
-    printf("#include \"AditiStatus.h\"\n");
-
-    /*
-    ** Declare all the RL data constants.
-    ** Each RL data constant is named mercury___aditi_rl_data__<module>.
-    */
-    for (node = rl_data; node != NULL; node = node->next) {
-        printf("extern const char %s[];\n", node->data);
-        printf("extern const int %s__length;\n", node->data);
-    }
-
-    printf("\n");
-    printf("extern MR_Box\n");
-    printf("MR_do_load_aditi_rl_code(MR_Box boxed_connection, "
-        "MR_Box boxed_transaction)\n{\n"),
-
-    /* Build an array containing the addresses of the RL data constants. */
-    printf("\tstatic const char *rl_data[] = {\n\t\t");
-    for (node = rl_data; node != NULL; node = node->next) {
-        printf("%s,\n\t\t", node->data);
-    }
-    printf("NULL};\n");
-
-    /* Build an array containing the lengths of the RL data constants. */
-    printf("\tstatic const int * const rl_data_lengths[] = {\n\t\t");
-    num_rl_modules = 0;
-    for (node = rl_data; node != NULL; node = node->next) {
-        num_rl_modules++;
-        printf("&%s__length,\n\t\t", node->data);
-    }
-    printf("0};\n");
-
-    printf("\tconst int num_rl_modules = %d;\n", num_rl_modules);
-
-    printf(
-"        /* The ADITI_TYPE macro puts a prefix on the type name. */\n"
-"        ADITI_TYPE(AditiStatus) status = ADITI_ENUM(AditiStatus_OK);\n"
-"        int    i;\n"
-"        char   *bytecode;\n"
-"        MR_Box result;\n"
-"        apiID  connection;\n"
-"        apiID  transaction;\n"
-"\n"
-"        MR_MAYBE_UNBOX_FOREIGN_TYPE(apiID, boxed_connection, \n"
-"                        connection);\n"
-"        MR_MAYBE_UNBOX_FOREIGN_TYPE(apiID, boxed_transaction, \n"
-"                        transaction);\n"
-"\n"
-"        /*\n"
-"        ** Load the Aditi-RL for each module in turn.\n"
-"        */\n"
-"        for (i = 0; i < num_rl_modules; i++) {\n"
-"            if (*rl_data_lengths[i] != 0) {\n"
-"                /* The ADITI_API macro puts a prefix on the function name. */\n"
-"                status = ADITI_API(api_blob_to_string)(*rl_data_lengths[i],\n"
-"                                (char *) rl_data[i], &bytecode);\n"
-"                /* The ADITI_ENUM macro puts a prefix on the enum constant. */\n"
-"                if (status != ADITI_ENUM(AditiStatus_OK)) {\n"
-"                    break;\n"
-"                }\n"
-"                status = ADITI_API(module_load)(connection,\n"
-"                        transaction, bytecode);\n"
-"                free(bytecode);\n"
-"                if (status != ADITI_ENUM(AditiStatus_OK)) {\n"
-"                    break;\n"
-"                }\n"
-"            }\n"
-"        }\n"
-"        MR_MAYBE_BOX_FOREIGN_TYPE(ADITI_TYPE(AditiStatus), status, result);\n"
-"        return result;\n"
-"}\n");
-}
-
-/*---------------------------------------------------------------------------*/
-
-static void
-add_rl_data(char *data)
-{
-    String_List *new_node;
-
-    new_node = checked_malloc(sizeof(String_List));
-    new_node->data = data;
-    new_node->next = rl_data;
-    rl_data = new_node;
-}
-
-/*---------------------------------------------------------------------------*/
-
 static int
 get_line(FILE *file, char *line, int line_max)
 {

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list