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

« back to all changes in this revision

Viewing changes to lib/tools/test/ignore_cores.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 2008-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
%%% File    : ignore_cores.erl
 
22
%%% Author  : Rickard Green <rickard.s.green@ericsson.com>
 
23
%%% Description : 
 
24
%%%
 
25
%%% Created : 11 Feb 2008 by Rickard Green <rickard.s.green@ericsson.com>
 
26
%%%-------------------------------------------------------------------
 
27
 
 
28
-module(ignore_cores).
 
29
 
 
30
-include_lib("test_server/include/test_server.hrl").
 
31
 
 
32
-export([init/1, fini/1, setup/3, setup/4, restore/1, dir/1]).
 
33
 
 
34
-record(ignore_cores, {org_cwd,
 
35
                       org_path,
 
36
                       org_pwd_env,
 
37
                       ign_dir = false,
 
38
                       cores_dir = false}).
 
39
 
 
40
%%
 
41
%% Takes a testcase config
 
42
%%
 
43
 
 
44
init(Config) ->
 
45
    {ok, OrgCWD} = file:get_cwd(),
 
46
    [{ignore_cores,
 
47
      #ignore_cores{org_cwd = OrgCWD,
 
48
                    org_path = code:get_path(),
 
49
                    org_pwd_env = os:getenv("PWD")}}
 
50
     | lists:keydelete(ignore_cores, 1, Config)].
 
51
    
 
52
fini(Config) ->
 
53
    #ignore_cores{org_cwd = OrgCWD,
 
54
                  org_path = OrgPath,
 
55
                  org_pwd_env = OrgPWD} = ?config(ignore_cores, Config),
 
56
    ok = file:set_cwd(OrgCWD),
 
57
    true = code:set_path(OrgPath),
 
58
    case OrgPWD of
 
59
        false -> ok;
 
60
        _ -> true = os:putenv("PWD", OrgPWD)
 
61
    end,
 
62
    lists:keydelete(ignore_cores, 1, Config).
 
63
 
 
64
setup(Suite, Testcase, Config) ->
 
65
    setup(Suite, Testcase, Config, false).
 
66
 
 
67
setup(Suite, Testcase, Config, SetCwd) when is_atom(Suite), 
 
68
                                            is_atom(Testcase),
 
69
                                            is_list(Config) ->
 
70
    #ignore_cores{org_cwd = OrgCWD,
 
71
                  org_path = OrgPath,
 
72
                  org_pwd_env = OrgPWD} = ?config(ignore_cores, Config),
 
73
    Path = lists:map(fun (".") -> OrgCWD; (Dir) -> Dir end, OrgPath),
 
74
    true = code:set_path(Path),
 
75
    PrivDir = ?config(priv_dir, Config),
 
76
    IgnDir = filename:join([PrivDir,
 
77
                         atom_to_list(Suite)
 
78
                         ++ "_"
 
79
                         ++ atom_to_list(Testcase)
 
80
                         ++ "_wd"]),
 
81
    ok = file:make_dir(IgnDir),
 
82
    case SetCwd of
 
83
        false ->
 
84
            ok;
 
85
        _ ->
 
86
            ok = file:set_cwd(IgnDir),
 
87
            OrgPWD = case os:getenv("PWD") of
 
88
                         false -> false;
 
89
                         PWD ->
 
90
                             os:putenv("PWD", IgnDir),
 
91
                             PWD
 
92
                     end
 
93
    end,
 
94
    ok = file:write_file(filename:join([IgnDir, "ignore_core_files"]), <<>>),
 
95
    %% cores are dumped in /cores on MacOS X
 
96
    CoresDir = case {?t:os_type(), filelib:is_dir("/cores")} of
 
97
                   {{unix,darwin}, true} ->
 
98
                       filelib:fold_files("/cores",
 
99
                                          "^core.*$",
 
100
                                          false,
 
101
                                          fun (C,Cs) -> [C|Cs] end,
 
102
                                          []);
 
103
                   _ ->
 
104
                       false
 
105
               end,
 
106
    lists:keyreplace(ignore_cores,
 
107
                     1,
 
108
                     Config,
 
109
                     {ignore_cores,
 
110
                      #ignore_cores{org_cwd = OrgCWD,
 
111
                                    org_path = OrgPath,
 
112
                                    org_pwd_env = OrgPWD,
 
113
                                    ign_dir = IgnDir,
 
114
                                    cores_dir = CoresDir}}).
 
115
 
 
116
restore(Config) ->
 
117
    #ignore_cores{org_cwd = OrgCWD,
 
118
                  org_path = OrgPath,
 
119
                  org_pwd_env = OrgPWD,
 
120
                  ign_dir = IgnDir,
 
121
                  cores_dir = CoresDir} = ?config(ignore_cores, Config),
 
122
    try
 
123
        case CoresDir of
 
124
            false ->
 
125
                ok;
 
126
            _ ->
 
127
                %% Move cores dumped by these testcases in /cores
 
128
                %% to cwd.
 
129
                lists:foreach(fun (C) ->
 
130
                                      case lists:member(C, CoresDir) of
 
131
                                          true -> ok;
 
132
                                          _ ->
 
133
                                              Dst = filename:join(
 
134
                                                      [IgnDir,
 
135
                                                       filename:basename(C)]),
 
136
                                              {ok, _} = file:copy(C, Dst),
 
137
                                              file:delete(C)
 
138
                                      end
 
139
                              end,
 
140
                              filelib:fold_files("/cores",
 
141
                                                 "^core.*$",
 
142
                                                 false,
 
143
                                                 fun (C,Cs) -> [C|Cs] end,
 
144
                                                 []))
 
145
        end
 
146
    after
 
147
        catch file:set_cwd(OrgCWD),
 
148
        catch code:set_path(OrgPath),
 
149
        case OrgPWD of
 
150
            false -> ok;
 
151
            _ -> catch os:putenv("PWD", OrgPWD)
 
152
        end
 
153
    end.
 
154
 
 
155
 
 
156
dir(Config) ->
 
157
    #ignore_cores{ign_dir = Dir} = ?config(ignore_cores, Config),
 
158
    Dir.