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

« back to all changes in this revision

Viewing changes to lib/ic/src/ic_symtab.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
67
67
    case soft_retrieve(G, Name) of
68
68
        {error, _} ->
69
69
            ets:insert(G#genobj.symtab, {Name, X});
70
 
        {ok, Y} when record(Y, forward) ->
 
70
        {ok, Y} when is_record(Y, forward) ->
71
71
            ets:insert(G#genobj.symtab, {Name, X});
72
72
        {ok, _Y} ->
73
73
            ic_error:error(G, {multiply_defined, X})
125
125
intf_resolv2(G, Scope, Id) ->
126
126
    N = scoped_id_add(Scope, Id),
127
127
    case soft_retrieve(G, scoped_id_strip(N)) of
128
 
        {ok, F} when record(F, forward) ->
 
128
        {ok, F} when is_record(F, forward) ->
129
129
            ic_error:error(G, {illegal_forward, Id}), [];
130
130
        {ok, _Val} -> 
131
131
            scoped_id_mk_global(N);
160
160
    #scoped_id{line=ic_forms:get_line(Id), id=[ic_forms:get_id(Id)]}.
161
161
 
162
162
%% Adds one more id to the list of ids
163
 
scoped_id_add(S1, S2) when record(S2, scoped_id) ->
 
163
scoped_id_add(S1, S2) when is_record(S2, scoped_id) ->
164
164
    S1#scoped_id{id=S2#scoped_id.id ++  S1#scoped_id.id, 
165
165
                 line=S2#scoped_id.line};
166
166
scoped_id_add(S, Id) ->
169
169
 
170
170
scoped_id_mk_global(S) -> S#scoped_id{type=global}.
171
171
 
172
 
scoped_id_is_global(S) when record(S, scoped_id), S#scoped_id.type==global -> 
 
172
scoped_id_is_global(S) when is_record(S, scoped_id), S#scoped_id.type==global -> 
173
173
    true;
174
174
scoped_id_is_global(_) -> false.
175
175