1/* Copyright (C) 1996-2002 UPM-CLIP */
    2
    3:- module(dict,[dictionary/1, dictionary/5, dic_node/2,
    4		 dic_lookup/3, dic_lookup/4,
    5		 dic_get/3, dic_replace/4,
    6		 old_or_new/1,
    7		 non_empty_dictionary/1]).    8
    9dictionary(X) :- term(X).  % A free variable is a valid dictionary.
   10
   11non_empty_dictionary(dic(K,V,L,R)):-
   12	term(K),
   13	term(V),
   14	dictionary(L),
   15	dictionary(R).
   16
   17term(_).
   18
   19old_or_new(old).
   20old_or_new(new).
   21
   22dictionary(dic(K,V,L,R),K,V,L,R).
   23
   24dic_node([], _) :- !, fail. % variable
   25dic_node(Node, Node).
   26dic_node(dic(_,_,L,_), Node) :- dic_node(L, Node).
   27dic_node(dic(_,_,_,R), Node) :- dic_node(R, Node).
   28
   29dic_lookup(Dic, Key, Val) :-
   30        dic_lookup(Dic, Key, Val, _Occ).
   31
   32dic_lookup(Dic, Key, Val, Occ) :-
   33	var(Dic), !,
   34	Dic=dic(Key,Val,_,_),
   35        Occ = new.
   36dic_lookup(dic(K,V,L,R), Key, Val, Occ) :-
   37	compare(Rel, Key, K),
   38	dic_lookup_(Rel, Key, Val, V, L, R, Occ).
   39
   40dic_lookup_(=, _, Val, Val, _, _, old).
   41dic_lookup_(<, Key, Val, _, L, _, Occ) :- dic_lookup(L, Key, Val, Occ).
   42dic_lookup_(>, Key, Val, _, _, R, Occ) :- dic_lookup(R, Key, Val, Occ).
   43
   44dic_get(Dic, Key, Val) :-
   45	nonvar(Dic),
   46	Dic=dic(K,V,L,R),
   47	compare(X, Key, K),
   48	dic_get_(X, Key, Val, V, L, R).
   49
   50dic_get_(=, _, Val, Val, _, _).
   51dic_get_(<, Key, Val, _, L, _) :- dic_get(L, Key, Val).
   52dic_get_(>, Key, Val, _, _, R) :- dic_get(R, Key, Val).
   53
   54dic_replace(Dic, Key, Val, Dic1) :-
   55	var(Dic), !,
   56	Dic1=dic(Key,Val,_,_).
   57dic_replace(dic(Key1,Val1,L1,R1), Key, Val, dic(Key1,Val2,L2,R2)) :-
   58	compare(X, Key, Key1),
   59	dic_replace_(X, Key, Val, Key1, Val1, L1, R1, Val2, L2, R2).
   60
   61dic_replace_(=, _, Val, _, _, L, R, Val, L, R).
   62dic_replace_(<, Key, Val, _, Val1, L1, R, Val1, L2, R) :-
   63	dic_replace(L1, Key, Val, L2).
   64dic_replace_(>, Key, Val, _, Val1, L, R1, Val1, L, R2) :-
   65	dic_replace(R1, Key, Val, R2)