The World Wide Web Software Stack: Threat or Menace?

James Mickens, in what he unfortunately says will be the last of his extraordinarily wonderful articles for Usenix, sums up the tentacled cthonic horror that is the software that underlies the World Wide Web:

People think that Web browsers are elegant computation platforms, and Web pages are light, fluffy things that you can edit in Notepad as you trade ironic comments with your friends in the coffee shop. Nothing could be further from the truth. A modern Web page is a catastrophe. It’s like a scene from one of those apocalyptic medieval paintings that depicts what would happen if Galactus arrived: people are tumbling into fiery crevasses and lamenting various lamentable things and hanging from playground equipment that would not pass OSHA safety checks.

(Title stolen from Rod Martens)

Fun with Prolog

Saw a post about currency arbitrage in Prolog on Hacker News, and wrote a more general solution:

:- use_module(library(lists)).
:- use_module(library('http/http_client')).
:- use_module(library('http/json')).

%! find_chains(+MaxLength) is semidet
%
% Prints possible profitable conversion chains.

find_chains(MaxLength) :-
  http_get('http://fx.priceonomics.com/v1/rates/', Json, []),
  atom_json_term(Json, json(Prices), []), % convert the json atom to a prolog term and extract the list of prices
  abolish(price/3),                       % clear any old price facts from the database
  assert_prices(Prices),                  % update the database with current prices
	
  % now get the set of all solutions for the predicate 
  % build_chain/3, and build a list of the results
  setof(chain(Symbols, Profit), build_chain(MaxLength, Symbols, Profit), Chains),
	
  % print the results
  write(Chains).

%! assert_prices(+List) is det
% 
% Adds the list of prices to the dynamic database.
%
assert_prices([]).
assert_prices([SymbolPair = Price | Rest]) :-
  atomic_list_concat([From, To], '_', SymbolPair),
  atom_number(Price, Num),
  assertz(price(From, To, Num)),
  assert_prices(Rest).

%! build_chain(+MaxLength, -Symbols, -Profit) is nondet
%
% Finds a profitable chain

build_chain(MaxLength, Symbols, Profit) :-
  price(Dest, Next, _), Dest \= Next, % pick a starting symbol (ignore repeats), with backtracking
  build_chain(MaxLength, Dest, [Dest], 1.0, Symbols, Profit).

%! build_chain(+Count, Dest, SymbolsIn, ProfitIn, SymbolsOut, ProfitOut)
%
% Finds a possible next link in the chain, checks to see if it's a loop, otherwise recurses.

build_chain(0, _, _, _, _, _) :- !, fail.    % stop backtracking when we hit our maximum length

build_chain(Count, Dest, SymbolsIn, ProfitIn, SymbolsOut, ProfitOut) :-
  price(A, B, P),                            % find a price record (backtracking over all of them)
  append(_, [A], SymbolsIn),                 % make sure the chain connects
  Profit is ProfitIn * P,                    % calculate our profit
	
  (B = Dest                                  % do we have a loop?
    ->  Profit > 1.0,                        % is it profitable?
        append(SymbolsIn, [B], SymbolsOut),  % if so, then we're done
        ProfitOut = Profit
		
    ;   \+ member(B, SymbolsIn),             % if not a loop, make sure we don't repeat interior symbols
        append(SymbolsIn, [B], SymbolsNext), % add B to a temp list
        NextCount is Count - 1,              % and recurse, decrementing our counter
        build_chain(NextCount, Dest, SymbolsNext, Profit, SymbolsOut, ProfitOut)).