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

« back to all changes in this revision

Viewing changes to lib/common_test/src/ct_hooks_lock.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2004-2011. 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
%%% @doc Common Test Framework test execution control module.
 
21
%%%
 
22
%%% <p>This module is a proxy for calling and handling locks in 
 
23
%%%    common test hooks.</p>
 
24
 
 
25
-module(ct_hooks_lock).
 
26
 
 
27
-behaviour(gen_server).
 
28
 
 
29
%% API
 
30
-export([start/1, stop/1, request/0, release/0]).
 
31
 
 
32
%% gen_server callbacks
 
33
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
 
34
         terminate/2, code_change/3]).
 
35
 
 
36
-define(SERVER, ?MODULE). 
 
37
 
 
38
-record(state, { id, locked = false, requests = [] }).
 
39
 
 
40
%%%===================================================================
 
41
%%% API
 
42
%%%===================================================================
 
43
 
 
44
%% @doc Starts the server
 
45
start(Id) ->
 
46
    case gen_server:start({local, ?SERVER}, ?MODULE, Id, []) of
 
47
        {error,{already_started, Pid}} ->
 
48
            {ok,Pid};
 
49
        Else ->
 
50
            Else
 
51
    end.
 
52
 
 
53
stop(Id) ->
 
54
    try
 
55
        gen_server:call(?SERVER, {stop,Id})
 
56
    catch exit:{noproc,_} ->
 
57
            stopped
 
58
    end.
 
59
    
 
60
request() ->
 
61
    try
 
62
        gen_server:call(?SERVER,{request,self()},infinity)
 
63
    catch exit:{noproc,_} ->
 
64
            locked
 
65
    end.
 
66
 
 
67
release() ->
 
68
    try
 
69
        gen_server:call(?SERVER,{release,self()})
 
70
    catch exit:{noproc,_} ->
 
71
            unlocked
 
72
    end.
 
73
 
 
74
%%%===================================================================
 
75
%%% gen_server callbacks
 
76
%%%===================================================================
 
77
 
 
78
%% @doc Initiates the server
 
79
init(Id) ->
 
80
    {ok, #state{ id = Id }}.
 
81
 
 
82
%% @doc Handling call messages
 
83
handle_call({stop,Id}, _From, #state{ id = Id, requests = Reqs } = State) ->
 
84
    [gen_server:reply(Req, locker_stopped) || {Req,_ReqId} <- Reqs],
 
85
    {stop, normal, stopped, State};
 
86
handle_call({stop,_Id}, _From, State) ->
 
87
    {reply, stopped, State};
 
88
handle_call({request, Pid}, _From, #state{ locked = false,
 
89
                                          requests = [] } = State) ->
 
90
    Ref = monitor(process, Pid),
 
91
    {reply, locked, State#state{ locked = {true, Pid, Ref}} };
 
92
handle_call({request, Pid}, From, #state{ requests = Reqs } = State) ->
 
93
    {noreply, State#state{ requests = Reqs ++ [{From,Pid}] }};
 
94
handle_call({release, Pid}, _From, #state{ locked = {true, Pid, Ref},
 
95
                                          requests = []} = State) ->
 
96
    demonitor(Ref,[flush]),
 
97
    {reply, unlocked, State#state{ locked = false }};
 
98
handle_call({release, Pid}, _From,
 
99
            #state{ locked = {true, Pid, Ref},
 
100
                    requests = [{NextFrom,NextPid}|Rest]} = State) ->
 
101
    demonitor(Ref,[flush]),
 
102
    gen_server:reply(NextFrom,locked),
 
103
    NextRef = monitor(process, NextPid),
 
104
    {reply,unlocked,State#state{ locked = {true, NextPid, NextRef},
 
105
                                 requests = Rest } };
 
106
handle_call({release, _Pid}, _From, State) ->
 
107
    {reply, not_locked, State}.
 
108
    
 
109
%% @doc Handling cast messages
 
110
handle_cast(_Msg, State) ->
 
111
    {noreply, State}.
 
112
 
 
113
%% @doc Handling all non call/cast messages
 
114
handle_info({'DOWN',Ref,process,Pid,_},
 
115
            #state{ locked = {true, Pid, Ref},
 
116
                    requests = [{NextFrom,NextPid}|Rest] } = State) ->
 
117
    gen_server:reply(NextFrom, locked),
 
118
    NextRef = monitor(process, NextPid),
 
119
    {noreply,State#state{ locked = {true, NextPid, NextRef},
 
120
                          requests = Rest } }.
 
121
 
 
122
%% @doc This function is called by a gen_server when it is about to terminate. 
 
123
terminate(_Reason, _State) ->
 
124
    ok.
 
125
 
 
126
%% @doc Convert process state when code is changed
 
127
code_change(_OldVsn, State, _Extra) ->
 
128
    {ok, State}.
 
129
 
 
130
%% -------------------------------------------------------------------------
 
131
%% Internal Functions
 
132
%% -------------------------------------------------------------------------