25
26:- module(udt, [oo/1,oo/2,is_oo/1,oo_call/3,jpl_call/3,oo_deref/2]). 27
29
30:- use_module(atts). 31:- use_module(multivar). 32
33oo(O):-multivar(O).
34oo(O,Value):-multivar(O),put_attr(O,oo,binding(O,Value)).
35oo:attr_unify_hook(B,Value):- B = binding(_Var,Prev),Prev.equals(Value).
36
37
38oo_set(UDT,Key, Value):- attvar(UDT),!,put_attr(UDT,Key, Value).
39oo_set(UDT,Key, Value):- jpl_set(UDT,Key,Value).
40
41
42
43put_oo(Key, UDT, Value, NewUDT):- is_dict(UDT),!,put_dict(Key, UDT, Value, NewUDT).
44put_oo(Key, UDT, Value, NewUDT):- oo_copy_term(UDT,NewUDT),put_oo(NewUDT,Key, Value).
45
46
47oo_copy_term(UDT,NewUDT):- copy_term(UDT,NewUDT).
48
49put_oo(Key, UDT, Value):- is_dict(UDT),!,put_dict(Key, UDT, Value).
50put_oo(Key, UDT, Value):- oo_set(UDT,Key, Value).
51
52
53get_oo(Key, UDT, Value):- oo_call(UDT,Key, Value).
54
55
56:- meta_predicate(fail_on_missing(0)). 57fail_on_missing(G):-catch(G,error(existence_error(_,_),_),fail).
58
59jpl_call(A,B,C):- B=..[H|L], fail_on_missing(jpl_call(A,H,L,C)),!.
60jpl_call(A,B,C):- jpl_get(A,B,C).
61
62
63
64is_oo(O):- (attvar(O);is_dict(O);jpl_is_ref(O)),!.
66
68oo_call(Self,Memb,Value):- is_dict(Self) ,!, '$dict_dot3'(Self, Memb, Value).
69oo_call(Self,Memb,Value):- attvar(Self),!,oo_call_av(Self,Memb,Value).
70oo_call(Self,Memb,Value):- compound(Self),!,oo_call_cmp(Self,Memb,Value).
71oo_call(Self,Memb,Value):- oo_deref(Self,NewSelf)->NewSelf\==Self,!,oo_call(NewSelf,Memb,Value).
72
73
74oo_call(Self,Memb,Value):- nb_linkval(Self,construct(Self,Memb,Value)),!,oo_call(Self,Memb,Value).
75oo_call(Self,Memb,Value):- to_member_path(Memb,[F|Path]),append(Path,[Value],PathWValue),
76 Call =.. [F,Self|PathWValue],
77 oo_call(Call).
78
79to_member_path(C,[F|ARGS]):-compound(C),!,compound_name_args(C,F,ARGS).
80to_member_path(C,[C]).
81
82
83oo_call_av(Self,Memb,Value):- get_attr(Self, Memb, Value),!.
84oo_call_av(Self,Memb,Value):- get_attr(Self, oo, NewSelf),!,oo_call(NewSelf,Memb,Value).
85
86oo_call_cmp(Self,Memb,Value):- jpl_is_ref(Self),!, jpl_call(Self, Memb, Value).
89oo_call_cmp(Self,Memb,Value):- oo_deref(Self,NewSelf),!, NewSelf\=Self, oo_call(NewSelf,Memb,Value).
90
91
92oo_deref(Obj,RObj):- var(Obj),!,once(get_attr(Obj,oo,binding(_,RObj));Obj=RObj),!.
93oo_deref(GVar,Value):- atom(GVar),nb_current(GVar,ValueM),!,oo_deref(ValueM,Value).
94oo_deref(Value,Value):- \+ compound(Value),!.
95oo_deref(cl_eval(Call),Result):-is_list(Call),!,cl_eval(Call,Result).
96oo_deref(cl_eval(Call),Result):-!,nonvar(Call),oo_deref(Call,CallE),!,call(CallE,Result).
97oo_deref(Value,Value):- jpl_is_ref(Value),!.
100oo_deref(Head,HeadE):- Head=..B,maplist(oo_deref,B,A),HeadE=..A,!.
101oo_deref(Value,Value).
102
103
104:- if(clause('$dicts':'.'(_,_,_),_)). 105
106:- clause('$dicts':'.'(Data, Func, Value),BODY),
107 asserta(('$dict_dot3'(Data, Func, Value):- '$dict':BODY)). 108
109
110:- else. 111
112'$dict_dot3'(Data, Func, Value) :-
113 ( '$get_dict_ex'(Func, Data, V0)
114 *-> Value = V0
115 ; is_dict(Data, Tag)
116 -> '$dicts':eval_dict_function(Func, Tag, Data, Value)
117 ; is_list(Data)
118 -> ( (atomic(Func) ; var(Func))
119 -> dict_create(Dict, _, Data),
120 '$get_dict_ex'(Func, Dict, Value)
121 ; '$type_error'(atom, Func)
122 )
123 ; '$type_error'(dict, Data)
124 ).
125
126:- endif. 127
128
129:-redefine_system_predicate('system':'.'(_Data, _Func, _Value)). 130:-'system':abolish('$dicts':'.'/3). 131
132'system':'.'(Data, Func, Value) :- oo_call(Data,Func,Value).
134
135
136
137
138
139get_oo(Key, Dict, Value, NewDict, NewDict) :- is_dict(Dict),!,
140 get_dict(Key, Dict, Value, NewDict, NewDict).
141get_oo(Key, Dict, Value, NewDict, NewDict) :-
142 get_oo(Key, Dict, Value),
143 put_oo(Key, Dict, NewDict, NewDict).
155eval_oo_function(Func, Tag, UDT, Value) :- is_dict(Tag),!,
156 '$dicts':eval_dict_function(Func, Tag, UDT, Value).
157
158eval_oo_function(get(Key), _, UDT, Value) :-
159 !,
160 get_oo(Key, UDT, Value).
161eval_oo_function(put(Key, Value), _, UDT, NewUDT) :-
162 !,
163 ( atomic(Key)
164 -> put_oo(Key, UDT, Value, NewUDT)
165 ; put_oo_path(Key, UDT, Value, NewUDT)
166 ).
167eval_oo_function(put(New), _, UDT, NewUDT) :-
168 !,
169 put_oo(New, UDT, NewUDT).
170eval_oo_function(Func, Tag, UDT, Value) :-
171 call(Tag:Func, UDT, Value).
179put_oo_path(Key, UDT, Value, NewUDT) :-
180 atom(Key),
181 !,
182 put_oo(Key, UDT, Value, NewUDT).
183put_oo_path(Path, UDT, Value, NewUDT) :-
184 get_oo_path(Path, UDT, _Old, NewUDT, Value).
185
186get_oo_path(Path, _, _, _, _) :-
187 var(Path),
188 !,
189 '$instantiation_error'(Path).
190get_oo_path(Path/Key, UDT, Old, NewUDT, New) :-
191 !,
192 get_oo_path(Path, UDT, OldD, NewUDT, NewD),
193 ( get_oo(Key, OldD, Old, NewD, New),
194 is_oo(Old)
195 -> true
196 ; Old = _{},
197 put_oo(Key, OldD, New, NewD)
198 ).
199get_oo_path(Key, UDT, Old, NewUDT, New) :-
200 get_oo(Key, UDT, Old, NewUDT, New),
201 is_oo(Old),
202 !.
203get_oo_path(Key, UDT, _{}, NewUDT, New) :-
204 put_oo(Key, UDT, New, NewUDT).
205
206
207oo_class(Name):-asserta(is_oo_class_impl(Name)).
208
209oo_class_end:-retract(is_oo_class_impl(Name)),assertz(is_oo_class_impl(Name)).
210
211
212oo_inner_class(Name,Inner):-asserta(is_oo_inner_class(Name,Inner)).
213oo_inner_class(Inner):-is_oo_class_impl(Name),oo_inner_class(Name,Inner).
214oo_inner_class_end:-retract(is_oo_inner_class(Name,Inner)),assertz(is_oo_inner_class(Name,Inner))