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

« back to all changes in this revision

Viewing changes to lib/cosTransactions/test/etrap_test_lib.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 1999-2010. 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(etrap_test_lib).
 
22
 
 
23
%%--------------- INCLUDES ---------------------------------------------
 
24
-include("etrap_test_lib.hrl").
 
25
-include_lib("cosTransactions/src/ETraP_Common.hrl").
 
26
 
 
27
%%--------------- EXPORTS ----------------------------------------------
 
28
-export([scratch_debug_fun/0,
 
29
         activate_debug_fun/5,
 
30
         update_debug_info/1,
 
31
         deactivate_debug_fun/3,
 
32
         eval_debug_fun/4,
 
33
         set_debug_context/4]).
 
34
 
 
35
%%--------------- CONSTANTS/DEFINITIONS --------------------------------
 
36
-define(DEBUG_TAB, etrap_debug).
 
37
-record(debug_info, {id, function, type, file, line}).
 
38
 
 
39
%%--------------- DEBUG FUNCTIONS --------------------------------------
 
40
%% Managing conditional debug functions
 
41
%%
 
42
%% The main idea with the debug_fun's is to allow test programs
 
43
%% to control the internal behaviour of CosTransactions. 
 
44
%%
 
45
%% First should calls to ?eval_debug_fun be inserted at well
 
46
%% defined places in CosTransaction's code. E.g. in critical situations
 
47
%% of startup, transaction commit, backups etc.
 
48
%%
 
49
%% Then compile CosTransactions with the compiler option 'debug'.
 
50
%%
 
51
%% In test programs ?activate_debug_fun should be called
 
52
%% in order to bind a fun to the debug identifier stated
 
53
%% in the call to ?eval_debug_fun.
 
54
 
 
55
scratch_debug_fun() ->
 
56
    catch ets:delete(?DEBUG_TAB),
 
57
    ets:new(?DEBUG_TAB,
 
58
            [set, public, named_table, {keypos, 2}]).
 
59
 
 
60
activate_debug_fun(FunId, Fun, Type, File, Line) ->
 
61
    io:format("Activiating ~p   RETRIES: ~p  WAIT: ~p~n", 
 
62
              [FunId, ?tr_max_retries, ?tr_comm_failure_wait]),
 
63
    Info = #debug_info{id = FunId,
 
64
                       function = Fun,
 
65
                       type = Type,
 
66
                       file = File,
 
67
                       line = Line},
 
68
    update_debug_info(Info).
 
69
 
 
70
update_debug_info(Info) ->
 
71
    case catch ets:insert(?DEBUG_TAB, Info) of
 
72
        {'EXIT', _} ->
 
73
            scratch_debug_fun(),
 
74
            ets:insert(?DEBUG_TAB, Info);
 
75
        _ ->
 
76
            ok
 
77
    end,
 
78
    ok.
 
79
 
 
80
deactivate_debug_fun(FunId, _File, _Line) ->
 
81
    catch ets:delete(?DEBUG_TAB, FunId),
 
82
    ok.
 
83
 
 
84
eval_debug_fun(FunId, Env, File, Line) ->
 
85
    case catch ets:lookup(?DEBUG_TAB, FunId) of
 
86
        [] ->
 
87
            ok;
 
88
        [Info] ->
 
89
            Fun = Info#debug_info.function,
 
90
            case Info#debug_info.type of
 
91
                transient ->
 
92
                    deactivate_debug_fun(FunId, File, Line);
 
93
                _->
 
94
                    ok
 
95
            end,
 
96
            io:format("Running debug fun ~p:~p (LINE: ~p)~n", [File, FunId, Line]),
 
97
            Fun(Env);
 
98
        {'EXIT', _R} -> 
 
99
            ok    
 
100
    end.
 
101
 
 
102
 
 
103
set_debug_context([], [], _, _)-> ok;
 
104
set_debug_context([], _, _, _)->
 
105
    ets:delete(?DEBUG_TAB),
 
106
    exit("failed transactions_SUITE. Bad configuration.");
 
107
set_debug_context(_, [], _, _)->
 
108
    ets:delete(?DEBUG_TAB),
 
109
    exit("failed transactions_SUITE Bad configuration.");
 
110
set_debug_context([RHead|RTail], [CHead|CTail], File, Line)->
 
111
    write_context(RHead, CHead, File, Line),
 
112
    set_debug_context(RTail, CTail, File, Line).
 
113
 
 
114
write_context(_Resource, [], _, _)-> ok;
 
115
write_context(Resource, [{Func, Fun, Type}|PTail], File, Line)->
 
116
    etrap_test_lib:activate_debug_fun({Resource, Func}, 
 
117
                                      Fun, Type, 
 
118
                                      File, Line),
 
119
    write_context(Resource, PTail, File, Line);
 
120
write_context(_,_, _, _) ->
 
121
    ets:delete(?DEBUG_TAB),
 
122
    exit("failed transactions_SUITE. Bad configuration.").
 
123
 
 
124
 
 
125
%%--------------- END OF MODULE ----------------------------------------