:- setup_call_cleanup('$current_typein_module'(TIM), setup_call_cleanup('$current_source_module'(SIM), npc_chat:ensure_loaded('/opt/logicmoo_workspace/packs_xtra/logicmoo_chat/npc/agent.pl'), '$set_source_module'(SIM)), '$set_typein_module'(TIM)). end_of_file. end_of_file. end_of_file. %:-module(agent,[]). :- use_module(library(pfc_lib)). :- style_check(- discontiguous). same_meanings(UserSaid,UserSaid). initial_goal(introductions(Self,User)):- me_you(Self,User). 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(Mode, P):- compound(P),compound_name_arguments(P,F,[Arg]),F==Mode,guard,call(Mode,Arg). %builtin(_, P ):- predicate_property(P,static),guard,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(User,English)):- !, said(User,UserSaid),!,same_meanings(UserSaid,English). until_guard(GBody,Body):- find_guard(GBody,Before,Body),!,call(Before). find_guard(GBody,Before,Body):- conjuncts_to_list(GBody,BodyL),append(BeforeL,[guard|AfterL],BodyL),!, list_to_conjuncts(BeforeL,Before),list_to_conjuncts(AfterL,Body). find_guard(GBody,true,GBody). ensure(Sit):- var(Sit),!,throw(var_ensure(Sit)). ensure([]). ensure(ensure(Sit)):- !, ensure(Sit). ensure(Goal):- compound(Goal),compound_name_arity(Goal,call,_),!, call(Goal). ensure(Sit):- check_builtin(ensure,Sit,GBody),!,call(GBody). ensure(Sit):- already_true(Sit),!, adbg(already_true(Sit)). ensure(Sit):- \+ \+ is_assumable_happens(Sit),!, assume(happens,Sit). ensure(Sit):- \+ \+ is_assumable(Sit),!, assume(is_assumable,Sit). ensure(Sit):- fail, Sit\=achieves(_,_),clause(make_true(achieves(Self,Sit)),GBody),dif(Self,user), until_guard(GBody,Body), adbg(trying(achieves(Self,Sit))),call(Body),!,assume(achieves(Self),Sit). ensure(Sit):- clause(make_true(Sit),GBody),until_guard(GBody,Body),adbg(trying(make_true(Sit))),call(Body),!,assume(made_true,Sit). ensure(Sit):- adbg(failed(ensure(Sit))),!,fail,ain(Sit). assume(Sit):- assume(assumed,Sit). assume(How,Sit):- check_builtin(assume(How),Sit,GBody),!,call(GBody). assume(How,Sit):- append_term(How,Sit,HowSit),adbg(HowSit), ( \+ call_u(Sit) -> (aina(Sit),ignore(forall(post_true(Sit),true))) ; true). check_builtin(How,Goal,Body):- clause(builtin(How,Goal),GBody),until_guard(GBody,Body),!. cant_assume(knows(_,_)). cant_assume(cpv(_,_,_)). 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(cpv(_,_,_)). 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,cpv)). %is_assumable(want(agent,cpv)). %is_assumable(heard(agent,cpv)). addressee(_,My,From,About,My):- From==About. addressee(You,_,From,About,You):- From\==About. english(From,cpv(About,Name,X),[YoursMy,Name,is,X]):- nonvar(X),addressee(your,my,From,About,YoursMy). english(From,cpv(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(cpv/3). cpv(robot,name,bina48). %cpv(user,name,doug). cpv(user,self,user). cpv(robot,self,robot). prop2(S,P,O):- atom(P), O=..[P,S]. set_cpv(X,Y,Z):- aina(cpv(X,Y,Z)). op_props(avoid(agent,cpv)). op_props(want(agent,cpv)). op_props(said(agent,cpv)). op_props(unknown(agent,cpv)). op_props(know(agent,cpv)). op_props(suspects(agent,cpv)). op_props(goal(agent,ensure)). show_p(P):- findall(p,(logicmoo_agi:call(P),wdmsg(P)),L),L\==[],!. show_p(P):- wdmsg(no(P)). know:- op_props(Decl),functor(Decl,F,A), functor(P,F,A), show_p(P), fail. know:- P = cpv(_,_,_), show_p(P), fail. know. test_agent:- make, me_you(Self,User), retract_all(know(_,_)), retract_all(goal(User,_)), retract_all(goal(Self,_)), forall(initial_goal(G),assume(goal(Self,G))), show_p(goal(_,_)), handle_wants. handle_wants:- retract(logicmoo_agi:goal(Self,G)), adbg(handle_wants(goal(Self,G))), ensure(G),!, handle_wants. handle_wants. % basic input driver listen_for_text:- repeat, sleep(0.1), audio_input(Input), % input continuely builds once((listening_for(Type,PropSent), meets_type(Input,Type,PropSent,Value), clear_audio_input, functor(PropSent,_,A), setarg(A,PropSent,Value))), fail. 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(User,Sit)):- compound(Sit), arg(1,Sit,User). already_true(Sit):- compound(Sit), clause(Sit,true). %post_true(want(Self,know(User,cpv(Self,Prop,_)))):- make_true(from_to_said(Self,User,"My $convo.property is bina48.")). /* satisfy(Self,want(Self,Sit)) :- already_true(know(Self,Sit)),!. satisfy(Self,want(Self, know(User,Sit))) :- %Sit = cpv(Self,Prop,_), already_true(know(Self,Sit)),!, make_true(from_to_said(Self,User,Sit)). */ %make_true(Sit) :- already_true(Sit). string_to_meaning(String,Said):- tokenize_atom(String,Said). audio_input(Input):- wait_for_user(Input). wait_for_user(Said):- write("user>"),read_line_to_string(current_input,String), string_to_meaning(String,Said). make_true(from_to_said(Self,User,Sit)):- Self == robot, guard, nonvar(Sit), adbg(from_to_said(Self,User,Sit)). make_true(from_to_said(Self,User,Sit)):- Self == user, guard, wait_for_user(Said), nonvar(Sit), adbg(from_to_said(Self,User,Said)). post_true(from_to_said(Self,User,Sit)):- nonvar(Sit), guard, adbg(from_to_said(Self,User,Sit)), post_true(( said(Self,Sit), heard(User,Sit))). make_true(heard(Self,ask(User,Sit))):- me_you(Self,User), ensure(from_to_said(Self,User,Sit)). make_true(heard(Self,tell(User,Sit))):- me_you(Self,User), ensure(from_to_said(Self,User,Sit)). make_true(heard(Self,tell(User,Sit))):- me_you(Self,User), ensure(heard(User,ask(Self,Sit))). make_true(know(User,Sit)):- make_true_know(User,Sit). % dont ask what they already know make_true_know(User,Sit) :- already_true(know(User,Sit)). make_true_know(User,Sit) :- compound(Sit), arg(1,Sit,Self), dif(Self,User), me_you(Self,User), ignore(call(Sit)), ensure([ heard(Self,tell(User,Sit))]). % may ask questions when they dont know make_true_know(Self,Sit) :- fail, compound(Sit), arg(1,Sit,User), dif(User,Self), me_you(Self,User), guard, ensure([ heard(Self,ask(User,Sit)), heard(User,tell(Self,Sit))]). make_true(introductions(Self,User)):- dif(Self,User), Prop = name, set_cpv(convo,property,Prop), ensure(( know(User,cpv(Self,Prop,_)), know(Self,cpv(User,Prop,_)))). :- dynamic(play_mode/1). me_you(Self,User):- dif(Self,User), cpv(robot,self,Self), cpv(user,self,User). % Self= robot,User= user. make_true_know(User,cpv(Self,Prop,_)):- me_you(Self,User), ignore(cpv(Self,Prop,_)), ensure(( set_cpv(convo,property,Prop), %play_mode(know(Self,$term)), cpv(Self,pronoun,"I"), cpv(User,pronoun,"you"), debug("i want you to know my $convo.property"), %play_mode(ensure(Self,$term)), play_mode(ensure), want(Self,know(User,cpv(Self,Prop,_))), % in case the system is in daydream mode said(Self,"My $convo.property is $bot.$convo.property."), debug("i want to know your $convo.property so I am going to ask you"), Goal = know(Self,cpv(Self,Prop,_)), ensure(want(Self,Goal)), % in case the system is in daydream mode Reject = avoid(User,Goal), Accepts = want(User,Goal), %Fullfills = make_true(User,Goal), said(Self,"What is your $convo.property so that I can know it?"), ((expect(User,Reject)->make_true(find_out_why(not(want(User,Goal)))) ; (expect(User,Accepts)-> ensure(want(User,know(Self,cpv(User,Prop,_))))))))). make_true_know(Self,cpv(User,Prop,_)):- me_you(Self,User), ignore(cpv(Self,Prop,_)), ensure(( set_cpv(convo,property,Prop), %play_mode(know(Self,$term)), cpv(Self,pronoun,"I"), cpv(User,pronoun,"you"), debug("i want you to know my $convo.property"), %play_mode(ensure(Self,$term)), play_mode(ensure), want(Self,know(User,cpv(Self,Prop,_))), % in case the system is in daydream mode said(Self,"My $convo.property is $bot.$convo.property."), debug("i want to know your $convo.property so I am going to ask you"), ensure(want(Self,Goal)), % in case the system is in daydream mode Reject = avoid(User,Goal), Accepts = want(User,Goal), %Fullfills = make_true(User,Goal), said(Self,"What is your $convo.property so that I can know it?"), ((expect(User,Reject)->make_true(find_out_why(not(want(User,Goal)))) ; (expect(User,Accepts)-> ensure(want(User,know(Self,cpv(User,Prop,_))))))))). make_true(knows_each_others_convo_property(Prop)):- set_cpv(convo,property,Prop), Self=robot, User=user, ensure(( play_mode(ensure), set_cpv(convo,i,Self), set_cpv(convo,you,User), debug("i want you to know my $convo.property"), assume(want(Self,know(User,cpv(Self,Prop,_)))), said(Self,"My $convo.property is $bot.$convo.property."), debug("i want me to know your $convo.property so I am going to ask you to spell it"), aquire_prop(Self,User,Prop))). make_true(aquire_prop(Self,User,Prop)):- PropSent = cpv(User,Prop,_), IKnowProp = know(Self,PropSent), IWant = want(Self,IKnowProp), UserKnowIWant = know(User,IWant), assume(IWant), assume(not(UserKnowIWant)), ensure(UserKnowIWant). make_true(UserKnowIWant):- UserKnowIWant = know(User,IWant), IWant = want(Self,IKnowProp), PropSent = cpv(User,Prop,_Value), IKnowProp = know(Self,PropSent), me_you(Self,User),guard, set_cpv(convo,property,Prop), ensure( (said(Self,"What is your $convo.property?"),listen_for(small,PropSent)) ; (said(Self,"Would you spell your $convo.property so that I can know it?"),listen_for(spelling,PropSent)) ), assume(UserKnowIWant). make_true(listen_for(Type,PropSent)):- assume(listening_for(Type,PropSent)). meets_type(Input,small,_,Value):- !, \+ is_sentence(Input)->Value=Input. meets_type(Input,spelling,PropSent,Value):- is_letter(Input)->Value=Input ; (repeat_last_request(PropSent),!,fail). meets_type(Input,large,PropSent,Value):- is_sentence(Input)->Value=Input ; (repeat_last_request(PropSent),!,fail). guard. repeat_last_request(PropSent):- me_you(Self,User),guard, ensure(aquire_prop(Self,User,PropSent)). post_true(UserKnowIWant):- UserKnowIWant = know(User,IWant), IWant = want(Self,IKnowProp), PropSent = cpv(User,_Prop,_Value), IKnowProp = know(Self,PropSent), listen_for(small,PropSent). /* LOCV = letters_of(Prop), IKnowProp = know(Self,cpv(User,Prop,_)), IWant = want(Self,IKnowProp), UserKnowIWant = know(User,IWant), assume(IWant), assume(not(UserKnowIWant)), ensure(UserKnowIWant). ((expect(User,"no")->make_true(find_out_why(not(want(User,know(Self,list(User,LOCV)))))) ; (expect(User,"yes")-> ensure(want(User,know(Self,list(User,LOCV))))))))). */ do_demo([]):-!. do_demo([X|Y]):- !, do_demo(X),do_demo(Y). do_demo(s(Say)):- !, sleep(0.2),writeln(Say). do_demo(w(Say)):- !, sleep(Say). do_demo(t(Say)):- !, nop((write("thinking..."),writeln('doing...: ' + Say))). do_demo(h(Say)):- !, write("listening..."),nl,get_char(_),writeln('Heard: ' + Say). user:do_s:- make,e_demo1(X),do_demo(X). e_demo1([ s("My $convo.property is $bot.$convo.property"), s("I am here for you to interact with."), s("I have come all the way from $bot.father and I am happy to be here! ...."), s("I am going to ask you some questions"), s("How old are you?"), t("listening for $user.age"), h("$user.age"), s("50! would you mind telling me your $convo.property?"), t("listening for $user.$convo.property"), h(yes_no_ok) -> s("OK, what is your $convo.property"), t("listening for $user.$convo.property"), h("Dug as"), s("I didn't quite catch that."), s("Can you repeat that?"), t("listening for $user.$convo.property"), h("Dug as"), s("Let us try this another way. First, how many letters are in your $convo.property?"), h("7"), s("$user.last .. ok I will listen for $user.last letters!"), h("okay"), s("Would you spell your $convo.property for me?"), s("I am waitng for you to spell your $convo.property for me!"), t("listening for letters"), h("Dee -> D"), s("listening..."), w(3), s("One more letter to go"), h("yes -> S"), s("Are there $user.name_len letters in your $convo.property?"), h("yes"), s("Let me try to spell it. I. T. "), s("... is that correct?"), h("no."), s("sorry that was a joke!"), s("You $convo.property is Douglas. D. O. U. G. L. A. S."), s("is that correct?"), h("yes."), s("Sometimes i am talking and trying to get your attention but you might be busy."), s("When that happens, you say wait a minute. And I will wait at least a minute. You can also say wait five minutes."), s("Afterwards, you can say, please wait, and I will wait and come back after a little while"), s("So we have differnt types of Experiments, Games and Stories we can do together "), s("Say Games, Story, Experiement, wait or goodbye"), s("You always can say wait or goodbye"), h("Wait"), s("Ok I will wait a minute "), h("Games"), s("I shall suggest a game and this game allows me to get to know things about you ...."), s("What is the $convo.property of the room we are in?"), h("The office"), s("What do you do in the office?"), h("we work on you"), s("On me?"), s("So in the room called the office you work on me? Professor Einstein"), h("yes"), s("When you are not working on Professor Einstein in the room called the office, what do you do?"), h("sleep"), s("Do you sleep in the room called the office?"), h("sometimes"), s("Name three objects you find in your room called the office."), h("You me my computer"), h("goodbye"), s("just say my $convo.property to begin talking again"), []]). :- fixup_exports. end_of_file. s(`
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. |