[m-dev.] Re: Visual vs total arity clash example [fwd]

Peter Nicholas MALKIN pnmalk at students.cs.mu.oz.au
Thu Jan 27 22:24:45 AEDT 2000


Hi,

Fact: to allow for *OLD* code using DCGs or code written explicitly using
io__state, to still work with the new io.m predicates that use EDCGs I must
allow EDCG predicates to be called in expanded form.

Consider the following code:

****************** Old Code **************************************************

	% app_all appends two lists onto the front of another list.
:- pred app_all(list(char), list(char), list(char), list(char)).
:- mode app_all(in, in, in, out) is det.

app_all(Cs1, Cs2, L0, L2) :-
	app(Cs2, L0, L1),	% This is an ambiguity error
	app(Cs1, L1, L2).	% This is an ambiguity error

:- pred app(list(char), list(char), list(char)).
:- mode app(in, in, out) is det.

app([], L0, L1).
app([C | Cs], L0, L2) :-
        app(Cs, L0, L1),	% This is an ambiguity error
        L2 = [C | L1].

****************** New Code **************************************************

:- htype(list_acc, list(char)).
:- hmode(list_acc, changed(in, out)).

:- pred app(list(char)) +hidden(changed(list_acc)).
:- mode app(in) is det.

app([]).
app([C | Cs]) -->>
        app(Cs),
        $=list_acc = [C | $list_acc].

*******************************************************************************

Now although there is no visual arity conflict here there is an ambiguity error
because the compiler does not know, even based upon types whether the call
within the old that the call to app/3 is a call to the old app/3 or the new
app/1 with total arity 3 because it could be a call to app/1 in expanded form.


On Wed, 26 Jan 2000, Peter Schachte wrote:

> > The following code will produce an ambiguity. This is because I have no idea
> > whether the clauses for app/1 (written in expanded form), are for app/1 or
> > for app/3.
> 
> Ah, I see.  I didn't realize you wanted to be able to write whole
> predicates using hidden arguments without using the proper syntax for
> it.
>
> > You may argue that I know that the clauses are for app/1 because the hidden
> > functor `-->>' is not used, however for facts this is not required
> 
> True.
> 
> > and secondly
> > because I cannot count on the fact that the user has not forgotten
> > to put it in.
> 
> Yes you can:  it should be an error to write a predicate involving
> hidden arguments with :- instead of -->>.  The reason for using -->>
> instead of :- is so that we know that the writer and reader know that
> this isn't an ordinary predicate, and conjunction isn't commutative.
> 
> But I would argue that (unlike DCGs) there's no reason to allow users
> to write EDCG clauses fully expanded.  Firstly, everything that can be
> done by writing clauses directly can also be done with EDCG syntax.
> Secondly, doing this requires that users understand how many arguments
> are added and in which order for each hidden variable, and also what
> order the variables are added.  (I sure hope you put the variables in
> some canonical order, eg alphabetically sorted, rather than using the
> order provided.  There's no reason to force users list these things in
> the right order when they list the hiddens that a predicate handles.
> Hiddens should be a set, not a list.)  Yes, this can all be explained,
> and it's not terribly difficult, but I see no reasons for users to
> have to understand these complications.  More importantly, by
> explaining them, you lock yourself into one implementation strategy
> when there may be better approaches.
> 
> Finally, there's very little benefit to allowing users to write
> expanded clauses, at least compared to the cost.  Can you give a
> realistic example of a clause that's somehow better written already
> expanded?  Remember, the cost is that you have to understand how EDGs
> will be expanded in order to know whether two predicates in the same
> module with the same name and different arities conflict.

Yes, I can.

The situation where you wish to use :- instead of -->> is for pragma c_code.
Actually this applies always, maybe some extra syntax for pragma c_code is
needed here. 

e.g.

**********************************************************************

:- pred io__rename_file_2(string, string, int, string) +hidden(changed(io)).
:- mode io__rename_file_2(in, in, out, out) is det.

:- pragma c_code(io__rename_file_2(OldFileName::in, NewFileName::in,
                RetVal::out, RetStr::out, IO0::di, IO::uo),
                [will_not_call_mercury, thread_safe],
"{
        RetVal = rename(OldFileName, NewFileName);
        ML_maybe_make_err_msg(RetVal != 0, ""rename failed: "",
                MR_PROC_LABEL, RetStr);
        update_io(IO0, IO);
}").

**********************************************************************

However there is another case where having an EDCG predicates'
clauses written in expanded form: see below.

> Here's another idea for avoiding this problem:  put each EDCG
> predicate/function in an 'EDCG' submodule of its proper module, and
> export it from this module to the parent module.  That way:
> 
> 1)  Misguided souls who understand the EDCG translation could write
>     EDCG clauses directly by just putting them in the 'EDCG'
>     submodule.
> 
> 2)  Other misguided souls who want to write calls to EDCG predicates
>     specifying all hidden arguments explicitly can do so.  If there's
>     an arity conflict with a non-EDCG predicate, they can overcome it
>     by explicitly module-qualifying the call.
> 
> 3)  For everybody else, it just works.  "Visual arity" is *the* arity.
> 
> Actually, this isn't quite right because, eg, a predicate p/2 with 2
> hidden arguments still conflicts with p/3 with 1 hidden argument.  So
> the full solution is to have a separate submodule for each visual
> arity.  In this example, 'EDCG2' and 'EDCG3'.

I really do not think that whether a predicate uses EDCGs or not should dictate
to the programmer where they put it in a module. This is too artificial a
constraint that could reduce program readability.

> I'd still argue against documenting how the translation works, but if
> you want to document that, at least with this scheme you can avoid
> mysterious arity conflicts and still let misguided users do their own
> hand translations.

Documentating how the translation works is only temporary, since the backwards
compatability requirement is only temporary too! So only for the duration of the
backwards compatability requirement does how the translation works need to be
documented.

On Thu, 27 Jan 2000, Peter Schachte wrote:

> On Wed, Jan 26, 2000 at 03:46:29PM +1100, Fergus Henderson wrote:
> > > I would argue that (unlike DCGs) there's no reason to allow users to
> > > write EDCG clauses fully expanded.
> > 
> > I pretty much agree -- the only reason to support this is for
> > backwards compatibility.
> 
> I assume you're talking about writing EDCG code that calls code
> written to be called from DCGs (whether it was coded using actual DCG
> notation or not)?  Eg,
> 
> 	% existing code:
> 	:- pred p(int, io__state, io__state).
> 	:- mode p(in, di, uo) is det.
> 
> 	p(X) --> ....
> 
> 
> 	% new code:
> 	:- pred q(int) +hidden(changed(io), changed(accum)).
> 	:- mode q(in) ... whatever ... is det.
> 
> 	q(X) -->>
> 		...,
> 		p(X),
> 		....
> 
> In this case, you can tell which thingy to pass as the two extra
> arguments in the call to p by type (I'm assuming accum is an int).
> But in other cases the types won't distinguish them.  At best, you can
> only have partial compatibility.
> 
> BTW, I can't see how this is a backward compatibility issue.  All old
> code will continue to work whichever way you do it.  It's a question
> of new code or old code modified to use EDCG syntax.

Easily modifying old code to interface with new code is part of backwards
compatability. What if I want to modify an existing predicate to receive a
hidden variable but I only want to modify the interface because propagating the
change would be tedious and why change code that works. Modifying the interface
of a module to use EDCGs to interface with other code, but leaving the
implementation alone is backwards compatability and good programming practice.
Only modifying the interface produces the case where a predicate using EDCGs has
clauses which do not.

i.e. 

What if I wished to change the interface of this predicate such that it used
EDCGs so that I could easily use it in other modules that do. I do not want to
be the one to remove all those curly braces and either propagate the change all
the way down the call graph or expand all predicates without curly braces by
adding "$io, $=io)".

**********************************************************************

:- pred mercury_compile(module_imports, io__state, io__state).
:- mode mercury_compile(in, di, uo) is det.

mercury_compile(Module) -->
        globals__io_lookup_bool_option(typecheck_only, TypeCheckOnly),
        globals__io_lookup_bool_option(errorcheck_only, ErrorCheckOnly),
        { bool__or(TypeCheckOnly, ErrorCheckOnly, DontWriteDFile) },
        % If we are only typechecking or error checking, then we should not
        % modify any files, this includes writing to .d files.
        mercury_compile__pre_hlds_pass(Module, DontWriteDFile,
                HLDS1, UndefTypes, UndefModes, Errors1), !,
        mercury_compile__frontend_pass(HLDS1, HLDS20, UndefTypes,
                UndefModes, Errors2), !,
        ( { Errors1 = no }, { Errors2 = no } ->
            globals__io_lookup_bool_option(verbose, Verbose),
            globals__io_lookup_bool_option(statistics, Stats),
            mercury_compile__maybe_write_dependency_graph(HLDS20,
                Verbose, Stats, HLDS21),
            mercury_compile__maybe_generate_schemas(HLDS21, Verbose),
            globals__io_lookup_bool_option(make_optimization_interface,
                MakeOptInt),
            globals__io_lookup_bool_option(make_transitive_opt_interface,
                MakeTransOptInt),
            ( { TypeCheckOnly = yes } ->
                []
            ; { ErrorCheckOnly = yes } ->
                % we may still want to run `unused_args' so that we get
                % the appropriate warnings
                globals__io_lookup_bool_option(warn_unused_args, UnusedArgs),
                ( { UnusedArgs = yes } ->
                        globals__io_set_option(optimize_unused_args, bool(no)),
                        mercury_compile__maybe_unused_args(HLDS21,
                                Verbose, Stats, _)
                ;
                        []
                )
            ; { MakeOptInt = yes } ->
                % only run up to typechecking when making the .opt file
                []
            ; { MakeTransOptInt = yes } ->
                mercury_compile__output_trans_opt_file(HLDS21)
            ;
                { module_imports_get_module_name(Module, ModuleName) },
                mercury_compile__maybe_output_prof_call_graph(HLDS21,
                        Verbose, Stats, HLDS25),
                mercury_compile__middle_pass(ModuleName, HLDS25, HLDS50), !,
                globals__io_lookup_bool_option(highlevel_code, HighLevelCode),
                globals__io_lookup_bool_option(aditi_only, AditiOnly),

                % magic sets can report errors.
                { module_info_num_errors(HLDS50, NumErrors) },
                ( { NumErrors = 0 } ->
                    { module_info_get_do_aditi_compilation(HLDS50, Aditi) },
                    ( { Aditi = do_aditi_compilation } ->
                        mercury_compile__generate_rl_bytecode(HLDS50,
                                Verbose, MaybeRLFile)
                    ;
                        { MaybeRLFile = no }
                    ),
                    ( { AditiOnly = yes } ->
                        []
                    ; { HighLevelCode = yes } ->
                        mercury_compile__mlds_backend(HLDS50),
                        globals__io_lookup_bool_option(compile_to_c,
                                CompileToC),
                        ( { CompileToC = no } ->
                                module_name_to_file_name(ModuleName, ".c", no,
                                        C_File),
                                module_name_to_file_name(ModuleName, ".o", yes,
                                        O_File),
                                mercury_compile__single_c_to_obj(
                                        C_File, O_File, _CompileOK)
                        ;
                            []
                        )
                    ;
                        mercury_compile__backend_pass(HLDS50, HLDS70,
                                GlobalData, LLDS), !,
                        mercury_compile__output_pass(HLDS70, GlobalData, LLDS,
                                MaybeRLFile, ModuleName, _CompileErrors)
                    )
                ;
                    []
                )
            )
        ;
            []
        ).

**********************************************************************

Peter

--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list