1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Env/internet.pl
    4%
    5%  Author    : Sebastian Sardina
    6%  Time-stamp: <03/09/27 22:52:54 ssardina>
    7%  email     : ssardina@cs.toronto.edu
    8%  WWW       : www.cs.toronto.edu/~ssardina
    9%  TESTED    : SWI Prolog 5.0.10 http://www.swi-prolog.org
   10%	       ECLiPSe 5.3 on RedHat Linux 6.2-7.2
   11%  TYPE CODE : system independent predicates
   12%
   13% DESCRIPTION: Prolog primitive actions to access the Internet and the Web
   14%
   15% This file provides primitive actions for programming an Internet Agent.
   16% where the IndiGolog program is running. Also, sensing outcomes for that
   17% actions are asked in the same terminal.
   18% On the other hand, exogenous events are handle depending the exogenous
   19% moduled loaded (e.g. another xterm terminal, or a TCL/TK windows, etc.)
   20%
   21%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   22%
   23%                             November 22, 2002
   24%
   25% This software was developed by the Cognitive Robotics Group under the
   26% direction of Hector Levesque and Ray Reiter.
   27%
   28%        Do not distribute without permission.
   29%        Include this notice in any copy made.
   30%
   31%
   32%         Copyright (c) 2000 by The University of Toronto,
   33%                        Toronto, Ontario, Canada.
   34%
   35%                          All Rights Reserved
   36%
   37% Permission to use, copy, and modify, this software and its
   38% documentation for non-commercial research purpose is hereby granted
   39% without fee, provided that the above copyright notice appears in all
   40% copies and that both the copyright notice and this permission notice
   41% appear in supporting documentation, and that the name of The University
   42% of Toronto not be used in advertising or publicity pertaining to
   43% distribution of the software without specific, written prior
   44% permission.  The University of Toronto makes no representations about
   45% the suitability of this software for any purpose.  It is provided "as
   46% is" without express or implied warranty.
   47% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   48% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   49% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   50% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   51% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   52% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   53% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   54% 
   55%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   56%
   57% Primitive actions are called using perform/3:
   58%
   59% -- perform(CommandList)
   60%       CommandL is a list-char codifying the command to be executed
   61%
   62%  OBS: If ActionT is the term containing the primitive action to be
   63%       called, your code using internet.pl should do something like this:
   64%
   65%       term_to_atom(perform(ActionT), ActionA), % Convert into a list-chars
   66%       concat_atom(['eclipse -b ', Dir, 'lib/internet.pl -e ','\'', 
   67%                     ActionA,'\''], Command),
   68%       exec(Command). 
   69%
   70% or issue the shell comamnd:
   71%
   72%     eclipse -b <path>/internet.pl -e 'perform(<ActionAsListChar>'
   73%
   74%
   75% The following low-level internet/system primitive actions are provided
   76% (i.e., they are legal commands to be used with perform/1)
   77%
   78% -- browser_new(+ID) 
   79%        create a new web browser called IdWeb
   80% -- browser_close(+ID)
   81%        remove web browser IdWeb
   82% -- browser_refresh(+ID)
   83%        refresh content of URL
   84% -- browser_open(+ID, +URL)
   85%        set browser IdWeb to URL
   86%
   87%  -- check_string_after(+URL, +S, +PAfter) 
   88%        sense whether there is a string S in in address A after pos PAfter
   89%  -- check_pos_string(+A, +S, +PAfter) 
   90%        sense the position in address A of string S after position PAfter
   91%  -- read_string_between(+A, +D1, +D2, +PAfter): 
   92%        sense the string between D1 and D2 in address A after pos PAfter
   93%  -- read_string_length(+URL, +D, +L, +PAfter): 
   94%        sense the string in address A that starts with string D for 
   95%        a length of L and after position PAfter
   96%  -- read_html_field(+URL, +FieldName, +Cont, +PAfter): 
   97%        sense the next string value of field FieldName after position PAfter
   98%        that includes string Cont
   99%  -- download(+URL, +File) 
  100%        download address URL to file File  sense the process id number
  101%  -- check_web_file(+URL)
  102%        senses whether WebFile exists
  103%
  104%  -- sense_proc_term(+Pid)
  105%        senses whether process Pid is finished
  106%  -- kill_proc(+Pid)
  107%        kills process Pid
  108%  -- wait_proc(+Pid)
  109%        waits for process Pid to finish
  110%  -- sense_proc_exists(+Pid) 
  111%        sesnes whether process Pid exists
  112%  -- sense_file_exists(+File) 
  113%        senses whether file File exists
  114%  -- say(+Phrase, +Language)
  115%        speak Phrase in Language (requires a voice synthesis 
  116%        like festival)
  117%
  118% The following actions may generate the following exogenous actions:
  119%     
  120%  -- int_bool_after(URL, String, PAfter, Bool) :
  121%         Bool=there is String after PAfter in URL
  122%  -- int_pos(URL, String, PAfter, Pos) :
  123%         Pos=the next String after PAfter in URL is at position Pos
  124%  -- int_string_between(URL, Del1, Del2, PAfter, String) :
  125%         String=string between Del1 and Del2 in URL after PAfter
  126%  -- int_string_length(URL, Del, Lenght, PAfter, String) :
  127%         String=string after Del1 of length Length in URL after PAfter
  128%  -- int_html_field(URL, FieldName, PAfter, String, Pos) :
  129%         String=value of field FieldName containing Cont in URL after PAfter
  130%         Pos=starting postition of String
  131%  -- int_bool_download(URL, File, Status) :
  132%         Downloading of URL to File finished with Status (ok/failed)
  133%  -- int_bool_urlexists(URL, Bool) :
  134%         Bool= URL exists
  135%  -- int_proc_waited(Pid, Status)
  136%         Status = result of waiting process Pid (may be failed)
  137%
  138%
  139% REQUIRED:
  140%
  141% -- compat_swi/compat_ecl compatibility libraries
  142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  143
  144%:- module(internet,
  145%	[check_string_after/3,		% +URL, +String, +Position
  146%	 check_pos_string/3, 		% +URL, +String, +Position
  147%	 read_string_between/4,		% +URL, +Del1, +Del2, +Position
  148%	 read_string_length/4,		% +URL, +Start, +Length, +Position
  149%	 download/2,			% +URL, +FileName	
  150%	 check_web_file/1,		% +URL
  151%	 sense_proc_term/1,		% +PID
  152%	 sense_proc_exists/1,		% +PID
  153%	 sense_file_exists/1,		% +FileName
  154%	]).
  155
  156%:-  set_stream(warning_output,3).
  157
  158%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  159%%%%%%%%%%%%%% AUTOMATIC LOAD OF REQUIRED LIBRARIESSECTION %%%%%%%%%%%%%%%%
  160%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  161% This subsection does the following:
  162%
  163%  (a) loads the neccessary compatibility library: compat_ecl or compat_swi
  164%  (b) sets ` to be the string construct (using set_backquoted_string)
  165
  166% Path is the root path of the IndiGolog system
  167% In SWI Pwd will be a string already
  168main_dir(Path):- getenv('PATH_INDIGOLOG',Pwd),
  169                 (string(Pwd) -> atom_string(APwd, Pwd) ; APwd=Pwd),
  170                 concat_atom([APwd, '/'], Path).
  171
  172% Load required libraries (depending wheter its SWI or ECLIPSE)
  173:- dynamic library_directory/1.  174:- library_directory(_) -> 
  175       main_dir(Dir),       % We are running in SWI 
  176       concat_atom([Dir,'lib'], LibDir),
  177       assert(library_directory(LibDir)),
  178       use_module(library(eclipse_swi)),
  179       use_module(library(tools_swi)),
  180       set_backquoted_string
  181   ;                        % We are in ECLIPSE (rely on ECLIPSELIBRARYPATH)
  182       set_stream(warning_output,3),  % Do not write warnings
  183       use_module(library(tools_ecl)),
  184       set_backquoted_string. 
  185
  186%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  187%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  188% 0 - TOOLS FOR SENDING SENSING OUTCOMES AND EXOGENOUS EVENTS
  189%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  190%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  191
  192% Sends any data by writing it as a term, writes a dot, nl, and flush.
  193send(Data) :- 
  194        write_term(Data, [quoted(true)]), 
  195        write_term('.',[]),
  196        nl, flush_output.
  197
  198% Write the sensing result to the environment via the set-up communication
  199send_sensing(Data)   :-  send([sensing, Data]).
  200
  201% Write the exogenous event to the environment via the set-up communication
  202send_exogenous(Exog) :- send([exog_action, Exog]).
  203
  204
  205% This is the tool callled from outside. 
  206% CommandL is a list-char codifying the command to be executed
  207perform(CommandList) :- 
  208        string_to_list(CommandS, CommandList), 
  209        string_to_atom(CommandS, CommandA), 
  210        term_to_atom(CommandT, CommandA),
  211        call(CommandT).
  212
  213
  214%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  215%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  216% 1 - INTERFACE IMPLEMENTATION
  217%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  218%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  219
  220
  221%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  222% check_string_after(+URL, +S, +PAfter) 
  223%     sense whether there is a string S in in address A after pos. PAfter
  224% Sensing Outcome : always succeeds with 1
  225% Exogenous action: int_bool_after/4
  226%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  227check_string_after(URL, S, PAfter) :- 
  228        send_sensing(1),
  229        (find_pos_web(URL, S, PAfter, Pos) -> 
  230             (Pos=(-1) ->
  231                  send_exogenous(int_bool_after(URL, S, PAfter, false))
  232             ; 
  233                  send_exogenous(int_bool_after(URL, S, PAfter, true))
  234             )
  235        ; 
  236             send_exogenous(int_bool_after(URL, S, PAfter, failed))).
  237
  238
  239%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  240% check_pos_string(+URL, +S, +PAfter) 
  241%     sense the position in address A of string S after position PAfter
  242% Sensing Outcome : always succeeds with 1
  243% Exogenous action: int_pos/4
  244%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  245check_pos_string(URL, S, PAfter) :- 
  246        send_sensing(1),
  247        (find_pos_web(URL, S, PAfter, Pos) ->
  248             send_exogenous(int_pos(URL, S, PAfter, Pos))
  249        ;
  250             send_exogenous(int_pos(URL, S, PAfter, failed))).
  251
  252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  253% read_string_between(+URL, +D1, +D2, +PAfter): 
  254%      sense the string between D1 and D2 in address A after position PAfter
  255% Sensing Outcome : always succeeds with 1
  256% Exogenous action: int_string_between/5
  257%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  258read_string_between(URL, Del1, Del2, PAfter) :- 
  259        send_sensing(1),
  260        (retrive_string_delim_web(URL, Del1, Del2, String, PAfter, _) ->
  261             post_process(String,S2),    % Remove initial/final padding
  262             send_exogenous(int_string_between(URL, Del1, Del2, PAfter, S2))
  263        ;
  264             send_exogenous(int_string_between(URL, Del1, Del2, PAfter, failed))).
  265
  266
  267%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  268% read_html_field(+URL, +FieldName, +Cont, +PAfter): 
  269%      sense the next string value of field FieldName after position PAfter
  270%      that includes strings SCont
  271%      By a field we mean a string of the form: ... FieldName="xxxxxx" .....
  272%          where xxxxxx is the string sensed that contains substring Cont
  273% Sensing Outcome : always succeeds with 1
  274% Exogenous action: int_html_field/6
  275%                   returns xxxxx and its starting position
  276%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  277read_html_field(URL, FieldName, Cont, PAfter) :- 
  278        send_sensing(1),
  279        concat_string([FieldName,'=\"'], FieldTag),
  280        retrive_string_delim_web(URL, [null, FieldTag], ['\"', null], 
  281                                  String, PAfter, Pos),
  282        post_process(String, S2),    % Remove initial/final padding
  283        any_to_string(Cont, SCont),
  284        once(substring(String, SCont, _)), !, % Done, good string found
  285        send_exogenous(int_html_field(URL, FieldName, Cont, PAfter, S2, Pos)).
  286
  287read_html_field(URL, FieldName, Cont, P) :- 
  288        send_exogenous(int_html_field(URL, FieldName, Cont, P, failed, failed)).
  289
  290
  291        
  292%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  293% read_string_length(+URL, +D, +L, +PAfter): 
  294%      sense the string in address A that starts with string D for a length
  295%      of L and after position PAfter
  296% Sensing Outcome : always succeed with 1
  297% Exogenous action: int_string_length/5
  298%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  299read_string_length(URL, D, L, PAfter) :- 
  300        send_sensing(1),
  301        (retrive_string_poslen_web(URL, D, L, PAfter, T) ->
  302             post_process(T,T1),
  303             send_exogenous(int_string_length(URL, D, L, PAfter,T1))
  304        ;
  305             send_exogenous(int_string_length(URL, D, L, PAfter, failed))).
  306
  307
  308%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  309% download(+URL, +File) 
  310%        download address URL to file File  sense the process id number
  311% Sensing Outcome : always succeeds with 1
  312% Exogenous action: int_bool_download
  313%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  314download(URL, File) :- 
  315        send_sensing(1),
  316        (download(real, URL, File) -> 
  317             send_exogenous(int_bool_download(URL, File, ok)) 
  318        ;
  319             send_exogenous(int_bool_download(URL, File, failed))). 
  320
  321% Real implementation: downloads the Address (atom) to FileName (atom)
  322download(real, URL, FileName):- 
  323        exists_web_file(URL),        
  324        concat_atom(['lynx --dump ', URL, ' > ', '\'', FileName, '\''], Com),
  325        call_to_exec(unix, Com, Command2), % Select right command for exec
  326        exec(Command2,[]).
  327
  328% Version for debugging: this version creates the corresponding file but with
  329% an empty content and it waits 10 second to "simulate" the downloading
  330download(debug, URL, FileName):- 
  331        exists_web_file(URL),        
  332        concat_atom(['echo ', URL, ' > ', '\'', FileName, '\''], Com),
  333        call_to_exec(unix, Com, Command2), % Select right command for exec
  334        exec(Command2,[]).
  335
  336
  337%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  338% check_web_file(+URL)
  339%      senses whether WebFile exists
  340% Sensing Outcome : always succeds with 1
  341% Exogenous action: int_bool_urlexists/2
  342%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  343check_web_file(URL) :- 
  344        send_sensing(1),
  345        (exists_web_file(URL) ->  
  346             send_exogenous(int_bool_urlexists(URL, true)) 
  347        ;
  348             send_exogenous(int_bool_urlexists(URL, false))).
  349
  350exists_web_file(WF) :- 
  351        concat_atom(['lynx --dump -head ', WF], Command),
  352        call_to_exec(unix, Command, Command2), % Select right command for exec
  353        exec(Command2, [null, streamout], Pid), 
  354        read_string(streamout, end_of_line, _, S),
  355        wait(Pid, _),   % This can be problematic if a signal arrives
  356        close(streamout),
  357        substring(S, `OK`, _).
  358
  359
  360
  361
  362%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  363% ACTIONS FOR THE MANAGEMENT OF (NAMED) WEB-BROWSERS
  364%
  365% All this action return 1 as sensing unless they fail to execute.
  366%
  367% -- browser_new(+ID) 
  368% -- browser_close(+ID)
  369% -- browser_refresh(+ID)
  370% -- browser_open(+ID, +URL)
  371% -- browser_get(+ID, -C)
  372%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  373:- dynamic browser/3.  374
  375% Open a new browser with name ID. Fails if ID already exists
  376browser_new(ID) :-                      
  377	\+ browser(ID, _, _),
  378	any_to_string('',ES),
  379	assert(browser(ID, _, ES)), !,
  380	send_sensing(1).
  381browser_new(_) :-                      
  382	send_sensing(failed).
  383
  384% Closes browser ID. Fails if ID does not exist
  385browser_close(ID) :-
  386	retract(browser(ID, _, _)) -> send_sensing(1) ; send_sensing(failed).
  387
  388% Refresh the content of browser ID. Fails if ID does not exist
  389browser_refresh(ID) :-                 
  390	broswer(ID, URL, _),
  391	browser_open(ID, URL), !,
  392	send_sensing(1).
  393browser_refresh(_) :-                 
  394	send_sensing(failed).
  395
  396
  397% Open web page URL on browser ID. Fails if ID does not exist
  398browser_open(ID, URL) :-               
  399	retract(browser(ID, _, _)),
  400	get_page(URL, C),
  401	assert(browser(ID, URL, C)), !,
  402	send_sensing(1).
  403browser_open(_, _) :-               
  404	send_sensing(failed).
  405
  406% This action is not used from programs, but it just used inside this file
  407% Obtain the (current) content of browser ID
  408%browser_get(ID, C) :-                  
  409%	browser(ID, _, C) -> send_sensing(1) ; send_sensing(failed).
  410browser_get(ID, C) :-                  
  411	browser(ID, _, C).
  412
  413
  414
  415%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  416% sense_proc_term(+Pid)
  417%       senses whether process Pid is finished
  418% Sensing Outcome: true/false (true= process did terminate)
  419%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  420sense_proc_term(Pid) :- 
  421        proc_term(Pid) -> send_sensing(true) ;
  422                          send_sensing(false).
  423
  424
  425%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  426% sense_proc_exists(+Pid) 
  427%       sesnes whether process Pid exists
  428% Sensing Outcome: true/false (true= process did terminate)
  429%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  430sense_proc_exists(Pid) :- 
  431        proc_exists(Pid) -> send_sensing(true) ;
  432                            send_sensing(false).
  433
  434
  435%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  436% kill_proc(+Pid) 
  437%       kills process Pid 
  438% Sensing Outcome: true/false (true= process was killed successfully)
  439%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  440kill_proc(Pid) :- 
  441        proc_kill(Pid) -> send_sensing(true) ;
  442                          send_sensing(false).
  443
  444%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  445% wait_proc(+Pid) 
  446%       waits for process Pid to finish
  447% Sensing Outcome : always succeds with 1
  448% Exogenous action: int_proc_waited/2
  449%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  450wait_proc(Pid) :- 
  451        send_sensing(1),
  452        (wait_proc(Pid, Status) ->  
  453             send_exogenous(int_proc_waited(Pid, Status)) 
  454        ;
  455             send_exogenous(int_proc_waited(Pid, failed))
  456        ).
  457
  458
  459%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  460% sense_file_exists(+File) 
  461%        senses whether file File exists
  462% Sensing Outcome: true/false (true= file does exist)
  463%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  464sense_file_exists(File) :- 
  465        file_exists(File) -> send_sensing(true) ;
  466                             send_sensing(false).
  467
  468
  469%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  470% say(+Phrase, +Lan) 
  471%        says Phrase in Lan(guage) via speech (requires festival or similar)
  472% Sensing Outcome: always return 1
  473%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  474say(List, Lan) :- is_list(List), !, 
  475        concat_atom(List, Phrase), say(Phrase, Lan).
  476say(Phrase, english) :- 
  477        concat_atom(['echo \'', Phrase, '\' | festival --tts'], Command),
  478        call_to_exec(unix, Command, Command2), % Select right command for exec
  479        exec(Command2, []),
  480        send_sensing(1).
  481say(Phrase, Lan) :- Lan\=english,
  482        concat_atom(['echo \'', Phrase, '\' | festival --tts --language ',Lan], 
  483                    Command),
  484        call_to_exec(unix, Command, Command2), % Select right command for exec
  485        exec(Command2, []),
  486        send_sensing(1).
  487
  488
  489%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  490%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  491% 3 - LOW-LEVEL procedures for working on the web.
  492%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  493%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  494
  495% C is the HTML string of address URL
  496get_page(URL, C)             :-  % URL stands for a current open browser
  497	browser_get(URL, C), !.
  498get_page(URL, C)             :- 
  499        any_to_string(URL, S),
  500        get_page(S, C, preparsed).
  501get_page(SA, S, preparsed)  :- 
  502        concat_string([`lynx --source --preparsed `, SA], Command),
  503        call_to_exec(unix, Command, Command2), % Select right command for exec
  504        exec(Command2, [null, streamout], Pid),
  505        read_string(streamout, end_of_file, _, S),
  506        wait(Pid, 0),
  507        close(streamout).
  508get_page(SA, S, raw)        :- 
  509        concat_string([`lynx --source `, SA], Command),
  510%        exec_group(C, [null, streamout], _),
  511        call_to_exec(unix, Command, Command2), % Select right command for exec
  512        exec(Command2, [null, streamout], Pid),
  513        read_string(streamout, end_of_file, _, S),
  514        wait(Pid, 0),
  515        close(streamout).
  516
  517
  518% Pos is the position of substring T in address A after position PAfter
  519find_pos_web(URL, T, PAfter, Pos) :- 
  520        get_page(URL, SA), 
  521        any_to_string(T, ST),
  522        (substring(SA, P2, _, ST), P2 > PAfter -> Pos=P2 ; Pos=(-1)).
  523
  524% URL = ......... Del11 ***** Del12 SResult Del12 ****** Del22
  525% Retrives SResult wrt two flexible Delimiters and after a Position
  526retrive_string_delim_web(URL, Del1, Del2, SResult, PAfter, Pos):-
  527        get_page(URL, S),
  528        extract_substring(S, Del1, Del2, SResult, PAfter, Pos).
  529
  530
  531% retrive_string_poslen_web/5: Retrive string with length after position
  532% SResult is a substring in the web page URL that is after
  533% string Del1 and with length Len
  534retrive_string_poslen_web(URL, Del1, Len, Pos, SResult) :- 
  535        get_page(URL, SA), 
  536        any_to_string(Del1, SDel1),
  537        substring(SA, P1, _, SDel1), P1>Pos, !,
  538        substring(SA, P1, Len, SResult).
  539
  540% retrive_bet_apos/5: Retrive Between Strings After a Position
  541% SResult is a substring in the web page with address URL that is between
  542% strings Del1 and Del2 and after position P
  543retrive_bet_apos(URL, Del1, Del2, P, SResult) :- 
  544        get_page(URL,SA), 
  545        any_to_string(Del1, SDel1),
  546        any_to_string(Del2, SDel2),
  547        substring(SA, P1, _, SDel1), P1 > P,
  548        substring(SA, P2, _, SDel2), P2 > P1, !,
  549        string_length(SDel1, L1),
  550        L is P2-P1-1-L1,
  551        P11 is P1+L1,
  552        substring(SA, P11, L, SResult).
  553
  554
  555% Post processing of a string: remove spaces and line breaks at the beginning
  556% 	                       and at the end of the string
  557post_process(T, T1):- 
  558        split_string(T, ``, ` `, [T2]),
  559        string_replace(T2,'\n','',T1).    % Remove end_of_line
  560
  561
  562
  563%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  564% EOF: Env/internet.pl
  565%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%