Mercurial > hg > dml-home
view .swiplrc @ 100:a4cd935561d4 dml-dockerised tip
small updates and version pin for cliopatria
author | wolffd <wolffd.mail@googlemail.com> |
---|---|
date | Fri, 29 Jun 2018 17:48:41 +0100 |
parents | cecf0cf46db3 |
children |
line wrap: on
line source
:- op(200,fy,@). % Shouldn't really need this... colour_terminal :- stream_property(user_output, tty(true)), getenv('TERM',Term), member(Term,[xterm,screen,'screen-256color','xterm-256color','xterm-color']). :- dynamic http_proxy/3. get_http_proxy(Host,Port,basic(User,Pwd)) :- getenv(use_proxy,yes), getenv(http_proxy,Proxy), % proxy looks like http://User:Password@Host:Port atom_concat('http://',Proxy1,Proxy), % strip off protocol split_atom(Proxy1,Auth,'@',HostPort), split_atom(Auth,User,':',Pwd), split_atom(HostPort,Host,':',APort), atom_number(APort,Port). split_atom(Atom,Pre,Mid,Post) :- sub_atom(Atom,LPre,_,LPost,Mid), sub_atom(Atom,0,LPre,_,Pre), sub_atom(Atom,_,LPost,0,Post). internal_host(localhost). internal_host(Proxy) :- http_proxy(Proxy,_,_). %internal_host(Host) :- sub_atom(Host,_,_,0,'bl.uk'). % New scheme for proxy handling (>=7.3.0) % :- multifile socket:proxy_for_url/3. % socket:proxy_for_url(_, Target, proxy(Host,Port)) :- % http_proxy(Host,Port,_), % \+internal_host(Target), % debug(proxy,'Using socketproxy ~w:~w for ~w',[Host,Port,Target]). % Old scheme, still required to provide authorisation details :- multifile http:open_options/2. http:open_options(Parts,[proxy(Host:Port),proxy_authorization(Auth)]) :- http_proxy(Host,Port,Auth), option(host(Target),Parts), \+internal_host(Target), debug(proxy,'Using HTTP proxy ~w:~w for ~w',[Host,Port,Target]). :- (colour_terminal -> load_files(library(ansi_term), [silent(true)]); true), set_prolog_flag(prompt_alternatives_on, determinism), set_prolog_flag(editor, '$EDITOR'), load_files(library(url), [silent(true)]), load_files(library(http/http_ssl_plugin), [silent(true)]), retractall(http_proxy(_,_,_)), ( get_http_proxy(Host,Port,Auth) -> assert(http_proxy(Host,Port,Auth)) ; true ).