[m-rev.] for review: pragma foreign_export_enum

Peter Wang wangp at students.csse.unimelb.edu.au
Tue Jul 24 20:11:27 AEST 2007


On 2007-07-24, Julien Fischer <juliensf at csse.unimelb.edu.au> wrote:
> 
>  Estimated hours taken: 30
>  Branches: main
> 
...
> 
>  compiler/module_qual.m:
>  	Handle foreign_export_enum pragmas.
> 
>  	Add a predicate to for module qualifying type_ctors, i.e. a
>  	type identified by it's sym_name and arity, for use by the
>  	above.

its

> 
>  compiler/mercury_to_mercury.m:
>  	Write out foreign_export_enum pragmas.
> 
>  compiler/hlds_module.m:
>  	Add a type to represent exported enumerations.
> 
>  	Add a field to the module_info to hold information about
>  	exported enumerations.  Add access procedures for this.
> 
>  compiler/make_hlds_passes.m:
>  compiler/add_pragma.m:
>  	Handle foreign_export_enum pragmas: generate the set of foreign names
>  	for each of the constructors of an enumeration type and check that
>  	their validity in the foreign language.  Attach this information to
>  	the HLDS.
> 
>  compiler/export.m:
>  	Output #defined constants for C foreign_export_enum pragmas in
>  	.mh files.
> 
>  compiler/mlds.m:
>  	Add an MLDS specific representation of exported enumerations.
> 
>  compiler/ml_type_gen.m:
>  	Convert the HLDS representation of exported enumerations into
>  	an MLDS specific one.
> 
>  compiler/mlds_to_c.m:
>  	Output #defined constants for C foreign_export_enum pragmas in
>  	.mih files.

Is it not enough to write them to the .mh files?

>  Index: NEWS
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/NEWS,v
>  retrieving revision 1.470
>  diff -u -r1.470 NEWS
>  --- NEWS	20 Jul 2007 01:21:58 -0000	1.470
>  +++ NEWS	24 Jul 2007 06:38:04 -0000
>  @@ -3,6 +3,8 @@
> 
>   Changes to the Mercury language:
> 
>  +* A new pragma, foreign_export_enum, allows the constructors of Merucry

Mercury

>  +  enumeration types, to be referred to in foreign language code.
>   * Some of the restrictions on typeclass instances have been relaxed, 
>  allowing
>     support for polymorphic instances with functional dependencies.
>   * We now support trace goals, which can be used to print progress messages 
>  or

>  Index: compiler/add_pragma.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/add_pragma.m,v
>  retrieving revision 1.66
>  diff -u -r1.66 add_pragma.m
>  --- compiler/add_pragma.m	14 Jul 2007 02:32:40 -0000	1.66
>  +++ compiler/add_pragma.m	23 Jul 2007 07:42:27 -0000

>  @@ -218,6 +226,10 @@
>           % Handle pragma foreign procs later on (when we process clauses).
>           Pragma = pragma_foreign_proc(_, _, _, _, _, _, _)
>       ;
>  +        % Handle pragma foregin_export_enum (after we have added all the

foreign_export_enum

>  +        % types).
>  +        Pragma = pragma_foreign_export_enum(_, _, _, _, _)
>  +    ;
>           % Handle pragma tabled decls later on (when we process clauses).
>           Pragma = pragma_tabled(_, _, _, _, _, _)
>       ;
>  @@ -583,6 +595,357 @@
> 
>   
>  %-----------------------------------------------------------------------------%
> 
>  +add_pragma_foreign_export_enum(Lang, TypeName, TypeArity, Attributes,
>  +        Overrides, _ImportStatus, Context, !ModuleInfo, !Specs) :-
>  +    TypeCtor = type_ctor(TypeName, TypeArity),
>  +    module_info_get_type_table(!.ModuleInfo, TypeDefnTable),
>  +    ContextPieces = [
>  +        words("In"), fixed("`pragma foreign_export_enum'"),
>  +        words("declaration for"),
>  +        sym_name_and_arity(TypeName / TypeArity), suffix(":"), nl
>  +    ],
>  +    ( +        % Emit an error message for export_num pragmas for the
>  +        % builtin atomic types.

foreign_export_enum

>  +:- pred build_overrides_map(sym_name::in, prog_context::in,
>  +    format_components::in, assoc_list(sym_name, string)::in,
>  +    maybe(map(sym_name, string))::out,
>  +    list(error_spec)::in, list(error_spec)::out) is det.

I suggest renaming that.

>  + +:- pred build_export_enum_name_map(format_components::in,
>  +    foreign_language::in, sym_name::in, arity::in, prog_context::in,
>  +    string::in, map(sym_name, string)::in, list(constructor)::in,
>  +    maybe(map(sym_name, string))::out,
>  +    list(error_spec)::in, list(error_spec)::out) is det.
>  +
>  +build_export_enum_name_map(ContextPieces, Lang, TypeName, TypeArity, 
>  Context, Prefix,
>  +        Overrides0, Ctors, MaybeMapping, !Specs) :-
>  +    ( +        TypeName = qualified(TypeModuleQual, _)
>  +
>  +    ;
>  +        % The type name should have been module qualified by now.
>  +        TypeName = unqualified(_),
>  +        unexpected(this_file, "unqualified type name for 
>  foreign_export_enum")
>  +    ),
>  + +    list.foldl3(add_ctor_to_name_map(Lang, Prefix, TypeModuleQual),
>  +        Ctors, Overrides0, Overrides, map.init, NameMap, [], BadCtors),
>  +    %
>  +    % Check for any remaining user-specified renamings that didn't
>  +    % match the constructors of the type and report and error
>  +    % for them.
>  +    %
>  +    ( not map.is_empty(Overrides) ->
>  +       InvalidRenamingPieces = [
>  +            words("user-specified foreign names for constructors"),
>  +            words("that do not match match any of the constructors of"),
>  +            sym_name_and_arity(TypeName / TypeArity), suffix(".")
>  +        ],
>  +        InvalidRenamings = map.keys(Overrides),
>  +        InvalidRenamingComponents =
>  +            list.map((func(S) = [sym_name(S)]), InvalidRenamings),
>  +        InvalidRenamingList = component_list_to_line_pieces(
>  +            InvalidRenamingComponents, [nl]),
>  +        InvalidRenamingVerbosePieces = [
>  +            words("The following"),
>  +            words(choose_number(InvalidRenamings,
>  +                "constructor does", "constructors do")),
>  +            words("not match"), suffix(":"), nl_indent_delta(2)
>  +        ] ++ InvalidRenamingList,
>  +        InvalidRenamingMsg = simple_msg(Context,
>  +            [
>  +                always(ContextPieces ++ InvalidRenamingPieces),
>  +                verbose_only(InvalidRenamingVerbosePieces)
>  +            ]),
>  +        InvalidRenamingSpec = error_spec(severity_error,
>  +            phase_parse_tree_to_hlds, [InvalidRenamingMsg]),
>  +        list.cons(InvalidRenamingSpec, !Specs),
>  +        MaybeMapping = no
>  +        % NOTE: in the presence of this error we do not report if
>  +        % contructors could not be converted to names in the foreign
>  +        % langugage.

language

>  +:- pred add_ctor_to_name_map(foreign_language::in,
>  +    string::in, sym_name::in, constructor::in,
>  +    map(sym_name, string)::in, map(sym_name, string)::out,
>  +    map(sym_name, string)::in, map(sym_name, string)::out,
>  +    list(sym_name)::in, list(sym_name)::out) is det.
>  +
>  +add_ctor_to_name_map(Lang, Prefix, _TypeModQual, Ctor, !Overrides, 
>  !NameMap,
>  +        !BadCtors) :-
>  +    CtorSymName = Ctor ^ cons_name,
>  +    ( +        % All of the constructor sym_names should be module 
>  qualified by now.
>  +        % We unqualify them before inserting them into the mapping since
>  +        % the code in export.m expects that to be done.
>  +        %
>  +        CtorSymName    = qualified(_, _),
>  +        UnqualCtorName = unqualify_name(CtorSymName),
>  +        UnqualSymName  = unqualified(UnqualCtorName) +    ;
>  +        CtorSymName = unqualified(_),
>  +        unexpected(this_file, "unqualified constructor name")
>  +    ),
>  +    %
>  +    % If the user specified a name for this constructor then use that.
>  +    %
>  +    ( map.remove(!.Overrides, UnqualSymName, ForeignName0, !:Overrides) ->

svmap.remove


>  Index: compiler/c_util.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/c_util.m,v
>  retrieving revision 1.36
>  diff -u -r1.36 c_util.m
>  --- compiler/c_util.m	17 Jul 2007 23:48:26 -0000	1.36
>  +++ compiler/c_util.m	18 Jul 2007 07:25:41 -0000

>  @@ -454,3 +467,10 @@
>   convert_bool_to_string(yes) = "yes".
> 
>   
>  %-----------------------------------------------------------------------------%
>  +
>  +is_valid_c_identifier(S) :-
>  +    string.first_char(S, Start, Rest),
>  +    char.is_alpha_or_underscore(Start),
>  +    string.is_all_alnum_or_underscore(Rest).

Not that it matters, but you can save on some garbage:

    is_valid_c_identifier(S) :-
	string.index(S, 0, Start),
	char.is_alpha_or_underscore(Start),
	string.is_all_alnum_or_underscore(S).

>  Index: compiler/export.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/export.m,v
>  retrieving revision 1.111
>  diff -u -r1.111 export.m
>  --- compiler/export.m	14 Jul 2007 02:32:41 -0000	1.111
>  +++ compiler/export.m	15 Jul 2007 12:43:21 -0000
>  @@ -750,6 +756,79 @@
>       ;
>           true
>       ).
>  + 
>  +%-----------------------------------------------------------------------------%
>  +%
>  +% Code for writing out foreign exported enumerations
>  +%
>  +
>  +% For C/C++ we emit a #defined constant for constructor exported from an
>  +% enumeration.
>  +

constructors


>  Index: compiler/hlds_module.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/hlds_module.m,v
>  retrieving revision 1.151
>  diff -u -r1.151 hlds_module.m
>  --- compiler/hlds_module.m	8 Jun 2007 00:47:09 -0000	1.151
>  +++ compiler/hlds_module.m	12 Jul 2007 07:36:18 -0000

>  @@ -770,6 +789,10 @@
>                   % All the directly imported module specifiers in the 
>  interface.
>                   % (Used by unused_imports analysis).
>                   interface_module_specifiers :: set(module_specifier),
>  + +                % Enumeration types that have been exported to a foreign
>  +                % language.
>  +                exported_enums :: list(exported_enum_info),

Indent the :: bit?

>  Index: compiler/mlds.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/mlds.m,v
>  retrieving revision 1.150
>  diff -u -r1.150 mlds.m
>  --- compiler/mlds.m	15 Jun 2007 12:12:30 -0000	1.150
>  +++ compiler/mlds.m	12 Jul 2007 05:25:04 -0000

>  @@ -381,7 +382,8 @@
>                   % XXX These only work for the C backend because 
>  initialisers
>                   % and finalisers do not (yet) work for the other backends.
>                   init_preds          :: list(string),
>  -                final_preds         :: list(string)
>  +                final_preds         :: list(string),
>  +                exported_enums      :: list(mlds_exported_enum)

Mention that these are in reverse order (if they are).

>  Index: compiler/mlds_to_c.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_c.m,v
>  retrieving revision 1.218
>  diff -u -r1.218 mlds_to_c.m
>  --- compiler/mlds_to_c.m	17 Jul 2007 23:48:27 -0000	1.218
>  +++ compiler/mlds_to_c.m	18 Jul 2007 07:25:42 -0000

>  +
>  +:- pred mlds_output_exported_enum_constant(pair(string, 
>  mlds_entity_defn)::in,
>  +    io::di, io::uo) is det.
>  +
>  +mlds_output_exported_enum_constant(NameAndTag, !IO) :-
>  +    NameAndTag = Name - Tag,
>  +    ( +        Tag = mlds_data(mlds_native_int_type, Initializer, 
>  gc_no_stmt),
>  +        Initializer = init_obj(const(mlconst_int(Value)))
>  +    ->
>  +        io.write_string("#define ", !IO),
>  +        io.write_string(Name, !IO),
>  +        io.write_string(" ", !IO),
>  +        io.write_int(Value, !IO),
>  +        io.nl(!IO)
>  +    ;
>  +        unexpected(this_file,
>  +            "bad entity_defn for exported enumeration value.")

mlds_entity_defn

>  Index: compiler/prog_io_pragma.m
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/compiler/prog_io_pragma.m,v
>  retrieving revision 1.125
>  diff -u -r1.125 prog_io_pragma.m
>  --- compiler/prog_io_pragma.m	14 Jul 2007 02:32:48 -0000	1.125
>  +++ compiler/prog_io_pragma.m	23 Jul 2007 08:08:15 -0000
>  @@ -213,6 +213,188 @@
>       parse_pragma_foreign_proc_pragma(ModuleName, "foreign_proc",
>           PragmaTerms, ErrorTerm, VarSet, Result).
> 
>  +
>  +%----------------------------------------------------------------------------%
>  +%
>  +% Code for parsing foreign_export_enum pragmas
>  +%
>  +
>  +parse_pragma_type(_ModuleName, "foreign_export_enum", PragmaTerms, 
>  ErrorTerm,
>  +        _VarSet, Result) :-
>  +    ( +
>  +        (
>  +            PragmaTerms = [LangTerm, MercuryTypeTerm],
>  +            MaybeAttributesTerm = no,
>  +            MaybeOverridesTerm = no
>  +        ;
>  +            PragmaTerms = [LangTerm, MercuryTypeTerm, AttributesTerm],
>  +            MaybeAttributesTerm = yes(AttributesTerm),
>  +            MaybeOverridesTerm = no
>  +
>  +        ;
>  +            PragmaTerms = [LangTerm, MercuryTypeTerm, AttributesTerm,
>  +                OverridesTerm],
>  +            MaybeAttributesTerm = yes(AttributesTerm),
>  +            MaybeOverridesTerm = yes(OverridesTerm)
>  +        )
>  +    ->
>  +        ( parse_foreign_language(LangTerm, ForeignLanguage) ->
>  +            parse_export_enum_type(MercuryTypeTerm, MaybeType),
>  +            (
>  +                MaybeType = ok2(Name, Arity),
>  +                maybe_parse_export_enum_attributes(MaybeAttributesTerm,
>  +                    MaybeAttributes),
>  +                (
>  +                    MaybeAttributes = ok1(Attributes),
>  +                    maybe_parse_export_enum_overrides(MaybeOverridesTerm,
>  +                        MaybeOverrides),
>  +                    (
>  +                        MaybeOverrides = ok1(Overrides),
>  +                        PragmaExportEnum = pragma_foreign_export_enum(
>  +                            ForeignLanguage, Name, Arity, Attributes,
>  +                            Overrides
>  +                        ),
>  +                        Item = item_pragma(user, PragmaExportEnum),
>  +                        Result = ok1(Item)
>  +                    ;
>  +                        MaybeOverrides = error1(Errors),
>  +                        Result = error1(Errors)
>  +                    )
>  +                )
>  +            ;
>  +                MaybeType = error2(Errors),
>  +                Result = error1(Errors)
>  +            )
>  +        ;
>  +            Msg = "invalid foreign_langauge in " ++

foreign_language

>  +:- pred process_export_enum_attribute(collected_export_enum_attribute::in,
>  +    export_enum_attributes::in, export_enum_attributes::out) is det.
>  +
>  +process_export_enum_attribute(ee_attr_prefix(MaybePrefix), _, Attributes) 
>  :-
>  +    Attributes = export_enum_attributes(MaybePrefix).
>  + +:- pred parse_export_enum_attr(term::in,
>  +    maybe1(collected_export_enum_attribute)::out) is det.
>  +
>  +parse_export_enum_attr(Term, Result) :- +    (
>  +        Term = functor(atom("prefix"), Args, _),
>  +        Args = [ ForeignNameTerm ],
>  +        ForeignNameTerm = functor(string(Prefix), [], _)
>  +    ->
>  +        Result = ok1(ee_attr_prefix(yes(Prefix)))
>  +    ;
>  +        Msg = "unrecongised attribute in foreign_export_enum pragma",

unrecognised

>  Index: doc/reference_manual.texi
>  ===================================================================
>  RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
>  retrieving revision 1.400
>  diff -u -r1.400 reference_manual.texi
>  --- doc/reference_manual.texi	20 Jul 2007 03:47:54 -0000	1.400
>  +++ doc/reference_manual.texi	24 Jul 2007 06:29:55 -0000
>  @@ -6175,7 +6175,10 @@
>                                          programming language.
>   * Using foreign types from Mercury::   How to use a type defined in
>   				       a different programming language
>  -				       in Mercury code. +				       in Mercury code.
>  +* Using Mercury enumerations in foreign code:: How to use a enumeration 
>  type

an enumeration type

>  +                                               defined in Mercury in a
>  +                                               different programming 
>  language.
>   * Data passing conventions::	       How Mercury types are passed to
>   				       different languages.
>   * Adding foreign declarations::        How to add declarations of
>  @@ -6918,6 +6921,83 @@
> 
>   @c -----------------------------------------------------------------------
> 
>  + at node Using Mercury enumerations in foreign code
>  + at section Using Mercury enumerations in foreign code
>  +
>  +Values of Mercury enumeration types can be made available to code in the
>  +bodies of @samp{foreign_proc} and @samp{foreign_code} pragmas via
>  +a declaration of the form:
>  +
>  + at example
>  +:- pragma foreign_export_enum(@var{Lang}, @var{MercuryType},
>  +        @var{Attributes}, @var{Overrides}).
>  + at end example
>  +
>  +This causes the compiler to create a symbolic name in language
>  + at var{Lang} for each of the constructors of @var{MercuryType}.
>  +The symbolic name allows the foreign code to create a value
>  +corresponding to that of the constructor it represents.
>  +(The exact mechanism used depends upon the foreign language;
>  +see the language specific information below for further details.)
>  +
>  +For each foreign language there is a default mapping between the name
>  +of a Mercury constructor and its symbolic name in the language @var{Lang}.
>  +This default mapping is not required to map every valid constructor name
>  +to a valid name in language @var{Lang}; where it does not the programmer
>  +must specify a valid symbolic name.
>  +The programmer may also choose to map a constructor to a symbolic name
>  +that differs from the one supplied by the default mapping for language
>  + at var{Lang}.
>  + at var{Overrides} is a list whose elements are pairs of constructor names
>  +and strings.
>  +The latter specify the name that the implementation should use as the
>  +symbolic name in the foreign language.
>  + at var{Overrides} has the following form:
>  +
>  + at example
>  +[consI - "symbolI", ..., consJ - "symbolJ"]
>  + at end example

I suggest underscores before I and J.  "lI" looks especially bad.

>  +
>  +This can be used to provide either a valid symbolic name where the
>  +default mapping does not, or to override a valid symbolic name
>  +generated by the default mapping.
>  +This argument may be omitted if @var{Overrides} is empty.
>  +
>  +The argument @var{Attributes} is a list of optional attributes.
>  +If empty, it may be omitted from the @samp{pragma foreign_export_enum}
>  +declaration.
>  +The following attribute must be supported by all Mercury implementations.
>  +
>  + at table @asis
>  + + at item @samp{prefix(Prefix)}
>  +Prefix each symbolic name, regardless of how it was generated, with
>  +the string @var{Prefix}.
>  +This occurs @emph{before} the validity of the symbolic name in the
>  +foreign language is checked, i.e. the effect of the @samp{prefix}
>  +attribute may cause an otherwise valid symbolic name to become invalid or
>  +vice versa.
>  +At most one @samp{prefix} attribute may be specified for a
>  + at samp{pragma foreign_export_enum} declaration.
>  +
>  + at end table
>  +
>  +It is an error if the mapping between constructors and symbolic names
>  +does not form a bijection.
>  +A program can contain multiple @samp{pragma foreign_export_enum}
>  +declarations for a single Mercury type.
>  +The implementation is not required to check that the symbolic names
>  +generated by separate @samp{pragma foreign_export_enum} declarations
>  +are unique.
>  +
>  +A module may contain @samp{pragma foreign_export_enum} declarations that
>  +refer to imported types, subject to the usual visibility restrictions.
>  +
>  +A @samp{pragma foreign_export_enum} declaration may not occur in the
>  +interface of module.

of a module

Maybe phrase it more directly:

    A pragma foreign_export_enum declaration may only occur within an
    implementation section of a module.

>  @@ -7072,11 +7152,12 @@
>   @subsection Interfacing with C
> 
>   @menu
>  -* Using pragma foreign_type for C 	:: Declaring C types in Mercury
>  -* Using pragma foreign_proc for C 	:: Calling C code from Mercury
>  -* Using pragma foreign_export for C     :: Calling Mercury code from C
>  -* Using pragma foreign_decl for C 	:: Including C declarations in Mercury
>  -* Using pragma foreign_code for C 	:: Including C code in Mercury
>  +* Using pragma foreign_type for C 	 :: Declaring C types in Mercury
>  +* Using pragma foreign_export_enum for C :: Using Mercury enumerations in C
>  +* Using pragma foreign_proc for C 	 :: Calling C code from Mercury
>  +* Using pragma foreign_export for C      :: Calling Mercury code from C
>  +* Using pragma foreign_decl for C 	 :: Including C declarations in Mercury
>  +* Using pragma foreign_code for C 	 :: Including C code in Mercury
>   @end menu
> 
>   @node Using pragma foreign_type for C
>  @@ -7126,6 +7207,27 @@
>   @c XXX we should eventually just move that section to here,
>   @c presenting it as an alternative to pragma foreign_type.
> 
>  + at node Using pragma foreign_export_enum for C
>  + at subsubsection Using pragma foreign_export_enum for C
>  +
>  +For C the symbolic names generated by a @samp{pragma foreign_export_enum}
>  +must form valid C identifiers.
>  +Theses identifiers are used as the names of preprocessor macros.

These

>  +The body of each of these macros expands to a value that is identical
>  +to that of the constructor to which the symbolic name corresponds in
>  +the mapping established by the @samp{pragma foreign_export_enum}
>  +declaration.
>  +
>  +As noted in the @pxref{C data passing conventions}, the type of these
>  +values is @samp{MR_Word}.
>  +
>  +The default mapping used by @samp{pragma foreign_export_enum}
>  +declarations for  C is to use the Mercury constructor name as the
>  +base of the symbolic name.

Add an example here.

The rest is probably fine.

Peter

--------------------------------------------------------------------------
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