1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Bousi-Prolog interactive system launcher
    3
    4%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    5
    6:- module(bousi, [
    7		main/0,
    8		exit/0
    9   ]).   10
   11%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   12% References to modules in folders
   13
   14% WordNet:
   15% Looks if wn modules are in the current directory:
   16wn_directory(Directory) :- 
   17  File='./wn/wn.pl',
   18  exists_file(File),
   19  absolute_file_name(File, Path),
   20  file_directory_name(Path, Directory),
   21  !.
   22  
   23% If not, look in the paths in the environment variable PATH
   24wn_directory(Directory) :- 
   25  user:file_search_path(path, Path),
   26  atomic_concat(Path,'/wn',Directory),
   27  atomic_concat(Directory,'/wn.pl',File),
   28  exists_file(File),
   29  !.
   30  
   31% If not found, issue and error, but the system can still be used 
   32% with non-WordNet features
   33wn_directory(_) :- 
   34  write('ERROR: wn directory not found. Access to WordNet is not \c
   35                available.'),
   36  nl.
   37  
   38:- (wn_directory(Directory)
   39    ->
   40     asserta(user:file_search_path(wn, Directory))
   41    ;
   42     true).   43%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   44
   45
   46%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   47% Modules loaded at start-up
   48
   49:- use_module(bplShell).   50:- use_module(foreign).   51:- use_module(test).   52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   53
   54
   55%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   56% Set double quotes for delimiting list of character codes,
   57% instead of the new SWI-Prolog behaviour to delimit strings
   58:- set_prolog_flag(double_quotes, codes).   59%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   60
   61
   62%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   63% Main predicate for launching the Bousi-Prolog system
   64%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 main
Initial predicate of the Bousi-Prolog system. This predicate loads the foreign library, shows a welcome message and initializes and launches the Bousi-Prolog command-line shell.
   74main :-
   75  set_host_safe,
   76	foreign:load_foreign_extension,
   77	flags:set_bpl_flag(continue('yes')),
   78	welcome_message, 
   79	bplShell:start_bpl_shell.
   80
   81	
   82%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   83% Predicate for setting a host safe execution mode
   84%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 set_host_safe
Sets host safe execution mode if indicated by the file host_safe
   92set_host_safe :-
   93  exists_file('./../../host_safe'),
   94	!,
   95	flags:set_bpl_flag(host_safe('yes')).
   96set_host_safe :-
   97	flags:set_bpl_flag(host_safe('no')).
   98	
   99
  100%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  101% Predicate for continuing the execution of the Bousi-Prolog system
  102%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 exit
Continues with Bousi-Prolog execution after a bk command.
  110exit :-
  111	flags:set_bpl_flag(continue('yes')),
  112	bplShell:bpl_shell_loop.
  113	
  114
  115%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  116% Miscellaneous predicates
  117%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 welcome_message
Shows Bousi-Prolog initial welcome message.
  125welcome_message :-
  126	nl,
  127	write('                                                    Universidad de'), nl,
  128	write('|O)               |D)                            Castilla - La Mancha'), nl,
  129	write('|O)(O)\\U(S)|I| ~~ || |R (O) |L (O) (G|.     (Version 3.2 ~~ April 2019)'), nl,
  130	write('----------------------------------------------------------------------------'), nl,
  131	write('Welcome to Bousi~Prolog, a fuzzy logic programming system created by'), nl,
  132	write('Juan Gallardo-Casero and Pascual Julian-Iranzo. Fernando Saenz-Perez'), nl,
  133	write('(UCM) contributed to this version. This software is for research and'), nl, 
  134	write('educational purposes only, and it is distributed with NO WARRANTY.'), nl,
  135	write('Please visit our website for the latest news on Bousi~Prolog:'), nl,
  136	write('https://dectau.uclm.es/bousi-prolog'), nl,
  137	write('----------------------------------------------------------------------------'), nl,
  138	nl,
  139	write('----------------------------------------------------------------------------'), nl,
  140	write('< bousi_pack by CapelliC >'), nl,
  141	write('----------------------------------------------------------------------------'), nl,
  142	nl,
  143	write('----------------------------------------------------------------------------'), nl,
  144	write('--            Enter \'hp\' to get help on the available commands            --'), nl,
  145	write('----------------------------------------------------------------------------'), nl,
  146	nl