1%:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )). 2%:- module(mud_telnet,[]). 3 4:- export(( 5 prolog_tnet_server/2, 6 setup_streams/2, 7 player_connect_menu/4, 8 look_brief/1, 9 cmdShowRoomGrid/1, 10 get_session_id_local/1, 11 inst_label/2, 12 display_grid_labels/0, 13 telnet_repl_writer/4, 14 telnet_repl_obj_to_string/3, 15 start_mud_telnet/0, 16 start_mud_telnet/1, 17 get_session_io/2, 18 kill_naughty_threads/0, 19 set_player_telnet_options/1, 20 register_player_stream_local/3, 21 fmtevent/2, 22 run_session/0, 23 run_session/2, 24 login_and_run_nodbg/0, 25 login_and_run_debug/0, 26 login_and_run_xhtml/0, 27 login_and_run/0, 28 login_and_run/2, 29 session_loop/2, 30 start_telnet/0 31 )). 32 33% Initial Telnet/Text console 34% ALL telnet client business logic is here (removed from everywhere else!) 35% 36% Logicmoo Project PrologMUD: A MUD server written in Prolog 37% Maintainer: Douglas Miles 38% Dec 13, 2035 39% 40:- include(prologmud(mud_header)). 41 42:- use_module(mud_http_hmud). 43%:- kb_shared(get_session_id/1). 44 45 46:- dynamic((lmcache:agent_session/2, 47 lmcache:session_agent/2, 48 lmcache:session_io/4, 49 lmcache:agent_session/2, 50 lmcache:session_agent/2, 51 lmcache:session_io/4)). 52 53:- volatile((lmcache:agent_session/2, 54 lmcache:session_agent/2, 55 lmcache:session_io/4, 56 lmcache:agent_session/2, 57 lmcache:session_agent/2, 58 lmcache:session_io/4)). 59 60:- ain(mtProlog(mud_telnet)). 61% UNDO % :- add_import_module(mud_telnet,world,end). 62 63% learnLaterWhenToCallProceedure(What):- ... code ... 64 65%:-ain(learnLaterWhenToCallProceedure(kill_naughty_threads)). 66 67%:-ain(unimpledTODO(learnLaterWhenToCallProceedure)). 68%:-ain(unimpledTODO(codeWithTODONextToIt)). 69 70% instanceRecognizedBy(codeWithTODONextToIt,grovelSourceCodeLookingForComment). 71 72 73 74kill_naughty_threads:-forall(thread_property(_,alias(ID)),sanify_thread(ID)). 75% ignore main thread 76sanify_thread(main):-!. 77sanify_thread(ID):- ( \+ atom_concat('httpd',_,ID)),!, 78 ignore(( thread_statistics(ID,local,Size),MSize is 200 * 1024, Size>MSize, dmsg(big_thread(ID,local,Size)))). 79sanify_thread(ID):- 80 ignore(( thread_statistics(ID,local,Size),MSize is 200 * 1024, Size>MSize, 81 % thread_signal(ID,abort) maybe 82 dmsg(killing_big_thread(ID,local,Size)), thread_exit(ID) )). 83 84 85:- meta_predicate show_room_grid_single( , , ). 86 87% :- include(prologmud(mud_header)). 88 89% :- disable_mpreds_in_current_file. 90 91% :- register_module_type (utility). 92 93% :- use_module(library(threadutil)). 94 95% =========================================================== 96% TELNET REPL + READER 97% =========================================================== 98start_mud_telnet :- app_argv1('--nonet'),!. 99start_mud_telnet:- 100 logicmoo_base_port(Base), 101 WebPort is Base, % + 1000, 102 whenever(run_network,start_mud_telnet(WebPort)). 103 104port_busy(Port):- 105 tcp_socket(ServerSocket), 106 tcp_setopt(ServerSocket, reuseaddr), 107 catch((tcp_bind(ServerSocket, Port),tcp_listen(ServerSocket, 5)),Error,true), 108 tcp_close_socket(ServerSocket), 109 !,nonvar(Error). 110 111:- dynamic(started_mud_telnet/1). 112start_mud_telnet(_):- started_mud_telnet(_),!. 113start_mud_telnet(Port):- port_busy(Port),!, NewPort is Port+100, start_mud_telnet(NewPort). 114start_mud_telnet(Port):- 115 asserta(started_mud_telnet(Port)), 116 start_tnet(login_and_run_nodbg , Port , "MUD Server"), 117 start_tnet(login_and_run_debug, Port+1 , "MUD Debug"), 118 start_tnet(login_and_run_xhtml, Port+2 , "MUDLET Telnet"), 119 start_tnet( repl, Port+3 , "WAM-CL Telnet"), 120 % Port+4 = srv_mu 121 % Port+23 = "screen -rx" 122 start_tnet( prolog, Port+25 , "PROLOG Telnet"), 123 !. 124 125golorpish:- nodebugx(golorp). 126 127:- dynamic(lmcache:main_thread_error_stream/1). 128:- volatile(lmcache:main_thread_error_stream/1). 129 130save_error_stream:- lmcache:main_thread_error_stream(_),!. 131save_error_stream:- ignore((thread_self_main,(quintus:current_stream(2, write, Err),asserta(lmcache:main_thread_error_stream(Err))))). 132:- initialization(save_error_stream,restore). 133:- save_error_stream. 134 135get_main_thread_error_stream(ES):-lmcache:main_thread_error_stream(ES),!. 136get_main_thread_error_stream(Main_error):- stream_property(Main_error, file_no(2)). 137 138get_session_io(In,Out):- 139 get_session_id_local(O), 140 thread_self(Id), 141 lmcache:session_io(O,In,Out,Id),!. 142 143get_session_io(In,Out):- 144 must(get_session_id_local(O)), 145 thread_self(Id), 146 current_input(In), 147 current_output(Out), 148 asserta(lmcache:session_io(O,In,Out,Id)),!. 149 150:- set_prolog_flag(debug_threads,false). 151:- set_prolog_flag(debug_threads,true). 152 153login_and_run_xhtml :- login_and_run. 154%login_and_run_xhtml :- login_and_run_debug. 155 156% login_and_run_nodbg:- current_prolog_flag(debug_threads,true),!,login_and_run. 157login_and_run_nodbg:- 158 nodebugx(login_and_run),!. 159 160login_and_run_debug:- \+ getenv('DISPLAY',_),login_and_run. 161login_and_run_debug:- 162 thread_self(Self), 163 tdebug(Self),% debug, % guitracer, 164 % fav_debug,!, 165 must_det(login_and_run),!. 166 167get_session_id_local(O):- must(baseKB:get_session_id(O)),!. 168 169 170ensure_player_attached(In,Out,P):- 171 call_u(( 172 current_agent(P)->true;player_connect_menu(In,Out,_,P))). 173 In,Out,Wants,P) (:- 175 setup_call_cleanup(set_local_modules(baseKB,Undo), 176 must_det(( 177 get_session_id_local(O), 178 format('~N~nHello session ~q!~n',[O]), 179 baseKB:foc_current_agent(Wants), 180 % must((foc_current_agent(P),sanity(nonvar(P)))), 181 must((baseKB:foc_current_agent(P),nonvar(P))), 182 ain(isa(P,tHumanControlled)), 183 register_player_stream_local(P,In,Out), 184 format('~N~nWelcome to the MUD ~w!~n',[P]), 185 format(Out,'~N~nThe stream ~w!~n',[Out]), 186 colormsg([blink,fg(red)],"this is not blinking red!"),!)),Undo),!. 187 188login_and_run_html:- 189 login_and_run. 190 191login_and_run:- 192 get_session_io(In,Out),!, 193 login_and_run(In,Out). 194 195set_player_telnet_options(P):- 196 ain(repl_writer(P,telnet_repl_writer)), 197 ain(repl_to_string(P,telnet_repl_obj_to_string)), 198 get_session_id_local(O), 199 asserta(t_l:telnet_prefix(O,[P,wants,to])). 200 201unset_player_telnet_options(P):- 202 get_session_id_local(O), 203 retractall(t_l:telnet_prefix(O,[P,wants,to])), 204 clr(repl_writer(P,_)), 205 clr(repl_to_string(P,_)). 206 207goodbye_player:- 208 call_u(foc_current_agent(P3)), 209 deliver_event(P3,goodBye(P3)). 210 211run_session:- 212 get_session_io(In,Out), 213 run_session(In,Out). 214 215login_and_run(In,Out):- 216 player_connect_menu(In,Out,_,_),!, 217 run_session(In,Out). 218 219set_local_modules(BaseKB,Undo):- 220 '$current_typein_module'(WasTM),'$current_source_module'(WasSM), 221 fileAssertMt(WasFileMt), 222 module(BaseKB),'$set_typein_module'(BaseKB),'$set_source_module'(BaseKB), 223 set_fileAssertMt(BaseKB),!, 224 Undo = (set_fileAssertMt(WasFileMt),'$set_typein_module'(WasTM),'$set_source_module'(WasSM)),!. 225 % set_defaultAssertMt(BaseKB), 226 227 228run_session(In,Out):- 229 setup_call_cleanup(set_local_modules(baseKB,Undo), 230 must_det(((( 231 get_session_id_local(O), 232 ensure_player_attached(In,Out,P), 233 call(retractall,lmcache:wants_logout(O)))),!, 234 register_player_stream_local(P,In,Out), 235 call_u((repeat, 236 once(session_loop(In,Out)), 237 call(retract,lmcache:wants_logout(O)))),!, 238 % this leaves the session 239 call(retractall,lmcache:wants_logout(O)), 240 ignore(current_agent(Agnt)->true;Agnt=P), 241 deregister_player_stream_local(Agnt,In,Out))),Undo). 242 243 244session_loop(In,Out):- 245 must_det(((( 246 get_session_id_local(O), 247 ensure_player_attached(In,Out,P), 248 call_u(start_agent_action_thread), 249 ignore(look_brief(P)),!, 250 (t_l:telnet_prefix(O,Prefix)->(sformat(Prompt,'~w ~w>',[P,Prefix]));sformat(Prompt,'~w> ',[P])), 251 prompt_read_telnet(In,Out,Prompt,List),!, 252 enqueue_session_action(P,List,O))))). 253 254 255:-export(register_player_stream_local/3). 256register_player_stream_local(P,In,Out):- 257 must_det(((( 258 set_player_telnet_options(P), 259 get_session_id_local(O),thread_self(Id), 260 retractall(lmcache:session_io(_,_,_,Id)), 261 retractall(lmcache:session_io(O,_,_,_)), 262 asserta_new(lmcache:session_io(O,In,Out,Id)), 263 % wdmsg(asserta_new(lmcache:session_io(O,In,Out,Id))), 264 retractall(lmcache:session_agent(O,_)), 265 asserta_new(lmcache:session_agent(O,P)), 266 retractall(lmcache:agent_session(_,O)), 267 asserta_new(lmcache:agent_session(P,O)), 268 nop(check_console(Id,In,Out,_Err)))))). 269 270deregister_player_stream_local(P,In,Out):- 271 must_det(((( 272 unset_player_telnet_options(P), 273 get_session_id_local(O),thread_self(Id), 274 retractall(lmcache:session_io(_,_,_,Id)), 275 retractall(lmcache:session_io(O,_,_,_)), 276 % wdmsg(asserta_new(lmcache:session_io(O,In,Out,Id))), 277 retractall(lmcache:session_agent(O,_)), 278 retractall(lmcache:agent_session(_,O)), 279 nop(check_console(Id,In,Out,_Err)))))). 280 281check_console(Id,In,Out,Err):- 282 (thread_self_main->get_main_thread_error_stream(Err); Err=Out), 283 (call(call,thread_util:has_console(Id,In, Out,Err))->true; 284 ((call(retractall,thread_util:has_console(Id,_,_,_)), 285 call(asserta,thread_util:has_console(Id,In,Out,Err))))). 286 287 288:-export(enqueue_session_action/3). 289 290enqueue_session_action(_A,[+, Text],_S):- string(Text), must(if_defined(assert_text(tWorld,Text))). 291%enqueue_session_action(A,[W0,W1|WL],S):- string(Text),!,enqueue_session_action(A,[actSay,[W0,W1|WL]],S). 292enqueue_session_action(A,L,S):- show_call(must(call_u(enqueue_agent_action(A,L,S)))),!. 293 294setup_streams:- 295 get_session_io(In,Out), 296 setup_streams(In, Out), 297 dmsg(call(call(listing,thread_util:has_console/4))). 298 299setup_streams(In,Out):- var(In),!,current_input(In),setup_streams(In,Out). 300setup_streams(In,Out):- var(Out),!,current_output(Out),setup_streams(In,Out). 301setup_streams(In,Out):- thread_self(Id), 302 thread_setup_streams(Id,In,Out). 303 304thread_setup_streams(Id,In,Out):- memberchk(Id,[0,main]),thread_self_main,!, 305 stream_property(Err,file_no(2)), 306 call(retractall,thread_util:has_console(Id, _, _, _)), 307 thread_at_exit(call(retractall,thread_util:has_console(Id, _, _, _))), 308 call(asserta,thread_util:has_console(Id, In, Out, Err)),!. 309thread_setup_streams(Id,In,Out):- 310 set_prolog_IO(In, Out, Out), thread_setup_streams(Id,In,Out,user_error). 311 312thread_setup_streams(Id,In,Out,Err):- 313 must_det_l(( 314 set_prolog_flag(color_term,true), 315 set_prolog_flag(tty_control, true), 316 setup_stream_props(current_input,In), 317 setup_stream_props(current_ouput,Out), 318 setup_error_stream(Id,Err))). 319 320setup_stream_props(Name,Stream):- 321 must_det_l(( 322 set_stream_ice(Stream, close_on_exec(false)), 323 set_stream_ice(Stream, close_on_abort(false)), 324 %set_stream_ice(Stream, alias(Name)), 325 current_prolog_flag(encoding, Enc),set_stream_ice(Stream, encoding(Enc)), 326 set_stream_ice(Stream, type(text)), 327 %stream_property(Stream,mode(_Dir)), 328 %set_stream_ice(Stream, type(text)), 329 %set_stream_ice(Stream, representation_errors(warn)), 330 %set_stream_ice(Stream, write_errors(warn)), 331 %set_stream_ice(Stream, eof_action(eof_code)), 332 %set_stream_ice(Stream, buffer_size(1)), 333 (stream_property(Stream,input)->set_stream_ice(Stream, newline(detect));true), 334 set_stream_ice(Stream, tty(true)), 335 nop(forall(stream_property(Stream,Prop),dmsg(stream_info(Name,Stream,Prop)))))). 336 337 338find_err_from_out(Out,Err):- 339 quintus:current_stream(N,write,Out), 340 dif(Out,Err), 341 ((quintus:current_stream(N,write,Err),stream_property(Err,alias(user_error))) -> true ; 342 ((quintus:current_stream(N,write,Err), \+ stream_property(Err,buffer(full)), \+ stream_property(Err,buffer(line))))). 343 344 345setup_error_stream(Id,Err):- 346 must_det_l(( 347 set_thread_error_stream(Id,Err),!, 348 %current_prolog_flag(encoding, Enc),set_stream_ice(Err, encoding(Enc)), 349 %atom_concat(user_error_,Id,StreamName),set_stream_ice(Err, alias(StreamName)), 350 %set_stream_ice(Err, alias(user_error)), 351 set_stream_ice(Err, close_on_exec(false)), 352 set_stream_ice(Err, close_on_abort(false)), 353 set_stream_ice(Err, buffer(none)), 354 set_stream_ice(Err, newline(dos)))),!. 355 356 357fmtevent(Out,NewEvent):-string(NewEvent),!,format(Out,'~s',[NewEvent]). 358fmtevent(Out,NewEvent):-format(Out,'~N~q.~n',[NewEvent]). 359 360:-thread_local(t_l:telnet_prefix/2). 361 362% :-set_tty_control(true). 363 364:-export(prompt_read/4). 365prompt_read_telnet(In,Out,Prompt,Atom):- 366 get_session_id_local(O), 367 prompt_read(In,Out,Prompt,IAtom), 368 (IAtom==end_of_file -> (call(assert,lmcache:wants_logout(O)),Atom='quit') ; IAtom=Atom),!. 369 370prompt_read(In,Out,Prompt,Atom):- 371 with_output_to(Out,color_format([reset,hfg(white),bold],'~w',[Prompt])),flush_output(Out), 372 repeat,read_code_list_or_next_command_with_prefix(In,Atom),!. 373 374local_to_words_list(Atom,Words):-var(Atom),!,Words = Atom. 375local_to_words_list(end_of_file,end_of_file):-!. 376local_to_words_list([],[]):-!. 377local_to_words_list(Atom,Words):-to_word_list(Atom,Words),!. 378 379maybe_prepend_prefix(Words,Words). 380 381read_code_list_or_next_command_with_prefix(In,Words):- read_code_list_or_next_command(In,Atom), 382 add_history(Atom), 383 %ignore(prolog:history(In, Atom);prolog:history(user_input, Atom);thread_signal(main,ignore(prolog:history(user_input, Atom)))), 384 show_call(local_to_words_list(Atom,WordsM)),!,maybe_prepend_prefix(WordsM,Words). 385 386 387read_code_list_or_next_command(Atom):-current_input(In),read_code_list_or_next_command(In,Atom),!. 388 389read_code_list_or_next_command(In,end_of_file):- at_end_of_stream(In),!. 390read_code_list_or_next_command(In,Atom):- 391 (var(In)->current_input(In);true), catch(wait_for_input([In], Ready, 1),_,fail),!, member(In,Ready), 392 read_pending_input(In,CodesL,[]),!,is_list(CodesL),CodesL\==[], 393 ((last(CodesL,EOL),member(EOL,[10,13])) -> code_list_to_next_command(CodesL,Atom); 394 (read_line_to_codes(In,CodesR), (is_list(CodesR)-> (append(CodesL,CodesR,NewCodes),code_list_to_next_command(NewCodes,Atom)); Atom=CodesR))),!. 395 396read_code_list_or_next_command(In,Atom):- 397 read_pending_input(In,CodesL,[]),is_list(CodesL),CodesL\==[], 398 ((last(CodesL,EOL),member(EOL,[10,13])) -> code_list_to_next_command(CodesL,Atom); 399 (read_line_to_codes(In,CodesR), (is_list(CodesR)-> (append(CodesL,CodesR,NewCodes),code_list_to_next_command(NewCodes,Atom)); Atom=CodesR))),!. 400 401code_list_to_next_command(end_of_file,end_of_file). 402code_list_to_next_command(NewCodes,Atom):-append(Left,[EOL],NewCodes),EOL<33,!,code_list_to_next_command(Left,Atom). 403code_list_to_next_command( [EOL|NewCodes],Atom):-EOL<33,!,code_list_to_next_command(NewCodes,Atom). 404code_list_to_next_command( [],"l"). 405code_list_to_next_command( [91|REST],TERM):- on_x_fail((atom_codes(A,[91|REST]),atom_to_term(A,TERM,[]))),!. 406code_list_to_next_command(NewCodes,Atom):-atom_codes(Atom,NewCodes),!. 407 408:-export(scan_src_updates/0). 409 410tick_tock:- 411 scan_src_updates,!,fmt('tick tock',[]),sleep(0.1),!. 412 413scan_src_updates:- !. 414scan_src_updates:- ignore((thread_self_main,ignore((catch(mmake,E,dmsg(E)))))). 415 416 417% =========================================================== 418% DEFAULT TELNET "LOOK" 419% =========================================================== 420 421telnet_repl_writer(_TL,call,ftTerm,Goal):-!,ignore(on_x_debug(Goal)). 422telnet_repl_writer( TL,text,Type,[V]):-telnet_repl_writer(TL,text,Type,V). 423telnet_repl_writer( TL,text,Type,V):- is_list(V),merge_elements(V,L),V\=@=L,!,telnet_repl_writer( TL,text,Type,L). 424telnet_repl_writer(_TL,text,Type,V):-copy_term(Type,TypeO),ignore(TypeO=t),fmt('text(~q).~n',[V]). 425telnet_repl_writer(_TL,N,Type,V):-copy_term(Type,TypeO),ignore(TypeO=t),fmt('~q=(~w)~q.~n',[N,TypeO,V]). 426 427telnet_repl_obj_to_string(O,_TypeHint,O):-!. 428telnet_repl_obj_to_string(O,_TypeHint,S):- must(object_string(O,S)),!. 429telnet_repl_obj_to_string(O,Type,toString(TypeO,O)):-copy_term(Type,TypeO),ignore(TypeO=s). 430 431 432% =========================================================== 433% DEFAULT TEXT 434% =========================================================== 435:- dynamic(baseKB:mudLastCommand/2). 436look_brief(Agent):- prop(Agent,mudLastCommand,X),nonvar(X),functor(X,actLook,_),!. 437 438look_brief(Agent):- !,call_u(look_as(Agent)),!. 439look_brief(Agent):- \+ prop(Agent,mudNeedsLook,vTrue),!. 440look_brief(Agent):- must(prop(Agent,mudNeedsLook,vTrue)),call_u(look_as(Agent)),!. 441 442merge_elements(V,V):-not(is_list((V))),!. 443merge_elements([],[]):-!. 444merge_elements([E],[E]):-!. 445merge_elements(V,V). 446% merge_elements(V,M):-list_to_set(V,[E|More]),maplist(simply_ ).. 447 448% Display what the agent sees in a form which 449% makes sense to me 450 451write_pretty([]). 452write_pretty(Percepts) :- 453 write_pretty_aux(Percepts, Rest, 0),!, 454 nl, 455 write_pretty(Rest),!. 456 457write_pretty_aux(Rest,Rest,5). 458write_pretty_aux([[]|Tail],Return,Column) :- 459 Ctemp is Column + 1, 460 typeHasGlyph(Obj,0), 461 write(Obj), write(' '), 462 write_pretty_aux(Tail,Return,Ctemp). 463write_pretty_aux([[vDark]|Tail],Return,Column) :- 464 Ctemp is Column + 1, 465 write('dk '), 466 write_pretty_aux(Tail,Return,Ctemp). 467write_pretty_aux([[Head]|Tail], Return, Column) :- 468 Ctemp is Column + 1, 469 typeHasGlyph(Map,Head), 470 write(Map), write(' '), 471 write_pretty_aux(Tail, Return, Ctemp). 472write_pretty_aux([[Agent]|Tail],Return,Column) :- 473 Ctemp is Column + 1, 474 isa(Agent,tAgent), 475 write('Ag'), write(' '), 476 write_pretty_aux(Tail,Return,Ctemp). 477write_pretty_aux([[_|_]|Tail],Return,Column) :- 478 Ntemp is Column + 1, 479 write('A+'), write(' '), 480 write_pretty_aux(Tail,Return,Ntemp). 481 482 483 484 485cmdShowRoomGrid(Room) :- ignore(show_room_grid_new(Room)),!. 486% cmdShowRoomGrid(Room) :-show_room_grid_old(Room),!. 487 488% =================================================================== 489% show_room_grid_new(Room) 490% =================================================================== 491:-export(show_room_grid_new/1). 492show_room_grid_new(Room):- 493 call_u(( 494 grid_size(Room,Xs,Ys,_Zs), 495 Ys1 is Ys+1,Xs1 is Xs+1, 496 forall(between(0,Ys1,Y), 497 ((nl, 498 forall(between(0,Xs1,X), 499 ((loc_to_xy(Room,X,Y,LOC), 500 write(' '), 501 OutsideTest = (not(between(1,Xs,X));not(between(1,Ys,Y))), 502 once(show_room_grid_single(Room,LOC,OutsideTest)))))))))),!,nl. 503show_room_grid_new(_):-nl. 504 505door_label(R,Dir,' '):- pathBetween_call(R,Dir,SP),atomic(SP). 506 507asserted_atloc_for_map(O,L):-asserted_atloc(O,L),O\=apathFn(_,_). 508asserted_atloc(O,L):-is_asserted(mudAtLoc(O,L)). 509 510show_room_grid_single(Room, xyzFn(Room,X,Y,Z),OutsideTest):- call_u((call(OutsideTest), doorLocation(Room,X,Y,Z,Dir),door_label(Room,Dir,Label))),write(Label),!. 511show_room_grid_single(_Room,_LOC,OutsideTest):- call(OutsideTest),!,write('[]'),!. 512show_room_grid_single(_Room,LOC,_OutsideTest):- asserted_atloc_for_map(Obj,LOC),inst_label(Obj,Label), write(Label), !. 513show_room_grid_single(_Room,LOC,_OutsideTest):- asserted_atloc_for_map(_Obj,LOC),write('..'), !. 514show_room_grid_single(_Room,_LOC,_OutsideTest):- write('--'), !. 515 516atom_label(SLabel,SLab2):- atom_concat('NPC0',L,SLabel),!,atom_label(L,SLab2),!. 517atom_label(SLabel,SLab2):- atom_concat('NPC',L,SLabel),!,atom_label(L,SLab2),!. 518atom_label(SLabel,SLab2):- once(i_name(SLabel,L)),L\=SLabel,atom_label(L,SLab2),!. 519%atom_label(SLabel,SLab2):- sub_atom(SLabel,2,2,_,SLab2),!. 520atom_label(SLabel,SLab2):- sub_atom(SLabel,1,2,_,SLab2),!. 521atom_label(SLabel,SLab2):- sub_atom(SLabel,0,2,_,SLab2),!. 522 523inst_label(Obj,Label):- typeHasGlyph(Obj,Label),!. 524inst_label(Obj,SLab2):- atom(Obj),atom_label(Obj,SLab2). 525inst_label(Obj,SLab2):- term_to_atom(Obj,SLabel),atom_label(SLabel,SLab2). 526inst_label(Obj,Label):- iprops(Obj,nameString(Val)),Val\=Obj,inst_label(Val,Label),!. 527inst_label(Obj,Label):- iprops(Obj,mudNamed(Val)),Val\=Obj,!,inst_label(Val,Label),!. 528inst_label(Obj,Label):- iprops(Obj,isa(Val)),Val\=Obj,inst_label(Val,Label),!. 529inst_label(_Obj,'&&'). 530 531% =================================================================== 532% show_room_grid_old(Room) 533% =================================================================== 534% Display world 535show_room_grid_old(Room) :- 536 call_u(gridValue(Room,1,G,_)), 537 length(G,N), 538 M is N + 1, 539 cmdShowRoomGrid(Room,1,1,M),!. 540 541cmdShowRoomGrid(Room,Old,N,N) :- 542 New is Old + 1, 543 \+ call_u(gridValue(Room,New,N,_)), 544 nl, 545 !. 546 547cmdShowRoomGrid(Room,Old,N,N) :- 548 New is Old + 1, 549 nl, 550 !, 551 cmdShowRoomGrid(Room,New,1,N). 552cmdShowRoomGrid(Room,Y,X,N) :- 553 loc_to_xy(Room,X,Y,LOC), 554 asserted_atloc(Obj,LOC), 555 props(Obj,isa(tAgent)), 556 list_agents(Agents), 557 obj_memb(Agent,Agents), 558 asserted_atloc(Agent,LOC), 559 write('Region1+'), write(' '), 560 XX is X + 1, 561 !, 562 cmdShowRoomGrid(Room,Y,XX,N). 563cmdShowRoomGrid(Room,Y,X,N) :- 564 loc_to_xy(Room,X,Y,LOC), 565 asserted_atloc(Obj,LOC), 566 (isa(Obj,Class), 567 typeHasGlyph(Label,Class)),!, 568 write(Label), write(' '), 569 XX is X + 1, 570 !, 571 cmdShowRoomGrid(Room,Y,XX,N). 572cmdShowRoomGrid(Room,Y,X,N) :- 573 loc_to_xy(Room,X,Y,LOC), 574 asserted_atloc(Agent,LOC), 575 isa(Agent,tAgent),!, 576 write('Ag'), write(' '), 577 XX is X + 1, 578 !, 579 cmdShowRoomGrid(Room,Y,XX,N). 580 581 582% Used to display the labels of the grid locations. (the key to the map). 583% Used at end of run. 584display_grid_labels :- 585 findall([Label,Name],typeHasGlyph(Name,Label),List), 586 forall(prop_memb([Label,Name],List), 587 (write(Label), write('='), write(Name), write(' '))), 588 nl. 589 590 591 592 593 594 595% :- include(prologmud(mud_footer)). 596 597 598 599:- use_module(library(socket)).
Currently defined options are:
ip(A,B,C,D)
.
Multiple of such terms can exist and access is granted
if the peer IP address unifies to one of them. If no
allow option is provided access is only granted from
ip(127,0,0,1)
(localhost).For example:
?- prolog_tnet_server(4000, []). % telnet localhost 4000 Welcome to the SWI-Prolog server on thread 3 1 ?-
633start_tnet(Call,Port,Description):- PortNum is Port, 634 must(prolog_tnet_server(PortNum, [allow(_),call(Call),description(Description)])),!. 635 636prolog_tnet_server(Port, Options):- 637 \+ member(alias(_),Options), 638 option(call(Call),Options,mud_telnet), 639 atomic_list_concat([Call,'_',Port],Alias),!, 640 prolog_tnet_server(Port, [alias(Alias)|Options]). 641 642prolog_tnet_server(_Port, Options) :- 643 member(alias(Alias),Options),thread_property(Base, status(running)),Base==Alias,!. 644 645prolog_tnet_server(Port, Options) :- 646 tcp_socket(ServerSocket), 647 tcp_setopt(ServerSocket, reuseaddr), 648 tcp_bind(ServerSocket, Port), 649 tcp_listen(ServerSocket, 5), 650 option(alias(Alias),Options,prolog_tnet_server), 651 option(description(Desc),Options,Alias), 652 dmsg(Port=Desc), 653 thread_create(mud_server_loop(ServerSocket, Options), _, 654 [ alias(Alias) 655 ]),!. 656 657peer_to_host(Peer,Host):- catch(tcp_host_to_address(Host, Peer),_,fail),!. 658peer_to_host(Peer,Host):- atom(Peer),Peer=Host,!. 659peer_to_host(Peer,Host):- compound(Peer),catch((Peer=..PeerL,atomic_list_concat(PeerL,'.',Host)),_,fail),!. 660peer_to_host(Peer,Host):- term_to_atom(Peer,Host),!. 661 662 663mud_server_loop(ServerSocket, Options) :- 664 tcp_accept(ServerSocket, ClientSock, Peer), 665 tcp_open_socket(ClientSock, In, Out), 666 set_stream(In, close_on_abort(false)), 667 set_stream(Out, close_on_abort(false)), 668 peer_to_host(Peer,Host), 669 gensym(inst_,Num), 670 option(alias(ServerAlias),Options,prolog_tnet_server), 671 atomic_list_concat(['client_',Host,'_',Num, '@', ServerAlias], Alias), 672 673 674 catch(thread_create( 675 call_service_mud_client(Host, Alias, ClientSock, In, Out, Peer, Options), 676 _, 677 [ alias(Alias),detached(true) 678 ]), 679 error(permission_error(create, thread, Alias), _), 680 fail), 681 !, 682 mud_server_loop(ServerSocket, Options). 683 684 685call_service_mud_client(Host, Alias, ClientSock, In, Out, Peer, Options):- 686 call(call,service_mud_client(Host, Alias, ClientSock, In, Out, Peer, Options)). 687 688service_mud_client(Host,Alias,ClientSock,In,Out,Peer,Options) :- 689 stream_property(Main_error, file_no(2)), 690 option(allow(PeerAllow),Options,ip(127,0,0,1))-> PeerAllow=Peer, 691 !, 692 thread_self(Id), 693 set_prolog_flag(tty_control, true), 694 set_prolog_IO(In, Out, Out), 695 set_stream(In, tty(true)), 696 % TODO figure out how to get immedate results 697 % set_stream(In, buffer_size(1)), 698 set_stream(user_output, tty(true)), 699 set_stream(user_error, tty(true)), 700 set_thread_error_stream(Id,user_error), 701 current_prolog_flag(encoding, Enc), 702 set_stream(user_input, encoding(Enc)), 703 set_stream(user_output, encoding(Enc)), 704 set_stream(user_error, encoding(Enc)), 705 set_stream(user_input, newline(detect)), 706 set_stream(user_output, newline(dos)), 707 set_stream(user_error, newline(dos)), 708 709 call(retractall,thread_util:has_console(Id, _, _, _)), 710 thread_at_exit(call(retractall,thread_util:has_console(Id, _, _, _))), 711 call(asserta,thread_util:has_console(Id, In, Out, Out)), 712 713 option(call(Call), Options, prolog), 714 format(Main_error,'~N~n~q~n~n',[service_mud_client_call(Call,Id,Alias,ClientSock,In,Out,Host,Peer,Options)]), 715 format(user_error, 716 'Welcome to the SWI-Prolog LogicMOO ~q on thread ~w~n~n', 717 [Call,Id]), 718 call_cleanup(Call, 719 ( close(In), 720 close(Out), 721 thread_detach(Id))). 722 723service_mud_client(Host,Alias,ClientSock,In,Out,Peer,Options):- 724 thread_self(Id),option(call(Call), Options, prolog), 725 format(main_error,'~N~n~q~n~n',[rejecting(Call,Id,Alias,ClientSock,In,Out,Host,Peer,Options)]), 726 format(Out, 'Bye!!~n', []), 727 close(In), 728 close(Out), 729 thread_detach(Id). 730 731 732make_client_alias(Host,Alias):- thread_self(Prefix),make_client_alias3(Prefix,Host,Alias). 733 734make_client_alias3(Prefix,Host,AliasH):- is_list(Host),must(atomic_list_concat([Prefix,'client'| Host], '.', AliasH)),!. 735make_client_alias3(Prefix,Host,AliasH):- compound(Host),Host=..HostL,make_client_alias3(Prefix,HostL,AliasH). 736make_client_alias3(Prefix,Host,AliasH):- term_to_atom(Host,AHost),must(atomic_list_concat([Prefix,'client', AHost], '_', AliasH)). 737 738 739call_close_and_detatch(In, Out, Id, Call):- 740 call_cleanup(call(Call),( close_connection(In, Out),ignore(thread_detach(Id)))). 741 742 743 744close_connection(In, Out) :- 745 call(retractall,thread_util:has_console(_,In,Out,_)), 746 ignore(catch(close(In, [force(true)]),_,true)), 747 ignore(catch(close(Out, [force(true)]),_,true)). 748 749strm_info(Out,Name,Strm):-nl,write(Out,Name = Strm),forall(stream_property(Strm,P),'format'(Out,', ~q',[P])),nl(Out). 750 751 752set_stream_ice(Stream, Alias, NV):- catch(set_stream(Alias,NV),_,catch(set_stream(Stream,NV),E,nop(dmsg(E)))). 753set_stream_ice(Stream, NV):- catch(set_stream(Stream,NV),E,(dmsg(set_stream(Stream,NV,E)))). 754 755 756 757baseKBdeliver_event_hooks(A,Event):- 758 subst(Event,reciever,you,NewEventM), 759 subst(NewEventM,A,you,NewEvent), 760 foreach(no_repeats(call_u(get_agent_sessions(A,O))), 761 foreach(no_repeats(lmcache:session_io(O,_In,Out,_Id)), 762 fmtevent(Out,NewEvent))). 763 764% correct_o_stream:-current_error(E),set_stream_ice(E). 765 766start_telnet :- app_argv('--notelnet'),!. 767start_telnet :- 768 % add_import_module(mud_telnet,baseKB,end), 769 must(start_mud_telnet), 770 nop(must(golorp_start)). 771 772 773:- all_source_file_predicates_are_transparent. 774:- fixup_exports. 775 776golorp_start :- !. 777golorp_start :- app_argv('--nogolorp'),!. 778golorp_start:- logicmoo_base_port(Port), 779 ensure_loaded('/opt/logicmoo_workspace/packs_xtra/logicmoo_packages/prolog/golorp/load'), 780 start_tnet(golorpish, Port+25 , "GOLORP Telnet"). 781 782:- after_boot(start_telnet).