~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1_server.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

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$
 
17
%%
 
18
 
 
19
%% Purpose: Provide complete encode/and pre-decode of asn1.
 
20
-module(asn1_server).
 
21
 
 
22
 
 
23
 
 
24
-behaviour(gen_server).
 
25
 
 
26
-export([start_link/0,client_port/0]).
 
27
 
 
28
%% Internal exports, call-back functions.
 
29
-export([init/1,handle_call/3,handle_cast/2,handle_info/2,code_change/3,
 
30
         terminate/2]).
 
31
 
 
32
 
 
33
%% Macros
 
34
-define(port_names,
 
35
        { asn1_drv01, asn1_drv02, asn1_drv03, asn1_drv04,
 
36
          asn1_drv05, asn1_drv06, asn1_drv07, asn1_drv08,
 
37
          asn1_drv09, asn1_drv10, asn1_drv11, asn1_drv12,
 
38
          asn1_drv13, asn1_drv14, asn1_drv15, asn1_drv16 }).
 
39
%%% --------------------------------------------------------
 
40
%%% Interface Functions. 
 
41
%%% --------------------------------------------------------
 
42
 
 
43
start_link() ->
 
44
    gen_server:start_link({local, asn1_server}, asn1_server, [], []).
 
45
 
 
46
init([]) ->
 
47
    process_flag(trap_exit, true),
 
48
    erl_ddll:start(),
 
49
    PrivDir = code:priv_dir(asn1),
 
50
    LibDir1 = filename:join([PrivDir, "lib"]),
 
51
    case erl_ddll:load_driver(LibDir1, asn1_erl_drv) of
 
52
        ok -> ok;
 
53
        {error,_} ->
 
54
            LibDir2 = 
 
55
                filename:join(LibDir1, 
 
56
                              erlang:system_info(system_architecture)),
 
57
            erl_ddll:load_driver(LibDir2, asn1_erl_drv)
 
58
    end,
 
59
    open_ports("asn1_erl_drv",size(?port_names)).
 
60
 
 
61
open_ports(_,0) ->
 
62
    {ok, []};
 
63
open_ports(Cmd,N) ->   
 
64
    Port = open_port({spawn, Cmd}, []),
 
65
    %% check that driver is loaded, linked and working
 
66
    case catch port_control(Port, 0, []) of
 
67
        {'EXIT', _} ->
 
68
            {stop, nodriver};
 
69
        _ ->
 
70
            register(element(N,?port_names), Port),
 
71
            open_ports(Cmd,N-1)
 
72
    end.
 
73
 
 
74
client_port() ->
 
75
    element(erlang:system_info(scheduler_id) rem size(?port_names) + 1,
 
76
            ?port_names).
 
77
 
 
78
 
 
79
%%% --------------------------------------------------------
 
80
%%% The call-back functions.
 
81
%%% --------------------------------------------------------
 
82
 
 
83
handle_call(_, _, State) ->
 
84
    {noreply, State}.
 
85
 
 
86
handle_cast(_, State) ->
 
87
    {noreply, State}.
 
88
 
 
89
handle_info({'EXIT', Pid, _Reason}, State) when is_pid(Pid) ->
 
90
    {noreply, State};
 
91
 
 
92
handle_info({'EXIT', Port, Reason}, State) when is_port(Port) ->
 
93
    {stop, {port_died, Reason}, State};
 
94
handle_info(_, State) ->
 
95
    {noreply, State}.
 
96
 
 
97
code_change(_OldVsn, State, _Extra) ->
 
98
    {ok, State}.
 
99
 
 
100
terminate(_Reason, _State) ->
 
101
    close_ports(size(?port_names)).
 
102
 
 
103
close_ports(0) ->
 
104
    ok;
 
105
close_ports(N) ->   
 
106
    element(N,?port_names) ! {self(), close}, %% almost same as port_close(Name)
 
107
    close_ports(N-1).