[m-rev.] for review: new erlang RTTI

Peter Wang wangp at students.csse.unimelb.edu.au
Fri Jun 1 11:33:52 AEST 2007


On 2007-06-01, Peter Ross <pro at missioncriticalit.com> wrote:
>  
> Index: compiler/erl_rtti.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/erl_rtti.m,v
> retrieving revision 1.2
> diff -u -r1.2 erl_rtti.m
> --- compiler/erl_rtti.m	30 May 2007 08:16:01 -0000	1.2
> +++ compiler/erl_rtti.m	31 May 2007 13:10:51 -0000
> @@ -7,7 +7,7 @@
>  %-----------------------------------------------------------------------------%
>  % 
>  % File: erl_rtti.m.
> -% Main author: wangp.
> +% Main author: wangp, petdr
>  % 
>  % This module converts from the back-end-independent RTTI data structures into
>  % ELDS function definitions.
> @@ -20,6 +20,8 @@
>  :- interface.
>  
>  :- import_module backend_libs.rtti.
> +:- import_module backend_libs.erlang_rtti.
> +
>  :- import_module erl_backend.elds.
>  :- import_module hlds.hlds_module.
>  

Sort that and remove the blank line.

> @@ -47,21 +59,187 @@
>  :- import_module bool.
>  :- import_module int.
>  :- import_module maybe.
> +:- import_module string.
>  :- import_module svvarset.
>  :- import_module univ.
>  :- import_module varset.
>  
>  %-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +
> +:- import_module require.
> +

Move that up or delete it.

> +    % Given the type_ctor_details return the erlang version of those
> +    % details.
> +    % This means conflating enum and no_tags into erlang_du,
> +    % aborting on reserved types, and specially handling the list type.
> +    %
> +:- func erlang_type_ctor_details(module_name, string,
> +    int, type_ctor_details) = erlang_type_ctor_details.
> +
> +erlang_type_ctor_details(ModuleName, TypeName, Arity, Details) = D :-
> +    (
> +        ModuleName = unqualified("list"),
> +        TypeName = "list",
> +        Arity = 1
> +    ->
> +        ( list_argument_type(Details, Type) ->
> +            D = erlang_list(Type)
> +        ;
> +            unexpected(this_file, "erlang_type_ctor_details: " ++
> +                "unable to determine type of list argument")
> +        )
> +    ;
> +        D = erlang_type_ctor_details_2(Details)
> +    ).
> +
> +    %
> +    % Given a type_ctor_detail which represents a list,
> +    % determine type type of the argument to the list.
> +    %

the type

> +convert_du_functor(du_functor(Name, Arity, Ordinal, _, ArgInfos, Exist)) =
> +    erlang_du_functor(Name, Arity, Ordinal + 1, Name, ArgInfos, Exist).
> +
> +:- func convert_to_rtti_maybe_pseudo_type_info_or_self(
> +    rtti_maybe_pseudo_type_info) = rtti_maybe_pseudo_type_info_or_self.
> +
> +convert_to_rtti_maybe_pseudo_type_info_or_self(pseudo(P)) = pseudo(P).
> +convert_to_rtti_maybe_pseudo_type_info_or_self(plain(P)) = plain(P).
> +
> +    %
> +    % Restrict the implementation artificats to only those
> +    % allowed on the erlang backend.
> +    %

artifacts

> -gen_init_special_pred(ModuleInfo, RttiProcIdUniv, Expr, !VarSet) :-
> -    ( univ_to_type(RttiProcIdUniv, RttiProcId) ->
> +:- pred gen_init_special_pred(module_info::in, maybe(rtti_proc_label)::in,
> +    elds_expr::out, prog_varset::in, prog_varset::out) is det.
> +
> +gen_init_special_pred(ModuleInfo, MaybeRttiProcId, Expr, !VarSet) :-
> +    ( MaybeRttiProcId = yes(RttiProcId),
>          erl_gen_special_pred_wrapper(ModuleInfo, RttiProcId, Expr, !VarSet)
> -    ;
> +    ; MaybeRttiProcId = no,
>          unexpected(this_file,
> -            "gen_init_special_pred: cannot extract univ value")
> +            "gen_init_special_pred: no special pred")
>      ).

Format switches like:

    (
	MaybeRttiProcId = yes(...),
	...
    ;
	MaybeRttiProcId = no,
	...
    )

>  :- pred erl_gen_special_pred_wrapper(module_info::in, rtti_proc_label::in,
> Index: compiler/erlang_rtti.m
> ===================================================================
> RCS file: compiler/erlang_rtti.m
> diff -N compiler/erlang_rtti.m
> --- /dev/null	1 Jan 1970 00:00:00 -0000
> +++ compiler/erlang_rtti.m	31 May 2007 13:10:51 -0000
> @@ -0,0 +1,171 @@
> +%-----------------------------------------------------------------------------%
> +% vim: ft=mercury ts=4 sw=4 et
> +%-----------------------------------------------------------------------------%
> +% Copyright (C) 2007 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.
> +%-----------------------------------------------------------------------------%
> +% 
> +% File: erlang_rtti.m.
> +% Authors: petdr, zs.
> +% 
> +% Definitions of data structures for representing run-time type information
> +% in the Erlang backend.

Add an explanation of the difference between this and erl_rtti.m.

> +    % A type_ctor_data structure contains all the information that the
> +    % runtime system needs to know about a type constructor.
> +    %
> +:- type erlang_type_ctor_data
> +    --->    erlang_type_ctor_data(
> +                etcr_version        :: int,
> +                etcr_module_name    :: module_name,
> +                etcr_type_name      :: string,
> +                etcr_arity          :: int,
> +                    
> +                    %
> +                    % It is possible that the type doesn't have
> +                    % a unify or compare predicate.
> +                    % eg one cannot unify higher-order types.
> +                    %
> +                etcr_unify          :: maybe(rtti_proc_label),
> +                etcr_compare        :: maybe(rtti_proc_label),
> +                etcr_rep_details    :: erlang_type_ctor_details
> +            ).

I don't think we indent comments in this context.

> Index: compiler/mercury_compile.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
> retrieving revision 1.437
> diff -u -r1.437 mercury_compile.m
> --- compiler/mercury_compile.m	28 May 2007 03:13:52 -0000	1.437
> +++ compiler/mercury_compile.m	31 May 2007 13:10:54 -0000
> @@ -5207,9 +5207,11 @@
>      list.append(OldTypeClassInfoRttiData, NewTypeClassInfoRttiData,
>          TypeClassInfoRttiData),
>      RttiDatas = TypeCtorRttiData ++ TypeClassInfoRttiData,
> +    ErlangRttiDatas = list.map(erlang_rtti_data(HLDS), RttiDatas),
>  
>      ELDS0 = elds(ModuleName, ForeignBodies, Defns, FEDefns, RttiDefns0),
> -    rtti_data_list_to_elds(HLDS, RttiDatas, RttiDefns),
> +    
> +    rtti_data_list_to_elds(HLDS, ErlangRttiDatas, RttiDefns),
>      ELDS = elds(ModuleName, ForeignBodies, Defns, FEDefns,
>          RttiDefns0 ++ RttiDefns).
>  
> Index: library/builtin.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/library/builtin.m,v
> retrieving revision 1.128
> diff -u -r1.128 builtin.m
> --- library/builtin.m	30 May 2007 08:16:02 -0000	1.128
> +++ library/builtin.m	31 May 2007 13:10:56 -0000
> @@ -594,6 +594,7 @@
>  
>  :- implementation.
>  :- use_module rtti_implementation.
> +:- use_module erlang_rtti_implementation.

Sort that.

>  call_rtti_generic_unify(X, Y) :-
>      rtti_implementation.generic_unify(X, Y).
> @@ -810,9 +811,8 @@
>      '__Unify____c_pointer_0'(_, _) ->
>          throw(""called unify for type `c_pointer'"").
>  
> -    % XXX TypeInfo ignored
>      compare_3_p_0(TypeInfo, X, Y) ->
> -        mercury__rtti_implementation:generic_compare_3_p_0(TypeInfo, X, Y).
> +        mercury__erlang_rtti_implementation:generic_compare_3_p_0(TypeInfo, X, Y).

Long line.
>  
>      compare_3_p_1(TypeInfo, X, Y) ->
>          compare_3_p_0(TypeInfo, X, Y).
> @@ -828,7 +828,7 @@
>          compare_3_p_0(TypeInfo, X, Y).
>  
>      unify_2_p_0(TypeInfo, X, Y) ->
> -        mercury__rtti_implementation:generic_unify_2_p_0(TypeInfo, X, Y).
> +        mercury__erlang_rtti_implementation:generic_unify_2_p_0(TypeInfo, X, Y).

Long line.


> Index: library/erlang_rtti_implementation.m
> ===================================================================
> RCS file: library/erlang_rtti_implementation.m
> diff -N library/erlang_rtti_implementation.m
> --- /dev/null	1 Jan 1970 00:00:00 -0000
> +++ library/erlang_rtti_implementation.m	31 May 2007 13:10:56 -0000
...
> +
> +:- implementation.
> +
> +:- import_module int.
> +:- import_module require.
> +:- import_module string.
> +
> +    %
> +    % A type_info can be represented for one of three ways

in one of

> +    % For a type with arity 0
> +    %   TypeCtorInfo
> +    % a type with arity > 0
> +    %   { TypeCtorInfo, TypeInfo0, ..., TypeInfoN }
> +    % a type with variable arity of size N
> +    %   { TypeCtorInfo, N, TypeCtorInfo0, ..., TypeCtorInfoN }
> +    %   
> +:- type type_info.
> +:- pragma foreign_type("Erlang", type_info, "").
> +:- type type_info ---> type_info.

You could remove the abstract type there, although I can see why you wrote it
like that.

> +    %
> +    % For the representation of a type_ctor_info
> +    % see erlang_rtti:type_ctor_data_to_elds
> +    %
> +:- type type_ctor_info.
> +:- pragma foreign_type("Erlang", type_ctor_info, "").
> +:- type type_ctor_info ---> type_ctor_info.
> +

Likewise.

> +    % The type_ctor_rep needs to be kept up to date with the alternatives
> +    % given by the function erl_rtti.erlang_type_ctor_rep/1
> +    %
> +:- type erlang_type_ctor_rep
> +    --->    du
> +    ;       list
> +    ;       eqv
> +    ;       int
> +    ;       float
> +    ;       char
> +    ;       string
> +    ;       void
> +    ;       stable_c_pointer
> +    ;       c_pointer
> +    ;       (pred)
> +    ;       (func)
> +    ;       tuple
> +    ;       ref
> +    ;       type_desc
> +    ;       pseudo_type_desc
> +    ;       type_ctor_desc
> +    ;       type_info
> +    ;       type_ctor_info
> +    ;       typeclass_info
> +    ;       base_typeclass_info
> +    ;       foreign
> +
> +            % These types shouldn't be needed they are
> +            % introduced for library predicates which
> +            % don't apply on this backend.
> +    ;       hp
> +    ;       subgoal
> +    ;       ticket
> +    .

It would be better to put prefixes on these functors but it can be done later.

> +
> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +
> +:- pragma foreign_code("Erlang", "
> +        % Location of element in a type_info
> +    ti_type_ctor_info() -> 1.
> +    ti_var_arity() -> 2.
> +
> +        % Location of elements in a type_ctor_info
> +    tci_arity() -> 1.
> +    tci_version() -> 2.
> +    tci_unify_pred() -> 3.
> +    tci_compare_pred() -> 4.
> +    tci_module_name() -> 5.
> +    tci_type_name() -> 6.
> +    tci_type_ctor_rep() -> 7.
> +    tci_functors() -> 8.
> +").

It might be worth using Erlang macros for these constants later on.

> +
> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +
> +    % We override the above definitions in the .NET backend.

Erlang backend


Otherwise it looks 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