1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Env/env_int_swi.pl
    4%
    5%  AUTHOR : Sebastian Sardina (2002)
    6%  EMAIL  : ssardina@cs.toronto.edu
    7%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
    8%  TYPE   : system dependent predicates (SWI threads and http libs)
    9%  TESTED : SWI Prolog 5.2.8 http://www.swi-prolog.org 
   10%
   11% This files provides the environment for working with the internet/web
   12% It allows the execution of many internet-system actions in paralell
   13% by using multiple threads (one per action requested to be executed)
   14%
   15%
   16% This environment is self-contained (it automatically loads the required
   17% libraries). It should be called as follows:
   18%
   19%   pl host=<HOST> port=<PORT> -b env_int_swi.pl -e start
   20%
   21% where HOST/PORT is the address of the environment manager socket.
   22%
   23% Written for SWI Prolog (http://www.swi-prolog.org) running under Linux 
   24%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   25%
   26%                             June 15, 2000
   27%
   28% This software was developed by the Cognitive Robotics Group under the
   29% direction of Hector Levesque and Ray Reiter.
   30%
   31%        Do not distribute without permission.
   32%        Include this notice in any copy made.
   33%
   34%
   35%         Copyright (c) 2000 by The University of Toronto,
   36%                        Toronto, Ontario, Canada.
   37%
   38%                          All Rights Reserved
   39%
   40% Permission to use, copy, and modify, this software and its
   41% documentation for non-commercial research purpose is hereby granted
   42% without fee, provided that the above copyright notice appears in all
   43% copies and that both the copyright notice and this permission notice
   44% appear in supporting documentation, and that the name of The University
   45% of Toronto not be used in advertising or publicity pertaining to
   46% distribution of the software without specific, written prior
   47% permission.  The University of Toronto makes no representations about
   48% the suitability of this software for any purpose.  It is provided "as
   49% is" without express or implied warranty.
   50% 
   51% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   52% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   53% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   54% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   55% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   56% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   57% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   58% 
   59%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   60% 
   61% This file assumes that the following is defined in env_gen.pl:
   62%
   63% -- start/0     : initialization of the environment (called when loaded)
   64% -- finalize/0  : finalization of the environment (called when exiting)
   65% -- main_dir/1  : obtain the root IndiGolog directory
   66% -- report_exog_event(A, M): 
   67%                  report exogenous event A with message M to the
   68%                  environment manager
   69% -- All compatibility libraries depending on the architecture such us:
   70%    -- compat_swi/compat_ecl compatibility libraries providing:
   71%
   72% -- The following two dynamic predicates should be available:
   73%    -- listen_to(Type, Name, Channel) 
   74%            listen to Channel of Type (stream/socket) with Name
   75%    -- terminate/0
   76%            order the termination of the application
   77%
   78% -- The following should be implemented here:
   79%
   80%  -- name_dev/1              : mandatory *
   81%  -- initializeInterfaces(L) : mandatory *
   82%  -- finalizeInterfaces(L)   : mandatory *
   83%  -- execute/4               : mandatory *
   84%  -- handle_steam/1          : as needed
   85%  -- listen_to/3             : as needed
   86%
   87%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   88:- use_module(library('http/http_open')).     % Load simple http library
   89:- use_module(library('http/http_client')).   % Load expert http library
   90:- use_module(library(sgml)).		      % Load SGML library
   91
   92:- include(env_gen).      % INCLUDE THE CORE OF THE DEVICE MANAGER
   93
   94
   95%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   96%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   97% CONSTANTS TO BE USED
   98%
   99% name_dev/1 : state the name of the device manager (e.g., simulator, rcx)
  100%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  101%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  102
  103% Name of the environment: <SIMULATOR>
  104% Set name of the environment here.
  105% THIS CONSTANT IS MANDATORY, DO NOT DELETE!
  106name_dev(internet). 
  107
  108% Set verbose debug level
  109:- set_debug_level(1).  110
  111
  112%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  113% A - INITIALIZATION AND FINALIZATION OF INTERFACES
  114%     initializeInterfaces/1 and finalizeInterfaces/1
  115%
  116% HERE YOU SHOULD INITIALIZE AND FINALIZE EACH OF THE INTERFACES TO BE USED
  117%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  118
  119initializeInterfaces(_) :-
  120	printKbInstructions.
  121finalizeInterfaces(_).
  122
  123
  124% printKbInstructions: Print instructions on this environment
  125printKbInstructions :-
  126    writeln('*********************************************************'), 
  127    writeln('* NOTE: This is the INTERNET and SYSTEM environment'), 
  128    writeln('*       This environment implements actions on the Internet     '), 
  129    writeln('*       and system actions (e.g., file-system actions, '),
  130    writeln('*       processes management, etc.)'),
  131    writeln('*********************************************************'), nl.
  132
  133
  134
  135
  136%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  137% B - HANDLERS FOR EACH STREAM/SOCKET THAT IS BEING HEARD:  handle_stream/1
  138%
  139% HERE YOU SHOULD WRITE HOW TO HANDLE DATA COMMING FROM EACH OF THE
  140% INTERFACES/CHANNELS USED
  141%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  142
  143% Handle streams associated with the execution of internet/system actions.
  144handle_stream(Stream) :- 
  145             	% There is data in stream S which corresponds to action (A,N)
  146	listen_to(_, action(A, N), Stream),   
  147        report_message(system(3), ['Handling data from action ',(A,N)]),
  148	read(Stream, Data),
  149	((Data= end_of_file ; Data=finish) ->    
  150             	% Stream is EOF or requested terminination (action is over)
  151	     close(Stream),
  152	     retract(listen_to(_, action(A, N), Stream)),
  153	     report_message(system(2), ['Action ',(A, N),' has finished completely'])
  154        ;
  155		% Data is sensing information, report it using report_sensing/4
  156        Data = [sensing, Outcome] ->
  157	     report_sensing(A, N, Outcome, _),
  158	     change_action_state(A,N,_,Outcome,_)
  159	;
  160		% Data is an exog. event, report it using report_exog_event/5
  161	Data = [exog_action, Action] ->
  162             report_exog_event(Action, ['Exogenous action ',Action, ' from Web']),
  163	     change_action_state(A,N,_,_,[Action])
  164	).
  165
  166
  167
  168%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  169% C - EXECUTION MODULE: execute/4
  170%
  171% This part implements the execution capabilities of the environment
  172%
  173% execute(Action, Type, N, Sensing) : execute Action of Type and return Sensing
  174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  175
  176
  177% This part implements the execution capabilities of the environment.
  178% 
  179% Each action is executed in an independent thread which can trigger
  180% exogenous events and sensing result at any time. 
  181% 
  182% The output of each action (sensing or exog. event) is treated as a regular
  183% stream (the same as data comming from the environment manager)
  184%
  185% The tools send_sensing/1 and send_exogenous/1 will be used by each thread
  186% to report sensing and exogenous events
  187execute(Action, _, N, null) :- 
  188        report_message(action, ['Executing action: ', '*',(Action,N),'*']),
  189	  % This pipe will be used to obtain sensing and exogenous events
  190	  % generated from the action thread. Thread will write in Write stream
  191	  % Build the alias for the action thread
  192	pipe(Read,Write),
  193	term_to_atom(action(Action,N,Write), Alias),
  194	  % Throw an independent thread to perform Action. 
  195	  % Action thread should write in stream "Write"
  196	thread_create(perform(Action,Write), _, [alias(Alias), detached(true)]),
  197	  % Block until sensing outcome is read
  198	  % This is not used since sensing is reported in each thread using
  199	  % the tool send_sensing/1 below
  200%	read(Read, S), 
  201%	report_sensing(Action, N, S, _),
  202          % Register a listen_to/3 in the DB to wait for exogenous events
  203	  % and sensing coming from the executed action
  204        assert(listen_to(stream, action(Action, N), Read)).
  205
  206
  207
  208
  209
  210
  211
  212
  213
  214
  215
  216
  217
  218
  219
  220
  221
  222
  223
  224
  225
  226
  227
  228
  229
  230
  231
  232
  233
  234
  235%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  236% BELOW IS THE CODE FOR THE ACTUAL IMPLEMENTATION OF THE ENVIRONMENT
  237%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  238
  239
  240%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  241%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  242%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  243%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  244% 0 - TOOLS FOR SENDING SENSING OUTCOMES AND EXOGENOUS EVENTS
  245%     FROM EACH ACTION THREAD
  246%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  247%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  248%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  249%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  250% contains the stream where the thread must write its sensing and exog actions
  251% actionStream/1 is LOCAL to each thread action so there is no ambiguity
  252:- thread_local actionStream/1. 
  253
  254
  255% This is the tool called to execute Prolog tool Command which should write
  256% its output (sensing/exog events) to stream Stream
  257% Command is a list-char codifying the command to be executed
  258perform(Command, Stream) :- 
  259	assert(actionStream(Stream)),  % Register the action stream
  260        call(Command),
  261	fail.
  262perform(_, Stream) :- 
  263	retract(actionStream(Stream)), % de-register the action stream and close it
  264	close(Stream).
  265
  266% Write the sensing result to the environment via the set-up communication
  267send_sensing(Data)   :- 
  268	send([sensing, Data]).
  269
  270% Write the exogenous event to the environment via the set-up communication
  271send_exogenous(Exog) :- 
  272	send([exog_action, Exog]).
  273	
  274% Sends any data by writing it as a term, writes a dot, nl, and flush.
  275% This is used by send_sensing/1 and send_exogenous/1
  276send(Data) :- 
  277	actionStream(Stream),	% Get the stream associated with the action
  278        write_term(Stream, Data, [quoted(true)]), 
  279        write_term(Stream, '.',[]),
  280        nl(Stream), 
  281	flush_output(Stream).
  282	
  283
  284
  285
  286
  287
  288
  289%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  290%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  291% 1 - INTERFACE IMPLEMENTATION
  292%     These are actual prolog predicates that provide different internet
  293%     a and system functionalities
  294%     This predicates will actually be executed in independent threads
  295%     and they should report sensing and exog. events using the tools
  296%     send_sensing/1 and send_exogenous/1 to write in the right stream
  297%
  298%     These predicates are the ones seen and known by the user who uses the
  299%     internet/system environment %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  300%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  301
  302
  303%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  304% check_string_after(+URL, +S, +PAfter) 
  305%     sense whether there is a string S in in address A after pos. PAfter
  306% Sensing Outcome : always succeeds with 1
  307% Exogenous action: int_bool_after/4
  308%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  309check_string_after(URL, S, PAfter) :- 
  310        send_sensing(1),
  311        (find_pos_web(URL, S, PAfter, Pos) -> 
  312             (Pos=(-1) ->
  313                  send_exogenous(int_bool_after(URL, S, PAfter, false))
  314             ; 
  315                  send_exogenous(int_bool_after(URL, S, PAfter, true))
  316             )
  317        ; 
  318             send_exogenous(int_bool_after(URL, S, PAfter, failed))).
  319
  320
  321%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  322% check_pos_string(+URL, +S, +PAfter) 
  323%     sense the position in address A of string S after position PAfter
  324% Sensing Outcome : always succeeds with 1
  325% Exogenous action: int_pos/4
  326%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  327check_pos_string(URL, S, PAfter) :- 
  328        send_sensing(1),
  329        (find_pos_web(URL, S, PAfter, Pos) ->
  330             send_exogenous(int_pos(URL, S, PAfter, Pos))
  331        ;
  332             send_exogenous(int_pos(URL, S, PAfter, failed))).
  333
  334%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  335% read_string_between(+URL, +D1, +D2, +PAfter): 
  336%      sense the string between D1 and D2 in address A after position PAfter
  337% Sensing Outcome : always succeeds with 1
  338% Exogenous action: int_string_between/5
  339%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  340read_string_between(URL, Del1, Del2, PAfter) :- 
  341        send_sensing(1),
  342        (retrive_string_delim_web(URL, Del1, Del2, String, PAfter, _) ->
  343             post_process(String,S2),    % Remove initial/final padding
  344             send_exogenous(int_string_between(URL, Del1, Del2, PAfter, S2))
  345        ;
  346             send_exogenous(int_string_between(URL, Del1, Del2, PAfter, failed))).
  347
  348
  349%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  350% read_html_field(+URL, +FieldName, +Cont, +PAfter): 
  351%      sense the next string value of field FieldName after position PAfter
  352%      that includes strings SCont
  353%      By a field we mean a string of the form: ... FieldName="xxxxxx" .....
  354%          where xxxxxx is the string sensed that contains substring Cont
  355% Sensing Outcome : always succeeds with 1
  356% Exogenous action: int_html_field/6
  357%                   returns xxxxx and its starting position
  358%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  359read_html_field(URL, FieldName, Cont, PAfter) :- 
  360        send_sensing(1),
  361        concat_string([FieldName,'=\"'], FieldTag),
  362        retrive_string_delim_web(URL, [null, FieldTag], ['\"', null], 
  363                                 String, PAfter, Pos),
  364        post_process(String, S2),    % Remove initial/final padding
  365        any_to_string(Cont, SCont),
  366        once(substring(String, SCont, _)), !, % Done, good string found
  367        send_exogenous(int_html_field(URL, FieldName, Cont, PAfter, S2, Pos)).
  368
  369read_html_field(URL, FieldName, Cont, P) :- 
  370        send_exogenous(int_html_field(URL, FieldName, Cont, P, failed, failed)).
  371
  372
  373	
  374	
  375%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  376% sense_nth_link(+URL, +N)
  377%      senses the nth link in the URL
  378%
  379% Sensing Outcome : atom "none" or term  "link(URL,Name)"
  380% Exogenous action: nothing
  381%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  382sense_nth_link(URL, N) :- 
  383	get_nth_link(URL, N, (Link,Name)) ->
  384        	send_sensing(link(Link,Name)) 
  385	;
  386		sense_sensing(none).
  387
  388%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  389% sense_no_links(+URL)
  390%      senses the number of links in URL
  391%
  392% Sensing Outcome : number
  393% Exogenous action: nothing
  394%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  395sense_no_links(URL) :- 
  396	get_no_links(URL, N) ->
  397        	send_sensing(N) 
  398	;
  399		sense_sensing(failed).
  400        
  401	
  402        
  403%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  404% read_string_length(+URL, +D, +L, +PAfter): 
  405%      sense the string in address A that starts with string D for a length
  406%      of L and after position PAfter
  407% Sensing Outcome : always succeed with 1
  408% Exogenous action: int_string_length/5
  409%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  410read_string_length(URL, D, L, PAfter) :- 
  411        send_sensing(1),
  412        (retrive_string_poslen_web(URL, D, L, PAfter, T) ->
  413             post_process(T,T1),
  414             send_exogenous(int_string_length(URL, D, L, PAfter,T1))
  415        ;
  416             send_exogenous(int_string_length(URL, D, L, PAfter, failed))).
  417
  418
  419%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  420% download(+URL, +File) 
  421%        download address URL to file File  sense the process id number
  422% Sensing Outcome : always succeeds with 1
  423% Exogenous action: int_bool_download
  424%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  425download(URL, File) :- 
  426        send_sensing(1),
  427        (download(real, URL, File) -> 
  428             send_exogenous(int_bool_download(URL, File, ok)) 
  429        ;
  430             send_exogenous(int_bool_download(URL, File, failed))). 
  431
  432% Real implementation: downloads the Address (atom) to FileName (atom)
  433download(real, URL, FileName):- 
  434        exists_web_file(URL),        
  435	open(FileName, write, StreamFile, [type(binary)]),
  436	http_open(URL, StreamURL, [], null),
  437	copy_stream_data(StreamURL, StreamFile),
  438	close(StreamFile),
  439	close(StreamURL).
  440
  441% Version for debugging: this version creates the corresponding file but with
  442% an empty content and it waits 10 second to "simulate" the downloading
  443download(debug, URL, FileName):- 
  444        exists_web_file(URL),        
  445        concat_atom(['echo ', URL, ' > ', '\'', FileName, '\''], Com),
  446        call_to_exec(unix, Com, Command2), % Select right command for exec
  447        exec(Command2,[]).
  448
  449
  450
  451%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  452% check_web_file(+URL)
  453%      senses whether WebFile exists
  454% Sensing Outcome : always succeds with 1
  455% Exogenous action: int_bool_urlexists/2
  456%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  457check_web_file(URL) :- 
  458        send_sensing(1),
  459        (exists_web_file(URL) ->  
  460             send_exogenous(int_bool_urlexists(URL, true)) 
  461        ;
  462             send_exogenous(int_bool_urlexists(URL, false))).
  463
  464exists_web_file(URL) :- 
  465	http_open(URL, S, [], null), 
  466	close(S).
  467
  468
  469
  470%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  471% ACTIONS FOR THE MANAGEMENT OF (NAMED) WEB-BROWSERS
  472%
  473% All this action return 1 as sensing unless they fail to execute.
  474%
  475% -- browser_new(+ID) 
  476% -- browser_close(+ID)
  477% -- browser_refresh(+ID)
  478% -- browser_open(+ID, +URL)
  479% -- browser_get(+ID, -CS, -CT)
  480%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  481:- dynamic browser/4.	% browser(Id, URL, ContentString, ContentTerm)
  482
  483% Open a new browser with name ID. 
  484% Sensing Outcomes could be: 
  485%	1 : action executed successfuly
  486%	failed : browser ID alredy exists
  487browser_new(ID) :-                      
  488	\+ browser(ID, _, _, _),
  489	any_to_string('',ES),
  490	assert(browser(ID, _, ES, '')), !,
  491	send_sensing(1).
  492browser_new(_) :-                      
  493	send_sensing(failed).
  494
  495% Closes browser ID. 
  496% Sensing Outcomes could be: 
  497%	1 : action executed successfuly
  498%	failed : browser ID does not exist
  499browser_close(ID) :-
  500	retract(browser(ID, _, _, _)) -> send_sensing(1) ; send_sensing(failed).
  501
  502% Refresh the content of browser ID.
  503% Sensing Outcomes could be: 
  504%	failed : browser ID does not exist
  505browser_refresh(ID) :-                 
  506	browser(ID, URL, _, _), !,
  507	browser_open(ID, URL).
  508browser_refresh(_) :-                 
  509	send_sensing(failed).
  510
  511% Open web page URL on browser ID. 
  512% Sensing Outcomes could be: 
  513%	1 : web page opened successfuly
  514%	0 : no page at URL
  515%	failed : browser ID does not exist
  516browser_open(ID, URL) :-               
  517	get_page(URL, string, CS),  		% Get page as string CS
  518	get_page(URL, term, CT),		% Get page as term CT
  519	retract(browser(ID, _, _, _)), !,
  520	assert(browser(ID, URL, CS, CT)), 	% Assert the page
  521	send_sensing(1).
  522browser_open(ID, URL) :-              
  523	retract(browser(ID, _, _, _)), 
  524	any_to_string('',ES),
  525	assert(browser(ID, URL, ES, '')),  !,	% Set the browser to empty
  526	send_sensing(0).
  527browser_open(_, _) :-              		% Failed if browser ID does not exists
  528	send_sensing(failed).
  529
  530% Refresh the content of browser ID.
  531% Sensing Outcomes could be: 
  532%	1 : action executed successfuly
  533%	failed : browser ID does not exist
  534browser_url(ID) :-                 
  535	broswer(ID, URL, _, _), !,
  536	send_sensing(URL).
  537browser_url(_) :-                 
  538	send_sensing(failed).
  539
  540	
  541% This action is not used from programs, but it just used inside this file
  542% Obtain the (current) content of browser ID
  543%browser_get(ID, C) :-                  
  544%	browser(ID, _, C) -> send_sensing(1) ; send_sensing(failed).
  545browser_get(ID, CS, CT) :-                  
  546	browser(ID, _, CS, CT).
  547
  548
  549
  550%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  551% sense_proc_term(+Pid)
  552%       senses whether process Pid is finished
  553% Sensing Outcome: true/false (true= process did terminate)
  554%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  555sense_proc_term(Pid) :- 
  556        proc_term(Pid) -> send_sensing(true) ;
  557                          send_sensing(false).
  558
  559
  560%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  561% sense_proc_exists(+Pid) 
  562%       sesnes whether process Pid exists
  563% Sensing Outcome: true/false (true= process did terminate)
  564%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  565sense_proc_exists(Pid) :- 
  566        proc_exists(Pid) -> send_sensing(true) ;
  567                            send_sensing(false).
  568
  569
  570%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  571% kill_proc(+Pid) 
  572%       kills process Pid 
  573% Sensing Outcome: true/false (true= process was killed successfully)
  574%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  575kill_proc(Pid) :- 
  576        proc_kill(Pid) -> send_sensing(true) ;
  577                          send_sensing(false).
  578
  579%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  580% wait_proc(+Pid) 
  581%       waits for process Pid to finish
  582% Sensing Outcome : always succeds with 1
  583% Exogenous action: int_proc_waited/2
  584%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  585wait_proc(Pid) :- 
  586        send_sensing(1),
  587        (wait_proc(Pid, Status) ->  
  588             send_exogenous(int_proc_waited(Pid, Status)) 
  589        ;
  590             send_exogenous(int_proc_waited(Pid, failed))
  591        ).
  592
  593
  594%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  595% sense_file_exists(+File) 
  596%        senses whether file File exists
  597% Sensing Outcome: true/false (true= file does exist)
  598%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  599sense_file_exists(File) :- 
  600        file_exists(File) -> send_sensing(true) ;
  601                             send_sensing(false).
  602
  603
  604%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  605% say(+Phrase, +Lan) 
  606%        says Phrase in Lan(guage) via speech (requires festival or similar)
  607% Sensing Outcome: always return 1
  608%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  609say(List, Lan) :- is_list(List), !, 
  610        concat_atom(List, Phrase), say(Phrase, Lan).
  611say(Phrase, english) :- 
  612        concat_atom(['echo \'', Phrase, '\' | festival --tts'], Command),
  613        call_to_exec(unix, Command, Command2), % Select right command for exec
  614        exec(Command2, []),
  615        send_sensing(1).
  616say(Phrase, Lan) :- Lan\=english,
  617        concat_atom(['echo \'', Phrase, '\' | festival --tts --language ',Lan], 
  618                    Command),
  619        call_to_exec(unix, Command, Command2), % Select right command for exec
  620        exec(Command2, []),
  621        send_sensing(1).
  622
  623
  624
  625%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  626%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  627% 3 - LOW-LEVEL PROCEDURES FOR WORKING ON THE WEB
  628%     These predicates are never seen or known by the user who uses the
  629%     internet/system environment
  630%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  631%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  632
  633% IMPORTANT TOOL TO OBTAIN THE WEB-PAGE SOURCE FROM A URL
  634% get_page(URL, Type, C): C is the HTML with Type string/term of link/browser URL
  635%
  636get_page(URL, string, CS)             :-  % URL stands for a current open browser
  637	browser_get(URL, CS, _), !.
  638get_page(URL, term, CT)        	      :-  % URL stands for a current open browser
  639	browser_get(URL, _, CT), !.
  640
  641get_page(URL, string, Reply)  :- !,
  642	http_get(URL, ReplyAtom, [], null), !,  % http_get/4 generalizes http_get/3
  643	any_to_string(ReplyAtom, Reply).
  644get_page(URL, term, Reply) :- !,
  645	http_open(URL, Stream, [], null), % http_open/4 generalizes http_open/3
  646	dtd(html, DTD), 
  647	load_structure(stream(Stream),Reply,[dtd(DTD),dialect(sgml),space(remove)]), 
  648	close(Stream), !.
  649
  650	
  651% Generalizes http_open/3 to account for errors and accept strings
  652http_open(URL, Stream, Options, Error) :-
  653	concat_atom([URL], URLA), 
  654	catch(http_open(URLA, Stream, Options), error(E1, _), true),
  655	(\+var(E1), E1=existence_error(_, _) -> 
  656		Error=error(file)    % File does not exists
  657	;
  658	 \+ var(E1), E1=socket_error(_) ->
  659	        Error=error(host)    % Host cannot be found
  660	;
  661	        Error=null           % No error
  662	).
  663
  664
  665% Generalizes http_get/3 to account for errors and accept strings
  666http_get(URL, Reply, Options, Error) :-
  667	concat_atom([URL], URLA), 
  668	catch(http_get(URLA, Reply, Options), error(E1, _), true),
  669	(\+var(E1), E1=existence_error(_, _) -> 
  670		Error=error(file)    % File does not exists
  671	;
  672	 \+ var(E1), E1=socket_error(_) ->
  673	        Error=error(host)    % Host cannot be found
  674	;
  675	        Error=null           % No error
  676	).
  677	
  678
  679
  680	
  681	
  682	
  683	
  684	
  685	
  686		
  687	
  688		
  689% Pos is the position of substring T in address A after position PAfter
  690find_pos_web(URL, T, PAfter, Pos) :- 
  691        get_page(URL, string, SA), 
  692        any_to_string(T, ST),
  693        (substring(SA, P2, _, ST), P2 > PAfter -> Pos=P2 ; Pos=(-1)).
  694
  695% URL = ......... Del11 ***** Del12 SResult Del12 ****** Del22
  696% Retrives SResult wrt two flexible Delimiters and after a Position
  697retrive_string_delim_web(URL, Del1, Del2, SResult, PAfter, Pos):-
  698        get_page(URL, string, S),
  699        extract_substring(S, Del1, Del2, SResult, PAfter, Pos).
  700
  701
  702% retrive_string_poslen_web/5: Retrive string with length after position
  703% SResult is a substring in the web page URL that is after
  704% string Del1 and with length Len
  705retrive_string_poslen_web(URL, Del1, Len, Pos, SResult) :- 
  706        get_page(URL, string, SA), 
  707        any_to_string(Del1, SDel1),
  708        substring(SA, P1, _, SDel1), P1>Pos, !,
  709        substring(SA, P1, Len, SResult).
  710
  711% retrive_bet_apos/5: Retrive Between Strings After a Position
  712% SResult is a substring in the web page with address URL that is between
  713% strings Del1 and Del2 and after position P
  714retrive_bet_apos(URL, Del1, Del2, P, SResult) :- 
  715        get_page(URL, string, SA), 
  716        any_to_string(Del1, SDel1),
  717        any_to_string(Del2, SDel2),
  718        substring(SA, P1, _, SDel1), P1 > P,
  719        substring(SA, P2, _, SDel2), P2 > P1, !,
  720        string_length(SDel1, L1),
  721        L is P2-P1-1-L1,
  722        P11 is P1+L1,
  723        substring(SA, P11, L, SResult).
  724
  725
  726% Post processing of a string: remove spaces and line breaks at the beginning
  727% 	                       and at the end of the string
  728post_process(T, T1):- 
  729        split_string(T, ``, ` `, [T2]),
  730        string_replace(T2,'\n','',T1).    % Remove end_of_line
  731
  732
  733	
  734	
  735	
  736	
  737	
  738	
  739	
  740	
  741	
  742	
  743	
  744	
  745	
  746	
  747	
  748	
  749	
  750	
  751	
  752	
  753	
  754get_nth_link(URL, N, Link) :- 
  755	get_page(URL, term, Content),
  756	extract_nth_link(Content, N, Link).
  757	
  758get_no_links(URL, N) :-
  759	get_page(URL, term, Content),
  760	extract_all_links(Content, Links),
  761	length(Links, N).
  762	
  763% extract_nth_link(Content, N, Link) :
  764%	given a web-page Content, extract the nth link
  765extract_nth_link(Content, N, Link) :-
  766	extract_all_links(Content, LLinks),
  767	nth1(N, LLinks, Link).
  768
  769% Trivial case when the content is just an atom with a link (e.g., .rmm files)
  770extract_all_links([Link], [(Link,'')]) :- atom(Link), !.
  771% The general case when the Content is complicated HTML source
  772extract_all_links(Content, LLinks) :-
  773	extract_all_links2(Content, LLinks2), !,
  774	flatten(LLinks2, LLinks).
  775
  776% extract_all_links(Content, LLink) :
  777%	given a web-page Content, extract all the links into list LLink
  778extract_all_links2(element(a, LAtrib, LContent), [(Link, Name)]) :- !,
  779	member(href=Link, LAtrib),
  780	extract_name(LContent, Name).
  781
  782extract_all_links2(element(_, _, LContent), LLinks) :- !,
  783	maplist(extract_all_links2, LContent, LLinks).
  784	
  785extract_all_links2(LContent, LLinks) :-
  786	is_list(LContent), !,
  787	maplist(extract_all_links2, LContent, LLinks).
  788	
  789extract_all_links2(_, []).
  790	
  791
  792% extract_name(LContent, Name) :
  793% 	given an element/3 term in LContent describing the name of a link, 
  794%	it extracts just the text in Name
  795extract_name(LContent, NameClean) :-
  796		% First just get the Name2
  797	extract_name2(LContent,Name2),
  798		% Clean up spaces in Name
  799	split_atom(Name2,' ','',L1),
  800	delete(L1,'',L2),
  801	join_atom(L2,' ',NameClean).	
  802	
  803% This just extracts the name but it may contain redundant spaces
  804extract_name2(element(_,_,R), Name) :- 
  805	extract_name2(R, Name).
  806extract_name2([A|LR], Name) :- 
  807	extract_name2(A, NameA),
  808	extract_name2(LR, NameR),
  809	concat_atom([NameA, ' ', NameR], Name).
  810extract_name2(LContent, LContent) :- LContent\=[], atom(LContent), !.
  811extract_name2(_,'').
  812	
  813	
  814%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  815% EOF:  Env/env_int_swi.pl
  816%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%