~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/stdlib/src/edlin_expand.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2005-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(edlin_expand).
46
46
    match(Prefix, code:all_loaded(), ":").
47
47
 
48
48
expand_function_name(ModStr, FuncPrefix) ->
49
 
    Mod = list_to_atom(ModStr),
50
 
    case erlang:module_loaded(Mod) of
51
 
        true ->
52
 
            L = Mod:module_info(),
53
 
            case lists:keyfind(exports, 1, L) of
54
 
                {_, Exports} ->
55
 
                    match(FuncPrefix, Exports, "(");
56
 
                _ ->
57
 
                    {no, [], []}
58
 
            end;
59
 
        false ->
 
49
    case to_atom(ModStr) of
 
50
        {ok, Mod} ->
 
51
            case erlang:module_loaded(Mod) of
 
52
                true ->
 
53
                    L = Mod:module_info(),
 
54
                    case lists:keyfind(exports, 1, L) of
 
55
                        {_, Exports} ->
 
56
                            match(FuncPrefix, Exports, "(");
 
57
                        _ ->
 
58
                            {no, [], []}
 
59
                    end;
 
60
                false ->
 
61
                    {no, [], []}
 
62
            end;
 
63
        error ->
60
64
            {no, [], []}
61
65
    end.
62
66
 
 
67
%% if it's a quoted atom, atom_to_list/1 will do the wrong thing.
 
68
to_atom(Str) ->
 
69
    case erl_scan:string(Str) of
 
70
        {ok, [{atom,_,A}], _} ->
 
71
            {ok, A};
 
72
        _ ->
 
73
            error
 
74
    end.
 
75
 
63
76
match(Prefix, Alts, Extra) ->
64
77
    Len = length(Prefix),
65
 
    Matches = [{S, A} || {H, A} <- Alts, prefix(Prefix, S=atom_to_list(H))],
 
78
    Matches = lists:sort(
 
79
                [{S, A} || {H, A} <- Alts,
 
80
                           prefix(Prefix, S=hd(io_lib:fwrite("~w",[H])))]),
66
81
    case longest_common_head([N || {N, _} <- Matches]) of
67
82
        {partial, []} ->
68
83
            {no, [], Matches}; % format_matches(Matches)};