blob: f2ac71e7eb2bc22687cdcf52076e8da0e52c650d [file] [log] [blame]
Harald Weltec5a102c2011-04-02 18:15:42 +02001-module(osmo_ss7_gtt_tests).
2-author('Harald Welte <laforge@gnumonks.org>').
3
4-include_lib("eunit/include/eunit.hrl").
5-include("sccp.hrl").
6-include("gtt.hrl").
7
8match_inrange_test() ->
9 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1]},
10 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000},
11 ?assertEqual(foobar, osmo_ss7_gtt:global_title_match([{Match, foobar}], Gt)).
12
13nomatch_outrange_test() ->
14 Gt = #global_title{phone_number = [1,2,3,5,0,0,0,1]},
15 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000},
16 ?assertEqual(false, osmo_ss7_gtt:global_title_match([{Match, foobar}], Gt)).
17
18nomatch_inrange_othercrit_test() ->
19 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1]},
20 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000, nature_of_addr_ind = 4},
21 ?assertEqual(false, osmo_ss7_gtt:global_title_match([{Match, foobar}], Gt)).
22
23match_inrange_othercrit_test() ->
24 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], nature_of_addr_ind = 4},
25 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000, nature_of_addr_ind = 4},
26 ?assertEqual(foobar, osmo_ss7_gtt:global_title_match([{Match, foobar}], Gt)).
27
28
29repl_digit_test() ->
30 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], nature_of_addr_ind = 4},
31 Act = #gtt_act_repl_digits{replace_digit_start = 1, replace_digit_end = 4, new_digits = [5,6,7,8]},
32 ReplGt = osmo_ss7_gtt:apply_gtt_actions(Gt, Act),
33 ?assertEqual(ReplGt, Gt#global_title{phone_number = [5,6,7,8,0,0,0,1]}).
34
35repl_numplan_test() ->
36 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], numbering_plan = 4},
37 Act = #gtt_act_repl_num_plan{numbering_plan = 3},
38 ReplGt = osmo_ss7_gtt:apply_gtt_actions(Gt, Act),
39 ?assertEqual(ReplGt, Gt#global_title{numbering_plan = 3}).
40
41apply_cb(Arg) ->
42 Arg.
43
44apply_test() ->
45 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], numbering_plan = 4},
46 Act = #gtt_act_apply{funct = fun apply_cb/1, args = [rtfm]},
47 ReplGt = osmo_ss7_gtt:apply_gtt_actions(Gt, Act),
48 ?assertEqual(rtfm, ReplGt).
49
50actlist_test() ->
51 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], numbering_plan = 4},
52 Act1 = #gtt_act_repl_digits{replace_digit_start = 1, replace_digit_end = 4, new_digits = [5,6,7,8]},
53 Act2 = #gtt_act_repl_num_plan{numbering_plan = 3},
54 ReplGt = osmo_ss7_gtt:apply_gtt_actions(Gt, [Act1, Act2]),
55 ?assertEqual(ReplGt, Gt#global_title{phone_number = [5,6,7,8,0,0,0,1], numbering_plan = 3}).
56
57execute_gtt_test() ->
58 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], numbering_plan = 4},
59 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000},
60 Act1 = #gtt_act_repl_digits{replace_digit_start = 1, replace_digit_end = 4, new_digits = [5,6,7,8]},
61 Act2 = #gtt_act_repl_num_plan{numbering_plan = 3},
62 Rules = [{Match, [Act1, Act2]}],
63 ReplGt = osmo_ss7_gtt:execute_gtt(Gt, Rules),
64 ?assertEqual(ReplGt, Gt#global_title{phone_number = [5,6,7,8,0,0,0,1], numbering_plan = 3}).
65
66
67execute_gtts_test() ->
68 Gt = #global_title{phone_number = [1,2,3,4,0,0,0,1], numbering_plan = 4},
69 SccpAddr = #sccp_addr{point_code = 23, ssn = 42, global_title = Gt},
70 Match = #gtt_match{gt_range_from = 12340000, gt_range_to = 12350000, dpc = 23},
71 % build list of two actions to perform
72 Act1 = #gtt_act_repl_digits{replace_digit_start = 1, replace_digit_end = 4, new_digits = [5,6,7,8]},
73 Act2 = #gtt_act_repl_num_plan{numbering_plan = 3},
74 Rules = [{Match, [Act1, Act2]}],
75 % compute the expected result
76 ExpGt = Gt#global_title{phone_number = [5,6,7,8,0,0,0,1], numbering_plan = 3},
77 ExpSccp = SccpAddr#sccp_addr{global_title = ExpGt},
78 ReplSccp = osmo_ss7_gtt:execute_gtt(SccpAddr, Rules),
79 ?assertEqual(ExpSccp, ReplSccp).