-module(tbray_qsort). -export([start/2]). find_match("/ongoing/When/" ++ Last, Matches) -> case lists:member($., Last) of false -> Matches ++ [Last]; true -> Matches end; find_match(_, Matches) -> Matches. process_binary(Pid, Bin) -> spawn(fun() -> L = string:tokens(binary_to_list(Bin), "\n"), V = lists:foldl( fun(Line, Matches) -> find_match(lists:nth(7, string:tokens(Line, " ")), Matches) end, [], L), Pid ! V end). split_on_newline(Bin, N, All) when size(Bin) < N -> All ++ [Bin]; split_on_newline(Bin, N, All) -> {_, <>} = split_binary(Bin, N), case C of $\n -> {B21, B22} = split_binary(Bin, N+1), split_on_newline(B22, N, All ++ [B21]); _ -> split_on_newline(Bin, N+1, All) end. split_on_newline(Bin, N) when N == size(Bin) -> [Bin]; split_on_newline(Bin, N) -> split_on_newline(Bin, N, []). sort([Pivot|T]) -> sort([ X || X <- T, X < Pivot]) ++ [Pivot] ++ sort([ X || X <- T, X >= Pivot]); sort([]) -> []. -record(count, {url, hits}). sort_count([Pivot|T]) -> sort_count([ X || X <- T, X#count.hits >= Pivot#count.hits]) ++ [Pivot] ++ sort_count([ X || X <- T, X#count.hits < Pivot#count.hits]); sort_count([]) -> []. start(Num, Input) -> {ok, Data} = file:read_file(Input), Bins = split_on_newline(Data, size(Data) div Num), Me = self(), Pids = [process_binary(Me, B) || B <- Bins], {Counts, _, _} = lists:foldl( fun(Url, S) -> {Counts, Last, LastCount} = S, if Url == Last -> {Counts, Url, LastCount + 1}; true -> { Counts ++ [#count{hits = LastCount, url = Last}], Url, 1 } end end, {[], [], 0}, sort(lists:foldl( fun(_, Total) -> receive X -> Total ++ X end end, [], Pids))++[[]]), {Popular, _} = lists:split(10, sort_count(Counts)), lists:foreach(fun(X) -> io:format("~w : ~s~n", [X#count.hits, X#count.url]) end, Popular).