aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/beam_lib.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/beam_lib.erl')
-rw-r--r--lib/stdlib/src/beam_lib.erl117
1 files changed, 73 insertions, 44 deletions
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index 74d4ad3da7..d9c645d787 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2000-2011. 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
@@ -54,13 +54,9 @@
-type beam() :: module() | file:filename() | binary().
-%% XXX: THE FOLLOWING SHOULD BE IMPORTED FROM SOMEWHERE ELSE
--type forms() :: term().
+-type forms() :: [erl_parse:abstract_form()].
--type abst_vsn() :: atom().
--type abst_code() :: {abst_vsn(), forms()} | 'no_abstract_code'.
--type attribute() :: atom().
--type attrvalue() :: term().
+-type abst_code() :: {AbstVersion :: atom(), forms()} | 'no_abstract_code'.
-type dataB() :: binary().
-type index() :: non_neg_integer().
-type label() :: integer().
@@ -74,9 +70,9 @@
| 'atoms'.
-type chunkref() :: chunkname() | chunkid().
--type attrib_entry() :: {attribute(), [attrvalue()]}.
--type compinfo_entry() :: {atom(), term()}.
--type labeled_entry() :: {atom(), arity(), label()}.
+-type attrib_entry() :: {Attribute :: atom(), [AttributeValue :: term()]}.
+-type compinfo_entry() :: {InfoKey :: atom(), term()}.
+-type labeled_entry() :: {Function :: atom(), arity(), label()}.
-type chunkdata() :: {chunkid(), dataB()}
| {'abstract_code', abst_code()}
@@ -85,20 +81,17 @@
| {'exports', [{atom(), arity()}]}
| {'labeled_exports', [labeled_entry()]}
| {'imports', [mfa()]}
- | {'indexed_imports', [{index(), module(), atom(), arity()}]}
+ | {'indexed_imports', [{index(), module(), Function :: atom(), arity()}]}
| {'locals', [{atom(), arity()}]}
| {'labeled_locals', [labeled_entry()]}
| {'atoms', [{integer(), atom()}]}.
--type info_pair() :: {'file', file:filename()}
- | {'binary', binary()}
- | {'module', module()}
- | {'chunks', [{chunkid(), integer(), integer()}]}.
-
%% Error reasons
-type info_rsn() :: {'chunk_too_big', file:filename(),
- chunkid(), integer(), integer()}
- | {'invalid_beam_file', file:filename(), integer()}
+ chunkid(), ChunkSize :: non_neg_integer(),
+ FileSize :: non_neg_integer()}
+ | {'invalid_beam_file', file:filename(),
+ Position :: non_neg_integer()}
| {'invalid_chunk', file:filename(), chunkid()}
| {'missing_chunk', file:filename(), chunkid()}
| {'not_a_beam_file', file:filename()}
@@ -118,20 +111,34 @@
%% Exported functions
%%
--spec info(beam()) -> [info_pair()] | {'error', 'beam_lib', info_rsn()}.
+-spec info(Beam) -> [InfoPair] | {'error', 'beam_lib', info_rsn()} when
+ Beam :: beam(),
+ InfoPair :: {'file', Filename :: file:filename()}
+ | {'binary', Binary :: binary()}
+ | {'module', Module :: module()}
+ | {'chunks', [{ChunkId :: chunkid(),
+ Pos :: non_neg_integer(),
+ Size :: non_neg_integer()}]}.
info(File) ->
read_info(beam_filename(File)).
--spec chunks(beam(), [chunkref()]) ->
- {'ok', {module(), [chunkdata()]}} | {'error', 'beam_lib', chnk_rsn()}.
+-spec chunks(Beam, ChunkRefs) ->
+ {'ok', {module(), [chunkdata()]}} |
+ {'error', 'beam_lib', chnk_rsn()} when
+ Beam :: beam(),
+ ChunkRefs :: [chunkref()].
chunks(File, Chunks) ->
read_chunk_data(File, Chunks).
--spec chunks(beam(), [chunkref()], ['allow_missing_chunks']) ->
- {'ok', {module(), [{chunkref(), chunkdata() | 'missing_chunk'}]}}
- | {'error', 'beam_lib', chnk_rsn()}.
+-spec chunks(Beam, ChunkRefs, Options) ->
+ {'ok', {module(), [ChunkResult]}} |
+ {'error', 'beam_lib', chnk_rsn()} when
+ Beam :: beam(),
+ ChunkRefs :: [chunkref()],
+ Options :: ['allow_missing_chunks'],
+ ChunkResult :: chunkdata() | {ChunkRef :: chunkref(), 'missing_chunk'}.
chunks(File, Chunks, Options) ->
try read_chunk_data(File, Chunks, Options)
@@ -142,49 +149,65 @@ chunks(File, Chunks, Options) ->
all_chunks(File) ->
read_all_chunks(File).
--spec cmp(beam(), beam()) -> 'ok' | {'error', 'beam_lib', cmp_rsn()}.
+-spec cmp(Beam1, Beam2) -> 'ok' | {'error', 'beam_lib', cmp_rsn()} when
+ Beam1 :: beam(),
+ Beam2 :: beam().
cmp(File1, File2) ->
try cmp_files(File1, File2)
catch Error -> Error end.
--spec cmp_dirs(atom() | file:filename(), atom() | file:filename()) ->
- {[file:filename()], [file:filename()],
- [{file:filename(), file:filename()}]}
- | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}.
+-spec cmp_dirs(Dir1, Dir2) ->
+ {Only1, Only2, Different} | {'error', 'beam_lib', Reason} when
+ Dir1 :: atom() | file:filename(),
+ Dir2 :: atom() | file:filename(),
+ Only1 :: [file:filename()],
+ Only2 :: [file:filename()],
+ Different :: [{Filename1 :: file:filename(), Filename2 :: file:filename()}],
+ Reason :: {'not_a_directory', term()} | info_rsn().
cmp_dirs(Dir1, Dir2) ->
catch compare_dirs(Dir1, Dir2).
--spec diff_dirs(atom() | file:filename(), atom() | file:filename()) ->
- 'ok' | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}.
+-spec diff_dirs(Dir1, Dir2) -> 'ok' | {'error', 'beam_lib', Reason} when
+ Dir1 :: atom() | file:filename(),
+ Dir2 :: atom() | file:filename(),
+ Reason :: {'not_a_directory', term()} | info_rsn().
diff_dirs(Dir1, Dir2) ->
catch diff_directories(Dir1, Dir2).
--spec strip(beam()) ->
- {'ok', {module(), beam()}} | {'error', 'beam_lib', info_rsn()}.
+-spec strip(Beam1) ->
+ {'ok', {module(), Beam2}} | {'error', 'beam_lib', info_rsn()} when
+ Beam1 :: beam(),
+ Beam2 :: beam().
strip(FileName) ->
try strip_file(FileName)
catch Error -> Error end.
--spec strip_files([beam()]) ->
- {'ok', [{module(), beam()}]} | {'error', 'beam_lib', info_rsn()}.
+-spec strip_files(Files) ->
+ {'ok', [{module(), Beam}]} | {'error', 'beam_lib', info_rsn()} when
+ Files :: [beam()],
+ Beam :: beam().
strip_files(Files) when is_list(Files) ->
try strip_fils(Files)
catch Error -> Error end.
--spec strip_release(atom() | file:filename()) ->
+-spec strip_release(Dir) ->
{'ok', [{module(), file:filename()}]}
- | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}.
+ | {'error', 'beam_lib', Reason} when
+ Dir :: atom() | file:filename(),
+ Reason :: {'not_a_directory', term()} | info_rsn().
strip_release(Root) ->
catch strip_rel(Root).
--spec version(beam()) ->
- {'ok', {module(), [term()]}} | {'error', 'beam_lib', chnk_rsn()}.
+-spec version(Beam) ->
+ {'ok', {module(), [Version :: term()]}} |
+ {'error', 'beam_lib', chnk_rsn()} when
+ Beam :: beam().
version(File) ->
case catch read_chunk_data(File, [attributes]) of
@@ -195,8 +218,10 @@ version(File) ->
Error
end.
--spec md5(beam()) ->
- {'ok', {module(), binary()}} | {'error', 'beam_lib', chnk_rsn()}.
+-spec md5(Beam) ->
+ {'ok', {module(), MD5}} | {'error', 'beam_lib', chnk_rsn()} when
+ Beam :: beam(),
+ MD5 :: binary().
md5(File) ->
case catch read_significant_chunks(File) of
@@ -207,7 +232,8 @@ md5(File) ->
Error
end.
--spec format_error(term()) -> [char() | string()].
+-spec format_error(Reason) -> io_lib:chars() when
+ Reason :: term().
format_error({error, Error}) ->
format_error(Error);
@@ -260,12 +286,15 @@ format_error(E) ->
| {'debug_info', mode(), module(), file:filename()}.
-type crypto_fun() :: fun((crypto_fun_arg()) -> term()).
--spec crypto_key_fun(crypto_fun()) -> 'ok' | {'error', term()}.
+-spec crypto_key_fun(CryptoKeyFun) -> 'ok' | {'error', Reason} when
+ CryptoKeyFun :: crypto_fun(),
+ Reason :: badfun | exists | term().
crypto_key_fun(F) ->
call_crypto_server({crypto_key_fun, F}).
--spec clear_crypto_key_fun() -> 'undefined' | {'ok', term()}.
+-spec clear_crypto_key_fun() -> 'undefined' | {'ok', Result} when
+ Result :: 'undefined' | term().
clear_crypto_key_fun() ->
call_crypto_server(clear_crypto_key_fun).