1:-module(help,
    2     [user_help/0, help/1, devman/1, devman/0]).    3
    4:- use_module(sciff_options).    5
    6:- dynamic(help/1).    7%:- [browser]. 
    8% Marco Gavanelli:
    9% I use ensure loaded in each of the exported files,
   10% so the compilation is faster, in case the user
   11% does never issue any help command.
   12
   13user_help :-
   14    ensure_loaded(browser),
   15    browse_html('userman.html',index).
   16
   17help(Option):-
   18    ensure_loaded(browser),
   19    browse_html('userman.html',Option).
   20devman(Option):-
   21    ensure_loaded(browser),
   22    browse_html('devman.html',Option).
   23devman:- devman(index),!.
   24devman:- ensure_loaded(browser),
   25    list_topics('devman.html').
   26/*
   27%----------------------------------------------------------
   28% OPTION
   29%----------------------------------------------------------
   30help(option) :- help(options).
   31help(options) :-
   32	findall(Option, sciff_option(Option, _), ListOption),
   33	nl, write('options available:'), nl, nl,
   34	print_options_list(ListOption),
   35	nl.
   36print_options_list( []).
   37print_options_list( [ Option | T]) :-
   38	write(Option), nl,
   39	print_options_list(T).
   40
   41
   42
   43
   44%----------------------------------------------------------
   45% HOWTO
   46%----------------------------------------------------------
   47help(howto) :-
   48    write('*** SCIFF proof-procedure ***\n'),
   49    write('Create a directory with a name (say "name") containing the following files:\n'),
   50    write('1. "name_sokb.pl" containing your SOKB (i.e., your program)\n'),
   51    write('2. "name_ics.txt" containing the integrity constraints\n'),
   52    write('3. "name_history.txt" containig the history\n'),
   53    write('call the goal: "build(name)"\n'),
   54    write('recompile SCIFF\n'),
   55    write('call either "run" or "run_no_close"\n').
   56
   57
   58
   59%----------------------------------------------------------
   60% SET_AN_OPTION
   61%----------------------------------------------------------
   62help(set_an_option) :-
   63    nl,
   64    write('Each option can be set using the predicate:\n'),
   65    write('set_option(Option,Value)\n'),
   66    write('where Option is the name of the option you want to modify,\n'),
   67    write('and Value is the new value you want to assign to it.'),
   68    nl.
   69
   70
   71%----------------------------------------------------------
   72% GET_AN_OPTION
   73%----------------------------------------------------------
   74help(get_an_option) :-
   75    nl,
   76    write('You can inspect the state of an option using the predicate:\n'),
   77    write('sciff_option(?Option, ?State).\n'),
   78    nl.
   79
   80
   81%----------------------------------------------------------
   82% SHOW_OPTION
   83%----------------------------------------------------------
   84help(show_options) :-
   85    nl,
   86    write('The predicate \'show_options\' shows all the options available and\n'),
   87    write('their state.\n'),
   88    nl.
   89
   90
   91
   92
   93
   94
   95%----------------------------------------------------------
   96% FULFILLER OPTION
   97%----------------------------------------------------------
   98help(fulfiller) :-
   99	nl,
  100	write('fulfiller option is '),
  101	sciff_option(fulfiller, Answer),
  102	write(Answer), nl, nl,
  103	write('fulfiller option enables the MarcoA\'s rule for generating histories (g-sciff).'), nl,
  104	write('This option should be set off unless you are using the g-sciff.'),
  105	nl, nl.
  106
  107
  108
  109%----------------------------------------------------------
  110% FDET OPTION
  111%----------------------------------------------------------
  112help(fdet) :-
  113	nl,
  114	write('fdet option is '),
  115	sciff_option(fdet, Answer),
  116	write(Answer), nl, nl,
  117	write('fdet option enables the deterministic behaviour of the sciff.'), nl,
  118	write('It is very useful whenever you must achieve better performances in spite of completeness.'), nl,
  119	write('Usually is off.'), nl,
  120	nl, nl.
  121	
  122	
  123
  124%----------------------------------------------------------
  125% SEQ_ACT OPTION
  126%
  127% There cannot be two events at the same time.
  128% Useful for the abductive Event Calculus
  129%----------------------------------------------------------
  130help(seq_act) :-
  131	nl,
  132	write('seq_act option is '),
  133	sciff_option(seq_act, Answer),
  134	write(Answer), nl, nl,
  135	write('seq_act option checks if two events are happening at the same time.'), nl,
  136	write('If seq_act is on, two events cannot happen at the same time.'), nl,
  137	write('If seq_act is off, more events can happen at the same time.'), nl,
  138	write('This option is primarly used in the abductive event calculus.'), nl,
  139	write('Usually is off.'), nl,
  140	nl, nl.
  141
  142
  143
  144%----------------------------------------------------------
  145% FACTORING OPTION
  146%----------------------------------------------------------
  147help(factoring) :-
  148	nl,
  149	write('factoring option is '),
  150	sciff_option(factoring, Answer),
  151	write(Answer), nl, nl,
  152	write('Actually unknown, introduced by MarcoG'), nl,
  153	write('Usually is off.'), nl,
  154	nl, nl.
  155
  156
  157
  158%----------------------------------------------------------
  159% SCIFF_DEBUG OPTION
  160%----------------------------------------------------------
  161help(sciff_debug) :-
  162	nl,
  163	write('sciff_debug option is '),
  164	sciff_option(sciff_debug, Answer),
  165	write(Answer), nl, nl,
  166	write('Print on screen debug messages.'), nl,
  167	write('Usually is off.'), nl,
  168	nl, nl.
  169
  170
  171%----------------------------------------------------------
  172% VIOLATION_CAUSES_FAILURE OPTION
  173%----------------------------------------------------------
  174help(violation_causes_failure) :-
  175	nl,
  176	write('violation_causes_failure option is '),
  177	sciff_option(violation_causes_failure, Answer),
  178	write(Answer), nl, nl,
  179	write('Decides if a violation of the protocol should induce a failure '),
  180	write('(and backtracking where possible) of the proof.'), nl,
  181	write('Allowed values are yes/no.'), nl,
  182	write('Default value is yes.'), nl,
  183	nl, nl.
  184	
  185
  186%----------------------------------------------------------
  187% GRAPHVIZ OPTION
  188%----------------------------------------------------------
  189help(graphviz) :-
  190	nl,
  191	write('graphviz option is '),
  192	sciff_option(graphviz, Answer),
  193	write(Answer), nl, nl,
  194	write('Represents the sciff transition in form of a graph, using the graphviz library '), nl,
  195	write('Default value is off.'), nl,
  196	nl, nl.
  197	
  198
  199%----------------------------------------------------------
  200% allow_events_not_expected OPTION
  201%----------------------------------------------------------
  202help(allow_events_not_expected) :-
  203	nl,
  204	write('allow_events_not_expected option is '),
  205	sciff_option(allow_events_not_expected, Answer),
  206	write(Answer), nl, nl,
  207	write('By default, sciff allows events to happen even if they are not expected.'), nl,
  208	write('By setting it to \'no\', sciff detects as violation if an'), nl,
  209	write('happened event does not have a corresponding expectation.'), nl,
  210	write('Default value is yes.'), nl,
  211	nl, nl.
  212
  213help(min_viol_closed):-
  214    writeln('min_viol_closed/1'),
  215    writeln('amongst the various branches selects the one with the minimal'),
  216    writeln('number of violations. Returns the number of violations.'),
  217    writeln('Useful when used in conjunction with the option'),
  218    writeln('violation_causes_failure -> no.'),
  219    writeln('Known bug: the number of violations is not precise: often'),
  220    writeln('the reported number of violations should be increased by 1.').
  221
  222help(min_viol_open):-
  223    writeln('min_viol_closed/1'),
  224    writeln('amongst the various branches selects the one with the minimal'),
  225    writeln('number of violations. Returns the number of violations.'),
  226    writeln('Useful when used in conjunction with the option'),
  227    writeln('violation_causes_failure -> no.'),
  228    writeln('Known bug: the number of violations is not precise: often'),
  229    writeln('the reported number of violations should be increased by 1.').
  230
  231writeln(X):- write(X), nl.
  232*/