1:-module(pac4pl,
    2         [flush_pac_cache/0,
    3          retrieve_pac_file/2,
    4          enumerate_network_interfaces/1,
    5          pac/4]).    6
    7:-use_foreign_library(foreign(pac4pl)).    8:-use_module(library(dhcp)).    9:-use_module(library(dcg/basics)).   10:-use_module(library(http/http_open)).

libPAC (Proxy-Auto-Config) interface for Prolog

author
- M Lilley (thetrime@gmail.com) */
   18retrieve_pac_file(Source, PacData):-
   19        ( Source = file(Filename)->
   20            setup_call_cleanup(open(Filename, read, Stream),
   21                               read_string(Stream, [], [], _, PacData),
   22                               close(Stream))
   23        ; Source = string(PacData)->
   24            true
   25        ; Source = detect ->
   26            debug(proxy, 'Trying to get WPAD info', []),
   27            with_mutex(wpad_mutex, detect_wpad(PacData)),
   28            debug(proxy, 'Successfully retrieved WPAD info!', [])      
   29        ; otherwise->
   30            throw(type_error(pac_source, Source))
   31        ).
   32
   33parse_pac_result([Method|Methods])-->
   34        blanks,
   35        pac_method(Method),
   36        blanks,
   37        ( ";" ->
   38            parse_pac_result(Methods)
   39        ; {Methods = []}
   40        ).
   41
   42pac_method(direct)-->
   43        "DIRECT", !.
   44
   45pac_method(proxy(Host, Port))-->
   46        "PROXY ", hostname(Host), ":", integer(Port), !.
   47
   48pac_method(socks(Host, Port))-->
   49        "SOCKS ", hostname(Host), ":", integer(Port), !.
   50
   51hostname(Hostname)-->
   52        string_without(":", HostnameString),
   53        {atom_string(Hostname, HostnameString)}.
   54
   55
   56pac(Source, RequestURL, RequestHostname, ConnectionMethods):-
   57        ( Source = file(Filename)->
   58            setup_call_cleanup(open(Filename, read, Stream),
   59                               read_string(Stream, [], [], _, PacData),
   60                               close(Stream))
   61        ; Source = string(PacData)->
   62            true
   63        ; Source = detect ->
   64            debug(proxy, 'Trying to get WPAD info', []),
   65            with_mutex(wpad_mutex, detect_wpad(PacData)),
   66            debug(proxy, 'Successfully retrieved WPAD info!', [])      
   67        ; otherwise->
   68            throw(type_error(pac_source, Source))
   69        ),
   70        ( c_pac(PacData, RequestURL, RequestHostname, PacResult)->
   71            string_codes(PacResult, PacResultCodes),
   72            parse_pac_result(ConnectionMethods, PacResultCodes, [])
   73        ; otherwise->
   74            ConnectionMethods = []
   75        ).
   76
   77:-dynamic(cached_wpad/2).
 flush_pac_cache
Empties the PAC cache of any entries. The next lookup will trigger a re-download of the PAC file.
   82flush_pac_cache:-
   83        retractall(cached_wpad(_, _)).
   84
   85detect_wpad(Atom):-
   86        cached_wpad(Atom, Expiry),
   87        get_time(CurrentTime),
   88        CurrentTime < Expiry,
   89        debug(proxy, 'WPAD was detected within expiry time. Using cached version', []),
   90        !.
   91
   92detect_wpad(PacData):-
   93        debug(proxy, 'No valid cached WPAD information is available. Asking the system...', []),
   94        system_wpad_url(URL),
   95        catch(setup_call_cleanup(http_open(URL, Stream, [bypass_proxy(true), timeout(10)]),
   96                                 read_string(Stream, [], [], _, PacData),
   97                                 close(Stream)),
   98              Exception,
   99              ( debug(proxy, 'DHCP returned ~w for the PAC URL, but when we connected we got ~p', [URL, Exception]),
  100                fail
  101              )),          
  102        !,
  103        get_time(CurrentTime),
  104        ExpiryTime is CurrentTime + 30 * 60,
  105        assert(cached_wpad(PacData, ExpiryTime)).
  106
  107
  108detect_wpad(PacData):-
  109        debug(proxy, 'System did not report a valid WPAD URL. Trying to ask the DHCP server (this may not be permitted by the OS)', []),
  110        retractall(cached_wpad(_, _)),
  111        catch(dhcp_wpad(URL),  % This requires superuser privileges since we must bind on port 68
  112              Exception,
  113              ( debug(proxy, 'Could not use DHCP method because ~p', [Exception]),
  114                fail)
  115             ),
  116        catch(setup_call_cleanup(http_open(URL, Stream, [bypass_proxy(true), timeout(10)]),
  117                                 read_string(Stream, [], [], _, PacData),
  118                                 close(Stream)),
  119              Exception,
  120              ( debug(proxy, 'DHCP returned ~w for the PAC URL, but when we connected we got ~p', [URL, Exception]),
  121                fail
  122              )),             
  123        !,
  124        get_time(CurrentTime),
  125        ExpiryTime is CurrentTime + 30 * 60,
  126        assert(cached_wpad(PacData, ExpiryTime)).
  127
  128detect_wpad(Atom):-
  129        debug(proxy, 'Could not retrieve WPAD via DHCP. Probing for WPAD via DNS... (this may take some time)', []),
  130        retractall(cached_wpad(_, _)),
  131        %gethostname(Hostname),
  132        Hostname = 'securitease.dundas.trime.wtf.im',
  133        atomic_list_concat(HostnameParts, '.', Hostname),
  134        detect_wpad_1(HostnameParts, Atom),
  135        get_time(CurrentTime),
  136        ExpiryTime is CurrentTime + 30 * 60,
  137        assert(cached_wpad(Atom, ExpiryTime)).
  138
  139detect_wpad(Fallback):-
  140        debug(proxy, 'Unable to automatically detect proxy via WPAD. If you want to use a proxy, either fix the network infrastructure or manually configure a PAC file', []),
  141        Fallback = 'function FindProxyForURL(url, host) {return "DIRECT";}',
  142        get_time(CurrentTime),
  143        % If we do the fallback, try again after just 1 minute
  144        ExpiryTime is CurrentTime + 1 * 60,
  145        assert(cached_wpad(Fallback, ExpiryTime)).
  146
  147detect_wpad_1(HostnameParts, PacData):-
  148        possible_wpad_url(HostnameParts, URL),
  149        debug(proxy, 'Trying to get WPAD from ~w', [URL]),
  150        catch(setup_call_cleanup(http_open(URL, Stream, [bypass_proxy(true), timeout(10)]),
  151                                 read_string(Stream, [], [], _, PacData),
  152                                 close(Stream)),
  153              _,
  154              fail),
  155        !.
  156
  157        
  158detect_wpad_1(HostnameParts, _):-
  159        findall(URL,
  160                possible_wpad_url(HostnameParts, URL),
  161                URLs),
  162        atomic_list_concat(URLs, '\n', Message),
  163        throw(error(format('Unable to find WPAD information at any of the following:\n~w', [Message]), _)).
  164
  165
  166% Avoid a few common pitfalls. Note that this list is by no means extensive, and it is not practical to test everything thoroughly
  167possible_wpad_url([_], _):- !, fail. % This would be http://wpad.com or http://wpad.nz or even http://wpad.local
  168possible_wpad_url([co, _], _):- !, fail. % This would be http://wpad.co.nz or http://wpad.co.uk
  169possible_wpad_url([com, _], _):- !, fail. % This would be http://wpad.com.au
  170possible_wpad_url([net, _], _):- !, fail. % This would be http://wpad.net.nz
  171possible_wpad_url([org, _], _):- !, fail. % This would be http://wpad.org.nz
  172
  173possible_wpad_url(HostnameParts, URL):-
  174        ( atomic_list_concat([wpad|HostnameParts], '.', Stem),
  175          format(atom(URL), 'http://~w/wpad.dat', [Stem])
  176        ; HostnameParts = [_|Rest],
  177          possible_wpad_url(Rest, URL)
  178        )