19
21
24:- nop(ensure_loaded('adv_main_commands')). 27printable_state(S,S).
28
29meta_pprint(D,K):- pprint(D,K).
30
32do_metacmd(quit, S0, S1) :-
33 declare(quit, S0, S1),
34 player_format('Bye!~n', []).
35do_metacmd(rtrace, S0, S0) :- admin, rtrace.
36do_metacmd( nortrace, S0, S0) :- admin, nortrace.
37do_metacmd(trace, S0, S0) :- admin, trace.
38do_metacmd( notrace, S0, S0) :- admin, notrace.
39do_metacmd(spy(Pred), S0, S0) :- admin, spy(Pred).
40do_metacmd(nospy(Pred), S0, S0) :- admin, nospy(Pred).
41do_metacmd(possess(NewAgent), S0, S0) :-
42 wizard,
43 retract(current_player(_Agent)),
44 asserta(current_player(NewAgent)).
45do_metacmd(Echo, S0, S0) :-
46 admin,
47 Echo =.. [echo|Args],
48 player_format('~w~n', [Args]).
49do_metacmd(state, S0, S0) :-
50 wizard,
51 printable_state(S0,S),
52 meta_pprint(S, general).
53do_metacmd(make, S0, S0) :-
54 wizard,
55 thread_signal(main,make).
56do_metacmd(prolog, S0, S0) :-
57 wizard,
58 prolog.
59do_metacmd(CLS, S0, S0) :- wizard, current_predicate(_, CLS), call(CLS), !.
60do_metacmd(memory(Agent), S0, S0) :-
61 wizard,
62 declared(memories(Agent, Memory), S0),
63 meta_pprint(Memory, general).
64
65do_metacmd(model(Spatial, Agent), S0, S0) :-
66 wizard,
67 declared(memories(Agent, Memory), S0),
68 thought_model(Spatial,ModelData, Memory),
69 meta_pprint(ModelData, general).
70
71do_metacmd(model(Agent), S0, S0) :-
72 wizard,
73 declared(memories(Agent, Memory), S0),
74 forall(thought(model(_Spatial, ModelData), Memory),
75 meta_pprint(ModelData, general)).
76
77do_metacmd(create(Object), S0, S1) :-
78 wizard,
79 current_player(Agent),
80 related(Spatial, How, Agent, Here, S0),
81 declare(h(Spatial, How, Object, Here), S0, S1),
82 player_format('You now see a ~w.~n', [Object]).
83do_metacmd(destroy(Object), S0, S1) :-
84 wizard,
85 undeclare(h(_Spatial, _, Object, _), S0, S1),
86 player_format('It vanishes instantly.~n', []).
87do_metacmd(AddProp, S0, S1) :-
88 wizard,
89 AddProp =.. [setprop, Object | Args],
90 Args \= [],
91 Prop =.. Args,
92 setprop(Object, Prop, S0, S1),
93 player_format('Properties of ~p now include ~w~n', [Object, Prop]).
94do_metacmd(DelProp, S0, S1) :-
95 wizard,
96 DelProp =.. [delprop, Object | Args],
97 Args \= [],
98 Prop =.. Args,
99 delprop(Object, Prop, S0, S1),
100 player_format('Deleted.~n', []).
101do_metacmd(properties(Object), S0, S0) :-
102 wizard,
103 (declared(props(Object, PropList), S0);declared(class_props(Object, PropList), S0)),!,
104 player_format('Properties of ~p are now ~w~n', [Object, PropList]).
105do_metacmd(undo, S0, S1) :-
106 declare(undo, S0, S1),
107 player_format('undo...OK~nKO...odnu~n', []).
108do_metacmd(save(Basename), S0, S0) :-
109 atom_concat(Basename, '.adv', Filename),
110 save_term(Filename, S0).
111
112do_metacmd(WA, S0, S1) :-
113 ((cmd_workarround(WA, WB) -> WB\==WA)), !, do_metacmd(WB, S0, S1)