1% :-module(xlisting_web,[ensure_sigma/0,search4term/0]).
    2%:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )). 
    3:- module(xlisting_web_server,
    4          [ register_logicmoo_browser/0,
    5            swish_reply_config_root/1
    6          ]).    7
    8:- set_module(class(library)).

xlisting_web_server

% Provides /logicmoo runtime preds browsing % % % Logicmoo Project PrologMUD: A MUD server written in Prolog % Maintainer: Douglas Miles % Dec 13, 2035 % */

   19:- public(swish_reply_config_root/1).   20:- export(swish_reply_config_root/1).   21swish_reply_config_root(Request):-
   22  (current_predicate(swish_config:swish_reply_config/1)
   23   -> call(call,swish_config:swish_reply_config(Request)); 
   24      swish_reply_config_root).
   25
   26swish_reply_config_root:-
   27  current_predicate(swish_config:json_config/2),!,
   28  call(call,swish_config:
   29  (json_config(JSON, []),
   30	 reply_json(JSON))).
   31swish_reply_config_root:- 
   32  user:file_search_path(xlisting_web,Here),
   33  atom_concat(Here,'/swish_config.json',ConfigFile),
   34  exists_file(ConfigFile),!,
   35  format('Content-type: application/json; charset=UTF-8~n~n'),
   36  read_file_to_string(ConfigFile,Config,[]),
   37  write(current_output, Config).
   38swish_reply_config_root:- 
   39  http_json:reply_json(_{}).
   40
   41
   42
   43
   44
   45:- http_handler('/swish_config.json', swish_reply_config_root,[]).   46
   47/*
   48
   49:- dynamic user:library_directory/1.
   50:- multifile user:library_directory/1.
   51hide_xpce_library_directory:- fail,
   52  user:library_directory(X),
   53  atom(X),
   54  atom_concat(_,'xpce/prolog/lib/',X),!,
   55  retract((user:library_directory(X))),
   56  assert((user:library_directory(X):- \+ current_prolog_flag(hide_xpce_library_directory,true))).
   57hide_xpce_library_directory.
   58
   59%:- hide_xpce_library_directory.
   60*/
   61%:- set_prolog_flag(hide_xpce_library_directory,true).
   62
   63
   64/*
   65:- system:use_module(library(http/thread_httpd)).
   66:- system:use_module(thread_httpd:library(http/http_dispatch)).
   67:- system:use_module(library(http/http_dispatch)).
   68
   69*/
   70%:- ensure_loaded(library(logicmoo_swilib)).
   71:- system:use_module(swi(library/http/html_head)).   72
   73:- system:use_module(library(http/http_path)).   74:- system:use_module(library(http/http_log)).   75:- system:use_module(library(http/http_client)).   76:- system:use_module(library(http/http_server_files)).   77:- system:use_module(library(http/http_parameters)).   78
   79:- system:use_module(library(uri)).   80:- system:use_module(library(http/http_openid)).   81:- system:use_module(library(http/http_host)).   82:- use_module(library(http/html_write)).   83:- system:use_module(library(http/http_error)).   84
   85
   86:- system:use_module(library(predicate_streams)).   87%:- system:use_module(library(logicmoo/with_no_x)).
   88:- system:use_module(library(logicmoo/each_call)).   89%:- use_module(library(logicmoo/butterfly_console)).
   90
   91
   92:- if(exists_source(cliopatria('applications/help/load'))).   93:- system:use_module(cliopatria('applications/help/load')).   94% Load ClioPatria itself.  Better keep this line.
   95:- system:use_module(cliopatria(cliopatria)).   96:- else.   97cp_menu:cp_menu(X,X).
   98:- endif.   99
  100
  101:- thread_initialization(nb_setval(pldoc_options,[ prefer(manual) ])).
 ensure_sigma(?ARG1) is det
Ensure Webserver.
  108ensure_sigma(Port) :- format(atom(A),'httpd@~w_1',[Port]),thread_property(_,alias(A)),!.
  109ensure_sigma(Port) :- on_x_debug(catch((http_server(http_dispatch,[ port(Port), workers(16) ])),E,wdmsg(E))).
 ensure_sigma is det
Ensure Webserver.
  116ensure_sigma:- ensure_sigma(3020).
  117
  118
  119:- if( \+ exists_source(library(logicmoo_utils_all))).  120:- dynamic user:file_search_path/2.  121:- multifile user:file_search_path/2.  122:- prolog_load_context(directory,Dir),
  123   DirFor = mpred_online,
  124   (( \+ user:file_search_path(DirFor,Dir)) ->asserta(user:file_search_path(DirFor,Dir));true),
  125   absolute_file_name('../../',Y,[relative_to(Dir),file_type(directory)]),
  126   (( \+ user:file_search_path(pack,Y)) ->asserta(user:file_search_path(pack,Y));true).  127:- initialization(attach_packs,now).  128% [Required] Load the Logicmoo Library Utils
  129:- endif.  130 
  131
  132
  133
  134handler_logicmoo_cyclone2a(X):- xlisting_web:handler_logicmoo_cyclone2(X).
  135handler_logicmoo_cyclone3a(X):- xlisting_web:handler_logicmoo_cyclone3(X).
 user:file_search_path(?ARG1, ?ARG2) is det
Hook To [file_search_path/2] For Module Mpred_www. File Search Path.
  142:- prolog_load_context(directory,Here),atom_concat(Here,'/pixmaps',NewDir),asserta_new((user:file_search_path(pixmapx,NewDir))).  143:- prolog_load_context(directory,Here),asserta_new((user:file_search_path(xlisting_web,Here))).  144%user:file_search_path(pixmapx, logicmoo('mpred_online/pixmapx')).
  145
  146%user:file_search_path(pixmapx,NewDir):- user:file_search_path(xlisting_web,Here), atom_concat(Here,'/pixmaps',NewDir).
  147
  148register_logicmoo_browser:- 
  149  %http_handler('/lm_xref/', handler_logicmoo_cyclone0, [prefix]), % chunked
  150  %http_handler('/lm_xref_nc/', handler_logicmoo_cyclone1, [prefix,chunked]),
  151  http_handler(('/swish/lm_xref'), handler_logicmoo_cyclone2a, [prefix,priority(50)]), % chunked
  152  call(call,http_handler(('/swish/lm_xref/swish_config.json'), swish_reply_config_root,[priority(200)])),
  153  http_handler(('/swish/lm_xref/slowcode'), handler_logicmoo_slowcode, [prefix,chunked,priority(100)]), % chunked
  154  http_handler(('/swish/lm_xref/pixmapx'), http_server_files:serve_files_in_directory(pixmapx), [prefix,priority(100)]),
  155  http_handler(('/swish/lm_xref_nc'), handler_logicmoo_cyclone3a, [prefix,chunked]),
  156
  157  nop(doc_collect(true)).
  158
  159:- fixup_module_exports_into(baseKB).  160:- fixup_module_exports_into(system).  161
  162:- register_logicmoo_browser.  163
  164
  165
  166% :- thread_property(_,alias('http@3020'))->true; http_server(http_dispatch, [port(3020)]).