~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/asn1/test/testMegaco.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
-module(testMegaco).
 
22
 
 
23
-export([compile/3,main/2,msg11/0]).
 
24
 
 
25
-include("test_server.hrl").
 
26
-define(MID, {ip4Address, #'IP4Address'{address = [124, 124, 124, 222],
 
27
                                            portNumber = 55555}}).
 
28
-define(A4444, ["11111111"]).
 
29
 
 
30
-record('MegacoMessage',
 
31
        {
 
32
          authHeader = asn1_NOVALUE,
 
33
          mess
 
34
         }).
 
35
 
 
36
-record('Message',
 
37
        {
 
38
          version, 
 
39
          mId, 
 
40
          messageBody
 
41
         }). % with extension mark
 
42
 
 
43
-record('IP4Address',
 
44
        {
 
45
          address,
 
46
          portNumber = asn1_NOVALUE
 
47
         }).
 
48
 
 
49
-record('TransactionRequest',
 
50
        {
 
51
          transactionId, 
 
52
          actions = []
 
53
         }). % with extension mark
 
54
 
 
55
-record('ActionRequest',
 
56
        {
 
57
          contextId, 
 
58
          contextRequest = asn1_NOVALUE, 
 
59
          contextAttrAuditReq = asn1_NOVALUE, 
 
60
          commandRequests = []
 
61
         }).
 
62
 
 
63
-record('CommandRequest',
 
64
        {
 
65
          command, 
 
66
          optional = asn1_NOVALUE, 
 
67
          wildcardReturn = asn1_NOVALUE
 
68
         }). % with extension mark
 
69
 
 
70
-record('NotifyRequest',
 
71
        {
 
72
          terminationID, 
 
73
          observedEventsDescriptor, 
 
74
          errorDescriptor = asn1_NOVALUE
 
75
         }). % with extension mark
 
76
 
 
77
-record('ObservedEventsDescriptor',
 
78
        {
 
79
          requestId, 
 
80
          observedEventLst = []
 
81
         }).
 
82
 
 
83
-record('ObservedEvent',
 
84
        {
 
85
          eventName, 
 
86
          streamID = asn1_NOVALUE, 
 
87
          eventParList = [], 
 
88
          timeNotation = asn1_NOVALUE
 
89
         }). % with extension mark
 
90
 
 
91
-record('EventParameter',
 
92
        {
 
93
          eventParameterName, 
 
94
          value
 
95
         }).
 
96
 
 
97
-record('TimeNotation',
 
98
        {
 
99
          date, 
 
100
          time
 
101
         }).
 
102
 
 
103
-record(megaco_term_id, {contains_wildcards = ["f"], id}).
 
104
 
 
105
 
 
106
compile(_Config,ber,[optimize]) ->
 
107
    {ok,no_module,no_module};
 
108
compile(_Config,per,[optimize]) ->
 
109
    {ok,no_module,no_module};
 
110
compile(Config,Erule,Options) ->
 
111
    ?line DataDir = ?config(data_dir,Config),
 
112
    ?line OutDir = ?config(priv_dir,Config),
 
113
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
114
 
 
115
    ?line ok = asn1ct:compile(DataDir ++ 
 
116
                              "MEDIA-GATEWAY-CONTROL.asn",
 
117
                              [Erule,{outdir,OutDir}]++Options),
 
118
    
 
119
    ?line ok = asn1ct:compile(DataDir ++ 
 
120
                              "OLD-MEDIA-GATEWAY-CONTROL.asn",
 
121
                              [Erule,{outdir,OutDir}]++Options),
 
122
    {ok,'OLD-MEDIA-GATEWAY-CONTROL','MEDIA-GATEWAY-CONTROL'}.
 
123
 
 
124
 
 
125
main(no_module,_) -> ok;
 
126
main('OLD-MEDIA-GATEWAY-CONTROL',_) ->
 
127
%    Msg = msg11(),
 
128
    {ok,Msg} = asn1ct:value('OLD-MEDIA-GATEWAY-CONTROL','MegacoMessage'),
 
129
    ?line {ok,Bytes} = asn1_wrapper:encode('OLD-MEDIA-GATEWAY-CONTROL',
 
130
                                           'MegacoMessage',Msg),
 
131
    ?line {ok,Msg} = asn1_wrapper:decode('OLD-MEDIA-GATEWAY-CONTROL',
 
132
                                         'MegacoMessage',
 
133
                                         Bytes),
 
134
    ok;
 
135
main(Mod='MEDIA-GATEWAY-CONTROL',Config) ->
 
136
    ?line DataDir = ?config(data_dir,Config),
 
137
    io:format("DataDir:~p~n",[DataDir]),
 
138
    ?line {ok,FilenameList} = file:list_dir(filename:join([DataDir,
 
139
                                                           megacomessages])),
 
140
    %% remove any junk files that may be in the megacomessage directory
 
141
    Pred = fun(X) ->
 
142
                   case lists:reverse(X) of
 
143
                       [$l,$a,$v,$.|_R] ->true;
 
144
                       _ -> false
 
145
                   end
 
146
           end,
 
147
    MegacoMsgFilenameList = lists:filter(Pred,FilenameList),
 
148
 
 
149
    Fun = fun(F) ->
 
150
                  M = read_msg(filename:join([DataDir,megacomessages,F])),
 
151
                  {ok,B} = asn1_wrapper:encode(Mod,element(1,M),M),
 
152
                  {ok,M} = asn1_wrapper:decode(Mod,element(1,M),B)
 
153
          end,
 
154
    ?line lists:foreach(Fun,MegacoMsgFilenameList),
 
155
    ok.
 
156
 
 
157
read_msg(File) ->
 
158
    case file:read_file(File) of
 
159
        {ok,Bin} ->
 
160
            binary_to_term(Bin);
 
161
        _ -> 
 
162
            io:format("couldn't read file ~p~n",[File])
 
163
    end.
 
164
 
 
165
 
 
166
request(Mid, TransId, ContextId, CmdReq) when list(CmdReq) ->
 
167
    Actions = [#'ActionRequest'{contextId = ContextId,
 
168
                                commandRequests = CmdReq}],
 
169
    Req = {transactions,
 
170
           [{transactionRequest,
 
171
             #'TransactionRequest'{transactionId = TransId,
 
172
                                   actions = Actions}}]},
 
173
    #'MegacoMessage'{mess = #'Message'{version = 1,
 
174
                                       mId = Mid,
 
175
                                       messageBody = Req}}.
 
176
 
 
177
msg11() ->
 
178
    TimeStamp = #'TimeNotation'{date = "19990729",
 
179
                                time = "22010001"},
 
180
    Parm = #'EventParameter'{eventParameterName = "ds",
 
181
                             value = "916135551212"},
 
182
 
 
183
    Event = #'ObservedEvent'{eventName = "ddce",
 
184
                             timeNotation = TimeStamp,
 
185
                             eventParList = [Parm]},
 
186
    Desc = #'ObservedEventsDescriptor'{requestId = 2223,
 
187
                                       observedEventLst = [Event]},
 
188
    NotifyReq = #'NotifyRequest'{terminationID = [#megaco_term_id{id = ?A4444}],
 
189
                                 observedEventsDescriptor = Desc},
 
190
    CmdReq = #'CommandRequest'{command = {notifyReq, NotifyReq}},
 
191
    request(?MID, 10002, 0, [CmdReq]).