HG-71: Added tests for invoices and payments (#32)

This commit is contained in:
Evgeny Levenets 2016-10-17 21:43:53 +03:00 committed by GitHub
parent 746b2c8f6d
commit f0e40b369d
7 changed files with 314 additions and 66 deletions

View File

@ -12,12 +12,14 @@
-export([insert/1]). -export([insert/1]).
-export([update/1]). -export([update/1]).
-export([get/1]). -export([get/1]).
-export([cleanup/0]).
%% %%
-type revision() :: pos_integer(). -type revision() :: pos_integer().
-type ref() :: _. -type ref() :: _.
-type data() :: _. -type data() :: _.
-type object() :: ref().
-spec head() -> revision(). -spec head() -> revision().
@ -76,3 +78,22 @@ update({Tag, {ObjectName, Ref, _Data}} = NewObject) ->
] ]
}, },
commit(head(), Commit). commit(head(), Commit).
-spec remove([object()]) -> ok.
remove(Objects) ->
Commit = #'Commit'{
ops = [
{remove, #'RemoveOp'{
object = Object
}} ||
Object <- Objects
]
},
commit(head(), Commit).
-spec cleanup() -> ok.
cleanup() ->
Domain = all(head()),
remove(maps:values(Domain)).

View File

@ -320,7 +320,7 @@ start_payment(PaymentParams, St, Context) ->
Events = wrap_payment_events(PaymentID, Events1 ++ Events2), Events = wrap_payment_events(PaymentID, Events1 ++ Events2),
{respond(PaymentID, Events, St, Action), Context2}. {respond(PaymentID, Events, St, Action), Context2}.
process_payment_signal(Signal, PaymentID, PaymentSession, St = #st{invoice = Invoice}, Context) -> process_payment_signal(Signal, PaymentID, PaymentSession, St, Context) ->
Opts = get_payment_opts(St), Opts = get_payment_opts(St),
case hg_invoice_payment:process_signal(Signal, PaymentSession, Opts, Context) of case hg_invoice_payment:process_signal(Signal, PaymentSession, Opts, Context) of
{{next, {Events, Action}}, Context1} -> {{next, {Events, Action}}, Context1} ->
@ -335,11 +335,16 @@ process_payment_signal(Signal, PaymentID, PaymentSession, St = #st{invoice = Inv
Events2 = [{public, ?invoice_ev(?invoice_status_changed(?paid()))}], Events2 = [{public, ?invoice_ev(?invoice_status_changed(?paid()))}],
{ok(wrap_payment_events(PaymentID, Events1) ++ Events2, St), Context1}; {ok(wrap_payment_events(PaymentID, Events1) ++ Events2, St), Context1};
?failed(_) -> ?failed(_) ->
{ok(wrap_payment_events(PaymentID, Events1), St, restore_timer(St)), Context1} %% TODO: fix this dirty hack
TmpPayments = lists:keydelete(PaymentID, 1, St#st.payments),
{
ok(wrap_payment_events(PaymentID, Events1), St, restore_timer(St#st{payments = TmpPayments})),
Context1
}
end end
end. end.
process_payment_call(Call, PaymentID, PaymentSession, St = #st{invoice = Invoice}, Context) -> process_payment_call(Call, PaymentID, PaymentSession, St, Context) ->
Opts = get_payment_opts(St), Opts = get_payment_opts(St),
case hg_invoice_payment:process_call(Call, PaymentSession, Opts, Context) of case hg_invoice_payment:process_call(Call, PaymentSession, Opts, Context) of
{{Response, {next, {Events, Action}}}, Context1} -> {{Response, {next, {Events, Action}}}, Context1} ->
@ -355,7 +360,17 @@ process_payment_call(Call, PaymentID, PaymentSession, St = #st{invoice = Invoice
Events2 = [{public, ?invoice_ev(?invoice_status_changed(?paid()))}], Events2 = [{public, ?invoice_ev(?invoice_status_changed(?paid()))}],
{respond(Response, wrap_payment_events(PaymentID, Events1) ++ Events2, St), Context1}; {respond(Response, wrap_payment_events(PaymentID, Events1) ++ Events2, St), Context1};
?failed(_) -> ?failed(_) ->
{respond(Response, wrap_payment_events(PaymentID, Events1), St, restore_timer(St)), Context1} %% TODO: fix this dirty hack
TmpPayments = lists:keydelete(PaymentID, 1, St#st.payments),
{
respond(
Response,
wrap_payment_events(PaymentID, Events1),
St,
restore_timer(St#st{payments = TmpPayments})
),
Context1
}
end end
end. end.
@ -460,16 +475,19 @@ get_payment_session(PaymentID, #st{payments = Payments}) ->
set_payment_session(PaymentID, PaymentSession, St = #st{payments = Payments}) -> set_payment_session(PaymentID, PaymentSession, St = #st{payments = Payments}) ->
St#st{payments = lists:keystore(PaymentID, 1, Payments, {PaymentID, PaymentSession})}. St#st{payments = lists:keystore(PaymentID, 1, Payments, {PaymentID, PaymentSession})}.
get_pending_payment(#st{payments = [V = {_PaymentID, {Payment, _}} | _]}) -> get_pending_payment(#st{payments = Payments}) ->
find_pending_payment(Payments).
find_pending_payment([V = {_PaymentID, {Payment, _}} | Rest]) ->
case get_payment_status(Payment) of case get_payment_status(Payment) of
?pending() -> ?pending() ->
V; V;
?processed() -> ?processed() ->
V; V;
_ -> _ ->
undefined find_pending_payment(Rest)
end; end;
get_pending_payment(#st{}) -> find_pending_payment([]) ->
undefined. undefined.
get_invoice_state(#st{invoice = Invoice, payments = Payments}) -> get_invoice_state(#st{invoice = Invoice, payments = Payments}) ->

View File

@ -14,6 +14,12 @@
-export([make_shop_details/1]). -export([make_shop_details/1]).
-export([make_shop_details/2]). -export([make_shop_details/2]).
-export([bank_card_tds_token/0]).
-export([bank_card_simple_token/0]).
-export([make_tds_payment_tool/0]).
-export([make_simple_payment_tool/0]).
-export([get_hellgate_url/0]).
-export([domain_fixture/1]). -export([domain_fixture/1]).
-include_lib("dmsl/include/dmsl_domain_thrift.hrl"). -include_lib("dmsl/include/dmsl_domain_thrift.hrl").
@ -21,6 +27,9 @@
%% %%
-define(HELLGATE_HOST, "hellgate").
-define(HELLGATE_PORT, 8022).
-type app_name() :: atom(). -type app_name() :: atom().
-spec start_app(app_name()) -> [app_name()]. -spec start_app(app_name()) -> [app_name()].
@ -32,7 +41,7 @@ start_app(lager = AppName) ->
{error_logger_hwm, 600}, {error_logger_hwm, 600},
{suppress_application_start_stop, true}, {suppress_application_start_stop, true},
{handlers, [ {handlers, [
{lager_common_test_backend, [debug, false]} {lager_common_test_backend, info}
]} ]}
]), #{}}; ]), #{}};
@ -42,17 +51,14 @@ start_app(woody = AppName) ->
]), #{}}; ]), #{}};
start_app(hellgate = AppName) -> start_app(hellgate = AppName) ->
Host = "hellgate",
Port = 8022,
RootUrl = "http://" ++ Host ++ ":" ++ integer_to_list(Port),
{start_app(AppName, [ {start_app(AppName, [
{host, Host}, {host, ?HELLGATE_HOST},
{port, Port}, {port, ?HELLGATE_PORT},
{automaton_service_url, <<"http://machinegun:8022/v1/automaton">>}, {automaton_service_url, <<"http://machinegun:8022/v1/automaton">>},
{eventsink_service_url, <<"http://machinegun:8022/v1/event_sink">>}, {eventsink_service_url, <<"http://machinegun:8022/v1/event_sink">>},
{accounter_service_url, <<"http://shumway:8022/accounter">>} {accounter_service_url, <<"http://shumway:8022/accounter">>}
]), #{ ]), #{
hellgate_root_url => RootUrl hellgate_root_url => get_hellgate_url()
}}; }};
start_app(AppName) -> start_app(AppName) ->
@ -60,6 +66,16 @@ start_app(AppName) ->
-spec start_app(app_name(), list()) -> [app_name()]. -spec start_app(app_name(), list()) -> [app_name()].
start_app(cowboy = AppName, Env) ->
#{
listener_ref := Ref,
acceptors_count := Count,
transport_opts := TransOpt,
proto_opts := ProtoOpt
} = Env,
cowboy:start_http(Ref, Count, TransOpt, ProtoOpt),
[AppName];
start_app(AppName, Env) -> start_app(AppName, Env) ->
genlib_app:start_application_with(AppName, Env). genlib_app:start_application_with(AppName, Env).
@ -142,12 +158,6 @@ make_invoice_params(PartyID, ShopID, Product, Due, {Amount, Currency}, Context)
} }
}. }.
make_due_date() ->
make_due_date(24 * 60 * 60).
make_due_date(LifetimeSeconds) ->
genlib_time:unow() + LifetimeSeconds.
-spec make_category_ref(dmsl_domain_thrift:'ObjectID'()) -> -spec make_category_ref(dmsl_domain_thrift:'ObjectID'()) ->
dmsl_domain_thrift:'CategoryRef'(). dmsl_domain_thrift:'CategoryRef'().
@ -169,6 +179,42 @@ make_shop_details(Name, Description) ->
description = Description description = Description
}. }.
-spec bank_card_tds_token() -> string().
bank_card_tds_token() ->
<<"TOKEN666">>.
-spec bank_card_simple_token() -> string().
bank_card_simple_token() ->
<<"TOKEN42">>.
-spec make_tds_payment_tool() -> hg_domain_thrift:'PaymentTool'().
make_tds_payment_tool() ->
{
{bank_card, #domain_BankCard{
token = bank_card_tds_token(),
payment_system = visa,
bin = <<"666666">>,
masked_pan = <<"666">>
}},
<<"SESSION666">>
}.
-spec make_simple_payment_tool() -> hg_domain_thrift:'PaymentTool'().
make_simple_payment_tool() ->
{
{bank_card, #domain_BankCard{
token = bank_card_simple_token(),
payment_system = visa,
bin = <<"424242">>,
masked_pan = <<"4242">>
}},
<<"SESSION42">>
}.
-type ref() :: _. -type ref() :: _.
-type data() :: _. -type data() :: _.
-spec domain_fixture(atom()) -> {ref(), data()}. -spec domain_fixture(atom()) -> {ref(), data()}.
@ -222,3 +268,14 @@ domain_fixture(proxy) ->
options = genlib_app:env(hellgate, provider_proxy_options, #{}) options = genlib_app:env(hellgate, provider_proxy_options, #{})
} }
}}. }}.
-spec get_hellgate_url() -> string().
get_hellgate_url() ->
"http://" ++ ?HELLGATE_HOST ++ ":" ++ integer_to_list(?HELLGATE_PORT).
make_due_date() ->
make_due_date(24 * 60 * 60).
make_due_date(LifetimeSeconds) ->
genlib_time:unow() + LifetimeSeconds.

View File

@ -6,15 +6,33 @@
-behaviour(hg_test_proxy). -behaviour(hg_test_proxy).
-export([get_service_spec/0]). -export([get_service_spec/0]).
-export([get_http_cowboy_spec/0]).
%% cowboy http callbacks
-export([init/3]).
-export([handle/2]).
-export([terminate/3]).
%% %%
-define(COWBOY_PORT, 9988).
-spec get_service_spec() -> -spec get_service_spec() ->
hg_proto:service_spec(). hg_proto:service_spec().
get_service_spec() -> get_service_spec() ->
{"/test/proxy/provider/dummy", {dmsl_proxy_provider_thrift, 'ProviderProxy'}}. {"/test/proxy/provider/dummy", {dmsl_proxy_provider_thrift, 'ProviderProxy'}}.
-spec get_http_cowboy_spec() -> #{}.
get_http_cowboy_spec() ->
Dispatch = cowboy_router:compile([{'_', [{"/", ?MODULE, []}]}]),
#{
listener_ref => ?MODULE,
acceptors_count => 10,
transport_opts => [{port, ?COWBOY_PORT}],
proto_opts => [{env, [{dispatch, Dispatch}]}]
}.
%% %%
-include_lib("dmsl/include/dmsl_proxy_provider_thrift.hrl"). -include_lib("dmsl/include/dmsl_proxy_provider_thrift.hrl").
@ -47,19 +65,51 @@ handle_function(
) -> ) ->
handle_callback(Payload, Target, State, PaymentInfo, Opts, Context). handle_callback(Payload, Target, State, PaymentInfo, Opts, Context).
-spec init(atom(), cowboy_req:req(), list()) -> {ok, cowboy_req:req(), state}.
init(_Transport, Req, []) ->
{ok, Req, undefined}.
-spec handle(cowboy_req:req(), state) -> {ok, cowboy_req:req(), state}.
handle(Req, State) ->
{Method, Req2} = cowboy_req:method(Req),
{ok, Req3} = handle_user_interaction_response(Method, Req2),
{ok, Req3, State}.
-spec terminate(term(), cowboy_req:req(), state) -> ok.
terminate(_Reason, _Req, _State) ->
ok.
process_payment(?processed(), undefined, _, _, Context) -> process_payment(?processed(), undefined, _, _, Context) ->
{{ok, sleep(1, <<"sleeping">>)}, Context}; {{ok, sleep(1, <<"sleeping">>)}, Context};
process_payment(?processed(), <<"sleeping">>, PaymentInfo, _, Context) -> process_payment(?processed(), <<"sleeping">>, PaymentInfo, _, Context) ->
{{ok, finish(PaymentInfo)}, Context}; {{ok, finish(PaymentInfo)}, Context};
process_payment(?captured(), undefined, _, Opts, Context) -> process_payment(?captured(), undefined, PaymentInfo, _Opts, Context) ->
Tag = hg_utils:unique_id(), Token3DS = hg_ct_helper:bank_card_tds_token(),
_Pid = spawn(fun () -> callback(Tag, <<"payload">>, <<"sure">>, Opts, 1000) end), case get_payment_token(PaymentInfo) of
{{ok, suspend(Tag, 3, <<"suspended">>)}, Context}; Token3DS ->
Tag = hg_utils:unique_id(),
Uri = genlib:to_binary("http://127.0.0.1:" ++ integer_to_list(?COWBOY_PORT)),
UserInteraction = {
'redirect',
{
'post_request',
#'BrowserPostRequest'{uri = Uri, form = #{<<"tag">> => Tag}}
}
},
{{ok, suspend(Tag, 3, <<"suspended">>, UserInteraction)}, Context};
_ ->
%% simple workflow without 3DS
{{ok, sleep(1, <<"sleeping">>)}, Context}
end;
process_payment(?captured(), <<"sleeping">>, PaymentInfo, _, Context) -> process_payment(?captured(), <<"sleeping">>, PaymentInfo, _, Context) ->
{{ok, finish(PaymentInfo)}, Context}. {{ok, finish(PaymentInfo)}, Context}.
handle_callback(<<"payload">>, ?captured(), <<"suspended">>, _, _, Context) -> handle_callback(<<"payload">>, ?captured(), <<"suspended">>, _PaymentInfo, _Opts, Context) ->
{{ok, respond(<<"sure">>, sleep(1, <<"sleeping">>))}, Context}. {{ok, respond(<<"sure">>, sleep(1, <<"sleeping">>))}, Context}.
finish(#'PaymentInfo'{payment = Payment}) -> finish(#'PaymentInfo'{payment = Payment}) ->
@ -74,11 +124,12 @@ sleep(Timeout, State) ->
next_state = State next_state = State
}. }.
suspend(Tag, Timeout, State) -> suspend(Tag, Timeout, State, UserInteraction) ->
#'ProxyResult'{ #'ProxyResult'{
intent = {suspend, #'SuspendIntent'{ intent = {suspend, #'SuspendIntent'{
tag = Tag, tag = Tag,
timeout = {timeout, Timeout} timeout = {timeout, Timeout},
user_interaction = UserInteraction
}}, }},
next_state = State next_state = State
}. }.
@ -89,9 +140,27 @@ respond(Response, Result) ->
result = Result result = Result
}. }.
callback(Tag, Payload, Expect, #{hellgate_root_url := RootUrl}, Timeout) -> get_payment_token(#'PaymentInfo'{payment = Payment}) ->
_ = timer:sleep(Timeout), #domain_InvoicePayment{payer = #domain_Payer{payment_tool = PaymentTool}} = Payment,
{ok, Expect} = hg_client_api:call( {'bank_card', #domain_BankCard{token = Token}} = PaymentTool,
proxy_host_provider, 'ProcessCallback', [Tag, Payload], Token.
hg_client_api:new(RootUrl)
). handle_user_interaction_response(<<"POST">>, Req) ->
{ok, Body, _Garbage} = cowboy_req:body(Req),
Tag = maps:get(<<"tag">>, binary_to_term(Body)),
RespCode = callback_to_hell(Tag),
cowboy_req:reply(RespCode, [{<<"content-type">>, <<"text/plain; charset=utf-8">>}], <<"">>, Req);
handle_user_interaction_response(_, Req) ->
%% Method not allowed.
cowboy_req:reply(405, Req).
callback_to_hell(Tag) ->
case hg_client_api:call(
proxy_host_provider, 'ProcessCallback', [Tag, <<"payload">>],
hg_client_api:new(hg_ct_helper:get_hellgate_url())
) of
{ok, _} -> 200;
{{ok, _}, _} -> 200;
{{error, _}, _} -> 500;
{{exception, _}, _} -> 500
end.

View File

@ -56,6 +56,7 @@ init_per_suite(C) ->
-spec end_per_suite(config()) -> _. -spec end_per_suite(config()) -> _.
end_per_suite(C) -> end_per_suite(C) ->
hg_domain:cleanup(),
[application:stop(App) || App <- ?c(apps, C)]. [application:stop(App) || App <- ?c(apps, C)].
-spec init_per_testcase(test_case_name(), config()) -> config(). -spec init_per_testcase(test_case_name(), config()) -> config().

View File

@ -10,7 +10,10 @@
-export([invoice_cancellation/1]). -export([invoice_cancellation/1]).
-export([overdue_invoice_cancelled/1]). -export([overdue_invoice_cancelled/1]).
-export([invoice_cancelled_after_payment_timeout/1]).
-export([payment_success/1]). -export([payment_success/1]).
-export([payment_success_on_second_try/1]).
-export([invoice_success_on_third_payment/1]).
-export([consistent_history/1]). -export([consistent_history/1]).
%% %%
@ -39,7 +42,10 @@ all() ->
[ [
invoice_cancellation, invoice_cancellation,
overdue_invoice_cancelled, overdue_invoice_cancelled,
invoice_cancelled_after_payment_timeout,
payment_success, payment_success,
payment_success_on_second_try,
invoice_success_on_third_payment,
consistent_history consistent_history
]. ].
@ -49,7 +55,12 @@ all() ->
-spec init_per_suite(config()) -> config(). -spec init_per_suite(config()) -> config().
init_per_suite(C) -> init_per_suite(C) ->
{Apps, Ret} = hg_ct_helper:start_apps([lager, woody, hellgate]), CowboySpec = hg_dummy_provider:get_http_cowboy_spec(),
{Apps, Ret} = hg_ct_helper:start_apps([lager, woody, hellgate, {cowboy, CowboySpec}]),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(currency)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(globals)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(party_prototype)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(proxy)),
RootUrl = maps:get(hellgate_root_url, Ret), RootUrl = maps:get(hellgate_root_url, Ret),
PartyID = hg_utils:unique_id(), PartyID = hg_utils:unique_id(),
Client = hg_client_party:start(make_userinfo(PartyID), PartyID, hg_client_api:new(RootUrl)), Client = hg_client_party:start(make_userinfo(PartyID), PartyID, hg_client_api:new(RootUrl)),
@ -58,12 +69,14 @@ init_per_suite(C) ->
{party_id, PartyID}, {party_id, PartyID},
{shop_id, ShopID}, {shop_id, ShopID},
{root_url, RootUrl}, {root_url, RootUrl},
{apps, Apps} | C {apps, Apps}
| C
]. ].
-spec end_per_suite(config()) -> _. -spec end_per_suite(config()) -> _.
end_per_suite(C) -> end_per_suite(C) ->
hg_domain:cleanup(),
[application:stop(App) || App <- ?c(apps, C)]. [application:stop(App) || App <- ?c(apps, C)].
%% tests %% tests
@ -89,7 +102,7 @@ init_per_testcase(_Name, C) ->
end_per_testcase(_Name, C) -> end_per_testcase(_Name, C) ->
_ = unlink(?c(test_sup, C)), _ = unlink(?c(test_sup, C)),
_ = application:set_env(hellgate, provider_proxy_url, undefined), _ = application:unset_env(hellgate, provider_proxy_url),
exit(?c(test_sup, C), shutdown). exit(?c(test_sup, C), shutdown).
-spec invoice_cancellation(config()) -> _ | no_return(). -spec invoice_cancellation(config()) -> _ | no_return().
@ -107,34 +120,71 @@ invoice_cancellation(C) ->
overdue_invoice_cancelled(C) -> overdue_invoice_cancelled(C) ->
Client = ?c(client, C), Client = ?c(client, C),
ShopID = ?c(shop_id, C), {ok, InvoiceID} = start_invoice(<<"rubberduck">>, make_due_date(1), 10000, C),
PartyID = ?c(party_id, C),
InvoiceParams = make_invoice_params(PartyID, ShopID, <<"rubberduck">>, make_due_date(1), 10000),
{ok, InvoiceID} = hg_client_invoicing:create(InvoiceParams, Client),
?invoice_created(?invoice_w_status(?unpaid())) = next_event(InvoiceID, Client),
?invoice_status_changed(?cancelled(<<"overdue">>)) = next_event(InvoiceID, Client). ?invoice_status_changed(?cancelled(<<"overdue">>)) = next_event(InvoiceID, Client).
-spec invoice_cancelled_after_payment_timeout(config()) -> _ | no_return().
invoice_cancelled_after_payment_timeout(C) ->
Client = ?c(client, C),
{ok, InvoiceID} = start_invoice(<<"rubberdusk">>, make_due_date(7), 1000, C),
PaymentParams = make_tds_payment_params(),
{ok, PaymentID} = attach_payment(InvoiceID, PaymentParams, Client),
?payment_interaction_requested(PaymentID, _) = next_event(InvoiceID, Client),
%% wait for payment timeout
?payment_status_changed(PaymentID, ?failed(_)) = next_event(InvoiceID, 5000, Client),
?invoice_status_changed(?cancelled(<<"overdue">>)) = next_event(InvoiceID, 5000, Client).
-spec payment_success(config()) -> _ | no_return(). -spec payment_success(config()) -> _ | no_return().
payment_success(C) -> payment_success(C) ->
Client = ?c(client, C), Client = ?c(client, C),
ProxyUrl = start_service_handler(hg_dummy_provider, C), {ok, InvoiceID} = start_invoice(<<"rubberduck">>, make_due_date(10), 42000, C),
ok = application:set_env(hellgate, provider_proxy_url, ProxyUrl),
ShopID = ?c(shop_id, C),
PartyID = ?c(party_id, C),
InvoiceParams = make_invoice_params(PartyID, ShopID, <<"rubberduck">>, make_due_date(2), 42000),
ok = hg_domain:update(hg_ct_helper:domain_fixture(proxy)),
PaymentParams = make_payment_params(), PaymentParams = make_payment_params(),
{ok, InvoiceID} = hg_client_invoicing:create(InvoiceParams, Client), {ok, PaymentID} = attach_payment(InvoiceID, PaymentParams, Client),
?invoice_created(?invoice_w_status(?unpaid())) = next_event(InvoiceID, Client),
{ok, PaymentID} = hg_client_invoicing:start_payment(InvoiceID, PaymentParams, Client),
?payment_started(?payment_w_status(?pending())) = next_event(InvoiceID, Client),
?payment_bound(PaymentID, ?trx_info(PaymentID)) = next_event(InvoiceID, Client),
?payment_status_changed(PaymentID, ?processed()) = next_event(InvoiceID, Client),
?payment_status_changed(PaymentID, ?captured()) = next_event(InvoiceID, Client), ?payment_status_changed(PaymentID, ?captured()) = next_event(InvoiceID, Client),
?invoice_status_changed(?paid()) = next_event(InvoiceID, Client), ?invoice_status_changed(?paid()) = next_event(InvoiceID, Client),
timeout = next_event(InvoiceID, 1000, Client). timeout = next_event(InvoiceID, 1000, Client).
-spec payment_success_on_second_try(config()) -> _ | no_return().
payment_success_on_second_try(C) ->
Client = ?c(client, C),
{ok, InvoiceID} = start_invoice(<<"rubberdick">>, make_due_date(20), 42000, C),
PaymentParams = make_tds_payment_params(),
{ok, PaymentID} = attach_payment(InvoiceID, PaymentParams, Client),
?payment_interaction_requested(PaymentID, UserInteraction) = next_event(InvoiceID, Client),
%% simulate user interaction
{URL, GoodBody} = get_post_request(UserInteraction),
BadBody = #{<<"tag">> => <<"666">>},
assert_failed_post_requiest({URL, BadBody}),
assert_success_post_requiest({URL, GoodBody}),
?payment_status_changed(PaymentID, ?captured()) = next_event(InvoiceID, Client),
?invoice_status_changed(?paid()) = next_event(InvoiceID, Client),
timeout = next_event(InvoiceID, 1000, Client).
-spec invoice_success_on_third_payment(config()) -> _ | no_return().
invoice_success_on_third_payment(C) ->
Client = ?c(client, C),
{ok, InvoiceID} = start_invoice(<<"rubberdock">>, make_due_date(60), 42000, C),
PaymentParams = make_tds_payment_params(),
{ok, PaymentID_1} = attach_payment(InvoiceID, PaymentParams, Client),
?payment_interaction_requested(PaymentID_1, _) = next_event(InvoiceID, Client),
%% wait for payment timeout and start new one after
?payment_status_changed(PaymentID_1, ?failed(_)) = next_event(InvoiceID, 5000, Client),
{ok, PaymentID_2} = attach_payment(InvoiceID, PaymentParams, Client),
?payment_interaction_requested(PaymentID_2, _) = next_event(InvoiceID, Client),
%% wait for payment timeout and start new one after
?payment_status_changed(PaymentID_2, ?failed(_)) = next_event(InvoiceID, 5000, Client),
{ok, PaymentID_3} = attach_payment(InvoiceID, PaymentParams, Client),
?payment_interaction_requested(PaymentID_3, UserInteraction) = next_event(InvoiceID, Client),
GoodPost = get_post_request(UserInteraction),
%% simulate user interaction FTW!
assert_success_post_requiest(GoodPost),
?payment_status_changed(PaymentID_3, ?captured()) = next_event(InvoiceID, Client),
?invoice_status_changed(?paid()) = next_event(InvoiceID, Client),
timeout = next_event(InvoiceID, 1000, Client).
%% %%
-spec consistent_history(config()) -> _ | no_return(). -spec consistent_history(config()) -> _ | no_return().
@ -189,8 +239,12 @@ make_invoice_params(PartyID, ShopID, Product, Cost) ->
make_invoice_params(PartyID, ShopID, Product, Due, Cost) -> make_invoice_params(PartyID, ShopID, Product, Due, Cost) ->
hg_ct_helper:make_invoice_params(PartyID, ShopID, Product, Due, Cost). hg_ct_helper:make_invoice_params(PartyID, ShopID, Product, Due, Cost).
make_tds_payment_params() ->
{PaymentTool, Session} = hg_ct_helper:make_tds_payment_tool(),
make_payment_params(PaymentTool, Session).
make_payment_params() -> make_payment_params() ->
{PaymentTool, Session} = make_payment_tool(), {PaymentTool, Session} = hg_ct_helper:make_simple_payment_tool(),
make_payment_params(PaymentTool, Session). make_payment_params(PaymentTool, Session).
make_payment_params(PaymentTool, Session) -> make_payment_params(PaymentTool, Session) ->
@ -203,16 +257,40 @@ make_payment_params(PaymentTool, Session) ->
} }
}. }.
make_payment_tool() ->
{
{bank_card, #domain_BankCard{
token = <<"TOKEN42">>,
payment_system = visa,
bin = <<"424242">>,
masked_pan = <<"4242">>
}},
<<"SESSION42">>
}.
make_due_date(LifetimeSeconds) -> make_due_date(LifetimeSeconds) ->
genlib_time:unow() + LifetimeSeconds. genlib_time:unow() + LifetimeSeconds.
start_invoice(Product, Due, Amount, C) ->
Client = ?c(client, C),
ProxyUrl = start_service_handler(hg_dummy_provider, C),
ok = application:set_env(hellgate, provider_proxy_url, ProxyUrl),
Client = ?c(client, C),
ShopID = ?c(shop_id, C),
PartyID = ?c(party_id, C),
ok = hg_domain:update(hg_ct_helper:domain_fixture(proxy)),
InvoiceParams = make_invoice_params(PartyID, ShopID, Product, Due, Amount),
{ok, InvoiceID} = hg_client_invoicing:create(InvoiceParams, Client),
?invoice_created(?invoice_w_status(?unpaid())) = next_event(InvoiceID, Client),
{ok, InvoiceID}.
attach_payment(InvoiceID, PaymentParams, Client) ->
{ok, PaymentID} = hg_client_invoicing:start_payment(InvoiceID, PaymentParams, Client),
?payment_started(?payment_w_status(?pending())) = next_event(InvoiceID, Client),
?payment_bound(PaymentID, ?trx_info(PaymentID)) = next_event(InvoiceID, Client),
?payment_status_changed(PaymentID, ?processed()) = next_event(InvoiceID, Client),
{ok, PaymentID}.
assert_success_post_requiest(Req) ->
{ok, 200, _RespHeaders, _ClientRef} = post_requiest(Req).
assert_failed_post_requiest(Req) ->
{ok, 500, _RespHeaders, _ClientRef} = post_requiest(Req).
post_requiest({URL, Body}) ->
Method = post,
Headers = [],
Options = [],
hackney:request(Method, URL, Headers, term_to_binary(Body), Options).
get_post_request({'redirect', {'post_request', #'BrowserPostRequest'{uri = URL, form = Body}}}) ->
{URL, Body}.

View File

@ -158,12 +158,16 @@ groups() ->
init_per_suite(C) -> init_per_suite(C) ->
{Apps, Ret} = hg_ct_helper:start_apps([lager, woody, hellgate]), {Apps, Ret} = hg_ct_helper:start_apps([lager, woody, hellgate]),
dmt_client_poller:poll(), ok = hg_domain:insert(hg_ct_helper:domain_fixture(currency)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(globals)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(party_prototype)),
ok = hg_domain:insert(hg_ct_helper:domain_fixture(proxy)),
[{root_url, maps:get(hellgate_root_url, Ret)}, {apps, Apps} | C]. [{root_url, maps:get(hellgate_root_url, Ret)}, {apps, Apps} | C].
-spec end_per_suite(config()) -> _. -spec end_per_suite(config()) -> _.
end_per_suite(C) -> end_per_suite(C) ->
hg_domain:cleanup(),
[application:stop(App) || App <- ?c(apps, C)]. [application:stop(App) || App <- ?c(apps, C)].
%% tests %% tests