aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/escript_SUITE_data/archive_script
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/escript_SUITE_data/archive_script')
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/ebin/archive_script_dict.app12
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/priv/archive_script_dict.txt1
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict.erl125
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_app.erl29
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_sup.erl39
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/ebin/archive_script_dummy.app10
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy.erl29
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_app.erl29
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_sup.erl33
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl61
-rw-r--r--lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl60
11 files changed, 428 insertions, 0 deletions
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/ebin/archive_script_dict.app b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/ebin/archive_script_dict.app
new file mode 100644
index 0000000000..d703977a1d
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/ebin/archive_script_dict.app
@@ -0,0 +1,12 @@
+{application, archive_script_dict,
+ [{description, "archive_script_dict"},
+ {vsn, "0.1"},
+ {modules, [
+ archive_script_dict,
+ archive_script_dict_sup
+ ]},
+ {registered, [
+ archive_script_dict_sup
+ ]},
+ {applications, [kernel, stdlib]},
+ {mod, {archive_script_dict_app, [[]]}}]}.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/priv/archive_script_dict.txt b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/priv/archive_script_dict.txt
new file mode 100644
index 0000000000..8fa2c8c064
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/priv/archive_script_dict.txt
@@ -0,0 +1 @@
+Some private data...
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict.erl
new file mode 100644
index 0000000000..a614817b04
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict.erl
@@ -0,0 +1,125 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dict).
+-behaviour(sys).
+
+%% Public
+-export([new/1, store/3, erase/2, find/2, foldl/3, erase/1]).
+
+%% Internal
+-export([init/3, loop/3]).
+
+%% supervisor callback
+-export([start_link/2]).
+
+%% sys callback functions
+-export([
+ system_continue/3,
+ system_terminate/4,
+ system_code_change/4
+ ]).
+
+-define(SUPERVISOR, archive_script_dict_sup).
+
+start_link(Name, Debug) ->
+ proc_lib:start_link(?MODULE, init, [self(), Name, Debug], infinity, []).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% Client
+
+new(Name) ->
+ supervisor:start_child(?SUPERVISOR, [Name]).
+
+store(Pid, Key, Val) ->
+ call(Pid, {store, Key, Val}).
+
+erase(Pid, Key) ->
+ call(Pid, {erase, Key}).
+
+find(Pid, Key) ->
+ call(Pid, {find, Key}).
+
+foldl(Pid, Fun, Acc) ->
+ call(Pid, {foldl, Fun, Acc}).
+
+erase(Pid) ->
+ call(Pid, stop).
+
+call(Name, Msg) when is_atom(Name) ->
+ call(whereis(Name), Msg);
+call(Pid, Msg) when is_pid(Pid) ->
+ Ref = erlang:monitor(process, Pid),
+ Pid ! {self(), Ref, Msg},
+ receive
+ {Ref, Reply} ->
+ erlang:demonitor(Ref, [flush]),
+ Reply;
+ {'DOWN', Ref, _, _, Reason} ->
+ {error, Reason}
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% Server
+
+init(Parent, Name, Debug) ->
+ register(Name, self()),
+ Dict = dict:new(),
+ proc_lib:init_ack(Parent, {ok, self()}),
+ loop(Dict, Parent, Debug).
+
+loop(Dict, Parent, Debug) ->
+ receive
+ {system, From, Msg} ->
+ sys:handle_system_msg(Msg, From, Parent, ?MODULE, Debug, Dict);
+ {ReplyTo, Ref, {store, Key, Val}} ->
+ Dict2 = dict:store(Key, Val, Dict),
+ ReplyTo ! {Ref, ok},
+ ?MODULE:loop(Dict2, Parent, Debug);
+ {ReplyTo, Ref, {erase, Key}} ->
+ Dict2 = dict:erase(Key, Dict),
+ ReplyTo ! {Ref, ok},
+ ?MODULE:loop(Dict2, Parent, Debug);
+ {ReplyTo, Ref, {find, Key}} ->
+ Res = dict:find(Key, Dict),
+ ReplyTo ! {Ref, Res},
+ ?MODULE:loop(Dict, Parent, Debug);
+ {ReplyTo, Ref, {foldl, Fun, Acc}} ->
+ Acc2 = dict:foldl(Fun, Acc, Dict),
+ ReplyTo ! {Ref, {ok, Acc2}},
+ ?MODULE:loop(Dict, Parent, Debug);
+ {ReplyTo, Ref, stop} ->
+ ReplyTo ! {Ref, ok},
+ exit(normal);
+ Msg ->
+ error_logger:format("~p got unexpected message: ~p\n",
+ [self(), Msg]),
+ ?MODULE:loop(Dict, Parent, Debug)
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% sys callbacks
+
+system_continue(Parent, Debug, Dict) ->
+ ?MODULE:loop(Dict, Parent, Debug).
+
+system_terminate(Reason, _Parent, _Debug, _Dict) ->
+ exit(Reason).
+
+system_code_change(Dict,_Module,_OldVsn,_Extra) ->
+ {ok, Dict}.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_app.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_app.erl
new file mode 100644
index 0000000000..09b22ea532
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_app.erl
@@ -0,0 +1,29 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dict_app).
+-behaviour(application).
+
+%% Public
+-export([start/2, stop/1]).
+
+start(_Type, Args) ->
+ archive_script_dict_sup:start_link(Args).
+
+stop(_State) ->
+ ok.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_sup.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_sup.erl
new file mode 100644
index 0000000000..9a6c088552
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dict/src/archive_script_dict_sup.erl
@@ -0,0 +1,39 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dict_sup).
+-behaviour(supervisor).
+
+%% Public
+-export([start_link/1]).
+
+%% Internal
+-export([init/1, start_simple_child/2]).
+
+-define(CHILD_MOD, archive_script_dict).
+
+start_link(Debug) ->
+ supervisor:start_link({local, ?MODULE}, ?MODULE, [Debug]).
+
+init([Debug]) ->
+ Flags = {simple_one_for_one, 0, 3600},
+ MFA = {?MODULE, start_simple_child, [Debug]},
+ {ok, {Flags, [{?MODULE, MFA, transient, timer:seconds(3), worker, [?CHILD_MOD]}]}}.
+
+start_simple_child(Debug, Name) ->
+ ?CHILD_MOD:start_link(Name, Debug).
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/ebin/archive_script_dummy.app b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/ebin/archive_script_dummy.app
new file mode 100644
index 0000000000..bbb071c19b
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/ebin/archive_script_dummy.app
@@ -0,0 +1,10 @@
+{application, archive_script_dummy,
+ [{description, "archive_script_dummy"},
+ {vsn, "0.1"},
+ {modules, [
+ archive_script_main,
+ archive_script_main2
+ ]},
+ {registered, []},
+ {applications, [kernel, stdlib, archive_script_dict]},
+ {mod, {archive_script_dummy_app, [[]]}}]}.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy.erl
new file mode 100644
index 0000000000..7c19ebf82f
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy.erl
@@ -0,0 +1,29 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dummy).
+-behaviour(application).
+
+%% Public
+-export([start/2, stop/1]).
+
+start(_Type, Args) ->
+ archive_script_main_sup:start_link(Args).
+
+stop(_State) ->
+ ok.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_app.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_app.erl
new file mode 100644
index 0000000000..c0910d379e
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_app.erl
@@ -0,0 +1,29 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dummy_app).
+-behaviour(application).
+
+%% Public
+-export([start/2, stop/1]).
+
+start(_Type, Args) ->
+ archive_script_dummy_sup:start_link(Args).
+
+stop(_State) ->
+ ok.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_sup.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_sup.erl
new file mode 100644
index 0000000000..8dff5c9335
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_dummy/src/archive_script_dummy_sup.erl
@@ -0,0 +1,33 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_dummy_sup).
+-behaviour(supervisor).
+
+%% Public
+-export([start_link/1]).
+
+%% Internal
+-export([init/1]).
+
+start_link(Debug) ->
+ supervisor:start_link({local, ?MODULE}, ?MODULE, [Debug]).
+
+init([Debug]) ->
+ Flags = {one_for_one, 0, 3600},
+ {ok, {Flags, []}}.
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl
new file mode 100644
index 0000000000..d257744cd7
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl
@@ -0,0 +1,61 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_main).
+-behaviour(escript).
+
+-export([main/1]).
+
+-define(DUMMY, archive_script_dummy).
+-define(DICT, archive_script_dict).
+
+main(MainArgs) ->
+ %% Some printouts
+ io:format("main:~p\n",[MainArgs]),
+ ErlArgs = init:get_arguments(),
+ io:format("dict:~p\n",[[E || E <- ErlArgs, element(1, E) =:= ?DICT]]),
+ io:format("dummy:~p\n",[[E || E <- ErlArgs, element(1, E) =:= ?DUMMY]]),
+
+ %% Start the applications
+ {error, {not_started, ?DICT}} = application:start(?DUMMY),
+ ok = application:start(?DICT),
+ ok = application:start(?DUMMY),
+
+ %% Access dict priv dir
+ PrivDir = code:priv_dir(?DICT),
+ PrivFile = filename:join([PrivDir, "archive_script_dict.txt"]),
+ case erl_prim_loader:get_file(PrivFile) of
+ {ok, Bin, _FullPath} ->
+ io:format("priv:~p\n", [{ok, Bin}]);
+ error ->
+ io:format("priv:~p\n", [{error, PrivFile}])
+ end,
+
+ %% Use the dict app
+ Tab = archive_script_main_tab,
+ Key = foo,
+ Val = bar,
+ {ok, _Pid} = ?DICT:new(Tab),
+ error = ?DICT:find(Tab, Key),
+ ok = ?DICT:store(Tab, Key, Val),
+ {ok, Val} = ?DICT:find(Tab, Key),
+ ok = ?DICT:erase(Tab, Key),
+ error = ?DICT:find(Tab, Key),
+ ok = ?DICT:erase(Tab),
+ ok.
+
diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl
new file mode 100644
index 0000000000..de56579998
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl
@@ -0,0 +1,60 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(archive_script_main2).
+-behaviour(escript).
+
+-export([main/1]).
+
+-define(DUMMY, archive_script_dummy).
+-define(DICT, archive_script_dict).
+
+main(MainArgs) ->
+ %% Some printouts
+ io:format("main2:~p\n",[MainArgs]),
+ ErlArgs = init:get_arguments(),
+ io:format("dict:~p\n",[[E || E <- ErlArgs, element(1, E) =:= ?DICT]]),
+ io:format("dummy:~p\n",[[E || E <- ErlArgs, element(1, E) =:= ?DUMMY]]),
+
+ %% Start the applications
+ {error, {not_started, ?DICT}} = application:start(archive_script_dummy),
+ ok = application:start(?DICT),
+ ok = application:start(?DUMMY),
+
+ %% Access dict priv dir
+ PrivDir = code:priv_dir(?DICT),
+ PrivFile = filename:join([PrivDir, "archive_script_dict.txt"]),
+ case erl_prim_loader:get_file(PrivFile) of
+ {ok, Bin, _FullPath} ->
+ io:format("priv:~p\n", [{ok, Bin}]);
+ error ->
+ io:format("priv:~p\n", [{error, PrivFile}])
+ end,
+
+ %% Use the dict app
+ Tab = archive_script_main_tab,
+ Key = foo,
+ Val = bar,
+ {ok, _Pid} = ?DICT:new(Tab),
+ error = ?DICT:find(Tab, Key),
+ ok = ?DICT:store(Tab, Key, Val),
+ {ok, Val} = ?DICT:find(Tab, Key),
+ ok = ?DICT:erase(Tab, Key),
+ error = ?DICT:find(Tab, Key),
+ ok = ?DICT:erase(Tab),
+ ok.