[m-rev.] diff: C# interface for .NET backend.
Peter Ross
peter.ross at miscrit.be
Tue May 1 02:48:49 AEST 2001
On Tue, May 01, 2001 at 12:41:44AM +1000, Tyson Dowd wrote:
> Hi,
>
> This is the new C# interface. If it bootstraps in hlc.gc, I plan to
> commit it to the main branch pretty soon. If it works out well (some
> more testing is needed) I will probably migrate the MC++ interface to
> use a similar technique.
>
> I'm keen to commit soon because:
> - this change is on petdr's critical path
> - this change splits a module apart, which is hard to maintain
> across branches
> - there are quite a few useful code clean-ups in this code that
> I find myself re-doing in other workspaces.
>
> The main change that will affect other people is the change to the
> mlds__var_name type.
>
> ===================================================================
>
>
> Estimated hours taken: 45
> Branches: main
>
> Implement a C# interface for the .NET backend.
>
> To use it, you currently need to set
> --backend-foreign-language csharp --use-foreign-language csharp
> in your MCFLAGS.
>
> The C# foreign language interface works by introducing a new sort of
> MLDS statement called outline_target_code. outline_target_code is expected
> to be turned into a separate procedure in a separate file. This is
> quite different to normal foreign code which has been renamed as inline
> target code, as it is really intended to be generated inline, inside the
> generated code.
>
> Because outline_target_code is expected to be generated outside the
> normal code, we don't need to generate variable renamings,
> initializations, casts and other complicated interfacing code.
>
> Any marshalling is done by the backend, which knows how to marshall
> arguments across the boundary into the outline code and back. In the
> case of marshalling to C# from the .NET backend, we currently don't do
> anything special (part of the point of .NET is that data
> representation don't have to change very often just because you are
> using different languages, so this is a property we should try to
> preserve).
>
> The actual implementation of the foreign code is therefore very simple.
> Simply generate an appropriate procedure, and insert the user's code in
> the middle.
>
> The bulk of this change to delay the mangling of MLDS var names, so we
> can still use the original user's var name when we output the outline
> procedure (since the user's foreign code will refer to these var names,
> it's important to keep them around).
>
> compiler/foreign.m:
> Handle the csharp foreign language.
>
> compiler/globals.m:
> Fix an XXX about converting to lowercase to do language name
> comparisons.
> Add new predicates to make conversion of foreign languages
> to strings more uniform.
>
> compiler/handle_options.m:
> Don't set backend_foreign_language to the default if it has
> already been set by hand.
>
> compiler/ml_call_gen.m:
> compiler/ml_code_gen.m:
> compiler/ml_code_util.m:
> Delay the mangling of MLDS var names by keeping the variable
> number around until the output phase.
>
> Slightly generalize the handling of foreign language interfacing.
> Handle C# foreign language interfacing.
>
> Add value_output_vars to the ml_gen_info, which are the variables
> returned rather than passed by reference. We need to know
> these variables for C# interfacing so that we can handle the return
> value of the forwarding function.
>
> Mark the beginning and end of the MLDS foreign language processing as
> a "sub-module" (in comments at least). Later I may put this code
> into a separate module.
>
Mention renaming of c_code predicate names to foreign_code.
> compiler/ml_elim_nested.m:
> compiler/ml_optimize.m:
> compiler/ml_string_switch.m:
> compiler/ml_type_gen.m:
> compiler/ml_unify_gen.m:
> compiler/ml_util.m:
> compiler/rtti_to_mlds.m:
> Handle the new var_name type, and the new target_code constructors.
>
> compiler/mlds.m:
> Add outline_target_code which is handled differently to the old
> target_code (which has been renamed inline_target_code).
>
> Change the definiton for mlds__var_name.
>
>
> compiler/mlds_to_c.m:
> Factor out mlds_output_to_file.
>
Mention that you have made changes to
"Handle the new var_name type, and the new target_code constructors."
> compiler/mlds_to_csharp.m:
> A new module to generate C# code suitable for foreign language
> interfacing. This is largely lifted from the MC++ code, with a few
> changes to the output syntax.
>
> compiler/mlds_to_il.m:
> Return the set of foreign languages processed instead of a bool
> saying wither MC++ was present. This is so we can generate the
> appropriate output .cs or .cpp files, and because we need to keep
> track of all the external assembly references we need to put in the
> .il file.
>
> Handle the inline_target_code and mlds__var_name changes.
>
> compiler/mlds_to_ilasm.m:
> Output .cpp and .cs files conditionally.
> Factor out output_to_file.
> Move MC++ output code to mlds_to_mcpp.m
>
> compiler/mlds_to_java.m:
> Factor out output_to_file.
> Handle the new var_name type, and the new target_code constructors.
>
> compiler/mlds_to_mcpp.m:
> New file to handle generating MC++ code suitable for foreign language
> interfacing.
>
> compiler/options.m:
> Add a way of setting the backend-foreign-language option.
>
> compiler/passes_aux.m:
> Add output_to_file which is used by the MLDS backend to generate
> output files.
>
> compiler/prog_data.m:
> Uncomment csharp as a foreign language.
>
> Index: compiler/ml_code_gen.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/ml_code_gen.m,v
> retrieving revision 1.82
> diff -u -r1.82 ml_code_gen.m
> --- compiler/ml_code_gen.m 2001/04/18 15:15:25 1.82
> +++ compiler/ml_code_gen.m 2001/04/30 13:50:33
> @@ -2043,6 +2050,12 @@
> % these should have been expanded out by now
> { error("ml_gen_goal_expr: unexpected shorthand") }.
>
> +% :- module ml_foreign.
> +%
> +% ml_foreign creates MLDS code to execute foreign language code.
> +%
> +%
> +
> :- pred ml_gen_nondet_pragma_c_code(code_model, pragma_foreign_proc_attributes,
Maybe you should change this to ml_gen_nondet_pragma_foreign_code to be
consistent.
> pred_id, proc_id, list(prog_var),
> list(maybe(pair(string, mode))), list(prog_type), prog_context,
> @@ -2225,10 +2238,10 @@
> raw_target_code(HashUndefs),
> raw_target_code("}\n")
> ] },
> - { Starting_C_Code_Stmt = target_code(lang_C, Starting_C_Code) },
> + { Starting_C_Code_Stmt = inline_target_code(lang_C, Starting_C_Code) },
> { Starting_C_Code_Statement = mlds__statement(
> atomic(Starting_C_Code_Stmt), mlds__make_context(Context)) },
> - { Ending_C_Code_Stmt = target_code(lang_C, Ending_C_Code) },
> + { Ending_C_Code_Stmt = inline_target_code(lang_C, Ending_C_Code) },
> { Ending_C_Code_Statement = mlds__statement(
> atomic(Ending_C_Code_Stmt), mlds__make_context(Context)) },
> { MLDS_Statements = list__condense([
> @@ -2239,6 +2252,63 @@
> ]) },
> { MLDS_Decls = ConvDecls }.
>
> +:- pred ml_gen_ordinary_pragma_foreign_code(code_model,
> + pragma_foreign_proc_attributes,
> + pred_id, proc_id, list(prog_var),
> + list(maybe(pair(string, mode))), list(prog_type),
> + string, prog_context,
> + mlds__defns, mlds__statements, ml_gen_info, ml_gen_info).
> +:- mode ml_gen_ordinary_pragma_foreign_code(in, in, in, in, in, in,
> + in, in, in, out, out, in, out) is det.
> +
> +ml_gen_ordinary_pragma_foreign_code(CodeModel, Attributes,
> + PredId, ProcId, ArgVars, ArgDatas, OrigArgTypes,
> + Foreign_Code, Context, MLDS_Decls, MLDS_Statements) -->
> + { foreign_language(Attributes, Lang) },
> + ( { Lang = c },
> + ml_gen_ordinary_pragma_c_code(CodeModel, Attributes,
> + PredId, ProcId, ArgVars, ArgDatas, OrigArgTypes,
> + Foreign_Code, Context, MLDS_Decls, MLDS_Statements)
> + ; { Lang = managed_cplusplus },
> + ml_gen_ordinary_pragma_c_code(CodeModel, Attributes,
> + PredId, ProcId, ArgVars, ArgDatas, OrigArgTypes,
> + Foreign_Code, Context, MLDS_Decls, MLDS_Statements)
> + ; { Lang = csharp },
> + ml_gen_ordinary_pragma_csharp_code(CodeModel, Attributes,
> + PredId, ProcId, ArgVars, ArgDatas, OrigArgTypes,
> + Foreign_Code, Context, MLDS_Decls, MLDS_Statements)
> + ).
> +
> +:- pred ml_gen_ordinary_pragma_csharp_code(code_model,
> + pragma_foreign_proc_attributes,
> + pred_id, proc_id, list(prog_var),
> + list(maybe(pair(string, mode))), list(prog_type),
> + string, prog_context,
> + mlds__defns, mlds__statements, ml_gen_info, ml_gen_info).
> +:- mode ml_gen_ordinary_pragma_csharp_code(in, in, in, in, in, in,
> + in, in, in, out, out, in, out) is det.
> +
> + % For ordinary (not model_non) pragma foreign_code in C#,
> + % we generate a call to an out-of-line procedure that contains
> + % the user's code.
> +
What happens if you declare nondet pragma foreign_code in C#?
> +ml_gen_ordinary_pragma_csharp_code(_CodeModel, Attributes,
> + _PredId, _ProcId, _ArgVars, _ArgDatas, _OrigArgTypes,
> + ForeignCode, Context, MLDS_Decls, MLDS_Statements) -->
> + { foreign_language(Attributes, ForeignLang) },
> + { MLDSContext = mlds__make_context(Context) },
> + =(MLDSGenInfo),
> + { ml_gen_info_get_value_output_vars(MLDSGenInfo, OutputVars) },
> + ml_gen_var_list(OutputVars, OutputVarLvals),
> + { OutlineStmt = outline_target_code(ForeignLang, OutputVarLvals,
> + ForeignCode) },
> +
> + { MLDS_Statements = [
> + mlds__statement(atomic(OutlineStmt), MLDSContext)
> + ] },
> + { MLDS_Decls = [] }.
> +
> +
> :- pred ml_gen_ordinary_pragma_c_code(code_model,
> pragma_foreign_proc_attributes,
> pred_id, proc_id, list(prog_var),
> Index: compiler/ml_util.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/ml_util.m,v
> retrieving revision 1.7
> diff -u -r1.7 ml_util.m
> --- compiler/ml_util.m 2001/02/20 07:52:15 1.7
> +++ compiler/ml_util.m 2001/04/30 13:50:33
> @@ -250,6 +264,14 @@
> default_contains_statement(default_case(Statement), SubStatement) :-
> statement_contains_statement(Statement, SubStatement).
>
> +has_foreign_languages(Statement, Langs) :-
> + GetTargetCode = (pred(Lang::out) is nondet :-
> + statement_contains_statement(Statement, SubStatement),
> + SubStatement = statement(atomic(
> + outline_target_code(Lang, _, _)), _)
> + ),
> + solutions(GetTargetCode, Langs).
> +
> %-----------------------------------------------------------------------------%
> %
> % routines that deal with definitions
> @@ -259,9 +281,22 @@
> Defn = mlds__defn(_Name, _Context, _Flags, Body),
> Body = function(_, _, yes(FunctionBody)),
> statement_contains_statement(FunctionBody, Statement),
> + Statement = mlds__statement(Stmt, _),
> + (
> + Stmt = atomic(inline_target_code(TargetLang, _)),
> + TargetLang \= NativeTargetLang
> + ;
> + Stmt = atomic(outline_target_code(_, _, _))
> + ).
> +
> +defn_contains_outline_foreign_code(ForeignLang, Defn) :-
> + Defn = mlds__defn(_Name, _Context, _Flags, Body),
> + Body = function(_, _, yes(FunctionBody)),
> + statement_contains_statement(FunctionBody, Statement),
> Statement = mlds__statement(Stmt, _),
> - Stmt = atomic(target_code(TargetLang, _)),
> - TargetLang \= NativeTargetLang.
> + (
> + Stmt = atomic(outline_target_code(ForeignLang, _, _))
> + ).
>
Don't need this set of brackets.
> defn_is_type(Defn) :-
> Defn = mlds__defn(Name, _Context, _Flags, _Body),
> Index: compiler/mlds.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mlds.m,v
> retrieving revision 1.49
> diff -u -r1.49 mlds.m
> --- compiler/mlds.m 2001/02/28 15:59:18 1.49
> +++ compiler/mlds.m 2001/04/30 13:50:33
> @@ -1011,7 +1011,6 @@
> ; mark_hp(mlds__lval)
> % Tell the heap sub-system to store a marker
> % (for later use in restore_hp/1 instructions)
> - % in the specified lval
> %
Why delete this line?
> % It's OK for the target to treat this as a no-op,
> % and probably that is what most targets will do.
> @@ -1034,12 +1033,31 @@
> % foreign language interfacing
> %
>
> - ; target_code(target_lang, list(target_code_component))
> + ; inline_target_code(target_lang, list(target_code_component))
> % Do whatever is specified by the
> % target_code_components, which can be any piece
> % of code in the specified target language (C,
> % assembler, or whatever) that does not have any
> % non-local flow of control.
> + % This is implemented by embedding the target
> + % code in the output stream of instructions or
> + % statements.
> + ; outline_target_code(
> + foreign_language,
> + % the foreign language of this code
> + list(mlds__lval),
> + % where to store return value(s)
> + string
> + % the user's foreign language code
What is the difference between the user's foreign language and the foreign
language of this code?
> + )
> + % Do whatever is specified by the string, which
> + % can be any piece of code in the specified
> + % foreign language (C#, managed C++, or
> + % whatever).
> + % This is implemented by calling an externally
> + % defined function, which the backend must
> + % generate the definition for (in some other
> + % file perhaps) and calling it.
> .
>
> %
> @@ -1125,7 +1143,10 @@
> % An mlds__var represents a variable or constant.
> %
> :- type mlds__var == mlds__fully_qualified_name(mlds__var_name).
> -:- type mlds__var_name == string.
> +:- type mlds__var_name --->
> + mlds__var_name(string, maybe(int)).
> + % var name and perhaps a unique number to be added as a
> + % suffix where necessary.
>
> %
> % An lval represents a data location or variable that can be used
> Index: compiler/mlds_to_c.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_c.m,v
> retrieving revision 1.84
> diff -u -r1.84 mlds_to_c.m
> --- compiler/mlds_to_c.m 2001/04/11 10:10:13 1.84
> +++ compiler/mlds_to_c.m 2001/04/30 13:50:34
> @@ -96,37 +96,13 @@
> module_name_to_file_name(ModuleSymName, ".h.tmp", yes, TmpHeaderFile),
> module_name_to_file_name(ModuleSymName, ".h", yes, HeaderFile),
> { Indent = 0 },
> - mlds_output_to_file(SourceFile, mlds_output_src_file(Indent, MLDS)),
> - mlds_output_to_file(TmpHeaderFile, mlds_output_hdr_file(Indent, MLDS)),
> + output_to_file(SourceFile, mlds_output_src_file(Indent, MLDS)),
> + output_to_file(TmpHeaderFile, mlds_output_hdr_file(Indent, MLDS)),
> update_interface(HeaderFile).
> %
> % XXX at some point we should also handle output of any non-C
> % foreign code (Ada, Fortran, etc.) to appropriate files.
>
> -:- pred mlds_output_to_file(string, pred(io__state, io__state),
> - io__state, io__state).
> -:- mode mlds_output_to_file(in, pred(di, uo) is det, di, uo) is det.
> -
> -mlds_output_to_file(FileName, Action) -->
> - globals__io_lookup_bool_option(verbose, Verbose),
> - globals__io_lookup_bool_option(statistics, Stats),
> - maybe_write_string(Verbose, "% Writing to file `"),
> - maybe_write_string(Verbose, FileName),
> - maybe_write_string(Verbose, "'...\n"),
> - maybe_flush_output(Verbose),
> - io__tell(FileName, Res),
> - ( { Res = ok } ->
> - Action,
> - io__told,
> - maybe_write_string(Verbose, "% done.\n"),
> - maybe_report_stats(Stats)
> - ;
> - maybe_write_string(Verbose, "\n"),
> - { string__append_list(["can't open file `",
> - FileName, "' for output."], ErrorMessage) },
> - report_error(ErrorMessage)
> - ).
> -
> %
> % Generate the header file
> %
> @@ -561,6 +537,8 @@
> io__write_string(Code).
> mlds_output_c_defn(_Indent, user_foreign_code(managed_cplusplus, _, _)) -->
> { sorry(this_file, "foreign code other than C") }.
> +mlds_output_c_defn(_Indent, user_foreign_code(csharp, _, _)) -->
> + { sorry(this_file, "foreign code other than C") }.
>
> :- pred mlds_output_pragma_export_decl(mlds_module_name, indent,
> mlds__pragma_export, io__state, io__state).
> @@ -1035,7 +1013,8 @@
> :- mode mlds_make_base_class(in, in, out, in, out) is det.
>
> mlds_make_base_class(Context, ClassId, MLDS_Defn, BaseNum0, BaseNum) :-
> - BaseName = string__format("base_%d", [i(BaseNum0)]),
> + BaseName = mlds__var_name(string__format("base_%d", [i(BaseNum0)]),
> + no),
> Type = ClassId,
> MLDS_Defn = mlds__defn(data(var(BaseName)), Context,
> ml_gen_public_field_decl_flags, data(Type, no_initializer)),
> @@ -1475,7 +1454,7 @@
> :- mode mlds_output_data_name(in, di, uo) is det.
>
> mlds_output_data_name(var(Name)) -->
> - mlds_output_mangled_name(Name).
> + mlds_output_mangled_name(ml_var_name_to_string(Name)).
> mlds_output_data_name(common(Num)) -->
> io__write_string("common_"),
> io__write_int(Num).
> @@ -2481,16 +2460,20 @@
> %
> % foreign language interfacing
> %
> -mlds_output_atomic_stmt(_Indent, _FuncInfo, target_code(TargetLang, Components),
> - Context) -->
> +mlds_output_atomic_stmt(_Indent, _FuncInfo,
> + inline_target_code(TargetLang, Components), Context) -->
> ( { TargetLang = lang_C } ->
> list__foldl(
> mlds_output_target_code_component(Context),
> Components)
> ;
> - { error("mlds_to_c.m: sorry, target_code only works for lang_C") }
> + { error("mlds_to_c.m: sorry, inline_target_code only works for lang_C") }
> ).
>
> +mlds_output_atomic_stmt(_Indent, _FuncInfo,
> + outline_target_code(_ForeignLang, _Lvals, _Code), _Context) -->
> + { error("mlds_to_c.m: outline_target_code is not used in C backend") }.
> +
> :- pred mlds_output_target_code_component(mlds__context, target_code_component,
> io__state, io__state).
> :- mode mlds_output_target_code_component(in, in, di, uo) is det.
> @@ -2626,7 +2609,12 @@
> :- mode mlds_output_var(in, di, uo) is det.
>
> mlds_output_var(VarName) -->
> - mlds_output_fully_qualified(VarName, mlds_output_mangled_name).
> + mlds_output_fully_qualified(VarName, mlds_output_var_name).
> +
> +:- pred mlds_output_var_name(mlds__var_name, io__state, io__state).
> +:- mode mlds_output_var_name(in, di, uo) is det.
> +mlds_output_var_name(VarName) -->
> + mlds_output_mangled_name(ml_var_name_to_string(VarName)).
>
> :- pred mlds_output_mangled_name(string, io__state, io__state).
> :- mode mlds_output_mangled_name(in, di, uo) is det.
> Index: compiler/mlds_to_csharp.m
> ===================================================================
> RCS file: mlds_to_csharp.m
> diff -N mlds_to_csharp.m
> --- /dev/null Mon Apr 16 11:57:05 2001
> +++ mlds_to_csharp.m Mon Apr 30 23:50:34 2001
> @@ -0,0 +1,554 @@
> +%-----------------------------------------------------------------------------%
> +% Copyright (C) 2001 The University of Melbourne.
> +% This file may only be copied under the terms of the GNU General
> +% Public License - see the file COPYING in the Mercury distribution.
> +%-----------------------------------------------------------------------------%
> +%
> +% mlds_to_csharp - Generate C# code for the foreign language interface.
> +% Main author: trd.
> +%
> +% This code converts the MLDS representation of foreign language code into C#
> +
> +:- module mlds_to_csharp.
> +:- interface.
> +
> +:- import_module mlds.
> +:- import_module io.
> +
> + % Convert the MLDS to C# and write it to a file.
> +
> +:- pred mlds_to_csharp__output_csharp_code(mlds, io__state, io__state).
> +:- mode mlds_to_csharp__output_csharp_code(in, di, uo) is det.
> +
> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +
> +:- implementation.
> +
> +:- import_module globals, options, passes_aux.
> +:- import_module builtin_ops, c_util, modules, tree.
> +:- import_module hlds_pred. % for `pred_proc_id'.
> +:- import_module prog_data, prog_out, llds_out.
> +:- import_module rtti, type_util, error_util.
> +
> +:- import_module ilds, ilasm, il_peephole.
> +:- import_module ml_util, ml_code_util.
> +:- import_module mlds_to_c. /* to output C code for .cpp files */
> +:- use_module llds. /* for user_c_code */
> +
> +:- import_module bool, int, map, string, list, assoc_list, term, std_util.
> +:- import_module library, require, counter.
> +
> +:- import_module mlds_to_il.
> +
I would imagine that the mlds_to_c import isn't needed.
> +%-----------------------------------------------------------------------------%
> +
> +
> +%-----------------------------------------------------------------------------%
> +
> + %
> + % Generate the `__csharp_code.cs' file which contains the c sharp
> + % code.
> + %
> +output_csharp_code(MLDS) -->
> + { MLDS = mlds(ModuleName, _ForeignCode, _Imports, _Defns) },
> + output_src_start(ModuleName),
> + io__nl,
> +
> + generate_c_code(MLDS),
> +
> + output_src_end(ModuleName).
> +
> +:- pred output_src_start(mercury_module_name, io__state, io__state).
> +:- mode output_src_start(in, di, uo) is det.
> +
> +output_src_start(ModuleName) -->
> + { library__version(Version) },
> + { prog_out__sym_name_to_string(ModuleName, ModuleNameStr) },
> + io__write_strings(
> + ["//\n// Automatically generated from `",
> + ModuleNameStr,
> + ".m' by the\n",
> + "// Mercury compiler, version ",
> + Version,
> + ".\n",
> + "// Do not edit.\n",
> + "\n\n"]).
> +
> +:- pred output_src_end(mercury_module_name, io__state, io__state).
> +:- mode output_src_end(in, di, uo) is det.
> +
> +output_src_end(ModuleName) -->
> + io__write_string("// End of module: "),
> + prog_out__write_sym_name(ModuleName),
> + io__write_string(". \n").
> +
> +%-----------------------------------------------------------------------------%
> +
> + % This section could very nearly be turned into a
> + % mlds_to_csharp module, which turns MLDS into managed C++.
> + % Note that it relies on quite a few predicates in mlds_to_il.
> + % XXX we should clean up the dependencies.
> + % XXX we don't output contexts for any of this.
Really that this section could almost be turned into a mlds_to_csharp
module?
> +:- pred generate_c_code(mlds, io__state, io__state).
> +:- mode generate_c_code(in, di, uo) is det.
> +generate_c_code(MLDS) -->
> +
> + { MLDS = mlds(ModuleName, ForeignCode, _Imports, Defns) },
> + { prog_out__sym_name_to_string(ModuleName, ModuleNameStr) },
> + { ClassName = mlds_module_name_to_class_name(
> + mercury_module_name_to_mlds(ModuleName)) },
> +
> + io__nl,
> + io__write_strings([
> + "// #using ""mercury_mcpp.dll""\n",
> + "// #using ""mercury_il.dll""\n",
> + "// #using """, ModuleNameStr, ".dll""\n",
> +
> + % XXX We have to use the mercury namespace, as
> + % llds_out still generates some of the code used in the
> + % C sharp interface, and so it doesn't have "mercury::"
> + % namespace qualifiers.
. not :: qualifier.
> + "using mercury;\n",
> + "\n"]),
> +
> + generate_foreign_header_code(mercury_module_name_to_mlds(ModuleName),
> + ForeignCode),
> +
> + { Namespace0 = get_class_namespace(ClassName) },
> + { list__reverse(Namespace0) = [Head | Tail] ->
> + Namespace = list__reverse([Head ++ "__csharp_code" | Tail])
> + ;
> + Namespace = Namespace0
> + },
> +
> + io__write_list(Namespace, "\n",
> + (pred(N::in, di, uo) is det -->
> + io__format("namespace %s {", [s(N)])
> + )),
> +
> + io__write_strings([
> + "\nclass mercury_code",
> + "{\n"]),
> +
> + % Output the contents of pragma foreign_code declarations.
> + generate_foreign_code(mercury_module_name_to_mlds(ModuleName),
> + ForeignCode),
> +
> + io__write_string("\n"),
> +
> + % Output the contents of foreign_proc declarations.
> + % Put each one inside a method.
> + list__foldl(generate_method_c_code(
> + mercury_module_name_to_mlds(ModuleName)), Defns),
> +
> + io__write_string("};\n"),
> +
> + % Close the namespace braces.
> + io__write_list(Namespace, "\n",
> + (pred(_N::in, di, uo) is det -->
> + io__write_string("}")
> + )),
> +
> + io__nl.
> +
> +
> + % XXX we don't handle export decls.
> +:- pred generate_foreign_code(mlds_module_name, mlds__foreign_code,
> + io__state, io__state).
> +:- mode generate_foreign_code(in, in, di, uo) is det.
> +generate_foreign_code(_ModuleName,
> + mlds__foreign_code(_RevHeaderCode, RevBodyCode,
> + _ExportDefns)) -->
> + { BodyCode = list__reverse(RevBodyCode) },
> + io__write_list(BodyCode, "\n",
> + (pred(llds__user_foreign_code(Lang, Code, _Context)::in,
> + di, uo) is det -->
> + ( { Lang = csharp } ->
> + io__write_string(Code)
> + ;
> + { sorry(this_file,
> + "foreign code other than MC++") }
> + )
> + )).
> +
> + % XXX we don't handle export decls.
> +:- pred generate_foreign_header_code(mlds_module_name, mlds__foreign_code,
> + io__state, io__state).
> +:- mode generate_foreign_header_code(in, in, di, uo) is det.
> +generate_foreign_header_code(_ModuleName,
> + mlds__foreign_code(RevHeaderCode, _RevBodyCode,
> + _ExportDefns)) -->
> + { HeaderCode = list__reverse(RevHeaderCode) },
> + io__write_list(HeaderCode, "\n",
> + (pred(llds__foreign_decl_code(Lang, Code, _Context)::in,
> + di, uo) is det -->
> + ( { Lang = csharp } ->
> + io__write_string(Code)
> + ;
> + { sorry(this_file,
> + "foreign code other than MC++") }
> + )
> + )).
> +
> +:- pred generate_method_c_code(mlds_module_name, mlds__defn,
> + io__state, io__state).
> +:- mode generate_method_c_code(in, in, di, uo) is det.
> +
> + % XXX we don't handle export
> +generate_method_c_code(_, defn(export(_), _, _, _)) --> [].
> +generate_method_c_code(_, defn(data(_), _, _, _)) --> [].
> +generate_method_c_code(_, defn(type(_, _), _, _, _)) --> [].
> +generate_method_c_code(_ModuleName,
> + defn(function(PredLabel, ProcId, MaybeSeqNum, _PredId),
> + _Context, _DeclFlags, Entity)) -->
> +
> + (
> + { Entity = mlds__function(_, Params, yes(Statement)) },
> + { has_foreign_languages(Statement, Langs) },
> + { list__member(csharp, Langs) }
> + ->
> + globals__io_lookup_bool_option(highlevel_data, HighLevelData),
> + { DataRep = il_data_rep(HighLevelData) },
> + { Params = mlds__func_params(Inputs, Outputs) },
> + { Outputs = [] ->
> + ReturnType = void
> + ; Outputs = [MLDSReturnType] ->
> + mlds_type_to_ilds_type(DataRep, MLDSReturnType) =
> + ilds__type(_, SimpleType),
> + ReturnType = simple_type(SimpleType)
> + ;
> + % IL doesn't support multiple return values
> + sorry(this_file, "multiple return values")
> + },
> +
> +
> + { predlabel_to_id(PredLabel, ProcId, MaybeSeqNum, Id) },
> + io__write_string("public static "),
> + write_il_ret_type_as_csharp_type(ReturnType),
> +
> + io__write_string(" "),
> +
> + io__write_string(Id),
> + io__write_string("("),
> + io__write_list(Inputs, ", ", write_input_arg_as_csharp_type),
> + io__write_string(")"),
> + io__nl,
> +
> + io__write_string("{\n"),
> + write_csharp_statement(Statement),
> + io__write_string("}\n")
> + ;
> + []
> + ).
> +
> +:- pred write_csharp_statement(mlds__statement, io__state, io__state).
> +:- mode write_csharp_statement(in, di, uo) is det.
> +write_csharp_statement(statement(Statement, _Context)) -->
> + (
> + { Statement = atomic(outline_target_code(csharp,
> + _Lvals, Code)) }
> + ->
> + io__write_string(Code),
> + io__nl
> + ;
> + { Statement = block(Defns, Statements) }
> + ->
> + io__write_list(Defns, "", write_csharp_defn_decl),
> + io__write_string("{\n"),
> + io__write_list(Statements, "", write_csharp_statement),
> + io__write_string("\n}\n")
> + ;
> + { Statement = return(Rvals) }
> + ->
> + ( { Rvals = [Rval] } ->
> + io__write_string("return "),
> + write_csharp_rval(Rval),
> + io__write_string(";\n")
> + ;
> + { sorry(this_file, "multiple return values") }
> + )
> + ;
> + { functor(Statement, SFunctor, Arity) },
> + io__write_string("// unimplemented: "),
> + io__write_string(SFunctor),
> + io__write_string("/"),
> + io__write(Arity),
> + io__nl
> + ).
> +
> +%-------------------------------------------------------------------
> +% code below here is not used.
> +%-------------------------------------------------------------------
> +
> + % XXX we ignore contexts
> +:- pred write_csharp_code_component(mlds__target_code_component,
> + io__state, io__state).
> +:- mode write_csharp_code_component(in, di, uo) is det.
> +write_csharp_code_component(user_target_code(Code, _MaybeContext)) -->
> + io__write_string(Code).
> +write_csharp_code_component(raw_target_code(Code)) -->
> + io__write_string(Code).
> + % XXX we don't handle name yet.
> +write_csharp_code_component(name(_)) --> [].
> +write_csharp_code_component(target_code_input(Rval)) -->
> + write_csharp_rval(Rval).
> +write_csharp_code_component(target_code_output(Lval)) -->
> + write_csharp_lval(Lval).
> +
> +:- pred write_csharp_rval(mlds__rval, io__state, io__state).
> +:- mode write_csharp_rval(in, di, uo) is det.
> +write_csharp_rval(lval(Lval)) -->
> + write_csharp_lval(Lval).
> +write_csharp_rval(mkword(_Tag, _Rval)) -->
> + io__write_string(" /* mkword rval -- unimplemented */ ").
> +write_csharp_rval(const(RvalConst)) -->
> + write_csharp_rval_const(RvalConst).
> +write_csharp_rval(unop(Unop, Rval)) -->
> + (
> + { Unop = std_unop(StdUnop) },
> + { c_util__unary_prefix_op(StdUnop, UnopStr) }
> + ->
> + io__write_string(UnopStr),
> + io__write_string("("),
> + write_csharp_rval(Rval),
> + io__write_string(")")
> + ;
> + { Unop = cast(Type) }
> + ->
> + io__write_string("("),
> + write_csharp_parameter_type(Type),
> + io__write_string(") "),
> + write_csharp_rval(Rval)
> + ;
> + io__write_string(" /* XXX box or unbox unop -- unimplemented */ "),
> + write_csharp_rval(Rval)
> + ).
> +write_csharp_rval(binop(Binop, Rval1, Rval2)) -->
> + (
> + { c_util__binary_infix_op(Binop, BinopStr) }
> + ->
> + io__write_string("("),
> + write_csharp_rval(Rval1),
> + io__write_string(") "),
> + io__write_string(BinopStr),
> + io__write_string(" ("),
> + write_csharp_rval(Rval2),
> + io__write_string(")")
> + ;
> + io__write_string(" /* binop rval -- unimplemented */ ")
> + ).
> +
> +write_csharp_rval(mem_addr(_)) -->
> + io__write_string(" /* mem_addr rval -- unimplemented */ ").
> +
> +:- pred write_csharp_rval_const(mlds__rval_const, io__state, io__state).
> +:- mode write_csharp_rval_const(in, di, uo) is det.
> +write_csharp_rval_const(true) --> io__write_string("1").
> +write_csharp_rval_const(false) --> io__write_string("0").
> +write_csharp_rval_const(int_const(I)) --> io__write_int(I).
> +write_csharp_rval_const(float_const(F)) --> io__write_float(F).
> + % XXX We don't quote this correctly.
> +write_csharp_rval_const(string_const(S)) -->
> + io__write_string(""""),
> + io__write_string(S),
> + io__write_string("""").
> +write_csharp_rval_const(multi_string_const(_L, _S)) -->
> + io__write_string(" /* multi_string_const rval -- unimplemented */ ").
> +write_csharp_rval_const(code_addr_const(CodeAddrConst)) -->
> + (
> + { CodeAddrConst = proc(ProcLabel, _FuncSignature) },
> + { mangle_mlds_proc_label(ProcLabel, no, ClassName,
> + MangledName) },
> + write_csharp_class_name(ClassName),
> + io__write_string("."),
> + io__write_string(MangledName)
> + ;
> + { CodeAddrConst = internal(ProcLabel, SeqNum,
> + _FuncSignature) },
> + { mangle_mlds_proc_label(ProcLabel, yes(SeqNum), ClassName,
> + MangledName) },
> + write_csharp_class_name(ClassName),
> + io__write_string("."),
> + io__write_string(MangledName)
> + ).
> +
> +
> +
> +write_csharp_rval_const(data_addr_const(_)) -->
> + io__write_string(" /* data_addr_const rval -- unimplemented */ ").
> +write_csharp_rval_const(null(_)) -->
> + io__write_string("0").
> +
> +:- pred write_csharp_lval(mlds__lval, io__state, io__state).
> +:- mode write_csharp_lval(in, di, uo) is det.
> +write_csharp_lval(field(_, Rval, named_field(FieldId, _Type), _, _)) -->
> + io__write_string("("),
> + write_csharp_rval(Rval),
> + io__write_string(")"),
> + io__write_string("."),
> + { FieldId = qual(_, FieldName) },
> + io__write_string(FieldName).
> +
> +write_csharp_lval(field(_, Rval, offset(OffSet), _, _)) -->
> + io__write_string("("),
> + write_csharp_rval(Rval),
> + io__write_string(")"),
> + io__write_string("["),
> + write_csharp_rval(OffSet),
> + io__write_string("]").
> +
> +write_csharp_lval(mem_ref(Rval, _)) -->
> + io__write_string("*"),
> + write_csharp_rval(Rval).
> +write_csharp_lval(var(Var, _VarType)) -->
> + { Var = qual(_, VarName) },
> + write_mlds_var_name_for_parameter(VarName).
> +
> +:- pred write_csharp_defn_decl(mlds__defn, io__state, io__state).
> +:- mode write_csharp_defn_decl(in, di, uo) is det.
> +write_csharp_defn_decl(Defn) -->
> + { Defn = mlds__defn(Name, _Context, _Flags, DefnBody) },
> + ( { DefnBody = data(Type, _Initializer) },
> + { Name = data(var(VarName)) }
> + ->
> + write_csharp_parameter_type(Type),
> + io__write_string(" "),
> + write_mlds_var_name_for_parameter(VarName),
> + io__write_string(";\n")
> + ;
> + io__write_string("// unimplemented defn decl\n")
> + ).
> +
> +:- pred write_csharp_parameter_type(mlds__type, io__state, io__state).
> +:- mode write_csharp_parameter_type(in, di, uo) is det.
> +write_csharp_parameter_type(Type) -->
> + globals__io_lookup_bool_option(highlevel_data, HighLevelData),
> + { DataRep = il_data_rep(HighLevelData) },
> + { ILType = mlds_type_to_ilds_type(DataRep, Type) },
> + write_il_type_as_csharp_type(ILType).
> +
> +:- pred type_is_byref_type(mlds__type, mlds__type).
> +:- mode type_is_byref_type(in, out) is semidet.
> +type_is_byref_type(Type, InnerType) :-
> + Type = mlds__ptr_type(InnerType).
> +
> +:- pred write_il_ret_type_as_csharp_type(ret_type::in,
> + io__state::di, io__state::uo) is det.
> +write_il_ret_type_as_csharp_type(void) --> io__write_string("void").
> +write_il_ret_type_as_csharp_type(simple_type(T)) -->
> + write_il_simple_type_as_csharp_type(T).
> +
> + % XXX need to revisit this and choose types appropriately
> +:- pred write_il_simple_type_as_csharp_type(simple_type::in,
> + io__state::di, io__state::uo) is det.
> +write_il_simple_type_as_csharp_type(int8) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(int16) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(int32) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(int64) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(uint8) -->
> + io__write_string("unsigned int").
> +write_il_simple_type_as_csharp_type(uint16) -->
> + io__write_string("unsigned int").
> +write_il_simple_type_as_csharp_type(uint32) -->
> + io__write_string("unsigned int").
> +write_il_simple_type_as_csharp_type(uint64) -->
> + io__write_string("unsigned int").
> +write_il_simple_type_as_csharp_type(native_int) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(native_uint) -->
> + io__write_string("unsigned int").
> +write_il_simple_type_as_csharp_type(float32) -->
> + io__write_string("float").
> +write_il_simple_type_as_csharp_type(float64) -->
> + io__write_string("float").
> +write_il_simple_type_as_csharp_type(native_float) -->
> + io__write_string("float").
> +write_il_simple_type_as_csharp_type(bool) -->
> + io__write_string("int").
> +write_il_simple_type_as_csharp_type(char) -->
> + io__write_string("char").
> +write_il_simple_type_as_csharp_type(refany) -->
> + io__write_string("mercury.MR_RefAny").
> +write_il_simple_type_as_csharp_type(class(ClassName)) -->
> + ( { ClassName = il_generic_class_name } ->
> + io__write_string("mercury.MR_Box")
> + ;
> + write_csharp_class_name(ClassName)
> + ).
> + % XXX this is not the right syntax
> +write_il_simple_type_as_csharp_type(value_class(ClassName)) -->
> + write_csharp_class_name(ClassName).
> + % XXX this is not the right syntax
> +write_il_simple_type_as_csharp_type(interface(ClassName)) -->
> + write_csharp_class_name(ClassName).
> + % XXX this needs more work
> +write_il_simple_type_as_csharp_type('[]'(_Type, _Bounds)) -->
> + io__write_string("object[]").
> +write_il_simple_type_as_csharp_type('&'(Type)) -->
> + % XXX is this always right?
> + io__write_string("ref "),
> + write_il_type_as_csharp_type(Type).
> +write_il_simple_type_as_csharp_type('*'(Type)) -->
> + write_il_type_as_csharp_type(Type),
> + io__write_string(" *").
> +
> +:- pred write_csharp_class_name(structured_name::in, io__state::di,
> + io__state::uo) is det.
> +write_csharp_class_name(structured_name(_Assembly, DottedName)) -->
> + io__write_list(DottedName, ".", io__write_string).
> +
> +:- pred write_il_type_as_csharp_type(ilds__type::in,
> + io__state::di, io__state::uo) is det.
> +write_il_type_as_csharp_type(ilds__type(Modifiers, SimpleType)) -->
> + io__write_list(Modifiers, " ",
> + write_il_type_modifier_as_csharp_type),
> + write_il_simple_type_as_csharp_type(SimpleType).
> +
> +:- pred write_il_type_modifier_as_csharp_type(ilds__type_modifier::in,
> + io__state::di, io__state::uo) is det.
> +write_il_type_modifier_as_csharp_type(const) -->
> + io__write_string("const").
> +write_il_type_modifier_as_csharp_type(readonly) -->
> + io__write_string("readonly").
> +write_il_type_modifier_as_csharp_type(volatile) -->
> + io__write_string("volatile").
> +
> +:- pred write_input_arg_as_csharp_type(
> + pair(mlds__entity_name, mlds__type)::in,
> + io__state::di, io__state::uo) is det.
> +write_input_arg_as_csharp_type(EntityName - Type) -->
> + globals__io_lookup_bool_option(highlevel_data, HighLevelData),
> + { DataRep = il_data_rep(HighLevelData) },
> + write_il_type_as_csharp_type(mlds_type_to_ilds_type(DataRep, Type)),
> + io__write_string(" "),
> + ( { EntityName = data(var(VarName)) } ->
> + write_mlds_var_name_for_parameter(VarName)
> + ;
> + { error("found a variable in a list") }
> + ).
> +
> +:- pred write_mlds_var_name_for_local(mlds__var_name::in,
> + io__state::di, io__state::uo) is det.
> +write_mlds_var_name_for_local(var_name(Name, MaybeNum)) -->
> + io__write_string(Name),
> + ( { MaybeNum = yes(Num) } ->
> + io__write_string("_"),
> + io__write_int(Num)
> + ;
> + []
> + ).
> +
> +:- pred write_mlds_var_name_for_parameter(mlds__var_name::in,
> + io__state::di, io__state::uo) is det.
> +write_mlds_var_name_for_parameter(var_name(Name, _)) -->
> + io__write_string(Name).
> +
> +:- func this_file = string.
> +this_file = "mlds_to_csharp.m".
> +
> +:- end_module mlds_to_csharp.
> Index: compiler/mlds_to_il.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_il.m,v
> retrieving revision 1.20
> diff -u -r1.20 mlds_to_il.m
> --- compiler/mlds_to_il.m 2001/04/24 13:05:06 1.20
> +++ compiler/mlds_to_il.m 2001/04/30 13:50:34
> @@ -64,8 +64,9 @@
> :- interface.
>
> :- import_module mlds, ilasm, ilds.
> -:- import_module io, list, bool, std_util.
> +:- import_module io, list, bool, std_util, set.
> :- import_module hlds_pred. % for `pred_proc_id'.
> +:- import_module prog_data. % for `foreign_language'.
>
> %-----------------------------------------------------------------------------%
>
> @@ -74,7 +75,8 @@
> %
> % This is where all the action is for the IL backend.
> %
> -:- pred generate_il(mlds, list(ilasm:decl), bool, io__state, io__state).
> +:- pred generate_il(mlds, list(ilasm:decl), set(foreign_language),
> + io__state, io__state).
> :- mode generate_il(in, out, out, di, uo) is det.
>
>
> @@ -142,7 +144,7 @@
> :- import_module ml_type_gen.
> :- use_module llds. /* for user_c_code */
>
> -:- import_module bool, int, map, string, list, assoc_list, term.
> +:- import_module bool, int, map, string, set, list, assoc_list, term.
> :- import_module library, require, counter.
>
> % We build up lists of instructions using a tree to make
> @@ -155,20 +157,21 @@
> module_name :: mlds_module_name, % the module name
> assembly_name :: assembly_name, % the assembly name
> imports :: mlds__imports, % the imports
> - file_c_code :: bool, % file contains c_code
> + file_c_code :: set(foreign_language), % file foreign code
> il_data_rep :: il_data_rep, % data representation.
> % class-wide attributes (all accumulate)
> alloc_instrs :: instr_tree, % .cctor allocation instructions
> init_instrs :: instr_tree, % .cctor init instructions
> classdecls :: list(classdecl), % class methods and fields
> has_main :: bool, % class contains main
> - class_c_code :: bool, % class contains c_code
> + class_c_code :: set(foreign_language),% class foreign code
> % method-wide attributes (accumulating)
> locals :: locals_map, % The current locals
> instr_tree :: instr_tree, % The instruction tree (unused)
> label_counter :: counter, % the label counter
> block_counter :: counter, % the block counter
> - method_c_code :: bool, % method contains c_code
> + method_c_code :: maybe(foreign_language),
> + % method contains foreign code
> % method-wide attributes (static)
> arguments :: arguments_map, % The arguments
> method_name :: member_name, % current method name
> @@ -182,7 +185,7 @@
>
Not sure that the *_c_code names are still appropiate, maybe switch to
foreign.
> %-----------------------------------------------------------------------------%
>
> -generate_il(MLDS, ILAsm, ContainsCCode, IO0, IO) :-
> +generate_il(MLDS, ILAsm, ForeignLangs, IO0, IO) :-
> MLDS = mlds(MercuryModuleName, _ForeignCode, Imports, Defns),
> ModuleName = mercury_module_name_to_mlds(MercuryModuleName),
> SymName = mlds_module_name_to_sym_name(ModuleName),
Otherwise the diff looks fine.
--------------------------------------------------------------------------
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