~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_name.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%%
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%%
 
16
%%     $Id: asn1ct_name.erl,v 1.1 2008/12/17 09:53:30 mikpe Exp $
 
17
%%
 
18
-module(asn1ct_name).
 
19
 
 
20
%%-compile(export_all).
 
21
-export([name_server_loop/1,
 
22
         start/0,
 
23
         stop/0,
 
24
         push/1,
 
25
         pop/1,
 
26
         curr/1,
 
27
         clear/0,
 
28
         delete/1,
 
29
         active/1,
 
30
         prev/1,
 
31
         next/1,
 
32
         all/1,
 
33
         new/1]).
 
34
 
 
35
start() ->
 
36
    start_server(asn1_ns, asn1ct_name,name_server_loop,[[]]).
 
37
 
 
38
stop() -> stop_server(asn1_ns).
 
39
 
 
40
name_server_loop(Vars) ->
 
41
%%    io:format("name -- ~w~n",[Vars]),
 
42
    receive
 
43
        {From,{current,Variable}} ->
 
44
            From ! {asn1_ns,get_curr(Vars,Variable)},
 
45
            name_server_loop(Vars);
 
46
        {From,{pop,Variable}} ->
 
47
            From ! {asn1_ns,done},
 
48
            name_server_loop(pop_var(Vars,Variable));
 
49
        {From,{push,Variable}} ->
 
50
            From ! {asn1_ns,done},
 
51
            name_server_loop(push_var(Vars,Variable));
 
52
        {From,{delete,Variable}} ->
 
53
            From ! {asn1_ns,done},
 
54
            name_server_loop(delete_var(Vars,Variable));
 
55
        {From,{new,Variable}} ->
 
56
            From ! {asn1_ns,done},
 
57
            name_server_loop(new_var(Vars,Variable));
 
58
        {From,{prev,Variable}} ->
 
59
            From ! {asn1_ns,get_prev(Vars,Variable)},
 
60
            name_server_loop(Vars);
 
61
        {From,{next,Variable}} ->
 
62
            From ! {asn1_ns,get_next(Vars,Variable)},
 
63
            name_server_loop(Vars);
 
64
        {From,stop} ->
 
65
            From ! {asn1_ns,stopped},
 
66
            exit(normal)
 
67
    end.
 
68
 
 
69
active(V) ->
 
70
    case curr(V) of
 
71
        nil -> false;
 
72
        _ -> true
 
73
    end.
 
74
 
 
75
req(Req) ->
 
76
    asn1_ns ! {self(), Req},
 
77
    receive {asn1_ns, Reply} -> Reply end.
 
78
 
 
79
pop(V) ->     req({pop,V}).
 
80
push(V) ->         req({push,V}).
 
81
clear() ->     req(stop), start().
 
82
curr(V) ->     req({current,V}).
 
83
new(V) ->      req({new,V}).
 
84
delete(V) ->   req({delete,V}).
 
85
prev(V) ->
 
86
    case req({prev,V}) of
 
87
        none ->
 
88
            exit('cant get prev of none');
 
89
        Rep -> Rep
 
90
    end.
 
91
 
 
92
next(V) ->
 
93
    case req({next,V}) of
 
94
        none ->
 
95
            exit('cant get next of none');
 
96
        Rep -> Rep
 
97
    end.
 
98
 
 
99
all(V) ->
 
100
    Curr = curr(V),
 
101
    if Curr == V -> [];
 
102
        true ->
 
103
            lists:reverse(generate(V,last(Curr),[],0))
 
104
    end.
 
105
 
 
106
generate(V,Number,Res,Pos) ->
 
107
    Ell = Pos+1,
 
108
    if
 
109
        Ell > Number ->
 
110
            Res;
 
111
        true ->
 
112
            generate(V,Number,[list_to_atom(lists:concat([V,Ell]))|Res],Ell)
 
113
    end.
 
114
 
 
115
last(V) ->
 
116
    last2(lists:reverse(atom_to_list(V))).
 
117
 
 
118
last2(RevL) ->
 
119
    list_to_integer(lists:reverse(get_digs(RevL))).
 
120
 
 
121
 
 
122
get_digs([H|T]) ->
 
123
    if
 
124
        H < $9+1,
 
125
        H > $0-1 ->
 
126
            [H|get_digs(T)];
 
127
        true ->
 
128
            []
 
129
    end.
 
130
 
 
131
push_var(Vars,Variable) ->
 
132
    case lists:keysearch(Variable,1,Vars) of
 
133
        false ->
 
134
            [{Variable,[0]}|Vars];
 
135
        {value,{Variable,[Digit|Drest]}} ->
 
136
            NewVars = lists:keydelete(Variable,1,Vars),
 
137
            [{Variable,[Digit,Digit|Drest]}|NewVars]
 
138
    end.
 
139
 
 
140
pop_var(Vars,Variable) ->
 
141
    case lists:keysearch(Variable,1,Vars) of
 
142
        false ->
 
143
            ok;
 
144
        {value,{Variable,[_Dig]}} ->
 
145
            lists:keydelete(Variable,1,Vars);
 
146
        {value,{Variable,[_Dig|Digits]}} ->
 
147
            NewVars = lists:keydelete(Variable,1,Vars),
 
148
            [{Variable,Digits}|NewVars]
 
149
    end.
 
150
 
 
151
get_curr([],Variable) ->
 
152
    Variable;
 
153
get_curr([{Variable,[0|_Drest]}|_Tail],Variable) ->
 
154
    Variable;
 
155
get_curr([{Variable,[Digit|_Drest]}|_Tail],Variable) ->
 
156
    list_to_atom(lists:concat([Variable,integer_to_list(Digit)]));
 
157
 
 
158
get_curr([_|Tail],Variable) ->
 
159
    get_curr(Tail,Variable).
 
160
 
 
161
new_var(Vars,Variable) ->
 
162
    case lists:keysearch(Variable,1,Vars) of
 
163
        false ->
 
164
            [{Variable,[1]}|Vars];
 
165
        {value,{Variable,[Digit|Drest]}} ->
 
166
            NewVars = lists:keydelete(Variable,1,Vars),
 
167
            [{Variable,[Digit+1|Drest]}|NewVars]
 
168
    end.
 
169
 
 
170
delete_var(Vars,Variable) ->
 
171
    case lists:keysearch(Variable,1,Vars) of
 
172
        false ->
 
173
            Vars;
 
174
        {value,{Variable,[N]}} when N =< 1  ->
 
175
            lists:keydelete(Variable,1,Vars);
 
176
        {value,{Variable,[Digit|Drest]}} ->
 
177
            case Digit of
 
178
                0 ->
 
179
                    Vars;
 
180
                _ ->
 
181
                    NewVars = lists:keydelete(Variable,1,Vars),
 
182
                    [{Variable,[Digit-1|Drest]}|NewVars]
 
183
            end
 
184
    end.
 
185
 
 
186
get_prev(Vars,Variable) ->
 
187
    case lists:keysearch(Variable,1,Vars) of
 
188
        false ->
 
189
            none;
 
190
        {value,{Variable,[Digit|_]}} when Digit =< 1 ->
 
191
            Variable;
 
192
        {value,{Variable,[Digit|_]}} when Digit > 1 ->
 
193
            list_to_atom(lists:concat([Variable,
 
194
                                       integer_to_list(Digit-1)]));
 
195
        _ ->
 
196
            none
 
197
    end.
 
198
 
 
199
get_next(Vars,Variable) ->
 
200
    case lists:keysearch(Variable,1,Vars) of
 
201
        false ->
 
202
            list_to_atom(lists:concat([Variable,"1"]));
 
203
        {value,{Variable,[Digit|_]}} when Digit >= 0 ->
 
204
            list_to_atom(lists:concat([Variable,
 
205
                                       integer_to_list(Digit+1)]));
 
206
        _ ->
 
207
            none
 
208
    end.
 
209
 
 
210
 
 
211
stop_server(Name) ->
 
212
    stop_server(Name, whereis(Name)).
 
213
stop_server(_Name, undefined) -> stopped;
 
214
stop_server(Name, _Pid) ->
 
215
    Name  ! {self(), stop},
 
216
    receive {Name, _} -> stopped end.
 
217
 
 
218
 
 
219
start_server(Name,Mod,Fun,Args) ->
 
220
    case whereis(Name) of
 
221
        undefined ->
 
222
            register(Name, spawn(Mod,Fun, Args));
 
223
        _Pid ->
 
224
            already_started
 
225
    end.