is divided into
%% s using the {p, Es} construct.
otp_xmlify_blockquote([#xmlElement{name=p} = E|Es]) ->
    [E | otp_xmlify_blockquote(Es)];
otp_xmlify_blockquote([#xmlText{} = E|Es]) ->
    {P, After} = find_p_ending(Es, []),
    [{p, [E|P]} | otp_xmlify_blockquote(After)];
otp_xmlify_blockquote([]) ->
    [].
%% otp_xmlify_code(E) -> Es
%% Takes a  xmlElement and split it into a list of  and
%% other xmlElements. Necessary when it contains more than a single
%% xmlText element.
%% Example:
%% #xmlElement{name=code,
%%             content=[#xmlText{}, #xmlElement{name=br}, #xmlText{}]}
%% =>
%% [#xmlElement{name=code, content=[#xmlText{}]},
%%  #xmlElement{name=br},
%%  #xmlElement{name=code, content=[#xmlText{}]}]
otp_xmlify_code(E) ->
    otp_xmlify_code(E, E#xmlElement.content, []).
otp_xmlify_code(Code, [#xmlText{} = E|Es], Acc) ->
    otp_xmlify_code(Code, Es, [Code#xmlElement{content=[E]}|Acc]);
otp_xmlify_code(Code, [#xmlElement{} = E|Es], Acc) ->
    otp_xmlify_code(Code, Es, [E|Acc]);
otp_xmlify_code(_Code, [], Acc) ->
    lists:reverse(Acc).
%% otp_xmlify_dl(Es1) -> Es2
%% Insert empty  elements if necessary.
%% OTP DTDs does not allow s with s but no - s.
otp_xmlify_dl([#xmlElement{name=dt} = E|Es]) ->
    [E|otp_xmlify_dl(Es, E)];
otp_xmlify_dl([E|Es]) ->
    [E|otp_xmlify_dl(Es)];
otp_xmlify_dl([]) ->
    [].
otp_xmlify_dl([#xmlElement{name=dd} = E|Es], _DT) ->
    [E|otp_xmlify_dl(Es)];
otp_xmlify_dl([#xmlElement{name=dt} = E|Es], DT) ->
    DD = DT#xmlElement{name=dd, attributes=[], content=[]},
    [DD,E|otp_xmlify_dl(Es, E)];
otp_xmlify_dl([E|Es], DT) ->
    [E|otp_xmlify_dl(Es, DT)];
otp_xmlify_dl([], DT) ->
    DD = DT#xmlElement{name=dd, attributes=[], content=[]},
    [DD].
%% otp_xmlify_table(Es1) -> Es2
%% Transform  contents into "text", that is, inline elements.
otp_xmlify_table([#xmlText{} = E|Es]) ->
    [E | otp_xmlify_table(Es)];
otp_xmlify_table([#xmlElement{name=tbody} = E|Es]) ->
    otp_xmlify_table(E#xmlElement.content)++otp_xmlify_table(Es);
otp_xmlify_table([#xmlElement{name=tr, content=Content}|Es]) ->
    %% Insert newlines between table rows
    otp_xmlify_table(Content)++[{br,[]}]++otp_xmlify_table(Es);
otp_xmlify_table([#xmlElement{name=th, content=Content}|Es]) ->
    [{em, Content} | otp_xmlify_table(Es)];
otp_xmlify_table([#xmlElement{name=td, content=Content}|Es]) ->
    otp_xmlify_e(Content) ++ otp_xmlify_table(Es);
otp_xmlify_table([]) ->
    [].
%% otp_xmlify_img(E) -> Es.
%% Transforms a ![]() into 
otp_xmlify_img(E0) ->
    Attrs = lists:map(
	      fun(#xmlAttribute{ name = src, value = Path} = A) ->
		      V = otp_xmlify_a_fileref(Path,this),
		      A#xmlAttribute{ name = file,
				      value = V };
		 (A) ->
		      A
	      end,E0#xmlElement.attributes),
    E0#xmlElement{name = image, expanded_name = image,
		       attributes = Attrs}.
%%--Misc help functions used by otp_xmlify/1 et al---------------------
%% find_next(Tag, Es) -> {Es1, Es2}
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
%% not including) the first element with tag Tag in Es, and Es2
%% is the remaining elements of Es.
find_next(Tag, Es) ->
    find_next(Tag, Es, []).
find_next(Tag, [#xmlElement{name=Tag} = E | Es], AccEs) ->
    {lists:reverse(AccEs), [E|Es]};
find_next(Tag, [E|Es], AccEs) ->
    find_next(Tag, Es, [E|AccEs]);
find_next(_Tag, [], AccEs) ->
    {lists:reverse(AccEs), []}.
%% find_p_ending(Es, []) -> {Es1, Es2}
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
%% not including) the first paragraph break in Es, and Es2 is
%% the remaining elements of Es2.
%% Paragraph break = into 
otp_xmlify_img(E0) ->
    Attrs = lists:map(
	      fun(#xmlAttribute{ name = src, value = Path} = A) ->
		      V = otp_xmlify_a_fileref(Path,this),
		      A#xmlAttribute{ name = file,
				      value = V };
		 (A) ->
		      A
	      end,E0#xmlElement.attributes),
    E0#xmlElement{name = image, expanded_name = image,
		       attributes = Attrs}.
%%--Misc help functions used by otp_xmlify/1 et al---------------------
%% find_next(Tag, Es) -> {Es1, Es2}
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
%% not including) the first element with tag Tag in Es, and Es2
%% is the remaining elements of Es.
find_next(Tag, Es) ->
    find_next(Tag, Es, []).
find_next(Tag, [#xmlElement{name=Tag} = E | Es], AccEs) ->
    {lists:reverse(AccEs), [E|Es]};
find_next(Tag, [E|Es], AccEs) ->
    find_next(Tag, Es, [E|AccEs]);
find_next(_Tag, [], AccEs) ->
    {lists:reverse(AccEs), []}.
%% find_p_ending(Es, []) -> {Es1, Es2}
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
%% not including) the first paragraph break in Es, and Es2 is
%% the remaining elements of Es2.
%% Paragraph break = tag or empty line
%% the next blank line,   or end-of-list as P, and the remaining
%% elements of Es as After.
find_p_ending([#xmlText{value="\n \n"++_} = E|Es], P) ->
    {lists:reverse(P), [E|Es]};
find_p_ending([#xmlElement{name=p} = E|Es], P) ->
    {lists:reverse(P), [E|Es]};
find_p_ending([E|Es], P) ->
    find_p_ending(Es, [E|P]);
find_p_ending([], P) ->
    {lists:reverse(P), []}.
%% is_paragraph(E | P) -> bool()
%%   P = {p, Es}
is_paragraph(#xmlElement{name=p}) -> true;
is_paragraph({p, _Es}) -> true;
is_paragraph(_E) -> false.
%% p_content(E | P) -> Es
p_content(#xmlElement{content=Content}) -> Content;
p_content({p, Content}) -> Content.
%% is_empty(Str) -> bool()
%%   Str = string()
%% Returns true if Str is empty in the sense that it contains nothing
%% but spaces, tabs or newlines.
is_empty("\n"++Str) ->
    is_empty(Str);
is_empty(" "++Str) ->
    is_empty(Str);
is_empty("\t"++Str) ->
    is_empty(Str);
is_empty("") ->
    true;
is_empty(_) ->
    false.
%% split(Str, Seps) -> [Str]
split(Str, Seps) ->
    split(Str, Seps, []).
split([Ch|Str], Seps, Acc) ->
    case lists:member(Ch, Seps) of
	true ->  split(Str, Seps, Acc);
	false -> split(Str, Seps, Acc, [Ch])
    end;
split([], _Seps, Acc) ->
    lists:reverse(Acc).
split([Ch|Str], Seps, Acc, Chs) ->
    case lists:member(Ch, Seps) of
	true ->  split(Str, Seps, [lists:reverse(Chs)|Acc]);
	false -> split(Str, Seps, Acc, [Ch|Chs])
    end;
split([], _Seps, Acc, Chs) ->
    lists:reverse([lists:reverse(Chs)|Acc]).
%%--Functions for creating an erlref document---------------------------
%% function_name(F) -> string()
%%   F = #xmlElement{name=function}
%% Returns the name of a function as "name/arity".
function_name(E) ->
    get_attrval(name, E) ++ "/" ++ get_attrval(arity, E).
%% functions(Fs) -> Es
%%   Fs = [{Name, F}]
%%     Name = string()  "name/arity"
%%     F = #xmlElement{name=function}
functions(Fs) ->
    Es = lists:flatmap(fun ({Name, E}) -> function(Name, E) end, Fs),
    if
	Es==[] ->
	    [];
	true ->
	    {funcs, Es}
    end.
function(_Name, E=#xmlElement{content = Es}) ->
    TypeSpec = get_content(typespec, Es),
    [?NL,{func, [ ?NL,
		  {name, 
			  case funcheader(TypeSpec) of
			      [] ->
				  signature(get_content(args, Es),
					    get_attrval(name, E));
			      Spec -> Spec
			  end
			 },
		  ?NL,{fsummary, fsummary(Es)},
		  ?NL,local_types(TypeSpec),
		  ?NL,{desc,
		       label_anchor(E)++
		       deprecated(Es)++
		       fulldesc(Es)++
		       seealso_function(Es)}
	   ]}].
fsummary([]) -> ["\s"];
fsummary(Es) ->
    Desc = get_content(description, Es),
    case get_content(briefDescription, Desc) of
	[] ->
	    fsummary_equiv(Es);    % no description at all if no equiv
	ShortDesc ->
	    text_only(ShortDesc)
    end.
fsummary_equiv(Es) ->
    case get_content(equiv, Es) of
	[] -> ["\s"];
	Es1 ->
	    case get_content(expr, Es1) of
		[] -> ["\s"];
		[Expr] ->
		    ["Equivalent to ", Expr, ".",?NL]
	    end
    end.
label_anchor(E) ->
    case get_attrval(label, E) of
	"" -> [];
	Ref -> [{marker, [{id, Ref}],[]},?NL]
    end.
label_anchor(Content, E) ->
    case get_attrval(label, E) of
	"" -> Content;
	Ref -> {p,[{marker, [{id, Ref}],[]},
		   {em, Content}]}
    end.
signature(Es, Name) -> 
    [Name, "("] ++ seq(fun arg/1, Es) ++ [") -> term()", ?NL].
arg(#xmlElement{content = Es}) ->
    [get_text(argName, Es)].
funcheader([]) -> [];
funcheader(Es) ->
    [t_name(get_elem(erlangName, Es))] ++ t_utype(get_elem(type, Es)).
local_types([]) -> [];
local_types(Es) ->
    local_defs2(get_elem(localdef, Es)).
-define(LOCAL_TYPES, edoc_local_defs).
local_defs2([]) -> [];
local_defs2(Es) ->
    case collect_local_types(Es) of
        [] -> local_defs3(Es);
        LocalTypes ->
            ?LOCAL_TYPES = ets:new(?LOCAL_TYPES, [named_table]),
            true = ets:insert(?LOCAL_TYPES, LocalTypes),
            try
                local_defs3(Es)
            after
                ets:delete(?LOCAL_TYPES)
            end
    end.
local_defs3(Es) ->
    {type,[?NL | [{v, localdef2(E)} || E <- Es]]}.
%% Does not work well for parametrized types.
collect_local_types(Es) ->
    lists:append([collect_local_type(E) || E <- Es]).
collect_local_type(#xmlElement{content = Es}) ->
    case get_elem(typevar, Es) of
        [] ->
            [{t_abstype(get_content(abstype, Es))}];
        [_] ->
            []
    end.
%% Like localdef/1, but does not use label_anchor/2 -- we don't want any
%% markers or em tags in  tag, plain text only!
%% When used stand-alone, EDoc generates links to local types. An ETS
%% table holds local types, to avoid generating links to them.
localdef2(#xmlElement{content = Es}) ->
    Var = case get_elem(typevar, Es) of
              [] ->
		  [t_abstype(get_content(abstype, Es))];
              [V] ->
                  t_var(V)
          end,
    Var ++ [" = "] ++ t_utype(get_elem(type, Es)).
type_name(#xmlElement{content = Es}) ->
    t_name(get_elem(erlangName, get_content(typedef, Es))).
types(Ts) ->
    Es = lists:flatmap(fun ({Name, E}) -> typedecl(Name, E) end, Ts),
    [?NL, {taglist,[?NL|Es]}].
typedecl(Name, #xmlElement{content = Es}) ->
    TypedefEs = get_content(typedef, Es),
    Id = "type-"++Name,
    [{tag, [{marker,[{id,Id}],[]}] ++ typedef(TypedefEs)},
     ?NL,
     {item, local_defs(get_elem(localdef, TypedefEs)) ++ fulldesc(Es)},
     ?NL].
typedef(Es) ->
    Name = ([t_name(get_elem(erlangName, Es)), "("]
  	    ++ seq(fun t_utype_elem/1, get_content(argtypes, Es), [")"])),
    case get_elem(type, Es) of
 	 [] ->
	    Name;
 	 Type ->
	    Name ++ [" = "] ++ t_utype(Type)
    end.
local_defs([]) -> [{p,[]}];
local_defs(Es) ->
    [?NL, {ul, [{li, [{p, localdef(E)}]} || E <- Es]}].
localdef(E = #xmlElement{content = Es}) ->
    Var = case get_elem(typevar, Es) of
	      [] -> 
		  [label_anchor(t_abstype(get_content(abstype, Es)), E)];
	      [V] ->
		  t_var(V)
	  end,
    Var ++ [" = "] ++ t_utype(get_elem(type, Es)).
deprecated(Es) ->
    case get_content(deprecated, Es) of
	[] -> [];
	DeprEs ->
	    Es2 = get_content(fullDescription,
			      get_content(description, DeprEs)),
	    Es3 = otp_xmlify_e(Es2),
	    [{p, [{em, ["This function is deprecated: "]} |Es3]}, ?NL]
    end.
fulldesc(Es) ->
    case get_content(fullDescription, get_content(description, Es)) of
	[] ->
	    index_desc(Es);
	Desc ->
	    [?NL|otp_xmlify(Desc)] ++ [?NL]
    end.
index_desc(Es) ->
    Desc = get_content(description, Es),
    case get_content(briefDescription, Desc) of
	[] ->
	    equiv(Es);    % no description at all if no equiv
	ShortDesc ->
	    ShortDesc
    end.
seealso_module(Es) ->
    case get_elem(see, Es) of
	[] -> [];
	Es1 ->
	    {section,[{title,["See also"]},{p,seq(fun see/1, Es1, [])}]}
    end.
seealso_function(Es) ->
    case get_elem(see, Es) of
	[] -> [];
	Es1 ->
	    [{p, [{em, ["See also:"]}, " "] ++ seq(fun see/1, Es1, ["."])},
	     ?NL]
    end.
%% ELEMENT see PCDATA
%% ATTLIST name PCDATA
%%         href PCDATA
see(#xmlElement{content=Es0} = E) ->
    Href0 = get_attrval(href, E),
    {Href, Es} = otp_xmlify_a_href(Href0, Es0),
    [{seealso, [{marker, Href}], Es}].
    
equiv(Es) ->
    case get_content(equiv, Es) of
	[] -> ["\s"];
	Es1 ->
	    case get_content(expr, Es1) of
		[] -> [];
		[Expr] ->
		    Expr1 = [Expr],
		    Expr2 = case get_elem(see, Es1) of
				[] ->
				    {c,Expr1};
				[E=#xmlElement{}] ->
 				    case get_attrval(href, E) of
 					"" ->
 					    {c,Expr1};
 					Ref ->
 					    {seealso, [{marker, Ref}], Expr1}
 				    end
			    end,
		    [{p, ["Equivalent to ", Expr2, "."]}, ?NL]
	    end
    end.
authors(Es) ->
    case get_elem(author, Es) of
	[] ->
	    [?NL,{aname,["\s"]},?NL,{email,["\s"]}];
	Es1 ->
	    [?NL|seq(fun author/1, Es1, "", [])]
    end.
author(E=#xmlElement{}) ->
    Name = case get_attrval(name, E) of
	       [] -> "\s";
	       N -> N
	   end,
    Mail = case get_attrval(email, E) of
	       [] -> "\s";
	       M -> M
	   end,
    [?NL,{aname,[Name]},?NL,{email,[Mail]}].
t_name([E]) ->
    N = get_attrval(name, E),
    case get_attrval(module, E) of
	"" -> N;
	M ->
	    S = M ++ ":" ++ N,
	    case get_attrval(app, E) of
		"" -> S;
		A -> "//" ++ A ++ "/" ++ S
	    end
    end.
t_utype([E]) ->
    flatten_type(t_utype_elem(E)).
%% Make sure see also are top elements of lists.
flatten_type(T) ->
    [case is_integer(E) of
         true -> [E];
         false -> E
     end || E <- lists:flatten(T)].
t_utype_elem(E=#xmlElement{content = Es}) ->
    case get_attrval(name, E) of
	"" -> t_type(Es);
	Name ->
	    T = t_type(Es),
	    case T of
		[Name] -> T;    % avoid generating "Foo::Foo"
		T -> [Name] ++ ["::"] ++ T
	    end
    end.
t_type([E=#xmlElement{name = typevar}]) ->
    t_var(E);
t_type([E=#xmlElement{name = atom}]) ->
    t_atom(E);
t_type([E=#xmlElement{name = integer}]) ->
    t_integer(E);
t_type([E=#xmlElement{name = range}]) ->
    t_range(E);
t_type([E=#xmlElement{name = float}]) ->
    t_float(E);
t_type([#xmlElement{name = nil}]) ->
    t_nil();
t_type([#xmlElement{name = list, content = Es}]) ->
    t_list(Es);
t_type([#xmlElement{name = nonempty_list, content = Es}]) ->
    t_nonempty_list(Es);
t_type([#xmlElement{name = tuple, content = Es}]) ->
    t_tuple(Es);
t_type([#xmlElement{name = 'fun', content = Es}]) ->
    t_fun(Es);
t_type([E = #xmlElement{name = abstype, content = Es}]) ->
    t_abstype(E, Es);
t_type([#xmlElement{name = union, content = Es}]) ->
    t_union(Es);
t_type([#xmlElement{name = record, content = Es}]) ->
    t_record(Es);
t_type([#xmlElement{name = map, content = Es}]) ->
    t_map(Es).
t_var(E) ->
    [get_attrval(name, E)].
t_atom(E) ->
    [get_attrval(value, E)].
t_integer(E) ->
    [get_attrval(value, E)].
t_range(E) ->
    [get_attrval(value, E)].
t_float(E) ->
    [get_attrval(value, E)].
t_nil() ->
    ["[]"].
t_list(Es) ->
    ["["] ++ t_utype(get_elem(type, Es)) ++ ["]"].
t_nonempty_list(Es) ->
    ["["] ++ t_utype(get_elem(type, Es)) ++ [", ...]"].
t_tuple(Es) ->
    ["{"] ++ seq(fun t_utype_elem/1, Es, ["}"]).
t_fun(Es) ->
    ["("] ++ seq(fun t_utype_elem/1, get_content(argtypes, Es),
		 [") -> "] ++ t_utype(get_elem(type, Es))).
t_record([E|Es]) ->
    ["#", get_attrval(value, E), "{"++ seq(fun t_field/1, Es) ++"}"].
t_field(#xmlElement{name=field, content=[Atom,Type]}) ->
    [get_attrval(value, Atom), "="] ++ t_utype_elem(Type).
t_map(Es) ->
    ["#{"] ++ seq(fun t_map_field/1, Es, ["}"]).
t_map_field(E = #xmlElement{name = map_field, content = [K,V]}) ->
    KElem = t_utype_elem(K),
    VElem = t_utype_elem(V),
    AS = case get_attrval(assoc_type, E) of
             "assoc" -> " => ";
             "exact" -> " := "
         end,
    [KElem ++ AS ++ VElem].
t_abstype(E, Es) ->
    see_type(E, t_abstype(Es)).
t_abstype(Es) ->
    Name = t_name(get_elem(erlangName, Es)),
    [Name, "("] ++ seq(fun t_utype_elem/1, get_elem(type, Es), [")"]).
see_type(E, Es0) ->
    case get_attrval(href, E) of
        [] -> Es0;
        Href0 ->
            try
                false = is_local_type(Es0),
                %% Fails for parametrized types:
                Text = #xmlText{value = lists:append(Es0)},
                {Href, Es} = otp_xmlify_a_href(Href0, [Text]),
                [{seealso, [{marker, Href}], Es}]
            catch
                _:_ ->
                    Es0
            end
    end.
is_local_type(Es) ->
    try
        [_] = ets:lookup(?LOCAL_TYPES, Es),
        true
    catch
        _:_->
            false
    end.
t_union(Es) ->
    seq(fun t_utype_elem/1, Es, " | ", []).
%% seq(Fun, Es)
%% seq(Fun, Es, Tail)
%% seq(Fun, Es, Sep, Tail) -> [string()]
%%   Fun = function(E) -> [string()]
%%   Sep = string()
%%   Tail = [string()]
%% Applies Fun to each element E in Es and return the appended list of
%% strings, separated by Sep which defaults to ", " and ended by Tail
%% which defaults to [].
seq(Fun, Es) ->
    seq(Fun, Es, []).
seq(Fun, Es, Tail) ->
    seq(Fun, Es, ", ", Tail).
seq(Fun, [E], _Sep, Tail) ->
    Fun(E) ++ Tail;
seq(Fun, [E | Es], Sep, Tail) ->
    Fun(E) ++ [Sep] ++ seq(Fun, Es, Sep, Tail);
seq(_Fun, [], _Sep, Tail) ->
    Tail.
%%--Misc functions for accessing fields etc-----------------------------
%% Type definitions used below:
%%   E = #xmlElement{} | #xmlText{}
%%   Es = [E]
%%   Tag = atom(), XHTML tag
%%   Name = atom(), XHTML attribute name
%%   Attrs = [#xmlAttribute{}]
%%   Ts = [#xmlText{}]
%% parent(E) -> module | overview
parent(E) ->
    Parents = E#xmlElement.parents,
    {Parent,_} = lists:last(Parents),
    Parent.
%% get_elem(Tag, Es1) -> Es2
%% Returns a list of all elements in Es which have the name Tag.
get_elem(Name, [#xmlElement{name = Name} = E | Es]) ->
    [E | get_elem(Name, Es)];
get_elem(Name, [_ | Es]) ->
    get_elem(Name, Es);
get_elem(_, []) ->
    [].
%% get_attr(Name, Attrs1) -> Attrs2
%% Returns a list of all attributes in Attrs1 which have the name Name.
get_attr(Name, [#xmlAttribute{name = Name} = A | As]) ->
    [A | get_attr(Name, As)];
get_attr(Name, [_ | As]) ->
    get_attr(Name, As);
get_attr(_, []) ->
    [].
%% get_attrval(Name, E) -> string()
%% If E has one attribute with name Name, return its value, otherwise ""
get_attrval(Name, #xmlElement{attributes = As}) ->
    case get_attr(Name, As) of
	[#xmlAttribute{value = V}] ->
	    V;
	[] -> ""
    end.
%% get_content(Tag, Es1) -> Es2
%% If there is one element in Es1 with name Tag, returns its contents,
%% otherwise []
get_content(Name, Es) ->
    case get_elem(Name, Es) of
	[#xmlElement{content = Es1}] ->
	    Es1;
	[] -> []
    end.
%% get_text(Tag, Es) -> string()
%% If there is one element in Es with name Tag, and its content is 
%% a single xmlText, return the value of this xmlText.
%% Otherwise return "".
get_text(Name, Es) ->
    case get_content(Name, Es) of
	[#xmlText{value = Text}] ->
	    Text;
	[] -> ""
    end.
%% get_text(E) -> string()
%% Return the value of an single xmlText which is the content of E,
%% possibly recursively.
get_text(#xmlElement{content=[#xmlText{value=Text}]}) ->
    Text;
get_text(#xmlElement{content=[E]}) ->
    get_text(E).
%% text_and_name_only(Es) -> {N, Ts}
text_and_a_name_only(Es) ->
    [Name|_] = [Name ||
                   #xmlElement{
                      name = a,
                      attributes = [#xmlAttribute{name=name}]}=Name <- Es],
    {Name#xmlElement{content = []}, text_only(Es)}.
%% text_only(Es) -> Ts
%% Takes a list of xmlElement and xmlText and return a lists of xmlText.
text_only([#xmlElement{content = Content}|Es]) ->
    text_only(Content) ++ text_only(Es);
text_only([#xmlText{} = E |Es]) ->
    [E | text_only(Es)];
text_only([]) ->
    [].