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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_backup.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: mnesia_backup.erl,v 1.1 2008/12/17 09:53:37 mikpe Exp $
 
17
%%
 
18
%0
 
19
 
 
20
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
21
%%
 
22
%% This module contains one implementation of callback functions
 
23
%% used by Mnesia at backup and restore. The user may however
 
24
%% write an own module the same interface as mnesia_backup and
 
25
%% configure Mnesia so the alternate module performs the actual
 
26
%% accesses to the backup media. This means that the user may put
 
27
%% the backup on medias that Mnesia does not know about, possibly
 
28
%% on hosts where Erlang is not running.
 
29
%%
 
30
%% The OpaqueData argument is never interpreted by other parts of
 
31
%% Mnesia. It is the property of this module. Alternate implementations
 
32
%% of this module may have different interpretations of OpaqueData.
 
33
%% The OpaqueData argument given to open_write/1 and open_read/1
 
34
%% are forwarded directly from the user.
 
35
%%
 
36
%% All functions must return {ok, NewOpaqueData} or {error, Reason}.
 
37
%%
 
38
%% The NewOpaqueData arguments returned by backup callback functions will
 
39
%% be given as input when the next backup callback function is invoked.
 
40
%% If any return value does not match {ok, _} the backup will be aborted.
 
41
%%
 
42
%% The NewOpaqueData arguments returned by restore callback functions will
 
43
%% be given as input when the next restore callback function is invoked
 
44
%% If any return value does not match {ok, _} the restore will be aborted.
 
45
%%
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
 
 
48
-module(mnesia_backup).
 
49
-behaviour(mnesia_backup).
 
50
 
 
51
-include_lib("kernel/include/file.hrl").
 
52
 
 
53
-export([
 
54
         %% Write access
 
55
         open_write/1, 
 
56
         write/2, 
 
57
         commit_write/1, 
 
58
         abort_write/1,
 
59
 
 
60
         %% Read access
 
61
         open_read/1, 
 
62
         read/1, 
 
63
         close_read/1
 
64
        ]).
 
65
 
 
66
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
67
%% Backup callback interface
 
68
-record(backup, {tmp_file, file, file_desc}).
 
69
 
 
70
%% Opens backup media for write
 
71
%%
 
72
%% Returns {ok, OpaqueData} or {error, Reason}
 
73
open_write(OpaqueData) ->
 
74
    File = OpaqueData,
 
75
    Tmp = lists:concat([File,".BUPTMP"]),
 
76
    file:delete(Tmp),
 
77
    file:delete(File),
 
78
    case disk_log:open([{name, make_ref()},
 
79
                        {file, Tmp},
 
80
                        {repair, false},
 
81
                        {linkto, self()}]) of
 
82
        {ok, Fd} ->
 
83
            {ok, #backup{tmp_file = Tmp, file = File, file_desc = Fd}};
 
84
        {error, Reason} ->
 
85
            {error, Reason}
 
86
    end.
 
87
 
 
88
%% Writes BackupItems to the backup media
 
89
%%
 
90
%% Returns {ok, OpaqueData} or {error, Reason}
 
91
write(OpaqueData, BackupItems) ->
 
92
    B = OpaqueData,
 
93
    case disk_log:log_terms(B#backup.file_desc, BackupItems) of
 
94
        ok ->
 
95
            {ok, B};
 
96
        {error, Reason} ->
 
97
            abort_write(B),
 
98
            {error, Reason}
 
99
    end.
 
100
 
 
101
%% Closes the backup media after a successful backup
 
102
%%
 
103
%% Returns {ok, ReturnValueToUser} or {error, Reason}
 
104
commit_write(OpaqueData) ->
 
105
    B = OpaqueData,
 
106
    case disk_log:sync(B#backup.file_desc) of
 
107
        ok ->
 
108
            case disk_log:close(B#backup.file_desc) of
 
109
                ok ->
 
110
                    case file:rename(B#backup.tmp_file, B#backup.file) of
 
111
                       ok ->
 
112
                            {ok, B#backup.file};
 
113
                       {error, Reason} ->
 
114
                            {error, Reason}
 
115
                    end;
 
116
                {error, Reason} ->
 
117
                    {error, Reason}
 
118
            end;
 
119
        {error, Reason} ->
 
120
            {error, Reason}
 
121
    end.
 
122
 
 
123
%% Closes the backup media after an interrupted backup
 
124
%%
 
125
%% Returns {ok, ReturnValueToUser} or {error, Reason}
 
126
abort_write(BackupRef) ->
 
127
    Res = disk_log:close(BackupRef#backup.file_desc),
 
128
    file:delete(BackupRef#backup.tmp_file),
 
129
    case Res of
 
130
        ok ->
 
131
            {ok, BackupRef#backup.file};
 
132
        {error, Reason} ->
 
133
            {error, Reason}
 
134
    end.
 
135
 
 
136
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
137
%% Restore callback interface
 
138
 
 
139
-record(restore, {file, file_desc, cont}).
 
140
 
 
141
%% Opens backup media for read
 
142
%%
 
143
%% Returns {ok, OpaqueData} or {error, Reason}
 
144
open_read(OpaqueData) ->
 
145
    File = OpaqueData,
 
146
    case file:read_file_info(File) of
 
147
        {error, Reason} ->
 
148
            {error, Reason};
 
149
        _FileInfo -> %% file exists
 
150
            case disk_log:open([{file, File},
 
151
                                {name, make_ref()},
 
152
                                {repair, false},
 
153
                                {mode, read_only},
 
154
                                {linkto, self()}]) of
 
155
                {ok, Fd} ->
 
156
                    {ok, #restore{file = File, file_desc = Fd, cont = start}};
 
157
                {repaired, Fd, _, {badbytes, 0}} ->
 
158
                    {ok, #restore{file = File, file_desc = Fd, cont = start}};
 
159
                {repaired, Fd, _, _} ->
 
160
                    {ok, #restore{file = File, file_desc = Fd, cont = start}};
 
161
                {error, Reason} ->
 
162
                    {error, Reason}
 
163
            end
 
164
    end.
 
165
 
 
166
%% Reads BackupItems from the backup media
 
167
%%
 
168
%% Returns {ok, OpaqueData, BackupItems} or {error, Reason}
 
169
%%
 
170
%% BackupItems == [] is interpreted as eof
 
171
read(OpaqueData) ->
 
172
    R = OpaqueData,
 
173
    Fd = R#restore.file_desc,
 
174
    case disk_log:chunk(Fd, R#restore.cont) of
 
175
        {error, Reason} ->
 
176
            {error, {"Possibly truncated", Reason}};
 
177
        eof ->
 
178
            {ok, R, []};
 
179
        {Cont, []} ->
 
180
            read(R#restore{cont = Cont});
 
181
        {Cont, BackupItems} ->
 
182
            {ok, R#restore{cont = Cont}, BackupItems}
 
183
    end.
 
184
 
 
185
%% Closes the backup media after restore
 
186
%%
 
187
%% Returns {ok, ReturnValueToUser} or {error, Reason}
 
188
close_read(OpaqueData) ->
 
189
    R = OpaqueData,
 
190
    case disk_log:close(R#restore.file_desc) of
 
191
        ok -> {ok, R#restore.file};
 
192
        {error, Reason} -> {error, Reason}
 
193
    end.
 
194
%0
 
195