diff options
Diffstat (limited to 'lib/stdlib/src/epp.erl')
| -rw-r--r-- | lib/stdlib/src/epp.erl | 329 | 
1 files changed, 151 insertions, 178 deletions
| diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index d3124ac593..45f616bb02 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -40,7 +40,7 @@  -type ifdef() :: 'ifdef' | 'ifndef' | 'else'. --type name() :: {'atom', atom()}. +-type name() :: atom().  -type argspec() :: 'none'                       %No arguments                   | non_neg_integer().           %Number of arguments  -type tokens() :: [erl_scan:token()]. @@ -49,7 +49,8 @@  -define(DEFAULT_ENCODING, utf8).  %% Epp state record. --record(epp, {file :: file:io_device(),         %Current file +-record(epp, {file :: file:io_device() +                    | 'undefined',              %Current file  	      location=1,         		%Current location                delta=0 :: non_neg_integer(),     %Offset from Location (-file)                name="" :: file:name(),           %Current file name @@ -57,21 +58,14 @@                istk=[] :: [ifdef()],             %Ifdef stack                sstk=[] :: [#epp{}],              %State stack                path=[] :: [file:name()],         %Include-path -              macs = dict:new()                 %Macros (don't care locations) -                  :: dict:dict(name(), {argspec(), tokens()}), -              uses = dict:new()                 %Macro use structure -                  :: dict:dict(name(), [{argspec(), [used()]}]), +              macs = #{}		        %Macros (don't care locations) +	            :: #{name() => {argspec(), tokens()}}, +              uses = #{}			%Macro use structure +	            :: #{name() => [{argspec(), [used()]}]},                default_encoding = ?DEFAULT_ENCODING :: source_encoding(),  	      pre_opened = false :: boolean()  	     }). -%%% Note on representation: as tokens, both {var, Location, Name} and -%%% {atom, Location, Name} can occur as macro identifiers. However, keeping -%%% this distinction here is done for historical reasons only: previously, -%%% ?FOO and ?'FOO' were not the same, but now they are. Removing the -%%% distinction in the internal representation would simplify the code -%%% a little. -  %% open(Options)  %% open(FileName, IncludePath)  %% open(FileName, IncludePath, PreDefMacros) @@ -549,7 +543,8 @@ init_server(Pid, Name, Options, St0) ->  			 default_encoding=DefEncoding},              From = wait_request(St),              Anno = erl_anno:new(AtLocation), -            enter_file_reply(From, Name, Anno, AtLocation, code), +            enter_file_reply(From, file_name(Name), Anno, +			     AtLocation, code),              wait_req_scan(St);  	{error,E} ->  	    epp_reply(Pid, {error,E}) @@ -560,18 +555,18 @@ init_server(Pid, Name, Options, St0) ->  %%  FILE, LINE, MODULE as undefined, MACHINE and MACHINE value.  predef_macros(File) -> -     Machine = list_to_atom(erlang:system_info(machine)), -     Anno = line1(), -     dict:from_list([ -	{{atom,'FILE'}, 	      {none,[{string,Anno,File}]}}, -	{{atom,'LINE'},		      {none,[{integer,Anno,1}]}}, -	{{atom,'MODULE'},	      undefined}, -	{{atom,'MODULE_STRING'},      undefined}, -	{{atom,'BASE_MODULE'},	      undefined}, -	{{atom,'BASE_MODULE_STRING'}, undefined}, -	{{atom,'MACHINE'},	      {none,[{atom,Anno,Machine}]}}, -	{{atom,Machine},	      {none,[{atom,Anno,true}]}} -     ]). +    Machine = list_to_atom(erlang:system_info(machine)), +    Anno = line1(), +    Defs = [{'FILE', 	           {none,[{string,Anno,File}]}}, +	    {'LINE',		   {none,[{integer,Anno,1}]}}, +	    {'MODULE',	           undefined}, +	    {'MODULE_STRING',      undefined}, +	    {'BASE_MODULE',	   undefined}, +	    {'BASE_MODULE_STRING', undefined}, +	    {'MACHINE',	           {none,[{atom,Anno,Machine}]}}, +	    {Machine,	           {none,[{atom,Anno,true}]}} +	   ], +    maps:from_list(Defs).  %% user_predef(PreDefMacros, Macros) ->  %%	{ok,MacroDict} | {error,E} @@ -580,28 +575,21 @@ predef_macros(File) ->  user_predef([{M,Val,redefine}|Pdm], Ms) when is_atom(M) ->      Exp = erl_parse:tokens(erl_parse:abstract(Val)), -    user_predef(Pdm, dict:store({atom,M}, {none,Exp}, Ms)); +    user_predef(Pdm, Ms#{M=>{none,Exp}});  user_predef([{M,Val}|Pdm], Ms) when is_atom(M) -> -    case dict:find({atom,M}, Ms) of -	{ok,_Defs} when is_list(_Defs) -> %% User defined macros +    case Ms of +	#{M:=Defs} when is_list(Defs) -> +	     %% User defined macros.  	    {error,{redefine,M}}; -	{ok,_Def} -> %% Predefined macros +	#{M:=_Defs} -> +	    %% Predefined macros.  	    {error,{redefine_predef,M}}; -	error -> +	_ ->  	    Exp = erl_parse:tokens(erl_parse:abstract(Val)), -	    user_predef(Pdm, dict:store({atom,M}, [{none, {none,Exp}}], Ms)) +	    user_predef(Pdm, Ms#{M=>[{none,{none,Exp}}]})      end;  user_predef([M|Pdm], Ms) when is_atom(M) -> -    case dict:find({atom,M}, Ms) of -	{ok,_Defs} when is_list(_Defs) -> %% User defined macros -	    {error,{redefine,M}}; -	{ok,_Def} -> %% Predefined macros -	    {error,{redefine_predef,M}}; -	error -> -            A = line1(), -	    user_predef(Pdm, -	                dict:store({atom,M}, [{none, {none,[{atom,A,true}]}}], Ms)) -    end; +    user_predef([{M,true}|Pdm], Ms);  user_predef([Md|_Pdm], _Ms) -> {error,{bad,Md}};  user_predef([], Ms) -> {ok,Ms}. @@ -615,7 +603,9 @@ wait_request(St) ->      receive  	{epp_request,From,scan_erl_form} -> From;  	{epp_request,From,macro_defs} -> -	    epp_reply(From, dict:to_list(St#epp.macs)), +	    %% Return the old format to avoid any incompability issues. +	    Defs = [{{atom,K},V} || {K,V} <- maps:to_list(St#epp.macs)], +	    epp_reply(From, Defs),  	    wait_request(St);  	{epp_request,From,close} ->  	    close_file(St), @@ -667,7 +657,8 @@ enter_file(NewName, Inc, From, St) ->  enter_file2(NewF, Pname, From, St0, AtLocation) ->      Anno = erl_anno:new(AtLocation),      enter_file_reply(From, Pname, Anno, AtLocation, code), -    Ms = dict:store({atom,'FILE'}, {none,[{string,Anno,Pname}]}, St0#epp.macs), +    Ms0 = St0#epp.macs, +    Ms = Ms0#{'FILE':={none,[{string,Anno,Pname}]}},      %% update the head of the include path to be the directory of the new      %% source file, so that an included file can always include other files      %% relative to its current location (this is also how C does it); note @@ -688,7 +679,7 @@ enter_file_reply(From, Name, LocationAnno, AtLocation, Where) ->                 generated -> erl_anno:set_generated(true, Anno0)             end,      Rep = {ok, [{'-',Anno},{atom,Anno,file},{'(',Anno}, -		{string,Anno,file_name(Name)},{',',Anno}, +		{string,Anno,Name},{',',Anno},  		{integer,Anno,get_line(LocationAnno)},{')',LocationAnno},                  {dot,Anno}]},      epp_reply(From, Rep). @@ -719,9 +710,8 @@ leave_file(From, St) ->                           name2=OldName2} = OldSt,                      CurrLoc = add_line(OldLoc, Delta),                      Anno = erl_anno:new(CurrLoc), -		    Ms = dict:store({atom,'FILE'}, -				    {none,[{string,Anno,OldName2}]}, -				    St#epp.macs), +		    Ms0 = St#epp.macs, +		    Ms = Ms0#{'FILE':={none,[{string,Anno,OldName2}]}},                      NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses},  		    enter_file_reply(From, OldName, Anno, CurrLoc, code),                      case OldName2 =:= OldName of @@ -796,91 +786,48 @@ scan_toks(Toks0, From, St) ->      end.  scan_module([{'-',_Lh},{atom,_Lm,module},{'(',_Ll}|Ts], Ms) -> -    scan_module_1(Ts, [], Ms); +    scan_module_1(Ts, Ms);  scan_module([{'-',_Lh},{atom,_Lm,extends},{'(',_Ll}|Ts], Ms) -> -    scan_extends(Ts, [], Ms); +    scan_extends(Ts, Ms);  scan_module(_Ts, Ms) -> Ms. -scan_module_1([{atom,_,_}=A,{',',L}|Ts], As, Ms) -> +scan_module_1([{atom,_,_}=A,{',',L}|Ts], Ms) ->      %% Parameterized modules. -    scan_module_1([A,{')',L}|Ts], As, Ms); -scan_module_1([{atom,Ln,A},{')',_Lr}|_Ts], As, Ms0) -> -    Mod = lists:concat(lists:reverse([A|As])), -    Ms = dict:store({atom,'MODULE'}, -		     {none,[{atom,Ln,list_to_atom(Mod)}]}, Ms0), -    dict:store({atom,'MODULE_STRING'}, {none,[{string,Ln,Mod}]}, Ms); -scan_module_1([{atom,_Ln,A},{'.',_Lr}|Ts], As, Ms) -> -    scan_module_1(Ts, [".",A|As], Ms); -scan_module_1([{'.',_Lr}|Ts], As, Ms) -> -    scan_module_1(Ts, As, Ms); -scan_module_1(_Ts, _As, Ms) -> Ms. - -scan_extends([{atom,Ln,A},{')',_Lr}|_Ts], As, Ms0) -> -    Mod = lists:concat(lists:reverse([A|As])), -    Ms = dict:store({atom,'BASE_MODULE'}, -		     {none,[{atom,Ln,list_to_atom(Mod)}]}, Ms0), -    dict:store({atom,'BASE_MODULE_STRING'}, {none,[{string,Ln,Mod}]}, Ms); -scan_extends([{atom,_Ln,A},{'.',_Lr}|Ts], As, Ms) -> -    scan_extends(Ts, [".",A|As], Ms); -scan_extends([{'.',_Lr}|Ts], As, Ms) -> -    scan_extends(Ts, As, Ms); -scan_extends(_Ts, _As, Ms) -> Ms. +    scan_module_1([A,{')',L}|Ts], Ms); +scan_module_1([{atom,Ln,A}=ModAtom,{')',_Lr}|_Ts], Ms0) -> +    ModString = atom_to_list(A), +    Ms = Ms0#{'MODULE':={none,[ModAtom]}}, +    Ms#{'MODULE_STRING':={none,[{string,Ln,ModString}]}}; +scan_module_1(_Ts, Ms) -> Ms. + +scan_extends([{atom,Ln,A}=ModAtom,{')',_Lr}|_Ts], Ms0) -> +    ModString = atom_to_list(A), +    Ms = Ms0#{'BASE_MODULE':={none,[ModAtom]}}, +    Ms#{'BASE_MODULE_STRING':={none,[{string,Ln,ModString}]}}; +scan_extends(_Ts, Ms) -> Ms.  %% scan_define(Tokens, DefineToken, From, EppState) -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',_}=Comma|Toks], _Def, From, St) +scan_define([{'(',_Lp},{Type,_Lm,_}=Mac|Toks], Def, From, St)    when Type =:= atom; Type =:= var -> +    scan_define_1(Toks, Mac, Def, From, St); +scan_define(_Toks, Def, From, St) -> +    epp_reply(From, {error,{loc(Def),epp,{bad,define}}}), +    wait_req_scan(St). + +scan_define_1([{',',_}=Comma|Toks], Mac,_Def, From, St) ->      case catch macro_expansion(Toks, Comma) of          Expansion when is_list(Expansion) -> -            case dict:find({atom,M}, St#epp.macs) of -                {ok, Defs} when is_list(Defs) -> -                    %% User defined macros: can be overloaded -                    case proplists:is_defined(none, Defs) of -                        true -> -                            epp_reply(From, {error,{loc(Mac),epp,{redefine,M}}}), -                            wait_req_scan(St); -                        false -> -                            scan_define_cont(From, St, -                                             {atom, M}, -                                             {none, {none,Expansion}}) -                    end; -                {ok, _PreDef} -> -                    %% Predefined macros: cannot be overloaded -                    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), -                    wait_req_scan(St); -                error -> -                    scan_define_cont(From, St, -                                     {atom, M}, -                                     {none, {none,Expansion}}) -            end; +	    scan_define_2(none, {none,Expansion}, Mac, From, St);          {error,ErrL,What} ->              epp_reply(From, {error,{ErrL,epp,What}}),              wait_req_scan(St)      end; -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St) -  when Type =:= atom; Type =:= var -> +scan_define_1([{'(',_Lc}|Toks], Mac, Def, From, St) ->      case catch macro_pars(Toks, []) of -        {ok, {As,Me}} -> +        {ok,{As,_}=MacroDef} ->              Len = length(As), -            case dict:find({atom,M}, St#epp.macs) of -                {ok, Defs} when is_list(Defs) -> -                    %% User defined macros: can be overloaded -                    case proplists:is_defined(Len, Defs) of -                        true -> -                            epp_reply(From,{error,{loc(Mac),epp,{redefine,M}}}), -                            wait_req_scan(St); -                        false -> -                            scan_define_cont(From, St, {atom, M}, -                                             {Len, {As, Me}}) -                    end; -                {ok, _PreDef} -> -                    %% Predefined macros: cannot be overloaded -                    %% (There are currently no predefined F(...) macros.) -                    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), -                    wait_req_scan(St); -                error -> -                    scan_define_cont(From, St, {atom, M}, {Len, {As, Me}}) -            end; +	    scan_define_2(Len, MacroDef, Mac, From, St);  	{error,ErrL,What} ->              epp_reply(From, {error,{ErrL,epp,What}}),              wait_req_scan(St); @@ -888,10 +835,29 @@ scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St)              epp_reply(From, {error,{loc(Def),epp,{bad,define}}}),              wait_req_scan(St)      end; -scan_define(_Toks, Def, From, St) -> +scan_define_1(_Toks, _Mac, Def, From, St) ->      epp_reply(From, {error,{loc(Def),epp,{bad,define}}}),      wait_req_scan(St). +scan_define_2(Arity, Def, {_,_,Key}=Mac, From, #epp{macs=Ms}=St) -> +    case Ms of +	#{Key:=Defs} when is_list(Defs) -> +	    %% User defined macros: can be overloaded +	    case proplists:is_defined(Arity, Defs) of +		true -> +		    epp_reply(From, {error,{loc(Mac),epp,{redefine,Key}}}), +		    wait_req_scan(St); +		false -> +		    scan_define_cont(From, St, Key, Defs, Arity, Def) +	    end; +	#{Key:=_} -> +	    %% Predefined macros: cannot be overloaded +	    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,Key}}}), +	    wait_req_scan(St); +	_ -> +	    scan_define_cont(From, St, Key, [], Arity, Def) +    end. +  %%% Detection of circular macro expansions (which would either keep  %%% the compiler looping forever, or run out of memory):  %%% When a macro is defined, we store the names of other macros it @@ -901,11 +867,17 @@ scan_define(_Toks, Def, From, St) ->  %%% the information from St#epp.uses is traversed, and if a circularity  %%% is detected, an error message is thrown. -scan_define_cont(F, St, M, {Arity, Def}) -> -    Ms = dict:append_list(M, [{Arity, Def}], St#epp.macs), -    try dict:append_list(M, [{Arity, macro_uses(Def)}], St#epp.uses) of +scan_define_cont(F, #epp{macs=Ms0}=St, M, Defs, Arity, Def) -> +    Ms = Ms0#{M=>[{Arity,Def}|Defs]}, +    try macro_uses(Def) of          U -> -            scan_toks(F, St#epp{uses=U, macs=Ms}) +	    Uses0 = St#epp.uses, +	    Val = [{Arity,U}|case Uses0 of +				 #{M:=UseList} -> UseList; +				 _ -> [] +			     end], +	    Uses = Uses0#{M=>Val}, +            scan_toks(F, St#epp{uses=Uses,macs=Ms})      catch          {error, Line, Reason} ->              epp_reply(F, {error,{Line,epp,Reason}}), @@ -923,23 +895,23 @@ macro_ref([{'?', _}, {'?', _} | Rest]) ->  macro_ref([{'?', _}, {atom, _, A}=Atom | Rest]) ->      Lm = loc(Atom),      Arity = count_args(Rest, Lm, A), -    [{{atom, A}, Arity} | macro_ref(Rest)]; +    [{A,Arity} | macro_ref(Rest)];  macro_ref([{'?', _}, {var, _, A}=Var | Rest]) ->      Lm = loc(Var),      Arity = count_args(Rest, Lm, A), -    [{{atom, A}, Arity} | macro_ref(Rest)]; +    [{A,Arity} | macro_ref(Rest)];  macro_ref([_Token | Rest]) ->      macro_ref(Rest).  %% scan_undef(Tokens, UndefToken, From, EppState)  scan_undef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _Undef, From, St) -> -    Macs = dict:erase({atom,M}, St#epp.macs), -    Uses = dict:erase({atom,M}, St#epp.uses), +    Macs = maps:remove(M, St#epp.macs), +    Uses = maps:remove(M, St#epp.uses),      scan_toks(From, St#epp{macs=Macs, uses=Uses});  scan_undef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _Undef, From,St) -> -    Macs = dict:erase({atom,M}, St#epp.macs), -    Uses = dict:erase({atom,M}, St#epp.uses), +    Macs = maps:remove(M, St#epp.macs), +    Uses = maps:remove(M, St#epp.uses),      scan_toks(From, St#epp{macs=Macs, uses=Uses});  scan_undef(_Toks, Undef, From, St) ->      epp_reply(From, {error,{loc(Undef),epp,{bad,undef}}}), @@ -1006,17 +978,17 @@ scan_include_lib(_Toks, Inc, From, St) ->  %%  Report a badly formed if[n]def test and then treat as undefined macro.  scan_ifdef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    scan_toks(From, St#epp{istk=[ifdef|St#epp.istk]}); -	error -> +	_ ->  	    skip_toks(From, St, [ifdef])      end;  scan_ifdef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    scan_toks(From, St#epp{istk=[ifdef|St#epp.istk]}); -	error -> +	_ ->  	    skip_toks(From, St, [ifdef])      end;  scan_ifdef(_Toks, IfDef, From, St) -> @@ -1024,17 +996,17 @@ scan_ifdef(_Toks, IfDef, From, St) ->      wait_req_skip(St, [ifdef]).  scan_ifndef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfnD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    skip_toks(From, St, [ifndef]); -	error -> +	_ ->  	    scan_toks(From, St#epp{istk=[ifndef|St#epp.istk]})      end;  scan_ifndef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfnD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    skip_toks(From, St, [ifndef]); -	error -> +	_ ->  	    scan_toks(From, St#epp{istk=[ifndef|St#epp.istk]})      end;  scan_ifndef(_Toks, IfnDef, From, St) -> @@ -1102,7 +1074,8 @@ scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},             {dot,_Ld}], Tf, From, St) ->      Anno = erl_anno:new(Ln),      enter_file_reply(From, Name, Anno, loc(Tf), generated), -    Ms = dict:store({atom,'FILE'}, {none,[{string,line1(),Name}]}, St#epp.macs), +    Ms0 = St#epp.macs, +    Ms = Ms0#{'FILE':={none,[{string,line1(),Name}]}},      Locf = loc(Tf),      NewLoc = new_location(Ln, St#epp.location, Locf),      Delta = get_line(element(2, Tf))-Ln + St#epp.delta, @@ -1190,40 +1163,42 @@ macro_expansion([], Anno0) -> throw({error,loc(Anno0),premature_end}).  %%  Expand the macros in a list of tokens, making sure that an expansion  %%  gets the same location as the macro call. -expand_macros(Type, MacT, M, Toks, Ms0) -> -    %% (Type will always be 'atom') -    {Ms, U} = Ms0, +expand_macros(MacT, M, Toks, Ms0) -> +    {Ms,U} = Ms0,      Lm = loc(MacT),      Tinfo = element(2, MacT), -    case expand_macro1(Type, Lm, M, Toks, Ms) of +    case expand_macro1(Lm, M, Toks, Ms) of  	{ok,{none,Exp}} -> -	    check_uses([{{Type,M}, none}], [], U, Lm), -	    Toks1 = expand_macros(expand_macro(Exp, Tinfo, [], dict:new()), Ms0), +	    check_uses([{M,none}], [], U, Lm), +	    Toks1 = expand_macros(expand_macro(Exp, Tinfo, [], #{}), Ms0),  	    expand_macros(Toks1++Toks, Ms0);  	{ok,{As,Exp}} -> -	    check_uses([{{Type,M}, length(As)}], [], U, Lm), -	    {Bs,Toks1} = bind_args(Toks, Lm, M, As, dict:new()), +	    check_uses([{M,length(As)}], [], U, Lm), +	    {Bs,Toks1} = bind_args(Toks, Lm, M, As, #{}),  	    expand_macros(expand_macro(Exp, Tinfo, Toks1, Bs), Ms0)      end. -expand_macro1(Type, Lm, M, Toks, Ms) -> +expand_macro1(Lm, M, Toks, Ms) ->      Arity = count_args(Toks, Lm, M), -    case dict:find({Type,M}, Ms) of -        error -> %% macro not found -            throw({error,Lm,{undefined,M,Arity}}); -        {ok, undefined} -> %% Predefined macro without definition +    case Ms of +	#{M:=undefined} -> +	    %% Predefined macro without definition.              throw({error,Lm,{undefined,M,Arity}}); -        {ok, [{none, Def}]} -> -            {ok, Def}; -        {ok, Defs} when is_list(Defs) -> -            case proplists:get_value(Arity, Defs) of +	#{M:=[{none,Def}]} -> +            {ok,Def}; +	#{M:=Defs} when is_list(Defs) -> +	    case proplists:get_value(Arity, Defs) of                  undefined ->                      throw({error,Lm,{mismatch,M}});                  Def -> -                    {ok, Def} +                    {ok,Def}              end; -        {ok, PreDef} -> %% Predefined macro -            {ok, PreDef} +        #{M:=PreDef} -> +	    %% Predefined macro. +            {ok,PreDef}; +        _ -> +	    %% Macro not found. +            throw({error,Lm,{undefined,M,Arity}})      end.  check_uses([], _Anc, _U, _Lm) -> @@ -1231,7 +1206,7 @@ check_uses([], _Anc, _U, _Lm) ->  check_uses([M|Rest], Anc, U, Lm) ->      case lists:member(M, Anc) of  	true -> -	    {{_, Name},Arity} = M, +	    {Name,Arity} = M,  	    throw({error,Lm,{circular,Name,Arity}});  	false ->  	    L = get_macro_uses(M, U), @@ -1240,23 +1215,23 @@ check_uses([M|Rest], Anc, U, Lm) ->      end.  get_macro_uses({M,Arity}, U) -> -    case dict:find(M, U) of -	error -> -	    []; -	{ok, L} -> -	    proplists:get_value(Arity, L, proplists:get_value(none, L, [])) +    case U of +	#{M:=L} -> +	    proplists:get_value(Arity, L, proplists:get_value(none, L, [])); +	_ -> +	    []      end.  %% Macro expansion  %% Note: io:scan_erl_form() does not return comments or white spaces.  expand_macros([{'?',_Lq},{atom,_Lm,M}=MacT|Toks], Ms) -> -    expand_macros(atom, MacT, M, Toks, Ms); +    expand_macros(MacT, M, Toks, Ms);  %% Special macros  expand_macros([{'?',_Lq},{var,Lm,'LINE'}=Tok|Toks], Ms) ->      Line = erl_scan:line(Tok),      [{integer,Lm,Line}|expand_macros(Toks, Ms)];  expand_macros([{'?',_Lq},{var,_Lm,M}=MacT|Toks], Ms) -> -    expand_macros(atom, MacT, M, Toks, Ms); +    expand_macros(MacT, M, Toks, Ms);  %% Illegal macros  expand_macros([{'?',_Lq},Token|_Toks], _Ms) ->      T = case erl_scan:text(Token) of @@ -1295,7 +1270,7 @@ macro_args(_Toks, Lm, M, _As, _Bs) ->  store_arg(L, M, _A, [], _Bs) ->      throw({error,L,{mismatch,M}});  store_arg(_L, _M, A, Arg, Bs) -> -    dict:store(A, Arg, Bs). +    Bs#{A=>Arg}.  %% count_args(Tokens, MacroLine, MacroName)  %%  Count the number of arguments in a macro call. @@ -1368,19 +1343,17 @@ macro_arg([], _E, Arg) ->  %%  and then the macro arguments, i.e. simulate textual expansion.  expand_macro([{var,_Lv,V}|Ts], L, Rest, Bs) -> -    case dict:find(V, Bs) of -	{ok,Val} -> -	    %% lists:append(Val, expand_macro(Ts, L, Rest, Bs)); +    case Bs of +	#{V:=Val} ->  	    expand_arg(Val, Ts, L, Rest, Bs); -	error -> +	_ ->  	    [{var,L,V}|expand_macro(Ts, L, Rest, Bs)]      end;  expand_macro([{'?', _}, {'?', _}, {var,_Lv,V}|Ts], L, Rest, Bs) -> -    case dict:find(V, Bs) of -	{ok,Val} -> -	    %% lists:append(Val, expand_macro(Ts, L, Rest, Bs)); +    case Bs of +	#{V:=Val} ->              expand_arg(stringify(Val, L), Ts, L, Rest, Bs); -	error -> +	_ ->  	    [{var,L,V}|expand_macro(Ts, L, Rest, Bs)]      end;  expand_macro([T|Ts], L, Rest, Bs) -> | 
