1%% ---------------------------------------------------------------------
2%% Licensed under the Apache License, Version 2.0 (the "License"); you may
3%% not use this file except in compliance with the License. You may obtain
4%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
5%%
6%% Unless required by applicable law or agreed to in writing, software
7%% distributed under the License is distributed on an "AS IS" BASIS,
8%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
9%% See the License for the specific language governing permissions and
10%% limitations under the License.
11%%
12%% Alternatively, you may use this file under the terms of the GNU Lesser
13%% General Public License (the "LGPL") as published by the Free Software
14%% Foundation; either version 2.1, or (at your option) any later version.
15%% If you wish to allow use of your version of this file only under the
16%% terms of the LGPL, you should delete the provisions above and replace
17%% them with the notice and other provisions required by the LGPL; see
18%% <http://www.gnu.org/licenses/>. If you do not delete the provisions
19%% above, a recipient may use your version of this file under the terms of
20%% either the Apache License or the LGPL.
21%%
22%% Note: EDoc uses @@ and @} as escape sequences, so in the doc text below,
23%% `@@' must be written `@@@@' and `@}' must be written `@@}'.
24%%
25%% @author Richard Carlsson <carlsson.richard@gmail.com>
26%% @copyright 2010-2015 Richard Carlsson
27%%
28%% @doc Metaprogramming in Erlang.
29%% Merl is a more user friendly interface to the `erl_syntax' module, making
30%% it easy both to build new ASTs from scratch and to
31%% match and decompose existing ASTs. For details that are outside the scope
32%% of Merl itself, please see the documentation of {@link erl_syntax}.
33%%
34%% == Quick start ==
35%%
36%% To enable the full power of Merl, your module needs to include the Merl
37%% header file:
38%% ```-include_lib("syntax_tools/include/merl.hrl").'''
39%%
40%% Then, you can use the `?Q(Text)' macros in your code to create ASTs or match
41%% on existing ASTs. For example:
42%% ```Tuple = ?Q("{foo, 42}"),
43%%    ?Q("{foo, _@Number}") = Tuple,
44%%    Call = ?Q("foo:bar(_@Number)")'''
45%%
46%% Calling `merl:print(Call)' will then print the following code:
47%% ```foo:bar(42)'''
48%%
49%% The `?Q' macros turn the quoted code fragments into ASTs, and lifts
50%% metavariables such as `_@Tuple' and `_@Number' to the level of your Erlang
51%% code, so you can use the corresponding Erlang variables `Tuple' and `Number'
52%% directly. This is the most straightforward way to use Merl, and in many
53%% cases it's all you need.
54%%
55%% You can even write case switches using `?Q' macros as patterns. For example:
56%% ```case AST of
57%%        ?Q("{foo, _@Foo}") -> handle(Foo);
58%%        ?Q("{bar, _@Bar}") when erl_syntax:is_integer(Bar) -> handle(Bar);
59%%        _ -> handle_default()
60%%    end'''
61%%
62%% These case switches only allow `?Q(...)' or `_' as clause patterns, and the
63%% guards may contain any expressions, not just Erlang guard expressions.
64%%
65%% If the macro `MERL_NO_TRANSFORM' is defined before the `merl.hrl' header
66%% file is included, the parse transform used by Merl will be disabled, and in
67%% that case, the match expressions `?Q(...) = ...', case switches using
68%% `?Q(...)' patterns, and automatic metavariables like `_@Tuple' cannot be
69%% used in your code, but the Merl macros and functions still work. To do
70%% metavariable substitution, you need to use the `?Q(Text, Map)' macro, e.g.:
71%% ```Tuple = ?Q("{foo, _@bar, _@baz}", [{bar, Bar}, {baz,Baz}])'''
72%%
73%% The text given to a `?Q(Text)' macro can be either a single string, or a
74%% list of strings. The latter is useful when you need to split a long
75%% expression over multiple lines, e.g.:
76%% ```?Q(["case _@Expr of",
77%%        "  {foo, X} -> f(X);",
78%%        "  {bar, X} -> g(X)",
79%%        "  _ -> h(X)"
80%%        "end"])'''
81%% If there is a syntax error somewhere in the text (like the missing semicolon
82%% in the second clause above) this allows Merl to generate an error message
83%% pointing to the exact line in your source code. (Just remember to
84%% comma-separate the strings in the list, otherwise Erlang will concatenate
85%% the string fragments as if they were a single string.)
86%%
87%% == Metavariable syntax ==
88%%
89%% There are several ways to write a metavariable in your quoted code:
90%% <ul>
91%%   <li>Atoms starting with `@', for example `` '@foo' '' or `` '@Foo' ''</li>
92%%   <li>Variables starting with `_@', for example `_@bar' or `_@Bar'</li>
93%%   <li>Strings starting with ``"'@'', for example ``"'@File"''</li>
94%%   <li>Integers starting with 909, for example `9091' or `909123'</li>
95%% </ul>
96%% Following the prefix, one or more `_' or `0' characters may be used to
97%% indicate "lifting" of the variable one or more levels, and after that, a `@'
98%% or `9' character indicates a glob metavariable (matching zero or more
99%% elements in a sequence) rather than a normal metavariable. For example:
100%% <ul>
101%%   <li>`` '@_foo' '' is lifted one level, and `_@__foo' is lifted two
102%%       levels</li>
103%%   <li>`_@@@@bar' is a glob variable, and `_@_@bar' is a lifted glob
104%%       variable</li>
105%%   <li>`90901' is a lifted variable,`90991' is a glob variable, and `9090091'
106%%       is a glob variable lifted two levels</li>
107%% </ul>
108%% (Note that the last character in the name is never considered to be a lift
109%% or glob marker, hence, `_@__' and `90900' are only lifted one level, not
110%% two. Also note that globs only matter for matching; when doing
111%% substitutions, a non-glob variable can be used to inject a sequence of
112%% elements, and vice versa.)
113%%
114%% If the name after the prefix and any lift and glob markers is `_' or `0',
115%% the variable is treated as an anonymous catch-all pattern in matches. For
116%% example, `_@_', `_@@@@_', `_@__', or even `_@__@_'.
117%%
118%% Finally, if the name without any prefixes or lift/glob markers begins with
119%% an uppercase character, as in `_@Foo' or `_@_@Foo', it will become a
120%% variable on the Erlang level, and can be used to easily deconstruct and
121%% construct syntax trees:
122%% ```case Input of
123%%        ?Q("{foo, _@Number}") -> ?Q("foo:bar(_@Number)");
124%%        ...'''
125%% We refer to these as "automatic metavariables". If in addition the name ends
126%% with `@', as in `_@Foo@', the value of the variable as an Erlang term will
127%% be automatically converted to the corresponding abstract syntax tree when
128%% used to construct a larger tree. For example, in:
129%% ```Bar = {bar, 42},
130%%    Foo = ?Q("{foo, _@Bar@@}")'''
131%% (where Bar is just some term, not a syntax tree) the result `Foo' will be a
132%% syntax tree representing `{foo, {bar, 42}}'. This avoids the need for
133%% temporary variables in order to inject data, as in
134%% ```TmpBar = erl_syntax:abstract(Bar),
135%%    Foo = ?Q("{foo, _@TmpBar}")'''
136%%
137%% If the context requires an integer rather than a variable, an atom, or a
138%% string, you cannot use the uppercase convention to mark an automatic
139%% metavariable. Instead, if the integer (without the `909'-prefix and
140%% lift/glob markers) ends in a `9', the integer will become an Erlang-level
141%% variable prefixed with `Q', and if it ends with `99' it will also be
142%% automatically abstracted. For example, the following will increment the
143%% arity of the exported function f:
144%% ```case Form of
145%%        ?Q("-export([f/90919]).") ->
146%%            Q2 = erl_syntax:concrete(Q1) + 1,
147%%            ?Q("-export([f/909299]).");
148%%        ...'''
149%%
150%% == When to use the various forms of metavariables ==
151%%
152%% Merl can only parse a fragment of text if it follows the basic syntactical
153%% rules of Erlang. In most places, a normal Erlang variable can be used as
154%% metavariable, for example:
155%% ```?Q("f(_@Arg)") = Expr'''
156%% but if you want to match on something like the name of a function, you have
157%% to use an atom as metavariable:
158%% ```?Q("'@Name'() -> _@@@@_." = Function'''
159%% (note the anonymous glob variable `_@@@@_' to ignore the function body).
160%%
161%% In some contexts, only a string or an integer is allowed. For example, the
162%% directive `-file(Name, Line)' requires that `Name' is a string literal and
163%% `Line' an integer literal:
164%%
165%% ```?Q("-file(\"'@File\", 9090).") = ?Q("-file(\"foo.erl\", 42).")).'''
166%% This will extract the string literal `"foo.erl"' into the variable `Foo'.
167%% Note the use of the anonymous variable `9090' to ignore the line number. To
168%% match and also bind a metavariable that must be an integer literal, we can
169%% use the convention of ending the integer with a 9, turning it into a
170%% Q-prefixed variable on the Erlang level (see the previous section).
171%%
172%% === Globs ===
173%%
174%% Whenever you want to match out a number of elements in a sequence (zero or
175%% more) rather than a fixed set of elements, you need to use a glob. For
176%% example:
177%% ```?Q("{_@@@@Elements}") = ?Q({a, b, c})'''
178%% will bind Elements to the list of individual syntax trees representing the
179%% atoms `a', `b', and `c'. This can also be used with static prefix and suffix
180%% elements in the sequence. For example:
181%% ```?Q("{a, b, _@@@@Elements}") = ?Q({a, b, c, d})'''
182%% will bind Elements to the list of the `c' and `d' subtrees, and
183%% ```?Q("{_@@@@Elements, c, d}") = ?Q({a, b, c, d})'''
184%% will bind Elements to the list of the `a' and `b' subtrees. You can even use
185%% plain metavariables in the prefix or suffix:
186%% ```?Q("{_@First, _@@@@Rest}") = ?Q({a, b, c})'''
187%% or
188%% ```?Q("{_@@@@_, _@Last}") = ?Q({a, b, c})'''
189%% (ignoring all but the last element). You cannot however have two globs as
190%% part of the same sequence.
191%%
192%% === Lifted metavariables ===
193%%
194%% In some cases, the Erlang syntax rules make it impossible to place a
195%% metavariable directly where you would like it. For example, you cannot
196%% write:
197%% ```?Q("-export([_@@@@Name]).")'''
198%% to match out all name/arity pairs in the export list, or to insert a list of
199%% exports in a declaration, because the Erlang parser only allows elements on
200%% the form `A/I' (where `A' is an atom and `I' an integer) in the export list.
201%% A variable like the above is not allowed, but neither is a single atom or
202%% integer, so `` '@@@@Name' '' or `909919' wouldn't work either.
203%%
204%% What you have to do in such cases is to write your metavariable in a
205%% syntactically valid position, and use lifting markers to denote where it
206%% should really apply, as in:
207%% ```?Q("-export(['@@_@@Name'/0]).")'''
208%% This causes the variable to be lifted (after parsing) to the next higher
209%% level in the syntax tree, replacing that entire subtree. In this case, the
210%% `` '@@_@@Name'/0 '' will be replaced with `` '@@@@Name' '', and the ``/0''
211%% part was just used as dummy notation and will be discarded.
212%%
213%% You may even need to apply lifting more than once. To match the entire
214%% export list as a single syntax tree, you can write:
215%% ```?Q("-export(['@@__Name'/0]).")'''
216%% using two underscores, but with no glob marker this time. This will make the
217%% entire ``['@@__Name'/0]'' part be replaced with `` '@@Name' ''.
218%%
219%% Sometimes, the tree structure of a code fragment isn't very obvious, and
220%% parts of the structure may be invisible when printed as source code. For
221%% instance, a simple function definition like the following:
222%% ```zero() -> 0.'''
223%% consists of the name (the atom `zero'), and a list of clauses containing the
224%% single clause `() -> 0'. The clause consists of an argument list (empty), a
225%% guard (empty), and a body (which is always a list of expressions) containing
226%% the single expression `0'. This means that to match out the name and the
227%% list of clauses of any function, you'll need to use a pattern like
228%% ``?Q("'@Name'() -> _@_@Body.")'', using a dummy clause whose body is a glob
229%% lifted one level.
230%%
231%% To visualize the structure of a syntax tree, you can use the function
232%% `merl:show(T)', which prints a summary. For example, entering
233%% ```merl:show(merl:quote("inc(X, Y) when Y > 0 -> X + Y."))'''
234%% in the Erlang shell will print the following (where the `+' signs separate
235%% groups of subtrees on the same level):
236%% ```function: inc(X, Y) when ... -> X + Y.
237%%      atom: inc
238%%      +
239%%      clause: (X, Y) when ... -> X + Y
240%%        variable: X
241%%        variable: Y
242%%        +
243%%        disjunction: Y > 0
244%%          conjunction: Y > 0
245%%            infix_expr: Y > 0
246%%              variable: Y
247%%              +
248%%              operator: >
249%%              +
250%%              integer: 0
251%%        +
252%%        infix_expr: X + Y
253%%          variable: X
254%%          +
255%%          operator: +
256%%          +
257%%          variable: Y'''
258%%
259%% This shows another important non-obvious case: a clause guard, even if it's
260%% as simple as `Y > 0', always consists of a single disjunction of one or more
261%% conjunctions of tests, much like a tuple of tuples. Thus:
262%% <ul>
263%%   <li>``"when _@Guard ->"'' will only match a guard with exactly one
264%%     test</li>
265%%   <li>``"when _@@@@Guard ->"'' will match a guard with one or more
266%%     comma-separated tests (but no semicolons), binding `Guard' to the list
267%%     of tests</li>
268%%   <li>``"when _@_Guard ->"'' will match just like the previous pattern, but
269%%     binds `Guard' to the conjunction subtree</li>
270%%   <li>``"when _@_@Guard ->"'' will match an arbitrary nonempty guard,
271%%     binding `Guard' to the list of conjunction subtrees</li>
272%%   <li>``"when _@__Guard ->"'' will match like the previous pattern, but
273%%     binds `Guard' to the whole disjunction subtree</li>
274%%   <li>and finally, ``"when _@__@Guard ->"'' will match any clause,
275%%     binding `Guard' to `[]' if the guard is empty and to `[Disjunction]'
276%%     otherwise</li>
277%% </ul>
278%%
279%% Thus, the following pattern matches all possible clauses:
280%% ```"(_@@Args) when _@__@Guard -> _@@Body"'''
281%% @end
282
283-module(merl).
284
285-export([term/1, var/1, print/1, show/1]).
286
287-export([quote/1, quote/2, qquote/2, qquote/3]).
288
289-export([template/1, tree/1, subst/2, tsubst/2, alpha/2, match/2, switch/2]).
290
291-export([template_vars/1, meta_template/1]).
292
293-export([compile/1, compile/2, compile_and_load/1, compile_and_load/2]).
294
295%% NOTE: this module may not include merl.hrl!
296
297-type tree() :: erl_syntax:syntaxTree().
298
299-type tree_or_trees() :: tree() | [tree()].
300
301-type pattern() :: tree() | template().
302
303-type pattern_or_patterns() :: pattern() | [pattern()].
304
305-type env() :: [{Key::id(), pattern_or_patterns()}].
306
307-type id() :: atom() | integer().
308
309%% A list of strings or binaries is assumed to represent individual lines,
310%% while a flat string or binary represents source code containing newlines.
311-type text() :: string() | binary() | [string()] | [binary()].
312
313-type location() :: erl_anno:location().
314
315
316%% ------------------------------------------------------------------------
317%% Compiling and loading code directly to memory
318
319%% @equiv compile(Code, [])
320compile(Code) ->
321    compile(Code, []).
322
323%% @doc Compile a syntax tree or list of syntax trees representing a module
324%% into a binary BEAM object.
325%% @see compile_and_load/2
326%% @see compile/1
327compile(Code, Options) when not is_list(Code)->
328    case type(Code) of
329        form_list -> compile(erl_syntax:form_list_elements(Code));
330        _ -> compile([Code], Options)
331    end;
332compile(Code, Options0) when is_list(Options0) ->
333    Forms = [erl_syntax:revert(F) || F <- Code],
334    Options = [verbose, report_errors, report_warnings, binary | Options0],
335    compile:noenv_forms(Forms, Options).
336
337
338%% @equiv compile_and_load(Code, [])
339compile_and_load(Code) ->
340    compile_and_load(Code, []).
341
342%% @doc Compile a syntax tree or list of syntax trees representing a module
343%% and load the resulting module into memory.
344%% @see compile/2
345%% @see compile_and_load/1
346compile_and_load(Code, Options) ->
347    case compile(Code, Options) of
348        {ok, ModuleName, Binary} ->
349            _ = code:load_binary(ModuleName, "", Binary),
350            {ok, Binary};
351        Other -> Other
352    end.
353
354
355%% ------------------------------------------------------------------------
356%% Utility functions
357
358
359-spec var(atom()) -> tree().
360
361%% @doc Create a variable.
362
363var(Name) ->
364    erl_syntax:variable(Name).
365
366
367-spec term(term()) -> tree().
368
369%% @doc Create a syntax tree for a constant term.
370
371term(Term) ->
372    erl_syntax:abstract(Term).
373
374
375%% @doc Pretty-print a syntax tree or template to the standard output. This
376%% is a utility function for development and debugging.
377
378print(Ts) when is_list(Ts) ->
379    lists:foreach(fun print/1, Ts);
380print(T) ->
381    io:put_chars(erl_prettypr:format(tree(T))),
382    io:nl().
383
384%% @doc Print the structure of a syntax tree or template to the standard
385%% output. This is a utility function for development and debugging.
386
387show(Ts) when is_list(Ts) ->
388    lists:foreach(fun show/1, Ts);
389show(T) ->
390    io:put_chars(pp(tree(T), 0)),
391    io:nl().
392
393pp(T, I) ->
394    [lists:duplicate(I, $\s),
395     limit(lists:flatten([atom_to_list(type(T)), ": ",
396                          erl_prettypr:format(erl_syntax_lib:limit(T,3))]),
397           79-I),
398     $\n,
399     pp_1(lists:filter(fun (X) -> X =/= [] end, subtrees(T)), I+2)
400    ].
401
402pp_1([G], I) ->
403    pp_2(G, I);
404pp_1([G | Gs], I) ->
405    [pp_2(G, I), lists:duplicate(I, $\s), "+\n" | pp_1(Gs, I)];
406pp_1([], _I) ->
407    [].
408
409pp_2(G, I) ->
410    [pp(E, I) || E <- G].
411
412%% limit string to N characters, stay on a single line and compact whitespace
413limit([$\n | Cs], N) -> limit([$\s | Cs], N);
414limit([$\r | Cs], N) -> limit([$\s | Cs], N);
415limit([$\v | Cs], N) -> limit([$\s | Cs], N);
416limit([$\t | Cs], N) -> limit([$\s | Cs], N);
417limit([$\s, $\s | Cs], N) -> limit([$\s | Cs], N);
418limit([C | Cs], N) when C < 32 -> limit(Cs, N);
419limit([C | Cs], N) when N > 3 -> [C | limit(Cs, N-1)];
420limit([_C1, _C2, _C3, _C4 | _Cs], 3) -> "...";
421limit(Cs, 3) -> Cs;
422limit([_C1, _C2, _C3 | _], 2) -> "..";
423limit(Cs, 2) -> Cs;
424limit([_C1, _C2 | _], 1) -> ".";
425limit(Cs, 1) -> Cs;
426limit(_, _) -> [].
427
428%% ------------------------------------------------------------------------
429%% Parsing and instantiating code fragments
430
431
432-spec qquote(Text::text(), Env::env()) -> tree_or_trees().
433
434%% @doc Parse text and substitute meta-variables.
435%%
436%% @equiv qquote(1, Text, Env)
437
438qquote(Text, Env) ->
439    qquote(1, Text, Env).
440
441
442-spec qquote(StartPos::location(), Text::text(), Env::env()) -> tree_or_trees().
443
444%% @doc Parse text and substitute meta-variables. Takes an initial scanner
445%% starting position as first argument.
446%%
447%% The macro `?Q(Text, Env)' expands to `merl:qquote(?LINE, Text, Env)'.
448%%
449%% @see quote/2
450
451qquote(StartPos, Text, Env) ->
452    subst(quote(StartPos, Text), Env).
453
454
455-spec quote(Text::text()) -> tree_or_trees().
456
457%% @doc Parse text.
458%%
459%% @equiv quote(1, Text)
460
461quote(Text) ->
462    quote(1, Text).
463
464
465-spec quote(StartPos::location(), Text::text()) -> tree_or_trees().
466
467%% @doc Parse text. Takes an initial scanner starting position as first
468%% argument.
469%%
470%% The macro `?Q(Text)' expands to `merl:quote(?LINE, Text, Env)'.
471%%
472%% @see quote/1
473
474quote({Line, Col}, Text)
475  when is_integer(Line), is_integer(Col) ->
476    quote_1(Line, Col, Text);
477quote(StartPos, Text) when is_integer(StartPos) ->
478    quote_1(StartPos, undefined, Text).
479
480quote_1(StartLine, StartCol, Text) ->
481    %% be backwards compatible as far as R12, ignoring any starting column
482    StartPos = case erlang:system_info(version) of
483                   "5.6" ++ _ -> StartLine;
484                   "5.7" ++ _ -> StartLine;
485                   "5.8" ++ _ -> StartLine;
486                   _ when StartCol =:= undefined -> StartLine;
487                   _ -> {StartLine, StartCol}
488               end,
489    FlatText = flatten_text(Text),
490    {ok, Ts, _} = erl_scan:string(FlatText, StartPos),
491    merge_comments(StartLine, erl_comment_scan:string(FlatText), parse_1(Ts)).
492
493parse_1(Ts) ->
494    %% if dot tokens are present, it is assumed that the text represents
495    %% complete forms, not dot-terminated expressions or similar
496    case split_forms(Ts) of
497        {ok, Fs} -> parse_forms(Fs);
498        error ->
499            parse_2(Ts)
500    end.
501
502split_forms(Ts) ->
503    split_forms(Ts, [], []).
504
505split_forms([{dot,_}=T|Ts], Fs, As) ->
506    split_forms(Ts, [lists:reverse(As, [T]) | Fs], []);
507split_forms([T|Ts], Fs, As) ->
508    split_forms(Ts, Fs, [T|As]);
509split_forms([], Fs, []) ->
510    {ok, lists:reverse(Fs)};
511split_forms([], [], _) ->
512    error;  % no dot tokens found - not representing form(s)
513split_forms([], _, [T|_]) ->
514    fail("incomplete form after ~p", [T]).
515
516parse_forms([Ts | Tss]) ->
517    case erl_parse:parse_form(Ts) of
518        {ok, Form} -> [Form | parse_forms(Tss)];
519        {error, R} -> parse_error(R)
520    end;
521parse_forms([]) ->
522    [].
523
524parse_2(Ts) ->
525    %% one or more comma-separated expressions?
526    %% (recall that Ts has no dot tokens if we get to this stage)
527    A = a0(),
528    case erl_parse:parse_exprs(Ts ++ [{dot,A}]) of
529        {ok, Exprs} -> Exprs;
530        {error, E} ->
531            parse_3(Ts ++ [{'end',A}, {dot,A}], [E])
532    end.
533
534parse_3(Ts, Es) ->
535    %% try-clause or clauses?
536    A = a0(),
537    case erl_parse:parse_exprs([{'try',A}, {atom,A,true}, {'catch',A} | Ts]) of
538        {ok, [{'try',_,_,_,_,_}=X]} ->
539            %% get the right kind of qualifiers in the clause patterns
540            erl_syntax:try_expr_handlers(X);
541        {error, E} ->
542            parse_4(Ts, [E|Es])
543    end.
544
545parse_4(Ts, Es) ->
546    %% fun-clause or clauses? (`(a)' is also a pattern, but `(a,b)' isn't,
547    %% so fun-clauses must be tried before normal case-clauses
548    A = a0(),
549    case erl_parse:parse_exprs([{'fun',A} | Ts]) of
550        {ok, [{'fun',_,{clauses,Cs}}]} -> Cs;
551        {error, E} ->
552            parse_5(Ts, [E|Es])
553    end.
554
555parse_5(Ts, Es) ->
556    %% case-clause or clauses?
557    A = a0(),
558    case erl_parse:parse_exprs([{'case',A}, {atom,A,true}, {'of',A} | Ts]) of
559        {ok, [{'case',_,_,Cs}]} -> Cs;
560        {error, E} ->
561            %% select the best error to report
562            parse_error(lists:last(lists:sort([E|Es])))
563    end.
564
565-dialyzer({nowarn_function, parse_error/1}). % no local return
566
567parse_error({L, M, R}) when is_atom(M), is_integer(L) ->
568    fail("~w: ~ts", [L, M:format_error(R)]);
569parse_error({{L,C}, M, R}) when is_atom(M), is_integer(L), is_integer(C) ->
570    fail("~w:~w: ~ts", [L,C,M:format_error(R)]);
571parse_error({_, M, R}) when is_atom(M) ->
572    fail(M:format_error(R));
573parse_error(R) ->
574    fail("unknown parse error: ~tp", [R]).
575
576%% ------------------------------------------------------------------------
577%% Templates, substitution and matching
578
579%% Leaves are normal syntax trees, and inner nodes are tuples
580%% {template,Type,Attrs,Groups} where Groups are lists of lists of nodes.
581%% Metavariables are 1-tuples {VarName}, where VarName is an atom or an
582%% integer. {'_'} and {0} work as anonymous variables in matching. Glob
583%% metavariables are tuples {'*',VarName}, and {'*','_'} and {'*',0} are
584%% anonymous globs.
585
586%% Note that although template() :: tree() | ..., it is implied that these
587%% syntax trees are free from metavariables, so pattern() :: tree() |
588%% template() is in fact a wider type than template().
589
590-type template() :: tree()
591                  | {id()}
592                  | {'*',id()}
593                  | {template, atom(), term(), [[template()]]}.
594
595-type template_or_templates() :: template() | [template()].
596
597-spec template(pattern_or_patterns()) -> template_or_templates().
598
599%% @doc Turn a syntax tree or list of trees into a template or templates.
600%% Templates can be instantiated or matched against, and reverted back to
601%% normal syntax trees using {@link tree/1}. If the input is already a
602%% template, it is not modified further.
603%%
604%% @see subst/2
605%% @see match/2
606%% @see tree/1
607
608template(Trees) when is_list(Trees) ->
609    [template_0(T) || T <- Trees];
610template(Tree) ->
611    template_0(Tree).
612
613template_0({template, _, _, _}=Template) -> Template;
614template_0({'*',_}=Template) -> Template;
615template_0({_}=Template) -> Template;
616template_0(Tree) ->
617    case template_1(Tree) of
618        false -> Tree;
619        {Name} when is_list(Name) ->
620            fail("bad metavariable: '~s'", [tl(Name)]);  % drop v/n from name
621        Template -> Template
622    end.
623
624%% returns either a template or a lifted metavariable {String}, or 'false'
625%% if Tree contained no metavariables
626template_1(Tree) ->
627    case subtrees(Tree) of
628        [] ->
629            case metavar(Tree) of
630                {"v_"++Cs}=V when Cs =/= [] -> V;  % to be lifted
631                {"n0"++Cs}=V when Cs =/= [] -> V;  % to be lifted
632                {"v@"++Cs} when Cs =/= [] -> {'*',list_to_atom(Cs)};
633                {"n9"++Cs} when Cs =/= [] -> {'*',list_to_integer(Cs)};
634                {"v"++Cs} -> {list_to_atom(Cs)};
635                {"n"++Cs} -> {list_to_integer(Cs)};
636                false -> false
637            end;
638        Gs ->
639            case template_2(Gs, [], false) of
640                Gs1 when is_list(Gs1) ->
641                    {template, type(Tree), erl_syntax:get_attrs(Tree), Gs1};
642                Other ->
643                    Other
644            end
645    end.
646
647template_2([G | Gs], As, Bool) ->
648    case template_3(G, [], false) of
649        {"v_"++Cs}=V when Cs =/= [] -> V;  % lift further
650        {"n0"++Cs}=V when Cs =/= [] -> V;  % lift further
651        {"v@"++Cs} when Cs =/= [] -> {'*',list_to_atom(Cs)};  % stop
652        {"n9"++Cs} when Cs =/= [] -> {'*',list_to_integer(Cs)};  % stop
653        {"v"++Cs} when is_list(Cs) -> {list_to_atom(Cs)};  % stop
654        {"n"++Cs} when is_list(Cs) -> {list_to_integer(Cs)};  % stop
655        false -> template_2(Gs, [G | As], Bool);
656        G1 -> template_2(Gs, [G1 | As], true)
657    end;
658template_2([], _As, false) -> false;
659template_2([], As, true) -> lists:reverse(As).
660
661template_3([T | Ts], As, Bool) ->
662    case template_1(T) of
663        {"v_"++Cs} when Cs =/= [] -> {"v"++Cs};  % lift
664        {"n0"++Cs} when Cs =/= [] -> {"n"++Cs};  % lift
665        false -> template_3(Ts, [T | As], Bool);
666        T1 -> template_3(Ts, [T1 | As], true)
667    end;
668template_3([], _As, false) -> false;
669template_3([], As, true) -> lists:reverse(As).
670
671
672%% @doc Turn a template into a syntax tree representing the template.
673%% Meta-variables in the template are turned into normal Erlang variables if
674%% their names (after the metavariable prefix characters) begin with an
675%% uppercase character. E.g., `_@Foo' in the template becomes the variable
676%% `Foo' in the meta-template. Furthermore, variables ending with `@' are
677%% automatically wrapped in a call to merl:term/1, so e.g. `_@Foo@ in the
678%% template becomes `merl:term(Foo)' in the meta-template.
679
680-spec meta_template(template_or_templates()) -> tree_or_trees().
681
682meta_template(Templates) when is_list(Templates) ->
683    [meta_template_1(T) || T <- Templates];
684meta_template(Template) ->
685    meta_template_1(Template).
686
687meta_template_1({template, Type, Attrs, Groups}) ->
688    erl_syntax:tuple(
689      [erl_syntax:atom(template),
690       erl_syntax:atom(Type),
691       erl_syntax:abstract(Attrs),
692       erl_syntax:list([erl_syntax:list([meta_template_1(T) || T <- G])
693                        || G <- Groups])]);
694meta_template_1({Var}=V) ->
695    meta_template_2(Var, V);
696meta_template_1({'*',Var}=V) ->
697    meta_template_2(Var, V);
698meta_template_1(Leaf) ->
699    erl_syntax:abstract(Leaf).
700
701meta_template_2(Var, V) when is_atom(Var) ->
702    case atom_to_list(Var) of
703        [C|_]=Name when C >= $A, C =< $Z ; C >= $À, C =< $Þ, C /= $× ->
704            case lists:reverse(Name) of
705                "@"++([_|_]=RevRealName) ->  % don't allow empty RealName
706                    RealName = lists:reverse(RevRealName),
707                    erl_syntax:application(erl_syntax:atom(merl),
708                                           erl_syntax:atom(term),
709                                           [erl_syntax:variable(RealName)]);
710                _ ->
711                    %% plain automatic metavariable
712                    erl_syntax:variable(Name)
713            end;
714        _ ->
715            erl_syntax:abstract(V)
716    end;
717meta_template_2(Var, V) when is_integer(Var) ->
718    if Var > 9, (Var rem 10) =:= 9 ->
719            %% at least 2 digits, ends in 9: make it a Q-variable
720            if Var > 99, (Var rem 100) =:= 99 ->
721                    %% at least 3 digits, ends in 99: wrap in merl:term/1
722                    Name = "Q" ++ integer_to_list(Var div 100),
723                    erl_syntax:application(erl_syntax:atom(merl),
724                                           erl_syntax:atom(term),
725                                           [erl_syntax:variable(Name)]);
726               true ->
727                    %% plain automatic Q-variable
728                    Name = integer_to_list(Var div 10),
729                    erl_syntax:variable("Q" ++ Name)
730            end;
731       true ->
732            erl_syntax:abstract(V)
733    end.
734
735
736
737-spec template_vars(template_or_templates()) -> [id()].
738
739%% @doc Return an ordered list of the metavariables in the template.
740
741template_vars(Template) ->
742    template_vars(Template, []).
743
744template_vars(Templates, Vars) when is_list(Templates) ->
745    lists:foldl(fun template_vars_1/2, Vars, Templates);
746template_vars(Template, Vars) ->
747    template_vars_1(Template, Vars).
748
749template_vars_1({template, _, _, Groups}, Vars) ->
750    lists:foldl(fun (G, V) -> lists:foldl(fun template_vars_1/2, V, G) end,
751                Vars, Groups);
752template_vars_1({Var}, Vars) ->
753    ordsets:add_element(Var, Vars);
754template_vars_1({'*',Var}, Vars) ->
755    ordsets:add_element(Var, Vars);
756template_vars_1(_, Vars) ->
757    Vars.
758
759
760-spec tree(template_or_templates()) -> tree_or_trees().
761
762%% @doc Revert a template to a normal syntax tree. Any remaining
763%% metavariables are turned into `@'-prefixed atoms or `909'-prefixed
764%% integers.
765%% @see template/1
766
767tree(Templates) when is_list(Templates) ->
768    [tree_1(T) || T <- Templates];
769tree(Template) ->
770    tree_1(Template).
771
772tree_1({template, Type, Attrs, Groups}) ->
773    %% flattening here is needed for templates created via source transforms
774    Gs = [lists:flatten([tree_1(T) || T <- G]) || G <- Groups],
775    erl_syntax:set_attrs(make_tree(Type, Gs), Attrs);
776tree_1({Var}) when is_atom(Var) ->
777    erl_syntax:atom(list_to_atom("@"++atom_to_list(Var)));
778tree_1({Var}) when is_integer(Var) ->
779    erl_syntax:integer(list_to_integer("909"++integer_to_list(Var)));
780tree_1({'*',Var}) when is_atom(Var) ->
781    erl_syntax:atom(list_to_atom("@@"++atom_to_list(Var)));
782tree_1({'*',Var}) when is_integer(Var) ->
783    erl_syntax:integer(list_to_integer("9099"++integer_to_list(Var)));
784tree_1(Leaf) ->
785    Leaf.  % any syntax tree, not necessarily atomic (due to substitutions)
786
787
788-spec subst(pattern_or_patterns(), env()) -> tree_or_trees().
789
790%% @doc Substitute metavariables in a pattern or list of patterns, yielding
791%% a syntax tree or list of trees as result. Both for normal metavariables
792%% and glob metavariables, the substituted value may be a single element or
793%% a list of elements. For example, if a list representing `1, 2, 3' is
794%% substituted for `var' in either of `[foo, _@var, bar]' or `[foo, _@@var,
795%% bar]', the result represents `[foo, 1, 2, 3, bar]'.
796
797subst(Trees, Env) when is_list(Trees) ->
798    [subst_0(T, Env) || T <- Trees];
799subst(Tree, Env) ->
800    subst_0(Tree, Env).
801
802subst_0(Tree, Env) ->
803    tree_1(subst_1(template(Tree), Env)).
804
805
806-spec tsubst(pattern_or_patterns(), env()) -> template_or_templates().
807
808%% @doc Like subst/2, but does not convert the result from a template back
809%% to a tree. Useful if you want to do multiple separate substitutions.
810%% @see subst/2
811%% @see tree/1
812
813tsubst(Trees, Env) when is_list(Trees) ->
814    [subst_1(template(T), Env) || T <- Trees];
815tsubst(Tree, Env) ->
816    subst_1(template(Tree), Env).
817
818subst_1({template, Type, Attrs, Groups}, Env) ->
819    Gs1 = [lists:flatten([subst_1(T, Env) || T <- G]) || G <- Groups],
820    {template, Type, Attrs, Gs1};
821subst_1({Var}=V, Env) ->
822    case lists:keyfind(Var, 1, Env) of
823        {Var, TreeOrTrees} -> TreeOrTrees;
824        false -> V
825    end;
826subst_1({'*',Var}=V, Env) ->
827    case lists:keyfind(Var, 1, Env) of
828        {Var, TreeOrTrees} -> TreeOrTrees;
829        false -> V
830    end;
831subst_1(Leaf, _Env) ->
832    Leaf.
833
834
835-spec alpha(pattern_or_patterns(), [{id(), id()}]) -> template_or_templates().
836
837%% @doc Alpha converts a pattern (renames variables). Similar to tsubst/1,
838%% but only renames variables (including globs).
839%% @see tsubst/2
840
841alpha(Trees, Env) when is_list(Trees) ->
842    [alpha_1(template(T), Env) || T <- Trees];
843alpha(Tree, Env) ->
844    alpha_1(template(Tree), Env).
845
846alpha_1({template, Type, Attrs, Groups}, Env) ->
847    Gs1 = [lists:flatten([alpha_1(T, Env) || T <- G]) || G <- Groups],
848    {template, Type, Attrs, Gs1};
849alpha_1({Var}=V, Env) ->
850    case lists:keyfind(Var, 1, Env) of
851        {Var, NewVar} -> {NewVar};
852        false -> V
853    end;
854alpha_1({'*',Var}=V, Env) ->
855    case lists:keyfind(Var, 1, Env) of
856        {Var, NewVar} -> {'*',NewVar};
857        false -> V
858    end;
859alpha_1(Leaf, _Env) ->
860    Leaf.
861
862
863-spec match(pattern_or_patterns(), tree_or_trees()) ->
864                   {ok, env()} | error.
865
866%% @doc Match a pattern against a syntax tree (or patterns against syntax
867%% trees) returning an environment mapping variable names to subtrees; the
868%% environment is always sorted on keys. Note that multiple occurrences of
869%% metavariables in the pattern is not allowed, but is not checked.
870%%
871%% @see template/1
872%% @see switch/2
873
874match(Patterns, Trees) when is_list(Patterns), is_list(Trees) ->
875    try {ok, match_1(Patterns, Trees, [])}
876    catch
877        error -> error
878    end;
879match(Patterns, Tree) when is_list(Patterns) -> match(Patterns, [Tree]);
880match(Pattern, Trees) when is_list(Trees) -> match([Pattern], Trees);
881match(Pattern, Tree) ->
882    try {ok, match_template(template(Pattern), Tree, [])}
883    catch
884        error -> error
885    end.
886
887match_1([P|Ps], [T | Ts], Dict) ->
888    match_1(Ps, Ts, match_template(template(P), T, Dict));
889match_1([], [], Dict) ->
890    Dict;
891match_1(_, _, _Dict) ->
892    erlang:error(merl_match_arity).
893
894%% match a template against a syntax tree
895match_template({template, Type, _, Gs}, Tree, Dict) ->
896    case type(Tree) of
897        Type -> match_template_1(Gs, subtrees(Tree), Dict);
898        _ -> throw(error)  % type mismatch
899    end;
900match_template({Var}, _Tree, Dict)
901  when Var =:= '_' ; Var =:= 0 ->
902    Dict;  % anonymous variable
903match_template({Var}, Tree, Dict) ->
904    orddict:store(Var, Tree, Dict);
905match_template(Tree1, Tree2, Dict) ->
906    %% if Tree1 is not a template, Tree1 and Tree2 are both syntax trees
907    case compare_trees(Tree1, Tree2) of
908        true -> Dict;
909        false -> throw(error)  % different trees
910    end.
911
912match_template_1([G1 | Gs1], [G2 | Gs2], Dict) ->
913    match_template_2(G1, G2, match_template_1(Gs1, Gs2, Dict));
914match_template_1([], [], Dict) ->
915    Dict;
916match_template_1(_, _, _Dict) ->
917    throw(error).  % shape mismatch
918
919match_template_2([{Var} | Ts1], [_ | Ts2], Dict)
920  when Var =:= '_' ; Var =:= 0 ->
921    match_template_2(Ts1, Ts2, Dict);  % anonymous variable
922match_template_2([{Var} | Ts1], [Tree | Ts2], Dict) ->
923    match_template_2(Ts1, Ts2, orddict:store(Var, Tree, Dict));
924match_template_2([{'*',Var} | Ts1], Ts2, Dict) ->
925    match_glob(lists:reverse(Ts1), lists:reverse(Ts2), Var, Dict);
926match_template_2([T1 | Ts1], [T2 | Ts2], Dict) ->
927    match_template_2(Ts1, Ts2, match_template(T1, T2, Dict));
928match_template_2([], [], Dict) ->
929    Dict;
930match_template_2(_, _, _Dict) ->
931    throw(error).  % shape mismatch
932
933%% match the tails in reverse order; no further globs allowed
934match_glob([{'*',Var} | _], _, _, _) ->
935    fail("multiple glob variables in same match group: ~w", [Var]);
936match_glob([T1 | Ts1], [T2 | Ts2], Var, Dict) ->
937    match_glob(Ts1, Ts2, Var, match_template(T1, T2, Dict));
938match_glob([], _Group, Var, Dict) when Var =:= '_' ; Var =:= 0 ->
939    Dict;  % anonymous glob variable
940match_glob([], Group, Var, Dict) ->
941    orddict:store(Var, lists:reverse(Group), Dict);
942match_glob(_, _, _, _Dict) ->
943    throw(error).  % shape mismatch
944
945
946%% compare two syntax trees for equivalence
947compare_trees(T1, T2) ->
948    Type1 = type(T1),
949    case type(T2) of
950        Type1 ->
951            case subtrees(T1) of
952                [] ->
953                    case subtrees(T2) of
954                        [] -> compare_leaves(Type1, T1, T2);
955                        _Gs2 -> false  % shape mismatch
956                    end;
957                Gs1 ->
958                    case subtrees(T2) of
959                        [] -> false;  % shape mismatch
960                        Gs2 -> compare_trees_1(Gs1, Gs2)
961                    end
962            end;
963        _Type2 ->
964            false  % different tree types
965    end.
966
967compare_trees_1([G1 | Gs1], [G2 | Gs2]) ->
968    compare_trees_2(G1, G2) andalso compare_trees_1(Gs1, Gs2);
969compare_trees_1([], []) ->
970    true;
971compare_trees_1(_, _) ->
972    false.  % shape mismatch
973
974compare_trees_2([T1 | Ts1], [T2 | Ts2]) ->
975    compare_trees(T1, T2) andalso compare_trees_2(Ts1, Ts2);
976compare_trees_2([], []) ->
977    true;
978compare_trees_2(_, _) ->
979    false.  % shape mismatch
980
981compare_leaves(Type, T1, T2) ->
982    case Type of
983        atom ->
984            erl_syntax:atom_value(T1)
985                =:= erl_syntax:atom_value(T2);
986        char ->
987            erl_syntax:char_value(T1)
988                =:= erl_syntax:char_value(T2);
989        float ->
990            erl_syntax:float_value(T1)
991                =:= erl_syntax:float_value(T2);
992        integer ->
993            erl_syntax:integer_value(T1)
994                =:= erl_syntax:integer_value(T2);
995        string ->
996            erl_syntax:string_value(T1)
997                =:= erl_syntax:string_value(T2);
998        operator ->
999            erl_syntax:operator_name(T1)
1000                =:= erl_syntax:operator_name(T2);
1001        text ->
1002            erl_syntax:text_string(T1)
1003                =:= erl_syntax:text_string(T2);
1004        variable ->
1005            erl_syntax:variable_name(T1)
1006                =:= erl_syntax:variable_name(T2);
1007        _ ->
1008            true  % trivially equal nodes
1009    end.
1010
1011
1012%% @doc Match against one or more clauses with patterns and optional guards.
1013%%
1014%% Note that clauses following a default action will be ignored.
1015%%
1016%% @see match/2
1017
1018-type switch_clause() ::
1019          {pattern_or_patterns(), guarded_actions()}
1020        | {pattern_or_patterns(), guard_test(), switch_action()}
1021        | default_action().
1022
1023-type guarded_actions() :: guarded_action() | [guarded_action()].
1024
1025-type guarded_action() :: switch_action() | {guard_test(), switch_action()}.
1026
1027-type switch_action() :: fun( (env()) -> any() ).
1028
1029-type guard_test() :: fun( (env()) -> boolean() ).
1030
1031-type default_action() :: fun( () -> any() ).
1032
1033
1034-spec switch(tree_or_trees(), [switch_clause()]) -> any().
1035
1036switch(Trees, [{Patterns, GuardedActions} | Cs]) when is_list(GuardedActions) ->
1037    switch_1(Trees, Patterns, GuardedActions, Cs);
1038switch(Trees, [{Patterns, GuardedAction} | Cs]) ->
1039    switch_1(Trees, Patterns, [GuardedAction], Cs);
1040switch(Trees, [{Patterns, Guard, Action} | Cs]) ->
1041    switch_1(Trees, Patterns, [{Guard, Action}], Cs);
1042switch(_Trees, [Default | _Cs]) when is_function(Default, 0) ->
1043    Default();
1044switch(_Trees, []) ->
1045    erlang:error(merl_switch_clause);
1046switch(_Tree, _) ->
1047    erlang:error(merl_switch_badarg).
1048
1049switch_1(Trees, Patterns, GuardedActions, Cs) ->
1050    case match(Patterns, Trees) of
1051        {ok, Env} ->
1052            switch_2(Env, GuardedActions, Trees, Cs);
1053        error ->
1054            switch(Trees, Cs)
1055    end.
1056
1057switch_2(Env, [{Guard, Action} | Bs], Trees, Cs)
1058  when is_function(Guard, 1), is_function(Action, 1) ->
1059    case Guard(Env) of
1060        true -> Action(Env);
1061        false -> switch_2(Env, Bs, Trees, Cs)
1062    end;
1063switch_2(Env, [Action | _Bs], _Trees, _Cs) when is_function(Action, 1) ->
1064    Action(Env);
1065switch_2(_Env, [], Trees, Cs) ->
1066    switch(Trees, Cs);
1067switch_2(_Env, _, _Trees, _Cs) ->
1068    erlang:error(merl_switch_badarg).
1069
1070
1071%% ------------------------------------------------------------------------
1072%% Internal utility functions
1073
1074-dialyzer({nowarn_function, fail/1}). % no local return
1075
1076fail(Text) ->
1077    fail(Text, []).
1078
1079fail(Fs, As) ->
1080    throw({error, lists:flatten(io_lib:format(Fs, As))}).
1081
1082flatten_text([L | _]=Lines) when is_list(L) ->
1083    lists:foldr(fun(S, T) -> S ++ [$\n | T] end, "", Lines);
1084flatten_text([B | _]=Lines) when is_binary(B) ->
1085    lists:foldr(fun(S, T) -> binary_to_list(S) ++ [$\n | T] end, "", Lines);
1086flatten_text(Text) when is_binary(Text) ->
1087    binary_to_list(Text);
1088flatten_text(Text) ->
1089    Text.
1090
1091-spec metavar(tree()) -> {string()} | false.
1092
1093%% Check if a syntax tree represents a metavariable. If not, 'false' is
1094%% returned; otherwise, this returns a 1-tuple with a string containing the
1095%% variable name including lift/glob prefixes but without any leading
1096%% metavariable prefix, and instead prefixed with "v" for a variable or "i"
1097%% for an integer.
1098%%
1099%% Metavariables are atoms starting with @, variables starting with _@,
1100%% strings starting with "'@, or integers starting with 909. Following the
1101%% prefix, one or more _ or 0 characters (unless it's the last character in
1102%% the name) may be used to indicate "lifting" of the variable one or more
1103%% levels , and after that, a @ or 9 character indicates a glob metavariable
1104%% rather than a normal metavariable. If the name after the prefix is _ or
1105%% 0, the variable is treated as an anonymous catch-all pattern in matches.
1106
1107metavar(Tree) ->
1108    case type(Tree) of
1109        atom ->
1110            case erl_syntax:atom_name(Tree) of
1111                "@" ++ Cs when Cs =/= [] -> {"v"++Cs};
1112                _ -> false
1113            end;
1114        variable ->
1115            case erl_syntax:variable_literal(Tree) of
1116                "_@" ++ Cs when Cs =/= [] -> {"v"++Cs};
1117                _ -> false
1118            end;
1119        integer ->
1120            case erl_syntax:integer_value(Tree) of
1121                N when N >= 9090 ->
1122                    case integer_to_list(N) of
1123                        "909" ++ Cs -> {"n"++Cs};
1124                        _ -> false
1125                    end;
1126                _ -> false
1127            end;
1128        string ->
1129            case erl_syntax:string_value(Tree) of
1130                "'@" ++ Cs -> {"v"++Cs};
1131                _ -> false
1132            end;
1133        _ ->
1134            false
1135    end.
1136
1137%% wrappers around erl_syntax functions to provide more uniform shape of
1138%% generic subtrees (maybe this can be fixed in syntax_tools one day)
1139
1140type(T) ->
1141    case erl_syntax:type(T) of
1142        nil  -> list;
1143        Type -> Type
1144    end.
1145
1146subtrees(T) ->
1147    case erl_syntax:type(T) of
1148        tuple ->
1149            [erl_syntax:tuple_elements(T)];  %% don't treat {} as a leaf
1150        nil ->
1151            [[], []];  %% don't treat [] as a leaf, but as a list
1152        list ->
1153            case erl_syntax:list_suffix(T) of
1154                none ->
1155                    [erl_syntax:list_prefix(T), []];
1156                S ->
1157                    [erl_syntax:list_prefix(T), [S]]
1158            end;
1159        binary_field ->
1160            [[erl_syntax:binary_field_body(T)],
1161             erl_syntax:binary_field_types(T)];
1162        clause ->
1163            case erl_syntax:clause_guard(T) of
1164                none ->
1165                    [erl_syntax:clause_patterns(T), [],
1166                     erl_syntax:clause_body(T)];
1167                G ->
1168                    [erl_syntax:clause_patterns(T), [G],
1169                     erl_syntax:clause_body(T)]
1170            end;
1171        receive_expr ->
1172            case erl_syntax:receive_expr_timeout(T) of
1173                none ->
1174                    [erl_syntax:receive_expr_clauses(T), [], []];
1175                E ->
1176                    [erl_syntax:receive_expr_clauses(T), [E],
1177                     erl_syntax:receive_expr_action(T)]
1178            end;
1179        record_expr ->
1180            case erl_syntax:record_expr_argument(T) of
1181                none ->
1182                    [[], [erl_syntax:record_expr_type(T)],
1183                     erl_syntax:record_expr_fields(T)];
1184                V ->
1185                    [[V], [erl_syntax:record_expr_type(T)],
1186                     erl_syntax:record_expr_fields(T)]
1187            end;
1188        record_field ->
1189            case erl_syntax:record_field_value(T) of
1190                none ->
1191                    [[erl_syntax:record_field_name(T)], []];
1192                V ->
1193                    [[erl_syntax:record_field_name(T)], [V]]
1194            end;
1195        _ ->
1196            erl_syntax:subtrees(T)
1197    end.
1198
1199make_tree(list, [P, []]) -> erl_syntax:list(P);
1200make_tree(list, [P, [S]]) -> erl_syntax:list(P, S);
1201make_tree(tuple, [E]) -> erl_syntax:tuple(E);
1202make_tree(binary_field, [[B], Ts]) -> erl_syntax:binary_field(B, Ts);
1203make_tree(clause, [P, [], B]) -> erl_syntax:clause(P, none, B);
1204make_tree(clause, [P, [G], B]) -> erl_syntax:clause(P, G, B);
1205make_tree(receive_expr, [C, [], _A]) -> erl_syntax:receive_expr(C);
1206make_tree(receive_expr, [C, [E], A]) -> erl_syntax:receive_expr(C, E, A);
1207make_tree(record_expr, [[], [T], F]) -> erl_syntax:record_expr(T, F);
1208make_tree(record_expr, [[E], [T], F]) -> erl_syntax:record_expr(E, T, F);
1209make_tree(record_field, [[N], []]) -> erl_syntax:record_field(N);
1210make_tree(record_field, [[N], [E]]) -> erl_syntax:record_field(N, E);
1211make_tree(Type, Groups) ->
1212    erl_syntax:make_tree(Type, Groups).
1213
1214merge_comments(_StartLine, [], [T]) -> T;
1215merge_comments(_StartLine, [], Ts) -> Ts;
1216merge_comments(StartLine, Comments, Ts) ->
1217    merge_comments(StartLine, Comments, Ts, []).
1218
1219merge_comments(_StartLine, [], [], [T]) -> T;
1220merge_comments(_StartLine, [], [T], []) -> T;
1221merge_comments(_StartLine, [], Ts, Acc) ->
1222    lists:reverse(Acc, Ts);
1223merge_comments(StartLine, Cs, [], Acc) ->
1224    merge_comments(StartLine, [], [],
1225                   [erl_syntax:set_pos(
1226                      erl_syntax:comment(Indent, Text),
1227                      anno(StartLine + Line - 1))
1228                    || {Line, _, Indent, Text} <- Cs] ++ Acc);
1229merge_comments(StartLine, [C|Cs], [T|Ts], Acc) ->
1230    {Line, _Col, Indent, Text} = C,
1231    CommentLine = StartLine + Line - 1,
1232    case erl_syntax:get_pos(T) of
1233        Pos when Pos < CommentLine ->
1234            %% TODO: traverse sub-tree rather than only the top level nodes
1235            merge_comments(StartLine, [C|Cs], Ts, [T|Acc]);
1236        CommentLine ->
1237            Tc = erl_syntax:add_postcomments(
1238                   [erl_syntax:comment(Indent, Text)], T),
1239            merge_comments(StartLine, Cs, [Tc|Ts], Acc);
1240        _ ->
1241            Tc = erl_syntax:add_precomments(
1242                   [erl_syntax:comment(Indent, Text)], T),
1243            merge_comments(StartLine, Cs, [Tc|Ts], Acc)
1244    end.
1245
1246a0() ->
1247    anno(0).
1248
1249anno(Location) ->
1250    erl_anno:new(Location).
1251