You selected menu.pl
/* sample of memu command and output to a file */
% modified: 22 Mar 2003.
% modified: 3 July 2003.
% modified: 7 July 2003.
% modified: 21 Aug 2003. tell_goal/4(forall_such_that), do_by_user_conform/3.
% modified: 8 Aug 2004. stopwatch and sampling tools to estimate completion time.
% modified: 2 Mar 2005. testing tools.
% modified: 12 Oct 2005. tell_goal/2. finalize rule revised.
% modified: 27 Oct 2005. forall_do_with_displaying_id/2 and total rearrangement of the code.
% modified: 28,31 Oct 2005. is_there_unspecified/2, do_by_user_conform/3.
% modified: 28,31 Mar 2006. tell_goal_0/2, tell_goal/2.
% modified: 27 Aug 2006. close_telling_file/0.
%---------------------------------------------------%
% Utilities for user choice menu, display goals,
% and file output
%---------------------------------------------------%
forall_write(A):- forall(member(X,A),(nl,write(X))).
forall_write_goals(A,B):- B,nl,write(A),fail.
forall_write_goals(_,_):- nl,write(complete).
% verify unspecified.
% added: 28 Oct 2005. (from impl13b.pl)
is_there_unspecified( No, User):-
\+ ( member(X,User),var(X)),
!,
No=no.
is_there_unspecified( yes, _).
% display all successful goals (with the count).
display_goals(G):-
(\+ var(G)->true;G=empty),
forall(G,(nl,write(G))).
display_goals(_).
display_goals(G,C):-
(\+ var(G)->true;G=empty),
(\+ var(C)->true;C=true),
forall((G,C),(nl,write(G))).
display_goals(_,_).
display_goals(G,C,N):-
(\+ var(G)->true;G=empty),
(\+ var(C)->true;C=true),
findall(G,(G,C),L),
length(L,N),
display_goals(G,member(G,L)),
nl,
write('the number of goals='),
write(N).
% save the successful goal into a specified text file.
%---------------------------------------------------%
% revised: 12 Oct 2005, 28,31 Mar 2006.
tell_goal_0(File,G):-
open(File,write,_S),
tell(File),
nl,
tstamp('% file output start time ',_),
nl,
write('%---------- start from here ------------%'),
nl,
G,
nl,
write('%---------- end of data ------------%'),
nl,
tstamp('% file output end time ',_),
tell(user),
current_stream(File,write,S0),
close(S0).
tell_goal(File,G):-
forall(current_stream(File,write,S0),close(S0)),
tell_goal_0(File,G),
forall(current_stream(File,write,S0),close(S0)),
write(complete).
% 成功するゴールをすべて保存
% save all successful goals to file.
%---------------------------------------------------%
tell_goal(File,forall,G):-
G0 = (nl,write(G),write('.')),
G1 = forall(G,G0),
tell_goal(File,G1).
% the conditionalized version
% Aug 2003.
tell_goal(File,forall_such_that,G,Condition):-
% G should be occurred in the Condition.
WRITE = (nl,write(G),write('.')),
G1 = forall(Condition,WRITE),
tell_goal(File,G1).
% close stream
%---------------------------------------------------%
close_telling_file:-
current_stream(A,write,B),
\+ member( A, [1,2]),
nl(user),write(user,'close ':A:'? (y):'),
read(y),
close(B),
nl,write('closed.'),
fail.
close_telling_file:-
nl,
write('no more.').
% 実行時刻の取得
% time stamp
%---------------------------------------------------%
tstamp(no,T):-
get_time(U),
convert_time(U,A,B,C,D,E,F,_G),
T = [date(A/B/C), time(D:E:F)],
nl.
tstamp(Word,T):-
\+ var(Word),
Word \= no,
get_time(U),
convert_time(U,A,B,C,D,E,F,_G),
T = [date(A/B/C), time(D:E:F)],
% format('~`.t~t~a~30|~`.t~t~70|~n',[Word]),
write((Word,T)),
nl.
% stopwatch
%---------------------------------------------------%
% added: 24 Feb 2004. (cited from: beleq03.pl)
% modified: 8 Mar 2004.
stopwatch_0(Goal,TD):-
get_time(TS),
Goal,
get_time(TF),
TD is TF - TS.
stopwatch(Goal,TD):-
stopwatch_0(Goal,TD),
nl,
write('% time elapsed (sec): '),
write(TD),
nl.
stopwatch_of_iterated_goals(_Goal,0,0,Display):-
rule_of_display_number_in_stopwatch(Display,JOB),
JOB.
stopwatch_of_iterated_goals(Goal,TD,Iteration,Display):-
number(Iteration),
Iteration > 0,
init_count_of_display,
rule_of_display_number_in_stopwatch(Display,JOB),
stopwatch(
forall(
(
Goal, %write(Goal),
update_count_of_display(K),
(K>Iteration->!,fail;true)
),
JOB
),
TD
).
rule_of_display_number_in_stopwatch(no,true):-
!.
rule_of_display_number_in_stopwatch(yes,display_counter).
% a display of counter for iterated goals.
%---------------------------------------------------%
% added: 22 Feb 2004.
% modified: 8--9 Mar 2004. minor bugfix.
:- dynamic temp_count_of_display/1.
temp_count_of_display(0).
init_count_of_display:-
abolish(temp_count_of_display/1),
assert(temp_count_of_display(0)).
update_count_of_display(K):-
retract(temp_count_of_display(K0)),
K is K0 + 1,
assert(temp_count_of_display(K)).
update_and_display_counter:-
update_count_of_display(_),
display_counter.
display_counter:-
temp_count_of_display(K),
nl,
write([K]).
% a sampling tool for estimating time complexity.
%---------------------------------------------------%
% added: 8--9 Mar 2004. (cited from: beleq03.pl)
get_average_time_by_sampling(H/LA,N,((SampleTime + TotalTime) / N)=AverageTime):-
length(A,LA),
Goal=..[H|A],
stopwatch_0(Goal,SampleTime),
rule_for_decide_number_of_trials(Goal,SampleTime,N),
(N = 0 -> !,fail; true),
N1 is N - 1,
length(B,LA),
Goal1=..[H|B],
stopwatch_of_iterated_goals(Goal1,TotalTime,N1,no),
AverageTime is (SampleTime + TotalTime) / N,
!.
rule_for_decide_number_of_trials(_,_,Trials):-
integer(Trials). % conform to user.
rule_for_decide_number_of_trials(_,SampleTime,20):-
SampleTime=<1.
rule_for_decide_number_of_trials(_,SampleTime,10):-
SampleTime>1,
SampleTime=<5.
rule_for_decide_number_of_trials(_,SampleTime,3):-
SampleTime>5,
SampleTime=<10.
rule_for_decide_number_of_trials(_,SampleTime,1):-
SampleTime>10.
% for debug:
check_if_false(_,G):-
G,!.
check_if_false(A,_G):-
nl, write('**** fail ****'),write(A),
nl, write('continue ? > '),read(y).
% displaying goals with update id numbers:
% an alternative for display_goals/1,2,3
%---------------------------------------------------%
% added: 27 Oct 2005 (cited from: impl13b.pl)
forall_do_with_displaying_id( G,M):-
init_count_of_display,
forall( G,
(
update_and_display_counter,
tab(1),
write(M)
)
).
% save all predicates to file
%---------------------------------------------------%
% cited from: impl12.pl(Jan 2003, added: 24 Sep 2002)
% modified and added: 3 June 2003.
tell_all_pred:-
Q=user_defined_predicate(P,Info),
G1=findall((P,Info),Q,D),
G2=forall(
(
member((P,Info),D)
),
(
P=..[X|Z],
%current_functor(X,Y)
length(Z,L),
write(X),write(' / '),
write(L),tab(2),write(Info),nl
)
),
G=(G1,G2),
tell_goal('all_pred.txt',G).
% added: 3 June 2003.
user_defined_predicate(P,[file(F),lines(L),clauses(N)]):-
predicate_property(P,line_count(L)),
predicate_property(P,number_of_clauses(N)),
predicate_property(P,file(F)),
\+ predicate_property(P,imported_from(system)),
\+ predicate_property(P,built_in).
% pretty print of the arities of the successful goal.
%-----------------------------------------
% added: 7 July 2003. (cited from: networ0.pl)
ppf(Functor):-
Functor=..[G|X],
nl,
write(functor:G),
forall(member(Z,X),(nl,tab(2),write(Z))).
ppg(Goal):-
Goal=..[G|X],
Goal,
nl,
write(goal:G),
forall(member(Z,X),(nl,tab(2),write(Z))).
ppl([Head|List]):-
nl,
write(Head),
forall(member(Z,List),(nl,tab(2),write(Z))).
% predicate equivalence cited from kalp01
%---------------------------------------------------%
% added : 2 Mar 2005.
verify_equality_of_goals(G1:V1,G2:V2,S,D):-
findall(V1,G1,S1),
findall(V2,G2,S2),
subtract(S1,S2,D1),
subtract(S2,S1,D2),
S=[S1,S2],D=[D1,D2].
% a script for generating goals as facts
%---------------------------------------------------%
:- dynamic id_of_temp_goal/1.
:- dynamic temp_goal/3.
update_id_of_temp_goal(ID):-
retract(id_of_temp_goal(ID_0)),
ID is ID_0 +1,
assert(id_of_temp_goal(ID)).
preliminary_to_factualize_goals:-
abolish(id_of_temp_goal/1),
abolish(temp_goal/3),
assert(id_of_temp_goal(0)).
factualize_goals(G):-
warn_if_not_a_list(G),
preliminary_to_factualize_goals,
factualize_goals(G,LID),
finalize_factualization(LID).
factualize_goals([Goal|Constraint],ID):-
Goal,
Constraint,
update_id_of_temp_goal(ID),
assert(temp_goal(ID,Goal,Constraint)),
fail.
factualize_goals(_,ID):-
id_of_temp_goal(ID).
finalize_factualization(Last_ID):-
write(complete),
nl,
write(total:Last_ID),
write(' successful goals have asserted as temp_goal/3.').
warn_if_not_a_list(G):-
length(G,_),
forall(member(X,G),clause(X,_)),
!.
warn_if_not_a_list(_):-
write('**** warning : not a list of executable goals.'),
nl,
write('no data has generated.'),
fail.
% a multiple-choice menu
%---------------------------------------------------%
menu(A,N,B):-
choice_menu1(A,N),
clause(A,B),
numbervars([A,B],f,1,_E).
choice_menu1(A,N):-
% write(helllo),
setof(B,A0^current_predicate(A0,B),Bs),
% write(Bs),
setof([K,A/L,B],
B^C^K1^(
nth1(K1,Bs,B),
K_min is 10,
%nth1(K_min,Bs,write(_)),
K1 > K_min,
K is K1 - K_min,
B=..[A|C],
% write(B),
length(C,L)
),
Menu),
forall(
member( [U,A,_],Menu),
(tab(1),write([U,A]),nl)
),
tab(3),
write(number),
read(U),
(
member( [U,_,B], Menu)
->
(N=U,A=B)
;
choice_menu1(A,N)
).
choice_menu2(A,N,Menu,Bag):-
\+ var( Menu),
Msg='正しく番号を入力し、ピリオドを打ってください。',
(
display_each( Menu),
(
read(U),
nth1( U,Menu,B))
->(
A = B, U = N, write(A), nl
)
;(
write( Msg), nl, choice_menu1(A,Bag)
)
).
display_each(Bag):-
forall(
nth1( K,Bag,B1),
(write(K),write('.'),write(B1),nl)
).
% user conform
%---------------------------------------------------%
do_by_user_conform(if(USER),then(ACT1),else(ACT2)):-
(var(USER)->read(USER);true),
(
member(USER,
[y,'Y',yes,'Yes','YES',ok,'OK',go]
)
-> ACT1 ; ACT2
).
return to front page.