1:- use_module(library(http/thread_httpd)).    2:- use_module(library(http/http_dispatch)).    3:- use_module(library(http/http_error)).    4:- use_module(library(debug)).    5:- use_module(library(http/html_write)).    6:- use_module(library(http/http_parameters)).    7:- use_module(library(url)).    8:- use_module(library(sgml)).    9
   10% including this turns on sessions
   11:- use_module(library(http/http_session)).   12
   13:- use_module(interpret).   14
   15% TODO it's long since time you broke this into two files
   16% :- use_module(library(porter_stem)).
   17
   18% The predicate server(?Port) starts the server. It simply creates a
   19% number of Prolog threads and then returns to the toplevel, so you can
   20% (re-)load code, debug, etc.
   21server(Port) :-
   22        http_server(http_dispatch, [port(Port)]).
   23
   24% define the root of our web system
   25web_root(X) :- X = '.'. % '/home/annie/prologclass/fromwindows'.
   26% convert path names and URIs for files
   27web_path(Relative,Absolute) :- web_root(Root), atom_concat(Root, Relative, Absolute).
   28%  handle static pages.
   29/* See
   30
   31http://old.nabble.com/How-to-load-an-image-into-a-web-page-with-swi-prolog-td14363488.html
   32Supposedly this handles everything in ./pages/ but it makes the compiler
   33freak
   34*/
   35:- http_handler( '/pages' , serve_page, [prefix]).   36
   37serve_page(Request) :-
   38        memberchk(path(Path), Request),
   39	web_path(Path, FilePath),
   40	http_reply_file(FilePath, [], Request).
   41
   42% Declare a handler, binding an HTTP path to a predicate.
   43% The notation root(hello_world) uses an alias-mechanism similar to
   44% absolute_file_name/3 and allows for moving parts of the server locations
   45% easily. See http_absolute_location/3. We could also have used '/hello_world'.
   46:- http_handler(root(hello_world), say_hi, []).   47% They say we can use an absolute URI so lets
   48% try it
   49:- http_handler('/tacos/of/god' , say_tacos, []).   50
   51% handler for the pseudo AIML language
   52:- http_handler('/aiml' , aiml_page , []).   53
   54% handle images
   55:- http_handler('/screenshot.png',
   56   http_reply_file('screenshot.png', []), []).   57
   58
   59/* The implementation of /hello_world. The single argument provides the request
   60details, which we ignore for now. Our task is to write a CGI-Document:
   61a number of name: value -pair lines, followed by two newlines, followed
   62by the document content, The only obligatory header line is the
   63Content-type: <mime-type> header.
   64Printing can be done using any Prolog printing predicate, but the
   65format-family is the most useful. See format/2.   */
   66
   67say_hi(_Request) :-
   68        reply_html_page(title('Hello World'),
   69                        [ h1('Hello World'),
   70                          p(['This example demonstrates generating HTML ',
   71                             'messages from Prolog'
   72                            ]),
   73			  img([width(32),height(32),src('screenshot.png')])
   74                        ]).
   75
   76say_tacos(_Request) :-
   77	debug(tacos , 'entered say_tacos', []),
   78	format('Content-type: text/html~n~n'),
   79	format('<html><body><h1>Tacos of God</h1></body></html').
   80
   81aiml_page(Request) :-
   82	(http_session_data(last_utterance(Last_Utterance));
   83	    Last_Utterance = '') ,
   84	(http_session_data(that(That)); That=[star(0)]),
   85	(http_session_data(topic(Topic)); Topic=[star(0)]),
   86	http_parameters(Request,
   87			[intext(Intext , [ default('') ])]),
   88	(http_session_retractall(last_utterance(_)) ; true),
   89	http_session_assert(last_utterance(Intext)),
   90	% TODO - need to use That, Topic, and Intext to find reply
   91	% from chatterbot
   92	chatterbot(memory(That, Topic), Intext, Response, NewTopic),
   93	!,  % cut in case something below fails - if there's an http problem
   94	% I don't want to retry the bot
   95	http_session_retractall(that(_)),
   96	http_session_assert(that(Response)),
   97	http_session_retractall(topic(_)),
   98	http_session_assert(topic(NewTopic)),
   99	reply_html_page(title('chatterbot'),
  100			[ h1('Talk with the chatterbot'),
  101			  p(['I\'m a chatterbot, you can talk with me']),
  102			  p(['You said ', Last_Utterance]),
  103			  p(['and your last message was ', Intext]),
  104			  p(['and my response is ', Response]),
  105			  form([action=