1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% FILE: lib/common.pl
    3%
    4%       COMMON LIBRARY TOOLS for Prolog
    5%
    6%  AUTHOR : Sebastian Sardina (2003)
    7%  EMAIL  : ssardina@cs.toronto.edu
    8%  WWW    : www.cs.toronto.edu/~ssardina 
    9%  TYPE   : system independent code
   10%  TESTED : SWI Prolog 5.0.10 http://www.swi-prolog.org
   11%           ECLIPSE 5.4 http://www.icparc.ic.ac.uk/eclipse/
   12%
   13%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   14%
   15% This files contains system independent predicates that are used by 
   16% several files (e.g., projectors, interpreters, etc.)
   17%
   18% 
   19% The following predicates are required:
   20%
   21%  -- islist/1
   22%  -- substring/4
   23%  -- string_length/2
   24%  -- string_to_atom/2
   25%  -- string_to_list/2
   26%  -- emptyString/1 : return the empty string
   27%  -- system/1
   28%  -- stream_select/3
   29%  -- argc/1
   30%  -- argv/2
   31%  -- maplist/3
   32%  -- call_to_exec/3
   33%  -- get_integer/3
   34%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   35
   36
   37
   38
   39%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   40% 1 - GENERAL
   41%
   42%  -- subv(+X1,+X2,+T1,-T2)    
   43%        T2 is T1 with X1 replaced by X2
   44%  -- get_argument(?Name, ?Value)    
   45%        Value is the value of argument name Name. (i.e., Name=Value in call)
   46%  -- get_list_arguments(-L)    
   47%        L is a list of arguments of the form [Name, Value]
   48%  -- replace_element_list(+List,+E1,+E2,-List2)
   49%        List2 is List with element E1 replaced by element E2
   50%  -- sublist(?SubList, +List)
   51%        Succeeds if List is the list which contains all elements from SubList 
   52%  -- get_integer(+Low, ?N, +High)
   53%        N is an integer between Low and High
   54%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   55
   56       /*  T2 is T1 with X1 replaced by X2  */
   57subv(X1,X2,T1,T2) :- var(T1), T1 == X1, !, T2 = X2.
   58subv(_,_,T1,T2)   :- var(T1), !, T2 = T1.
   59subv(X1,X2,T1,T2) :- T1 == X1, !, T2 = X2.
   60subv(X1,X2,T1,T2) :- T1 =..[F|L1], subvl(X1,X2,L1,L2), T2 =..[F|L2].
   61
   62subvl(_,_,[],[]).
   63subvl(X1,X2,[T1|L1],[T2|L2]) :- subv(X1,X2,T1,T2), subvl(X1,X2,L1,L2).
   64
   65
   66% Command line argument Name has Value
   67% Name can be a symbolic name when the argument is of the form "Name=Value"
   68% or the number of the argument 
   69% OBS: Value is always a string, Name is an atom
   70get_argument(Name, Value) :- 
   71        get_list_arguments(L),
   72        member([Name, Value], L).
   73
   74% Obtain the list of command line arguments
   75% L is a list of [Name, Value] where Name is the value of the argument
   76% and Value is its value when the argument has the form Name=Value
   77% (e.g., port=2134). Otherwise, if the argument does not have that form, 
   78% Name is the number of the argument (e.g., [3, "notime"])
   79% OBS: Value is always a string, Name is an atom
   80get_list_arguments(L) :-
   81        argc(N), 
   82        N2 is N-1, 
   83        (N2 > 0 -> collect_all_arguments(N2, L) ; L=[]).
   84
   85collect_all_arguments(0, []) :- !.
   86collect_all_arguments(N, [[Name,Value]|L]) :-
   87        argv(N, SArgN),
   88        (split_string(SArgN, `=`, ``, [SName, Value]),
   89         string_to_atom(SName, Name) ->
   90             true
   91        ;
   92             Name=N,
   93             Value=SArgN
   94        ),
   95        N2 is N-1,
   96        collect_all_arguments(N2, L).
   97
   98
   99% -- replace_element_list(+List,+E1,+E2,-List2)
  100%     List2 is List with element E1 replaced by element E2
  101replace_element_list([],_,_,[]).
  102replace_element_list([CE1|R],CE1,CE2,[CE2|RR]):- !,
  103        replace_element_list(R,CE1,CE2,RR).
  104replace_element_list([E|R],CE1,CE2,[E|RR]):- 
  105        replace_element_list(R,CE1,CE2,RR).
  106
  107
  108
  109
  110%sublist(?SubList, +List)
  111%            Succeeds if List is the list which contains all elements 
  112%            from SubList 
  113sublist([],_).
  114sublist([X|R], L) :-
  115	member(X,L),
  116	sublist(R,L).
  117
  118
  119%get_integer(+Low, ?N, +High) :
  120%            Integer N is between Low and High (included)
  121/* ECL
  122get_integer(L, L, H) :- L=<H.
  123get_integer(L, N, H) :- L<H, L2 is L+1, get_integer(L2, N, H).
  124*/
  125get_integer(L, N, H) :- between(L,H,N).
Extract Value of option Name(Value) from list of options LOptions If the option is not mentioned in the list, assume value Default
  134extract_option(LOptions,NameOption,Value) :-
  135	extract_option(LOptions,NameOption,Value,_),
  136	\+ var(Value).
  137extract_option(LOptions,NameOption,Value,Default) :-
  138	ground(NameOption), 
  139	Option =.. [NameOption|[ValueOption]],
  140	member(Option,LOptions) -> Value=ValueOption ; Value=Default.
  141extract_option(LOptions,NameOption,Value,_Default) :-
  142	\+ ground(NameOption),
  143	member(Option,LOptions),
  144	Option =.. [NameOption|[Value]].
  145
  146	
  147%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  148% 2 - STRINGS AND ATOMS
  149%
  150% -- extract_substring(+String1, +Del1, +Del2, -String2, +PAfter, -Pos)
  151%     Very flexible extraction of a substring
  152%       String1= ......... Del11 ***** Del12 String2 Del21 ****** Del22
  153%     String2 starts at position Pos and Del11 is after position PosAfter
  154%     Del11 and Del22 may be null
  155%     This procedure will backtrack giving all possible solutions
  156%
  157% -- any_to_number(+T, -Number) 
  158%       Convert an atom, string, or list of chars T into a number
  159% -- any_to_string(+T, -String) 
  160%       Convert an atom, string, or list of chars T into string String
  161% -- lanything_to_string(+ListofT, -String) 
  162%       Generalizes any_to_string/2 to a list of atoms, strings, or chars
  163% -- string_replace(+S, +E1, +E2, -S2)
  164%       String/atom S2 is string/atom S with all chars E1 replaced by E2
  165% -- join_atom/3
  166% -- join_atom(+List, +Glue, -Atom)
  167%       Atom is the atom formed by concatenating the elements of List with an 
  168%       instance of Glue beween each of them.
  169% -- split_atom(+Atom, +SepChars, +PadChars, -SubAtoms) 
  170%       Decompose atom Atom into SubAtoms according to separators SepChars 
  171%       and padding characters PadChars.
  172%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  173
  174
  175% String1= ......... Del11 ***** Del12 String2 Del21 ****** Del22
  176% String2 starts at position Pos and Del11 is after position PosAfter
  177% Del11 and Del22 may be null
  178% This procedure will backtrack giving all possible solutions
  179
  180% Case where one of the delimiters is not a pair.
  181extract_substring(String1, Del1, Del2, String2, PAfter, Pos):-
  182    (\+ is_list(Del1) ; \+ is_list(Del2)), !,
  183    (is_list(Del1) -> NDel1=Del1 ; NDel1=[null, Del1]),
  184    (is_list(Del2) -> NDel2=Del2 ; NDel2=[Del2, null]),
  185    extract_substring(String1,NDel1,NDel2, String2, PAfter, Pos).
  186
  187extract_substring(String1,[Del11,Del12], [Del21,Del22], String2, PAfter, Pos):-
  188        % Convert all delimeters to strings if necessary
  189        any_to_string(Del11, Del11S),
  190        any_to_string(Del12, Del12S),
  191        any_to_string(Del21, Del21S),
  192        any_to_string(Del22, Del22S), !,
  193        % Set Pos1, if no Del11 then Pos1=PAfter
  194        % Pos2 is the first place of Del12 after Pos1
  195        (Del11=null -> 
  196             Pos1=PAfter,
  197             substring(String1, Pos2, _, Del12S), % Allow backtracking on Del12
  198             Pos2>Pos1
  199             ;
  200             substring(String1, Pos1, _, Del11S), 
  201             Pos1>PAfter,   % Allow backtracking on Del11, not on Del12
  202             once((substring(String1, Pos2, _, Del12S), 
  203                   is_after_string(Del11S, Pos1, Pos2)))
  204        ),
  205        % Pos3 is the first place of Del21 after Pos2
  206        once((substring(String1, Pos3, _, Del21S), 
  207              is_after_string(Del12S, Pos2, Pos3))),
  208        % If Del22\=null, check that there is a Del22 string after Pos3
  209        (Del22=null -> 
  210             true
  211        ; 
  212             once((substring(String1, Pos4, _, Del22S), 
  213                   is_after_string(Del21S, Pos3, Pos4)))
  214        ),
  215        % Calculate Pos: where String2 starts
  216        string_length(Del12S, LDel12),
  217        Pos is Pos2+LDel12,
  218        % Calcualte Length: length of String2
  219        Length is Pos3-Pos,
  220        % Extract String2 using its Pos and Length
  221        substring(String1, Pos, Length, String2).
  222
  223% P2 > Length(S)+P
  224is_after_string(S, P, P2) :-
  225        string_length(S, LS),
  226        SEnd is P+LS,
  227        P2 > SEnd.
  228
  229% Convert anything into a number
  230any_to_number(N, N) :- number(N).
  231any_to_number(A, N) :- atom(A), atom_number(A, N).
  232any_to_number(S, N) :- string(S), string_to_number(S, N).
  233
  234
  235% Convert anything into a string
  236any_to_string(S, S) :- string(S).
  237any_to_string(A, S) :- atom(A), string_to_atom(S, A).
  238any_to_string(A, S) :- number(A), string_to_number(S, A).
  239any_to_string(A, S) :- is_list(A), 
  240        ( (member(X,A), \+ number(X)) -> 
  241              build_string(A, S)   % Manually build string S
  242        ;
  243              string_to_list(S, A) % A is list of char codes!
  244        ).
  245any_to_string(A, S) :- \+ is_list(A), compound(A), string_to_term(S, A).
  246any_to_string(A, '_Var') :- var(A).
  247
  248% Convert a list of anything to into a list of strings
  249lany_to_string([], []).
  250lany_to_string([A|R], [SA|SR]) :- any_to_string(A, SA),
  251                                  lany_to_string(R, SR).
  252
  253% S is the empty string
  254emptyString(S) :- string_to_list(S,[]).
  255
  256build_string([], S)    :- emptyString(S).
  257build_string([E|R], S) :- 
  258        build_string(R, S2),
  259        any_to_string(E, SE),
  260        concat_string([SE,S2],S).
  261
  262% -- string_replace(S, E1, E2, S2)
  263%       String/atom S2 is string/atom S with all chars E1 replaced by E2
  264string_replace(S, E1, E2, S2) :- 
  265        lany_to_string([S,E1,E2],[SS,SE1,SE2]), 
  266        emptyString(ES),
  267        split_string(SS, SE1, ES, L),
  268        join_string(L, SE2, S2).
  269
  270% -- join_atom(List, Glue, Atom)
  271%      Atom is the atom formed by concatenating the elements of List with an 
  272%      instance of Glue beween each of them.
  273join_atom(List, Glue, Atom) :-
  274        maplist(any_to_string, List, List2),
  275        join_string(List2, Glue, String),
  276        string_to_atom(String, Atom).
  277
  278% -- split_atom(Atom, SepChars, PadChars, SubAtoms) 
  279%      Decompose atom Atom into SubAtoms according to separators SepChars 
  280%      and padding characters PadChars.
  281split_atom(Atom, SepChars, PadChars, SubAtoms) :-
  282        string_to_atom(SA1, Atom),
  283        string_to_atom(SA2, SepChars),
  284        string_to_atom(SA3, PadChars),
  285        split_string(SA1, SA2, SA3, SL),
  286        maplist(string_to_atom, SL, SubAtoms).
  287
  288
  289
  290%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  291% 3 - OPERATING SYSTEM: processes, files
  292%
  293% -- proc_exists(+Pid)
  294% -- proc_term(+Pid)
  295% -- proc_kill(+Pid)
  296%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  297
  298% Process Pid exists if it's listed by <ps -f pid>
  299proc_exists(Pid):- 
  300        concat_atom(['ps -f ',Pid], Command),
  301        call_to_exec(unix, Command, Command2), % Select right command for exec
  302        exec(Command2, [null, streamout]), 
  303        (read_string(streamout, end_of_line, _, _),
  304         read_string(streamout, end_of_line, _, _) -> 
  305             close(streamout)
  306        ;
  307             close(streamout),fail).
  308
  309% Process Pid is finished if it's listed with status Z with <ps -f pid>
  310% (SWI does not provide that)
  311proc_term(Pid):- 
  312        concat_atom(['ps -f ',Pid], Command),
  313        call_to_exec(unix, Command, Command2), % Select right command for exec
  314        exec(Command2,[null, streamout], _), 
  315        (read_string(streamout, end_of_line, _, _),
  316         read_string(streamout, end_of_line, _, S) -> 
  317             close(streamout),
  318             string_to_atom(Z, 'Z'),
  319             substring(S, Z, _)
  320        ;
  321             close(streamout), fail).
  322
  323% Kill process PID by sending signal 9 (MOST PROLOG'S PROVIDE THIS)
  324%proc_kill(Pid):- 
  325%        concat_atom(['kill -9 ',Pid], Com),
  326%        system(Com).
  327
  328
  329
  330
  331
  332%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  333% 4 - SOCKET COMMUNICATION PROTOCOL
  334%
  335%
  336% DESCRIPTION : This package provides a simple unified protocol via sockets 
  337%               to communication between the environment manager and each
  338%               of the individual environments.
  339%
  340% Single message = [Source, Data] where Source is the sender and
  341%                  data is the actual info sent. 
  342%
  343% Data has usullay the following form [Type, ...,...,...] where Type
  344%      defines the kind of message (sensing outcome, exogenous action, etc)
  345%
  346% -- send_data_socket(+Socket, +Data) :
  347%       Writes [Env, Data] to the Socket where Env is the name of the actual 
  348%       environment. Socket should be already connected to destination
  349% -- receive_list_data_socket(+Socket, -LMessages) :
  350%       Read (a possibly empty) list of messages from the Socket
  351% -- receive_data_socket(+Socket, -Message) :
  352%       Read 1 Message from the Socket (block if there is nothing yet)
  353%
  354% OBS: Requires name_env/1 to be on the DB to recognize the sender
  355%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  356:- dynamic name_env/1. % Stores the name of the current module
  357
  358  
  359% Send: [Env, Data] where Env is the name of the device (e.g., simulator)        
  360send_data_socket(Socket, Data) :- 
  361        (name_env(Env2) -> Env=Env2 ; Env=unknown),
  362        decode_data(_, DataToSent, [Env, Data]),
  363        				% Changed quote(true) --> quote(false) so that TERMS can be transmited (e.g., begin(photo,1,id_2))
  364        				% Otherwise, the term is quoted!
  365        write_term(Socket, DataToSent, [quoted(false)]),
  366        write(Socket, '.'),
  367        nl(Socket),
  368        flush(Socket).
  369
  370% Receive a list of [Env, Data] where Env is the id of the sender 
  371receive_list_data_socket(Socket, []) :- 
  372        stream_select([Socket], 0, []), !.      % Wait almost nothing
  373receive_list_data_socket(Socket, [Data|L]) :- 
  374        receive_data_socket(Socket, Data),
  375        (Data = [_, [_, end_of_file]] -> 
  376             L=[]
  377        ;
  378             receive_list_data_socket(Socket, L)
  379        ).
  380         
  381receive_data_socket(Socket, TData) :- 
  382         read_term(Socket, TRead, []),
  383         decode_data(Socket, TRead, TData).
  384
  385% decode_data(Socket, Data, CodifiedData)
  386%      Codify Data as as CodifiedData to send via socket S
  387decode_data(Socket, end_of_file, [socket(Socket), [system, end_of_file]]) :- !.
  388decode_data(_, [Env, Data], [Env, Data]) :- !.
  389decode_data(_, Data, [unknown, Data]).
  390
  391
  392
  393
  394
  395
  396
  397%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  398% 5 - TOOL FOR REPORTING MESSAGES
  399%
  400% -- report_message(+T, +M)       
  401%       Report messsage M of type T
  402% -- set_debug_level(+N) : set the debug level to N (nothing >N is shown)
  403%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  404:- dynamic 
  405	debug_level/1,
  406	warn_off/0.  407
  408% Set warn on/off for warnings
  409set_debug_level(warn_off) :- warn_off -> true ; assert(warn_off).
  410set_debug_level(warn_on)  :- retractall(warn_off).
  411
  412% Set te debug level to be below N (the higher the N, the more debug messages)
  413set_debug_level(N) :- 
  414	retractall(debug_level(_)),
  415	assert(debug_level(N)),
  416        report_message(system(0), ['Debug level set to ',N]).
  417
  418report_message(T, L) :- 
  419	is_list(L), !, 
  420	maplist(any_to_string,L,LS),
  421	any_to_string(' ', Space),
  422	join_string(LS, Space, M2), % Include space between each element
  423	report_message(T, M2).
  424
  425report_message(system(N), _)    :-   % Do not print this debug message
  426        debug_level(N2), N2<N, !.
  427report_message(system(N), T)    :- !,
  428        N2 is N-1,
  429        tab(N2),
  430        write('DEBUG '),  write(N), write(': '), writeln(T).
  431
  432report_message(warning, T)    :- !,
  433	(warn_off -> true ; write('!!! WARNING: '), writeln(T)).
  434
  435report_message(error, T)    :- !,
  436        write('!!! ERROR ----> '),  writeln(T).
  437
  438report_message(program, T)    :- !,
  439        write('  ***** PROGRAM:: '),  writeln(T).
  440
  441report_message(action, T)    :- !,
  442        write('>>>>>>>>>>>> ACTION EVENT:: '),  writeln(T).
  443
  444report_message(sensing, T)    :- !,
  445        write('--------------> SENSING EVENT:: '),  writeln(T).
  446
  447report_message(exogaction, T) :- !,
  448	nl,
  449        write('=========> EXOGENOUS EVENT:: '), writeln(T).
  450
  451report_message(user, T) :- !,
  452        write('  **** USER MESSAGE:: '),  writeln(T).
  453
  454report_message(_, T) :-
  455        write('  **** OTHER EVENT:: '),  writeln(T).
  456
  457
  458%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  459% EOF: lib/common.pl
  460%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%