Moving on from the excitement of tic-tac-toe, I wanted to try my hand at something a little more complex. I decided to have a look at implementing ebay style “automatic bidding“, which turned out to be a lot more interesting than I expected.
It’s a good exercise because it’s realistic, the behaviour is well documented, and there are plenty of examples. I chose to implement it as a gen_server, but it would work in any language.
I started out by just implementing basic bidding with a starting price, if the bid is higher than the current bid then it is accepted:
-record(state, {starting_price, bids=[]}).
-record(bid, {bidder, amount, time}).
-type money() :: {integer(), integer()}.
-spec start_link([money()]) -> {ok, pid()}.
start_link(StartingPrice) ->
gen_server:start_link(?MODULE, [StartingPrice], []).
init([StartingPrice]) ->
{ok, #state{starting_price = StartingPrice}}.
handle_call({bid, _UserId, Bid}, _From, State) when Bid < State#state.starting_price ->
{reply, bid_too_low, State};
handle_call({bid, UserId, BidAmount}, _From, State) when State#state.bids =:= [] ->
Bid = #bid{bidder = UserId, amount = BidAmount, time = calendar:universal_time()},
NewState = State#state{bids = [Bid | State#state.bids]},
{reply, bid_accepted, NewState};
handle_call({bid, UserId, BidAmount}, _From, State) ->
CurrentHighBid = hd(State#state.bids),
case BidAmount > CurrentHighBid#bid.amount of
true ->
Bid = #bid{bidder = UserId, amount = BidAmount, time = calendar:universal_time()},
NewState = State#state{bids = [Bid | State#state.bids]},
{reply, bid_accepted, NewState};
false ->
{reply, bid_too_low, State}
end;
handle_call(list_bids, _From, State) ->
{reply, State#state.bids, State};
I decided to handle currency as a tuple of pounds & pennies, due to the way Erlang term comparisons work they are ordered correctly.
With this in place, I started moving towards automatic bidding (the commit history is available, but I’ll skip ahead). The algorithm is fairly simple, but as always the devil is in the details!
-type user_id() :: integer().
-record(bid, {bidder :: user_id(), amount :: eb_money:money(), time :: calendar:datetime(), automatic = false :: boolean()}).
-record(state, {starting_price :: eb_money:money(), bids = [] :: [#bid{}], high_bid :: #bid{}}).
-spec start_link(eb_money:money(), calendar:datetime()) -> {ok, pid()}.
start_link(StartingPrice, EndTime) ->
gen_server:start_link(?MODULE, [StartingPrice, EndTime], []).
init([StartingPrice, EndTime]) ->
lager:info("Bidding begins. Starting price: ~p", [StartingPrice]),
TimeRemaining = calculate_time_remaining(EndTime),
lager:info("Time remaining: ~p", [TimeRemaining]),
_TimerRef = erlang:send_after(TimeRemaining, self(), bidding_ends),
{ok, #state{starting_price = StartingPrice}}.
handle_call({bid, _UserId, MaxBid}, _From, State) when MaxBid < State#state.starting_price ->
{reply, bid_too_low, State};
handle_call({bid, UserId, MaxBid}, _From, State) when State#state.bids =:= [] ->
BidTime = calendar:universal_time(),
Bid = #bid{bidder = UserId, amount = State#state.starting_price, time = BidTime},
NewState = State#state{bids = [Bid | State#state.bids], high_bid = #bid{bidder = UserId, amount = MaxBid, time = BidTime}},
{reply, bid_accepted, NewState};
handle_call({bid, UserId, MaxBid}, _From, State) ->
HighBid = State#state.high_bid,
case HighBid#bid.bidder =:= UserId of
true ->
update_bid_for_high_bidder(State, UserId, MaxBid);
false ->
handle_new_bid(State, MaxBid, UserId)
end;
handle_call(list_bids, _From, State) ->
{reply, lists:reverse(State#state.bids), State};
handle_info(bidding_ends, State) when State#state.bids =:= [] ->
lager:info("Bidding ends", []),
lager:info("No winner", []),
{stop, normal, State};
handle_info(bidding_ends, State) ->
lager:info("Bidding ends", []),
WinningBid = hd(State#state.bids),
lager:info("Winner: ~p, Bid: ~p", [WinningBid#bid.bidder, WinningBid#bid.amount]),
{stop, normal, State};
update_bid_for_high_bidder(State, UserId, MaxBid) ->
HighBid = State#state.high_bid,
case MaxBid > HighBid#bid.amount of
true ->
NewState = State#state{high_bid = #bid{bidder = UserId, amount = MaxBid, time = calendar:universal_time()}},
{reply, bid_accepted, NewState};
false ->
{reply, bid_too_low, State}
end.
handle_new_bid(State, MaxBid, UserId) ->
CurrentBid = hd(State#state.bids),
case MaxBid =< CurrentBid#bid.amount of
true ->
{reply, bid_too_low, State};
false ->
handle_valid_new_bid(State, MaxBid, UserId)
end.
handle_valid_new_bid(State, MaxBid, UserId) ->
HighBid = State#state.high_bid,
BidTime = calendar:universal_time(),
case MaxBid =< HighBid#bid.amount of
true ->
bid_lower_than_or_equal_to_high_bid(State, MaxBid, UserId, BidTime, HighBid);
false ->
bid_higher_than_current_high_bid(State, MaxBid, UserId, BidTime, HighBid)
end.
bid_lower_than_or_equal_to_high_bid(State, MaxBid, UserId, BidTime, HighBid) ->
LosingBid = #bid{bidder=UserId, amount=MaxBid, time=BidTime},
update_bid_list(State, LosingBid, HighBid).
bid_higher_than_current_high_bid(State, MaxBid, UserId, BidTime, HighBid) ->
WinningBid = #bid{bidder=UserId, amount=MaxBid, time=BidTime},
update_bid_list(State, HighBid, WinningBid).
update_bid_list(State, LosingBid, WinningBid) ->
NewAmount = eb_money:add(LosingBid#bid.amount, eb_bid_increments:get(LosingBid#bid.amount)),
NewHighBid = case NewAmount < WinningBid#bid.amount of
true ->
#bid{bidder = WinningBid#bid.bidder, amount = NewAmount, time = WinningBid#bid.time, automatic = true};
false ->
#bid{bidder = WinningBid#bid.bidder, amount = WinningBid#bid.amount, time = WinningBid#bid.time, automatic = false}
end,
NewState = State#state{bids = [NewHighBid | [LosingBid | State#state.bids]]},
{reply, bid_accepted, NewState}.
calculate_time_remaining(EndTime) ->
Now = calendar:universal_time(),
(calendar:datetime_to_gregorian_seconds(EndTime) - calendar:datetime_to_gregorian_seconds(Now)) * 1000. %% milliseconds!
Once you get used to the convenience of features like tuples and pattern matching, it can be quite painful to go back to a language without them. The next step was reserve price auctions, and some day I might get round to implementing the lowering of them.
If you want to play along, the tests can be found here.