[m-rev.] for review: new calling convention for exported procedures to java

Peter Wang novalazy at gmail.com
Thu Nov 26 13:45:59 AEDT 2009


Branches: main

Add a new calling convention for Mercury procedures exported to Java with
`:- pragma foreign_export'.  When the procedure has multiple output arguments,
require the caller to pass instances of a `Ref<T>' class which contain a field
to hold the output value.  This is more verbose than return an `Object[]'
array, and requires extra memory allocations, but is more type-safe.  Another
advantage is that the Ref arguments will appear at the same positions as the
output arguments in the Mercury procedure.

The new convention must be enabled with `--java-export-ref-out'.  The plan is
to enable it by default in the future.

compiler/options.m:
doc/reference_manual.texi:
        Add the option.

compiler/ml_proc_gen.m:
        When the option is set, disable `--det-copy-out' and generate the
        function parameters assuming pass-by-reference for outputs.
        Only use the new convention when necessary.

compiler/mlds_to_java.m:
        Make the code to generate the exported forwarding methods account for
        `mlds_ptr_type' parameters.  These are converted to `Ref<T>' arguments.

java/runtime/Ref.java:
        Add the reference class.

diff --git a/compiler/ml_proc_gen.m b/compiler/ml_proc_gen.m
index f5922a5..2b566fb 100644
--- a/compiler/ml_proc_gen.m
+++ b/compiler/ml_proc_gen.m
@@ -54,6 +54,8 @@
 :- import_module parse_tree.prog_type.
 
 :- import_module bool.
+:- import_module getopt_io.
+:- import_module int.
 :- import_module list.
 :- import_module map.
 :- import_module maybe.
@@ -208,11 +210,43 @@ ml_gen_pragma_export_proc(ModuleInfo, PragmaExportedProc, Defn) :-
     PragmaExportedProc = pragma_exported_proc(Lang, PredId, ProcId,
         ExportName, ProgContext),
     ml_gen_proc_label(ModuleInfo, PredId, ProcId, Name, ModuleName),
-    FuncParams = ml_gen_proc_params(ModuleInfo, PredId, ProcId),
+    ml_gen_export_proc_params(ModuleInfo, PredId, ProcId, FuncParams),
     MLDS_Context = mlds_make_context(ProgContext),
     Defn = ml_pragma_export(Lang, ExportName,
         qual(ModuleName, module_qual, Name), FuncParams, MLDS_Context).
 
+:- pred ml_gen_export_proc_params(module_info::in, pred_id::in, proc_id::in,
+    mlds_func_params::out) is det.
+
+ml_gen_export_proc_params(ModuleInfo, PredId, ProcId, FuncParams) :-
+    module_info_get_globals(ModuleInfo, Globals),
+    globals.get_target(Globals, Target),
+    (
+        Target = target_java,
+        globals.lookup_bool_option(Globals, java_export_ref_out, yes),
+        globals.set_option(det_copy_out, bool(no), Globals, GlobalsByRef),
+        module_info_set_globals(GlobalsByRef, ModuleInfo, ModuleInfoByRef),
+        FuncParamsByRef = ml_gen_proc_params(ModuleInfoByRef, PredId, ProcId),
+        FuncParamsByRef = mlds_func_params(Args, ReturnTypes),
+        (
+            ReturnTypes = [],
+            % If there is only one output argument, then we should use the
+            % return value.
+            list.filter(has_ptr_type, Args, OutArgs),
+            list.length(OutArgs) > 1
+        ;
+            ReturnTypes = [_ | _]
+        )
+    ->
+        FuncParams = FuncParamsByRef
+    ;
+        FuncParams = ml_gen_proc_params(ModuleInfo, PredId, ProcId)
+    ).
+
+:- pred has_ptr_type(mlds_argument::in) is semidet.
+
+has_ptr_type(mlds_argument(_, mlds_ptr_type(_), _)).
+
 %-----------------------------------------------------------------------------%
 %
 % Stuff to generate MLDS code for HLDS predicates & functions.
diff --git a/compiler/mlds_to_java.m b/compiler/mlds_to_java.m
index 8229e62..84437da 100644
--- a/compiler/mlds_to_java.m
+++ b/compiler/mlds_to_java.m
@@ -491,10 +491,14 @@ mlds_get_java_foreign_code(AllForeignCode) = ForeignCode :-
 :- pred output_exports(java_out_info::in, indent::in,
     list(mlds_pragma_export)::in, io::di, io::uo) is det.
 
-output_exports(_, _, [], !IO).
-output_exports(Info, Indent, [Export | Exports], !IO) :-
-    Export = ml_pragma_export(Lang, ExportName, MLDS_Name, MLDS_Signature,
-        MLDS_Context),
+output_exports(Info, Indent, Exports, !IO) :-
+    list.foldl(output_export(Info, Indent), Exports, !IO).
+
+:- pred output_export(java_out_info::in, indent::in, mlds_pragma_export::in,
+    io::di, io::uo) is det.
+
+output_export(Info, Indent, Export, !IO) :-
+    Export = ml_pragma_export(Lang, ExportName, _, MLDS_Signature, _),
     expect(unify(Lang, lang_java), this_file,
         "foreign_export for language other than Java."),
     indent_line(Indent, !IO),
@@ -512,6 +516,30 @@ output_exports(Info, Indent, [Export | Exports], !IO) :-
         io.write_string("java.lang.Object []", !IO)
     ),
     io.write_string(" " ++ ExportName, !IO),
+    (
+        list.member(Param, Parameters),
+        has_ptr_type(Param)
+    ->
+        (
+            ( ReturnTypes = []
+            ; ReturnTypes = [_]
+            ),
+            output_export_ref_out(Info, Indent, Export, !IO)
+        ;
+            ReturnTypes = [_, _ | _],
+            unexpected(this_file, "output_export: multiple return values")
+        )
+    ;
+        output_export_no_ref_out(Info, Indent, Export, !IO)
+    ).
+
+:- pred output_export_no_ref_out(java_out_info::in, indent::in,
+    mlds_pragma_export::in, io::di, io::uo) is det.
+
+output_export_no_ref_out(Info, Indent, Export, !IO) :-
+    Export = ml_pragma_export(_Lang, _ExportName, MLDS_Name, MLDS_Signature,
+        MLDS_Context),
+    MLDS_Signature = mlds_func_params(Parameters, ReturnTypes),
     output_params(Info, Indent + 1, MLDS_Context, Parameters, !IO),
     io.nl(!IO),
     indent_line(Indent, !IO),
@@ -523,17 +551,122 @@ output_exports(Info, Indent, [Export | Exports], !IO) :-
         ReturnTypes = [_ | _],
         io.write_string("return ", !IO)
     ),
+    write_export_call(MLDS_Name, Parameters, !IO),
+    indent_line(Indent, !IO),
+    io.write_string("}\n", !IO).
+
+:- pred output_export_ref_out(java_out_info::in, indent::in,
+    mlds_pragma_export::in, io::di, io::uo) is det.
+
+output_export_ref_out(Info, Indent, Export, !IO) :-
+    Export = ml_pragma_export(_Lang, _ExportName, MLDS_Name, MLDS_Signature,
+        MLDS_Context),
+    MLDS_Signature = mlds_func_params(Parameters, ReturnTypes),
+    list.filter(has_ptr_type, Parameters, RefParams, NonRefParams),
+
+    output_export_params_ref_out(Info, Indent, MLDS_Context, Parameters, !IO),
+    io.nl(!IO),
+    indent_line(Indent, !IO),
+    io.write_string("{\n", !IO),
+    indent_line(Indent + 1, !IO),
+    io.write_string("java.lang.Object[] results = ", !IO),
+    write_export_call(MLDS_Name, NonRefParams, !IO),
+
+    ( ReturnTypes = [] ->
+        FirstRefArg = 0
+    ; ReturnTypes = [mlds_native_bool_type] ->
+        % Semidet procedure.
+        FirstRefArg = 1
+    ;
+        unexpected(this_file, "output_export_ref_out: unexpected ReturnTypes")
+    ),
+    list.foldl2(assign_ref_output(Info, Indent + 1), RefParams,
+        FirstRefArg, _, !IO),
+    (
+        FirstRefArg = 0
+    ;
+        FirstRefArg = 1,
+        indent_line(Indent + 1, !IO),
+        Stmt = "return ((java.lang.Boolean) results[0]).booleanValue();\n",
+        io.write_string(Stmt, !IO)
+    ),
+    indent_line(Indent, !IO),
+    io.write_string("}\n", !IO).
+
+:- pred output_export_params_ref_out(java_out_info::in, indent::in,
+    mlds_context::in, list(mlds_argument)::in, io::di, io::uo) is det.
+
+output_export_params_ref_out(Info, Indent, Context, Parameters, !IO) :-
+    io.write_string("(", !IO),
+    (
+        Parameters = []
+    ;
+        Parameters = [_ | _],
+        io.nl(!IO),
+        io.write_list(Parameters, ",\n",
+            output_export_param_ref_out(Info, Indent + 1, Context), !IO)
+    ),
+    io.write_string(")", !IO).
+
+:- pred output_export_param_ref_out(java_out_info::in, indent::in,
+    mlds_context::in, mlds_argument::in, io::di, io::uo) is det.
+
+output_export_param_ref_out(Info, Indent, _Context, Argument, !IO) :-
+    Argument = mlds_argument(Name, Type, _),
+    indent_line(Indent, !IO),
+    ( Type = mlds_ptr_type(InnerType) ->
+        io.write_string("jmercury.runtime.Ref<", !IO),
+        output_boxed_type(Info, InnerType, !IO),
+        io.write_string("> ", !IO)
+    ;
+        output_type(Info, normal_style, Type, !IO),
+        io.write_string(" ", !IO)
+    ),
+    output_name(Name, !IO).
+
+:- pred write_export_call(mlds_qualified_entity_name::in,
+    list(mlds_argument)::in, io::di, io::uo) is det.
+
+write_export_call(MLDS_Name, Parameters, !IO) :-
     output_fully_qualified_name(MLDS_Name, !IO),
     io.write_char('(', !IO),
-    WriteCallArg = (pred(Arg::in, !.IO::di, !:IO::uo) is det :-
-        Arg = mlds_argument(Name, _, _),
-        output_name(Name, !IO)
-    ),
-    io.write_list(Parameters, ", ", WriteCallArg, !IO),
-    io.write_string(");\n", !IO),
+    io.write_list(Parameters, ", ", write_argument_name, !IO),
+    io.write_string(");\n", !IO).
+
+:- pred write_argument_name(mlds_argument::in, io::di, io::uo) is det.
+
+write_argument_name(Arg, !IO) :-
+    Arg = mlds_argument(Name, _, _),
+    output_name(Name, !IO).
+
+:- pred assign_ref_output(java_out_info::in, indent::in, mlds_argument::in,
+    int::in, int::out, io::di, io::uo) is det.
+
+assign_ref_output(Info, Indent, Arg, N, N + 1, !IO) :-
+    Arg = mlds_argument(Name, Type, _),
     indent_line(Indent, !IO),
-    io.write_string("}\n", !IO),
-    output_exports(Info, Indent, Exports, !IO).
+    output_name(Name, !IO),
+    io.write_string(".val = (", !IO),
+    ( Type = mlds_ptr_type(InnerType) ->
+        output_boxed_type(Info, InnerType, !IO)
+    ;
+        output_boxed_type(Info, Type, !IO)
+    ),
+    io.format(") results[%d];\n", [i(N)], !IO).
+
+:- pred output_boxed_type(java_out_info::in, mlds_type::in,
+    io::di, io::uo) is det.
+
+output_boxed_type(Info, Type, !IO) :-
+    ( java_builtin_type(Type, _, JavaBoxedName, _) ->
+        io.write_string(JavaBoxedName, !IO)
+    ;
+        output_type(Info, normal_style, Type, !IO)
+    ).
+
+:- pred has_ptr_type(mlds_argument::in) is semidet.
+
+has_ptr_type(mlds_argument(_, mlds_ptr_type(_), _)).
 
 %-----------------------------------------------------------------------------%
 %
diff --git a/compiler/options.m b/compiler/options.m
index 6a323a0..7a94271 100644
--- a/compiler/options.m
+++ b/compiler/options.m
@@ -411,6 +411,9 @@
     ;       put_commit_in_own_func
     ;       put_nondet_env_on_heap
 
+    % Java back-end compilation model options
+    ;       java_export_ref_out
+
     % IL back-end compilation model options
     ;       verifiable_code
     ;       il_refany_fields
@@ -1297,6 +1300,9 @@ option_defaults_2(compilation_model_option, [
     put_commit_in_own_func              -   bool(no),
     put_nondet_env_on_heap              -   bool(no),
 
+    % Java back-end compilation model options
+    java_export_ref_out                 -   bool(no),
+
     % IL back-end compilation model options
     verifiable_code                     -   bool(no),
     il_funcptr_types                    -   bool(no),
@@ -2151,6 +2157,8 @@ long_option("det-copy-out",         det_copy_out).
 long_option("nondet-copy-out",      nondet_copy_out).
 long_option("put-commit-in-own-func",   put_commit_in_own_func).
 long_option("put-nondet-env-on-heap",   put_nondet_env_on_heap).
+% Java back-end compilation model options
+long_option("java-export-ref-out",  java_export_ref_out).
 % IL back-end compilation model options
 long_option("verifiable-code",      verifiable_code).
 long_option("verifiable",           verifiable_code).
@@ -4257,7 +4265,7 @@ options_help_compilation_model -->
         "\tUse an alternative higher-level data representation.",
 %       "--high-level\t\t\t(grades: hl, hl_nest, il, java)",
         "--high-level\t\t\t(grades: hl, il, java)",
-        "\tAn abbreviation for `--high-level-code --high-level-data'."
+        "\tAn abbreviation for `--high-level-code --high-level-data'.",
 % The --gcc-nested-functions option is not yet documented,
 % because it doesn't pass our test suite, and it is
 % probably not very useful.
@@ -4296,6 +4304,9 @@ options_help_compilation_model -->
 %       "\tnondeterministic Mercury procedures on the heap,",
 %       "\trather than on the stack.",
 %
+        "--java-export-ref-out",
+        "\tUse pass-by-reference for exported procedures with multiple",
+        "\toutput arguments."
 %   ]),
 %   io.write_string("\n      IL back-end compilation model options:\n"),
 %   write_tabbed_lines([
diff --git a/doc/reference_manual.texi b/doc/reference_manual.texi
index 9e3ddac..fbb7424 100644
--- a/doc/reference_manual.texi
+++ b/doc/reference_manual.texi
@@ -6969,9 +6969,6 @@ the length of the array is the number of elements in the tuple.
 Mercury variables whose type is a type variable will be passed as
 @code{java.lang.Object}.
 Mercury array types are mapped to Java array types.
-When compiling with @samp{--no-high-level-data}, all other Mercury variables
-are passed as @code{java.lang.Object[]}.
-When compiling with @samp{--high-level-data},
 Mercury variables whose type is a Mercury discriminated union type
 will be passed as a Java type whose type name is determined from
 the Mercury type name (ignoring any type parameters) followed by
@@ -7000,13 +6997,20 @@ whose result has an input mode, then the Mercury function result is
 appended to the list of input parameters, so that the Mercury function
 result becomes the last parameter to the corresponding Java function.
 
+The handling of multiple output arguments depends on the option
+ at samp{--java-export-ref-out}.  It is disabled by default, but in the
+future will become enabled by default.
+
+ at noindent
+Without @samp{--java-export-ref-out}:
+
 The result of the Java function will be a sequence comprised of
 the outputs of the Mercury procedure.  If the Mercury procedure's
 determinism indicates that it can fail, then its first output will
 be a @samp{boolean} success indicator, with a @samp{true} value
 denoting success and a @samp{false} value denoting failure. The
 remaining outputs will be the subsequence of the Mercury procedure's
-arguments and function result (if any) that have output modes.            
+arguments and function result (if any) that have output modes.
  
 If the sequence has length zero then the return type of the
 Java function is @samp{void}.
@@ -7014,7 +7018,30 @@ If the sequence has length one then the return type of the
 Java function is the type of the item in question.
 Otherwise, the Java function will return an array of type
 @samp{java.lang.Object[]}.
-                                                                                
+
+ at noindent
+With @samp{--java-export-ref-out}:
+
+If the Mercury procedure is deterministic and has no output arguments,
+then the return type of the Java function is @samp{void}; if it has
+one output argument, then the return value of the function is that
+output argument.
+
+If the Mercury procedure is deterministic and has two or more output
+arguments, then the return type of the Java function is @samp{void}.
+At the position of each output argument, the Java function takes a
+value of the type @samp{jmercury.runtime.Ref<T>} where @samp{T} is the
+Java type corresponding to the type of the output argument.
+ at samp{Ref} is a class with a single field @samp{val}, which is
+assigned the output value when the function returns.
+
+If the Mercury procedure is semi-deterministic then the Java function
+returns a @samp{boolean}.  A @samp{true} return value denotes success
+and @samp{false} denotes failure.  Output arguments are handled in the
+same way as multiple outputs deterministic procedures, using the
+ at samp{Ref} class.  On failure the values of the @samp{val} fields are
+undefined.
+
 Arguments of type @samp{io.state} or @samp{store.store(_)} are not
 passed or returned at all.
 (The reason for this is that these types represent mutable state,
diff --git a/java/runtime/Ref.java b/java/runtime/Ref.java
new file mode 100644
index 0000000..00b07be
--- /dev/null
+++ b/java/runtime/Ref.java
@@ -0,0 +1,14 @@
+//
+// Copyright (C) 2009 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.
+//
+// This class is used in some cases to hold output values of Mercury
+// procedures exported to Java.
+//
+
+package jmercury.runtime;
+
+public class Ref<T> {
+    public T val;
+}

--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list