Replace_unifies

I was writing some code for a game. It handles geometry, so there’s lots of numeric constants. It was fairly obvious this was the road to hell.

Not wanting to dig constants out of a fact, I decided to use $cell_width type constants, so quickly banged this out.

:- module(symbolic_constant,
          [
              sym/2
          ]).

:- dynamic symbolic_constant/2.

sym(Name, Val) :-
    asserta(symbolic_constant(Name, Val)).

expand_constants(In, In) :-
    var(In),
    !.
expand_constants($In, Out) :-
    symbolic_constant(In, Out).
expand_constants($In, _Out) :-
    \+ symbolic_constant(In, _),
    throw(format('no such constant'-[In])).
expand_constants(In, In) :-
    atomic(In).
expand_constants(In, Out) :-
    is_dict(In),
    dict_pairs(In, Tag, Pairs),
    maplist(expand_pair, Pairs, PairsOut),
    dict_pairs(Out, Tag, PairsOut),
    !.
expand_constants(In, Out) :-
    compound(In),
    In =.. InList,
    maplist(expand_constants, InList, OutList),
    Out =.. OutList.
expand_constants(In, Out) :-
    is_list(In),
    maplist(expand_constants, In, Out).

expand_pair(K-V, KO-VO) :-
    expand_constants(K, KO),
    expand_constants(V, VO).

user:term_expansion(In, Out) :-
    expand_constants(In, Out).

very dissatisfied. Is there a more robust way to do this, preferably a system predicate?

Ideally there would be some general map_term that takes each sub_term and applies some transform to it. I can trivially convert the above to such a thing, but I’m wondering why there isn’t a library predicate that does this. Am I missing it? I end up doing this about every 6 months.

Since recently (after a similar discussion), mapargs/3 :slight_smile:

1 Like

Can’t see how mapargs/3 is relevant here.

This just feels like a general pattern. Last time I needed it I needed to do XSLT’s job - I had XML and wanted to replace some pattern with another one.

Something like this:

:- use_module(library(terms)).

map_symbols(TermIn, TermOut) :-
    mapargs(map, TermIn, TermOut).

map($X, Val) =>
    (   symbol(X, Val0)
    ->  Val = Val0
    ;   existence_error(symbol, X)
    ).
map(X, Val) => Val = X.

symbol(pi, 3.14).

And then:

?- map_symbols(x($pi), T).
T = x(3.14).
1 Like

Can this be used for term expansion as well – as a way to introduce constants …

Also, what does map_symbols/2 do – it isn’t called from map/2

Jan - I’m doing

foo(7.14, blah(_{barg: $pi}, _), [1, 3, mep($tau)]) goes to
foo(7.14, blah(_{barg:3.14}, _), [1, 3, mep(6.28)])

and more generally, would like to do replace all patterns that match using a lambda

Sorry, example called wrong predicate. Edited.

Oops, I thought mapargs/3 works recursively. Sorry. I’ve just added mapsubterms/3 that does the job recursively. Now your call works with

:- use_module(library(terms)).

map_symbols(TermIn, TermOut) :-
    mapsubterms(map, TermIn, TermOut).

map($(X), Val), atom(X) =>
    (   symbol(X, Val0)
    ->  Val = Val0
    ;   existence_error(symbol, X)
    ).
map(_, _) =>
    fail.

symbol(pi, 3.14).
symbol(tau, 6.28).

Docs for the new predicate are below. Details may change depending on feedback, e.g.

  • Better name? I deliberately omitted the underscore are none of the mapping predicates use this.
  • Should we call the mapper on variables?
  • ???

mapsubterms(:Goal, +Term1, -Term2) is det.

Recursively map sub terms of Term1 into subterms of Term2 for every pair for which call(Goal, ST1, ST2) succeeds. Procedurably, the mapping for each (sub) term pair T1/T2 is defined as:

  • If T1 is a variable, Unify T2 with T1.
  • If call(Goal, T1, T2) succeeds we are done. Note that the mapping does not continue in T2. If this is desired, Goal must call mapsubterms/3 explicitly as part of it conversion.
  • If T1 is a dict, map all values, i.e., the tag and keys are left untouched.
  • If T1 is a list, map all elements, i.e., the list structure is left untouched.
  • If T1 is a compound, use same_functor/3 to instantiate T2 and recurse over the term arguments left to right.
  • Otherwise T2 is unified with T1.
2 Likes

yay! much better to have it in the library. I didn’t like my roll yer own

Depending on your use-case, perhaps destructive assignment to dicts? (b_set_dict/3).

But there doesn’t seem to be a mapdict, although it’s easy to roll your own with dict_pairs/2, maplist/3, and the various predicates that operate on pairs.

not destructive.

The assignment is undone on backtracking, if that’s what you mean. (And the key must already be in the dict)

?- D=d{a:1,b:2}, (b_set_dict(a,D,555), writeln(D), fail ; writeln(D)).
d{a:555,b:2}
d{a:1,b:2}
D = d{a:1, b:2}.