~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/asn1/asn1_db.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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: asn1_db.erl,v 1.1 2008/12/17 09:53:29 mikpe Exp $
 
17
%%
 
18
-module(asn1_db).
 
19
%-compile(export_all).
 
20
-export([dbnew/1,dbsave/2,dbload/1,dbput/3,dbget/2,dbget_all/1]).
 
21
-export([dbget_all_mod/1,dbstop/0,dbclear/0,dberase_module/1,dbstart/1,stop_server/1]).
 
22
%% internal exports
 
23
-export([dbloop0/1,dbloop/2]).
 
24
 
 
25
%% Db stuff
 
26
dbstart(Includes) ->    
 
27
    start_server(asn1db, asn1_db, dbloop0, [Includes]).
 
28
 
 
29
dbloop0(Includes) ->
 
30
    dbloop(Includes, ets:new(asn1, [set,named_table])).
 
31
        
 
32
opentab(Tab,Mod,[]) ->
 
33
    opentab(Tab,Mod,["."]);
 
34
opentab(Tab,Mod,Includes) ->
 
35
    Base = lists:concat([Mod,".asn1db"]),
 
36
    opentab2(Tab,Base,Mod,Includes,ok).
 
37
 
 
38
opentab2(_Tab,_Base,_Mod,[],Error) ->
 
39
    Error;
 
40
opentab2(Tab,Base,Mod,[Ih|It],_Error) ->
 
41
    File = filename:join(Ih,Base),
 
42
    case ets:file2tab(File) of
 
43
        {ok,Modtab} ->
 
44
            ets:insert(Tab,{Mod, Modtab}),
 
45
            {ok,Modtab};
 
46
        NewErr -> 
 
47
            opentab2(Tab,Base,Mod,It,NewErr)
 
48
    end.
 
49
 
 
50
 
 
51
dbloop(Includes, Tab) ->
 
52
    receive
 
53
        {From,{set, Mod, K2, V}} ->
 
54
            [{_,Modtab}] = ets:lookup(Tab,Mod),
 
55
            ets:insert(Modtab,{K2, V}),
 
56
            From ! {asn1db, ok},
 
57
            dbloop(Includes, Tab);
 
58
        {From, {get, Mod, K2}} ->
 
59
            Result = case ets:lookup(Tab,Mod) of
 
60
                         [] -> 
 
61
                             opentab(Tab,Mod,Includes);
 
62
                         [{_,Modtab}] -> {ok,Modtab}
 
63
                     end,
 
64
            case Result of
 
65
                {ok,Newtab} ->
 
66
                    From ! {asn1db, lookup(Newtab, K2)};
 
67
                _Error ->
 
68
                    From ! {asn1db, undefined}
 
69
            end,
 
70
            dbloop(Includes, Tab);
 
71
        {From, {all_mod, Mod}} ->
 
72
            [{_,Modtab}] = ets:lookup(Tab,Mod),
 
73
            From ! {asn1db, ets:tab2list(Modtab)},
 
74
            dbloop(Includes, Tab);
 
75
        {From, {delete_mod, Mod}} ->
 
76
            [{_,Modtab}] = ets:lookup(Tab,Mod),
 
77
            ets:delete(Modtab),
 
78
            ets:delete(Tab,Mod),
 
79
            From ! {asn1db, ok},
 
80
            dbloop(Includes, Tab);
 
81
        {From, {save, OutFile,Mod}} ->
 
82
            [{_,Mtab}] = ets:lookup(Tab,Mod),
 
83
            {From ! {asn1db, ets:tab2file(Mtab,OutFile)}},
 
84
            dbloop(Includes,Tab);
 
85
        {From, {load, Mod}} ->
 
86
            Result = case ets:lookup(Tab,Mod) of
 
87
                         [] -> 
 
88
                             opentab(Tab,Mod,Includes);
 
89
                         [{_,Modtab}] -> {ok,Modtab}
 
90
                     end,
 
91
            {From, {asn1db,Result}},
 
92
            dbloop(Includes,Tab);
 
93
        {From, {new, Mod}} ->
 
94
            case ets:lookup(Tab,Mod) of
 
95
                [{_,Modtab}] -> 
 
96
                    ets:delete(Modtab);
 
97
                _  ->
 
98
                    true
 
99
            end,
 
100
            Tabname = list_to_atom(lists:concat(["asn1_",Mod])),
 
101
            ets:new(Tabname, [set,named_table]),
 
102
            ets:insert(Tab,{Mod,Tabname}),
 
103
            From ! {asn1db, ok},
 
104
            dbloop(Includes,Tab);
 
105
        {From, stop} ->
 
106
                    From ! {asn1db, ok};  %% nothing to store
 
107
        {From, clear} ->
 
108
            ModTabList = [Mt||{_,Mt} <- ets:tab2list(Tab)],
 
109
            lists:foreach(fun(T) -> ets:delete(T) end,ModTabList),
 
110
            ets:delete(Tab),
 
111
            From ! {asn1db, cleared},
 
112
            dbloop(Includes, ets:new(asn1, [set]))
 
113
    end.
 
114
 
 
115
 
 
116
%%all(Tab, K) ->
 
117
%%    pickup(K, ets:match(Tab, {{K, '$1'}, '$2'})).
 
118
%%pickup(K, []) -> [];
 
119
%%pickup(K, [[V1,V2] |T]) ->
 
120
%%    [{{K,V1},V2} | pickup(K, T)].
 
121
 
 
122
lookup(Tab, K) ->
 
123
    case ets:lookup(Tab, K) of
 
124
        [] -> undefined;
 
125
        [{K,V}] -> V
 
126
    end.
 
127
 
 
128
 
 
129
dbnew(Module) -> req({new,Module}).
 
130
dbsave(OutFile,Module) -> req({save,OutFile,Module}).
 
131
dbload(Module) -> req({load,Module}).
 
132
    
 
133
dbput(Module,K,V) -> req({set, Module, K, V}).
 
134
dbget(Module,K) ->   req({get, Module, K}).
 
135
dbget_all(K) ->   req({get_all, K}).
 
136
dbget_all_mod(Mod) -> req({all_mod,Mod}).
 
137
dbstop() ->       stop_server(asn1db).
 
138
dbclear() ->      req(clear).
 
139
dberase_module({module,M})->  
 
140
    req({delete_mod, M}).
 
141
 
 
142
req(R) ->
 
143
    asn1db ! {self(), R},
 
144
    receive {asn1db, Reply} -> Reply end.
 
145
 
 
146
stop_server(Name) ->
 
147
    stop_server(Name, whereis(Name)).
 
148
stop_server(_, undefined) -> stopped;
 
149
stop_server(Name, _Pid) ->
 
150
    Name  ! {self(), stop},
 
151
    receive {Name, _} -> stopped end.
 
152
 
 
153
 
 
154
start_server(Name,Mod,Fun,Args) ->      
 
155
    case whereis(Name) of
 
156
        undefined ->
 
157
            register(Name, spawn(Mod,Fun, Args));
 
158
        _Pid ->
 
159
            already_started
 
160
    end.
 
161
 
 
162