How to disable specific multifile predicates? i.e. portray(cr(A))

For portray/1, which is a multifile predicate, there are existing predicates of portray(cr(A)).

Can some specific predicates be disabled?


Details

When parsing with DCGs

One module has portray/1 predicates for terminals. (rfc5234_base_types).
Another module for the non-terminals uses the portray/1 predicates from the module for terminals. (rfc5234_structures)

A listing of portray(cr(_)) shows other portray/1 predicates for cr(_) that are not desired.

?- listing(portray(cr(_))).
:- multifile rfc5234_base_types:portray/1.

rfc5234_base_types:portray(cr(String)) :-
    write(String).

:- multifile rfc5234_structures:portray/1.


:- dynamic portray/1.
:- multifile portray/1.

portray(cr(A)) :-
    pce_portray:
    (   cr(A)= @(Ref),
        object(cr(A)),
        !,
        (   send(cr(A), '_instance_of'(var))
        ->  get(cr(A), '_value', Value),
            format('@~w(= ~p)', [Ref, Value])
        ;   get(cr(A), '_class_name', CN),
            format('@~w/~w', [Ref, CN])
        )
    ).
portray(cr(A)) :-
    portray_text:
    (   do_portray_text(true),
        '$skip_list'(Length, cr(A), Tail),
        portray_text_option(min_length, MinLen),
        Length>=MinLen,
        all_ascii(cr(A)),
        portray_text_option(ellipsis, IfLonger),
        put_char('"'),
        (   Length>IfLonger
        ->  First is IfLonger+ -5,
            Skip is Length+ -5,
            skip_first(Skip, cr(A), Rest),
            put_n_codes(First, cr(A)),
            format(..., [])
        ;   Rest=cr(A)
        ),
        (   var_or_numbered(Tail)
        ->  put_var_codes(Rest)
        ;   format('~s', [Rest])
        ),
        put_char('"')
    ).

true.

EDIT

For now I will call this a workaround because I believe there is a better solution, I just don’t know it.

Instead of trying to disable or exclude certain predicates, the desired predicates are called specifically using the module name, e.g.

in rfc5234_structures.pl

portray(crlf(CR,LF)) :-
    rfc5234_base_types:portray(CR),
    rfc5234_base_types:portray(LF).

This is defeating the purpose of multifile but it works.


Personal Notes - click to expand

As noted by Jan W.

This is the result of a dubious property of listing/1 (bug). If you look at the code you’ll see it uses a plain variable rather than cr(A) .

pce_portray is a module found in GitHub - SWI-Prolog - packages-xpce/prolog/boot/pce_portray.pl

(ref)

user:portray(Obj) :-
    Obj = @Ref,
    object(Obj),
    !,
    (   send(Obj, '_instance_of', var)
    ->  get(Obj, '_value', Value),
        format('@~w(= ~p)', [Ref, Value])
    ;   get(Obj, '_class_name', CN),
        format('@~w/~w', [Ref, CN])
    ).

portray_text is a module found in GitHub - SWI-Prolog - swipl-devel/library/portray_test.pl

(ref)

:- multifile
    user:portray/1.
:- dynamic
    user:portray/1.

user:portray(Codes) :-
    do_portray_text(true),
    '$skip_list'(Length, Codes, Tail),
    portray_text_option(min_length, MinLen),
    Length >= MinLen,
    all_ascii(Codes),
    portray_text_option(ellipsis, IfLonger),
    put_char('"'),
    (   Length > IfLonger
    ->  First is IfLonger - 5,
        Skip is Length - 5,
        skip_first(Skip, Codes, Rest),
        put_n_codes(First, Codes),
        format('...', [])
    ;   Rest = Codes
    ),
    (   var_or_numbered(Tail)
    ->  put_var_codes(Rest)
    ;   format('~s', [Rest])
    ),
    put_char('"').

When first reading the note by Jan W. it seemed the variable causing the bug was in the use of _ in listing(portray(cr(_))).. In inspecting the listed predicates it is obvious that their use of a variable is the reason the extra predicates show up, e.g.

user:portray(Obj)

and

user:portray(Codes)

is unifying with portray(cr(_)) and resulting in them being listed.

The extra predicates show up after executing gtrace/0, e.g.

Welcome to SWI-Prolog (threaded, 64 bits, version 8.3.4-11-g1db629e24)

?- listing(portray(cr(_))).
:- dynamic portray/1.
:- multifile portray/1.


true.

?- gtrace.
% The graphical front-end will be used for subsequent tracing
true.

[trace]  ?- nodebug.
true.

?- listing(portray(cr(_))).
:- dynamic portray/1.
:- multifile portray/1.

portray(cr(A)) :-
    pce_portray:
    (   cr(A)= @(Ref),
        object(cr(A)),
        !,
        (   send(cr(A), '_instance_of'(var))
        ->  get(cr(A), '_value', Value),
            format('@~w(= ~p)', [Ref, Value])
        ;   get(cr(A), '_class_name', CN),
            format('@~w/~w', [Ref, CN])
        )
    ).
portray(cr(A)) :-
    portray_text:
    (   do_portray_text(true),
        '$skip_list'(Length, cr(A), Tail),
        portray_text_option(min_length, MinLen),
        Length>=MinLen,
        all_ascii(cr(A)),
        portray_text_option(ellipsis, IfLonger),
        put_char('"'),
        (   Length>IfLonger
        ->  First is IfLonger+ -5,
            Skip is Length+ -5,
            skip_first(Skip, cr(A), Rest),
            put_n_codes(First, cr(A)),
            format(..., [])
        ;   Rest=cr(A)
        ),
        (   var_or_numbered(Tail)
        ->  put_var_codes(Rest)
        ;   format('~s', [Rest])
        ),
        put_char('"')
    ).

true.

As a further example after gtrace/0 is run, listing(portray(dummy(_))). will also list the predicates using a variable name instead of a functor.


By Jan W.

Defining a hook without using the thing that is hooked can’t be right.

This is referring to the calling of portray/1 directly. It is not meant to be called directly and if not for having the property multifile, it would probably not be accessible.

?- predicate_property(portray(_),P).
P = interpreted ;
P = visible ;
P =  (dynamic) ;
P =  (multifile) ;
P = number_of_clauses(0) ;
P = number_of_rules(0) ;
P = last_modified_generation(0) ;
P = defined ;
P = size(112).

If one reads the documentation for portray/1 it notes

A dynamic predicate, which can be defined by the user to change the behaviour of print/1 on (sub)terms. For each subterm encountered that is not a variable print/1 first calls portray/1 using the term as argument. For lists, only the list as a whole is given to portray/1. If portray/1 succeeds print/1 assumes the term has been written.

So portray/1 is only to be used via print/1 and not called directly.


EDIT

For an example of converting a structure back into text, look at how callgraph generated the dot file in dot.pl

1 Like

This is the result of a dubious property of listing/1 (bug). If you look at the code you’ll see it uses a plain variable rather than cr(A).

Using portray effectively typically involve you can quite uniquely detect the term you want to portray. Note that portray/1 is intended for debugging and human toplevel interaction only. It should not be considered a way to hook writing terms. It mainly simplifies interaction that include huge unreadable terms or terms that are hard to interpret, such as integer character codes (you rather see the character), etc.

OK

What would be the preferred way to take a structure that was created by parsing text (original) using DCGs then convert that structure back into text (reconstructed) for use with a fixed point check where the reconstructed text and the original text should be identical?

Original text → Parse with DCG → structure → ??? → reconstructed text
??? is currently done using portray/1

Fix point check
Original text = reconstructed text

The current code for the fixed point check.
I note this because I don’t see that I am hooking the writing of terms. The entire structure created by the DCG (Rules_1) is passed to portray/1.

fixed_point_check(Abnf_path) :-
    setup_call_cleanup(
        open(Abnf_path,read,Abnf_stream),
        (
            set_stream(Abnf_stream, newline(posix)),
            read_stream_to_codes(Abnf_stream,Codes_1),
            DCG1 = rulelist(Rules_1),
            phrase(DCG1,Codes_1,[])
        ),
        close(Abnf_stream)
    ),
    with_output_to(string(BNF_1),portray(Rules_1)),
    format('~w',[BNF_1]),
    string_codes(BNF_1,Codes2),
    DCG2 = rulelist(Rules_2),
    phrase(DCG2,Codes2,[]),
    with_output_to(string(BNF_2),portray(Rules_2)),
    assertion( BNF_1 == BNF_2).

I suppose that using a different DCG to convert the structure back into text would work, but portray is so much more simplistic and beautiful.

EDIT

After a small coffee break came to this realization.

Instead of using portray/1 another predicate name can be used. The head and body of all of the existing clauses remain the same only the name has been changed. This then removes the multifile requirement when using portray and the module system can be used. :smiley:

Yip. Defining a hook without using the thing that is hooked can’t be right. DCGs are really elegant ways to serialize terms though, generally even cleaner than using them for parsing.

1 Like

After fix for listing/1.

Welcome to SWI-Prolog (threaded, 64 bits, version 8.3.4-18-ge5d07a583)

?- listing(portray(cr(_))).
:- dynamic portray/1.
:- multifile portray/1.


true.

?- gtrace.
% The graphical front-end will be used for subsequent tracing
true.

[trace]  ?- nodebug.
true.

?- listing(portray(cr(_))).
:- dynamic portray/1.
:- multifile portray/1.

portray(Obj) :-
    pce_portray:
    (   Obj= @(Ref),
        object(Obj),
        !,
        (   send(Obj, '_instance_of'(var))
        ->  get(Obj, '_value', Value),
            format('@~w(= ~p)', [Ref, Value])
        ;   get(Obj, '_class_name', CN),
            format('@~w/~w', [Ref, CN])
        )
    ).
portray(Codes) :-
    portray_text:
    (   do_portray_text(true),
        '$skip_list'(Length, Codes, Tail),
        portray_text_option(min_length, MinLen),
        Length>=MinLen,
        all_ascii(Codes),
        portray_text_option(ellipsis, IfLonger),
        put_char('"'),
        (   Length>IfLonger
        ->  First is IfLonger+ -5,
            Skip is Length+ -5,
            skip_first(Skip, Codes, Rest),
            put_n_codes(First, Codes),
            format(..., [])
        ;   Rest=Codes
        ),
        (   var_or_numbered(Tail)
        ->  put_var_codes(Rest)
        ;   format('~s', [Rest])
        ),
        put_char('"')
    ).

true.

Notice that portray(cr(A)) :- is now portray(Obj) :-.

1 Like