%:-module(agent,[]).
:- use_module(library(pfc_lib)).
:- style_check(- discontiguous).
same_meanings(UserSaid,UserSaid).
initial_goal(introductions(Agent2,Agent1)):-
prop(robot,self,Agent2),
prop(user,self,Agent1).
builtin(Mode,(A,B)):- !,call(Mode,A),call(Mode,B).
builtin(Mode,[A|B]):- !,call(Mode,A),call(Mode,B).
builtin(Mode,(A;B)):- !,(call(Mode,A);call(Mode,B)).
builtin(Mode,(A->B)):- !,(call(Mode,A)->call(Mode,B)).
builtin(Mode,(A*->B)):- !,(call(Mode,A)*->call(Mode,B)).
builtin(Mode,(A->B;C)):- !,(call(Mode,A)->call(Mode,B);call(Mode,C)).
builtin(Mode,(A*->B;C)):- !,(call(Mode,A)*->call(Mode,B);call(Mode,C)).
builtin(Mode, \+(A)):- !, \+ call(Mode,A).
builtin(_,(A=B)):- !, A=B.
% builtin(_, P ):- predicate_property(P,static),call(P).
builtin(_,play_mode(Mode)):- !, retractall(play_mode(_)),asserta(play_mode(Mode)).
builtin(_,noplay_mode):- !, retractall(play_mode(_)),!.
%builtin(Mode,ensure(Game)):- !, ensure(Mode,Game).
builtin(_Mode,debug(English)):- nop(ain(pipeline(English))),adbg(debug(English)).
builtin(_Mode,expect(Agent2,English)):- !, said(Agent2,UserSaid),!,same_meanings(UserSaid,English).
ensure(Sit):- var(Sit),!,throw(var_ensure(Sit)).
ensure([]).
ensure(ensure(Sit)):- !, ensure(Sit).
ensure(Sit):- clause(builtin(ensure,Sit),(A,Body)),call(A),!,call(Body).
ensure(Sit):- already_true(Sit),!, adbg(already_true(Sit)).
ensure(Sit):- \+ \+ is_assumable_happens(Sit),!, update_true(happens,Sit).
ensure(Sit):- \+ \+ is_assumable(Sit),!, update_true(is_assumable,Sit).
ensure(Sit):- fail, Sit\=achieves(_,_),clause(make_true(achieves(Agent1,Sit)),Body),dif(Agent1,user),
adbg(trying(achieves(Agent1,Sit))),call(Body),!,update_true(achieves(Agent1),Sit).
ensure(Sit):- clause(make_true(Sit),Body),adbg(trying(make_true(Sit))),call(Body),!,update_true(made_true,Sit).
ensure(Sit):- adbg(failed(ensure(Sit))),!,fail,ain(Sit).
update_true(How,Sit):- clause(builtin(update_true(How),Sit),(A,Body)),call(A),!,ignore(call(Body)).
update_true(How,Sit):- append_term(How,Sit,HowSit),adbg(HowSit), ( \+ call_u(Sit) -> (ain(Sit),ignore(forall(post_true(Sit),true))) ; true).
cant_assume(knows(_,_)).
cant_assume(prop(_,_,_)).
is_assumable_happens(X):- \+ \+ cant_assume(X),!, fail.
is_assumable_happens(said(Robot,_)):- Robot\==user.
%is_assumable_happens(X):- is_assumable(X).
%is_assumable(X):- \+ \+ cant_assume(X),!, fail.
is_assumable(prop(_,_,_)).
is_assumable(want(_,_)).
%is_assumable(heard(User,_)):- robot\==User.
is_assumable(Sit):-compound(Sit),arg(1,Sit,V),nonvar(V),functor(Sit,F,A),functor(Prop2,F,A),!,is_assumable(Prop2).
is_assumable(avoid(agent,prop)).
is_assumable(want(agent,prop)).
%is_assumable(heard(agent,prop)).
addressee(_,My,From,About,My):- From==About.
addressee(You,_,From,About,You):- From\==About.
english(From,prop(About,Name,X),[YoursMy,Name,is,X]):- nonvar(X),addressee(your,my,From,About,YoursMy).
english(From,prop(About,Name,X),['Something',is,YoursMy,Name]):- var(X),addressee(your,my,From,About,YoursMy).
english(From,ask(Prop),[what,E,?]):- english(From,Prop,E).
english(From,tell(About,Prop),[Robot,tell,Someone,E,'.']):- english(From,Prop,E),addressee(you,me,From,About,Someone),addressee(you,me,robot,From,Robot).
english(From,C,[IYou,Know,E]):- C =..[Know,About,Prop],addressee(you,i,From,About,IYou), english(From,Prop,E).
english(From,C,[About,E]):- C =..[About,Prop],english(From,Prop,E).
english(_,C,[C]).
adbg(X):- notrace(adbg0(X)).
%adbg0(X):- english(robot,X,E),flatten([E],[W|En]),write(W),maplist(adbg1,En),!,write('\t\t%%%'),adbg1(X),nl,!.
adbg0(X):- wdmsg(X),!.
adbg1(C):- compound(C),!,write(' '),writeq(C).
adbg1(C):- write(' '),write(C).
:- dynamic(prop/3).
prop(user,name,bina48).
%prop(robot,name,doug).
prop(user,self,user).
prop(robot,self,robot).
prop(S,P,O):- atom(P), O=..[P,S].
op_props(avoid(agent,prop)).
op_props(want(agent,prop)).
op_props(said(agent,prop)).
op_props(unknown(agent,prop)).
op_props(know(agent,prop)).
op_props(suspects(agent,prop)).
define_op_props(Decl):- functor(Decl,F,A),dynamic(F/A).
:- forall(op_props(Pred),define_op_props(Pred)).
% agents already know their props
already_true(know(Agent2,Sit)):- compound(Sit), arg(1,Sit,Agent2).
already_true(Sit):- compound(Sit), clause(Sit,true).
%post_true(want(Agent1,know(Agent2,prop(Agent1,name,_)))):- make_true(from_to_said(Agent1,Agent2,"My name is bina48.")).
/*
satisfy(Agent1,want(Agent1,Sit)) :- already_true(know(Agent1,Sit)),!.
satisfy(Agent1,want(Agent1, know(Agent2,Sit))) :-
%Sit = prop(Agent1,name,_),
already_true(know(Agent1,Sit)),!,
make_true(from_to_said(Agent1,Agent2,Sit)).
*/
%make_true(Sit) :- already_true(Sit).
string_to_meaning(String,Said):- tokenize_atom(String,Said).
wait_for_user(Said):- write("user>"),read_line_to_string(current_input,String), string_to_meaning(String,Said).
make_true(from_to_said(Agent1,Agent2,Sit)):- Agent1 == robot,
nonvar(Sit), adbg(from_to_said(Agent1,Agent2,Sit)).
make_true(from_to_said(Agent1,Agent2,Sit)):- Agent1 == user,
wait_for_user(Said),
nonvar(Sit), adbg(from_to_said(Agent1,Agent2,Said)).
post_true(from_to_said(Agent1,Agent2,Sit)):-
nonvar(Sit),
adbg(from_to_said(Agent1,Agent2,Sit)),
post_true((
said(Agent1,Sit),
heard(Agent2,Sit))).
make_true(heard(Agent1,ask(Agent2,Sit))):-
ensure(say_from_to(Agent1,Agent2,Sit)).
make_true(heard(Agent1,tell(Agent2,Sit))):-
ensure(say_from_to(Agent1,Agent2,Sit)).
make_true(heard(Agent1,tell(Agent2,Sit))):-
ensure(heard(Agent2,ask(Agent1,Sit))).
make_true(know(Agent2,Sit)):- make_true_know(Agent2,Sit).
% dont ask what they already know
make_true_know(Agent2,Sit) :- already_true(know(Agent2,Sit)).
% may ask questions when they dont know
make_true_know(Agent2,Sit) :-
compound(Sit),
arg(1,Sit,Agent1),
dif(Agent1,Agent2),
ensure([
heard(Agent2,ask(Agent1,Sit)),
heard(Agent1,tell(Agent2,Sit))]).
make_true(introductions(Agent1,Agent2)):-
dif(Agent1,Agent2),
ensure((
know(Agent2,prop(Agent1,name,_)),
know(Agent1,prop(Agent2,name,_)))).
:- dynamic(play_mode/1).
make_true_know(Agent1,prop(Agent2,name,_)):-
ensure((
%play_mode(know(Agent1,$term)),
prop(Agent1,pronoun,"I"),
prop(Agent2,pronoun,"you"),
debug("i want you to know my name"),
%play_mode(ensure(Agent1,$term)),
play_mode(ensure),
want(Agent1,know(Agent2,prop(Agent1,name,_))), % in case the system is in daydream mode
said(Agent1,"My name is Bina48."),
debug("i want to know your name so I am going to ask you"),
ensure(want(Agent1,Goal)), % in case the system is in daydream mode
Reject = avoid(Agent2,Goal),
Accepts = want(Agent2,Goal),
%Fullfills = make_true(Agent2,Goal),
said(Agent1,"What is your name so that I can know it?"),
((expect(Reject)->make_true(find_out_why(not(want(Agent2,Goal)))) ;
(expect(Accepts)-> ensure(want(Agent2,know(Agent1,prop(Agent2,name,_))))))))).
make_true(knows_each_others_name):-
Agent1=robot,
Agent2=user,
ensure((
play_mode(ensure),
prop(Agent1,pronoun,"I"),
prop(Agent2,pronoun,"you"),
debug("i want you to know my name"),
want(Agent1,know(Agent2,prop(Agent1,name,_))),
said(Agent1,"My name is Bina48."),
debug("i want me to know your name so I am going to ask you to spell it"),
ensure(want(Agent1,know(Agent1,list(Agent2,letters_of_first_name,_)))),
said(Agent1,"Would you spell your first name so that I can know it?"),
((expect(Agent2,"no")->make_true(find_out_why(not(want(Agent2,know(Agent1,list(Agent2,letters_of_first_name,_)))))) ;
(expect(Agent2,"yes")-> ensure(want(Agent2,know(Agent1,list(Agent2,letters_of_first_name,_))))))))).
s("my name is professor einstein").
s("i am here for you to interact with. I have come all the way from Hanson Robotics and I am happy to be here").
s("i am going to ask you some questions").
s("How old are you?").
s("think: listening for small phrase").
s("50").
s("50! would you mind telling me your name?").
s("think: listening for small phrase").
s("heard: Dug as").
s("I didn't quite catch that.
are you able to hear what I'm saying Sorry, it seemed like there was an error during request. you are Sorry, it seemed like there was an error during request. Doug Sorry, it seemed like there was an error during request. Douglas Sorry, it seemed like there was an error during request. |