~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2002-2011. All Rights Reserved.
5
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
66
66
%%
67
67
%% Called by compiler or ets/dbg:fun2ms when errors/warnings occur
68
68
%%
 
69
 
 
70
-spec(format_error(Error) -> Chars when
 
71
      Error :: {error, module(), term()},
 
72
      Chars :: io_lib:chars()).
 
73
 
69
74
format_error({?WARN_SHADOW_VAR,Name}) ->
70
75
    lists:flatten(
71
76
      io_lib:format("variable ~p shadowed in ms_transform fun head",
186
191
%%
187
192
%% Called when translating in shell
188
193
%%
 
194
 
 
195
-spec transform_from_shell(Dialect, Clauses, BoundEnvironment) -> term() when
 
196
      Dialect :: ets | dbg,
 
197
      Clauses :: [erl_parse:abstract_clause()],
 
198
      BoundEnvironment :: erl_eval:binding_struct().
 
199
 
189
200
transform_from_shell(Dialect, Clauses, BoundEnvironment) ->
190
201
    SaveFilename = setup_filename(),
191
202
    case catch ms_clause_list(1,Clauses,Dialect,gb_sets:new()) of
211
222
%%
212
223
%% Called when translating during compiling
213
224
%%
 
225
 
 
226
-spec parse_transform(Forms, Options) -> Forms when
 
227
      Forms :: [erl_parse:abstract_form()],
 
228
      Options :: term().
 
229
 
214
230
parse_transform(Forms, _Options) ->
215
231
    SaveFilename = setup_filename(),
216
232
    %io:format("Forms: ~p~n",[Forms]),
317
333
form(AnyOther) ->
318
334
    AnyOther.
319
335
function(Name, Arity, Clauses0) ->
320
 
    {Clauses1,_} = clauses(Clauses0,gb_sets:new()),
 
336
    Clauses1 = clauses(Clauses0),
321
337
    {Name,Arity,Clauses1}.
322
 
clauses([C0|Cs],Bound) ->
323
 
    {C1,Bound1} = clause(C0,Bound),
324
 
    {C2,Bound2} = clauses(Cs,Bound1),
325
 
    {[C1|C2],Bound2};
326
 
clauses([],Bound) -> {[],Bound}.
 
338
clauses([C0|Cs]) ->
 
339
    C1 = clause(C0,gb_sets:new()),
 
340
    C2 = clauses(Cs),
 
341
    [C1|C2];
 
342
clauses([]) -> [].
 
343
 
327
344
clause({clause,Line,H0,G0,B0},Bound) ->
328
345
    {H1,Bound1} = copy(H0,Bound),
329
 
    {B1,Bound2} = copy(B0,Bound1),
330
 
    {{clause,Line,H1,G0,B1},Bound2}.
 
346
    {B1,_Bound2} = copy(B0,Bound1),
 
347
    {clause,Line,H1,G0,B1}.
331
348
 
332
349
copy({call,Line,{remote,_Line2,{atom,_Line3,ets},{atom,_Line4,fun2ms}},
333
350
      As0},Bound) ->