1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(trees_to_ascii, [
   17		trees_to_ascii/2  % +SyntaxLists, -Ascii
   18	]).

ASCII trees

This module creates ASCII graphics for syntax trees.

author
- Tobias Kuhn
version
- 2008-03-17 */
 trees_to_ascii(+SyntaxLists, -Ascii)
Returns the trees described by the syntax list as an atom (ASCII graphics).
   33trees_to_ascii([], '').
   34        
   35trees_to_ascii([FirstAndOnly], Ascii) :-
   36	tree_to_ascii(FirstAndOnly, Ascii),
   37	!.
   38
   39trees_to_ascii([First | Rest], Ascii) :-
   40	tree_to_ascii(First, AsciiFirst),
   41	trees_to_ascii(Rest, AsciiRest),
   42	format(atom(Ascii), '~w~n~w', [AsciiFirst, AsciiRest]).
 tree_to_ascii(+SyntaxList, -Ascii)
   47tree_to_ascii(Tree, Ascii) :-
   48	retractall(char(_,_,_)),
   49	retractall(final_line(_)),
   50	depth(Tree, Depth),
   51	FinalLine is Depth * 2,
   52	assert(final_line(FinalLine)),
   53	draw_tree(Tree, 0, 0, _, _),
   54	get_ascii(0, Ascii).
 char(+Line, +Pos, -Char)
   59:- dynamic(char/3).
 final_line(-FinalLine)
   64:- dynamic(final_line/1).
 get_ascii(+Line, -Ascii)
   69get_ascii(Line, Ascii) :-
   70	setof(P, C^char(Line,P,C), Ps),
   71	!,
   72	last(Ps, MaxPos),
   73	get_line(Line, 0, MaxPos, Atom),
   74	NewLine is Line + 1,
   75	get_ascii(NewLine, AsciiRest),
   76	atom_concat(Atom, '\n', AtomT),
   77	atom_concat(AtomT, AsciiRest, Ascii).
   78
   79get_ascii(_, '').
 get_line(+Line, +Pos, +End, -Ascii)
   84get_line(_, Pos, End, '') :-
   85	Pos > End,
   86	!.
   87
   88get_line(Line, Pos, End, Ascii) :-
   89	( char(Line, Pos, Char) ; Char = ' ' ),
   90	!,
   91	NewPos is Pos + 1,
   92	get_line(Line, NewPos, End, AsciiRest),
   93	atom_concat(Char, AsciiRest, Ascii).
 draw_tree(+Tree, +Line, +Start, -Head, -End)
   98draw_tree(Tree, Line, Start, Start, End) :-
   99	(Tree = [Atom] ; Tree = Atom),
  100	atomic(Atom),
  101	!,
  102	atom_chars(Atom, AtomChars),
  103	final_line(FinalLine),
  104	draw_vertical_line(Start, Line, FinalLine-1),
  105	draw_chars(FinalLine, Start, AtomChars),
  106	length(AtomChars, Length),
  107	End is Start + Length.
  108
  109draw_tree([Parent|Children], Line, Start, Head, End) :-
  110	draw_children(Children, Line + 2, Start, ChildrenEnd, [FirstHead|HeadList]),
  111	last([FirstHead|HeadList], LastHead),
  112	draw_horizontal_line(Line + 1, FirstHead, LastHead),
  113	Head is (FirstHead + LastHead) // 2,
  114	atom_chars(Parent, ParentChars),
  115	draw_chars(Line, Head, ParentChars),
  116	draw_char(Line + 1, Head, '|'),
  117	length(ParentChars, Length),
  118	(ChildrenEnd > Head + Length -> End = ChildrenEnd ; End is Head + Length).
 draw_children(+Children, +Line, +Start, -End, -HeadList)
  123draw_children([Child], Line, Start, End, [Head]) :-
  124	!,
  125	draw_tree(Child, Line, Start, Head, End).
  126
  127draw_children([Child|Rest], Line, Start, End, [Head|HeadList]) :-
  128	draw_tree(Child, Line, Start, Head, TempPos),
  129	draw_children(Rest, Line, TempPos + 1, End, HeadList).
 draw_chars(+Line, +Pos, -CharList)
  134draw_chars(_, _, []).
  135
  136draw_chars(Line, Pos, [Char|Rest]) :-
  137	draw_char(Line, Pos, Char),
  138	NewPos is Pos + 1,
  139	draw_chars(Line, NewPos, Rest).
 draw_horizontal_line(+Line, +Start, +End)
  144draw_horizontal_line(_, Start, End) :-
  145	Start > End,
  146	!.
  147
  148draw_horizontal_line(Line, Start, End) :-
  149	draw_char(Line, Start, '_'),
  150	draw_horizontal_line(Line, Start + 1, End).
 draw_vertical_line(+Pos, +LineStart, +LineEnd)
  155draw_vertical_line(_, LineStart, LineEnd) :-
  156	LineStart > LineEnd,
  157	!.
  158
  159draw_vertical_line(Pos, LineStart, LineEnd) :-
  160	draw_char(LineStart, Pos, '|'),
  161	draw_vertical_line(Pos, LineStart + 1, LineEnd).
 draw_char(+Line, +Pos, +Char)
  166draw_char(Line, Pos, Char) :-
  167	LineE is Line,
  168	PosE is Pos,
  169	asserta(char(LineE, PosE, Char)).
 depth(+List, -Depth)
  174depth(Atom, 0) :-
  175	atomic(Atom).
  176
  177depth([Atom], 0) :-
  178	atomic(Atom),
  179	!.
  180
  181depth([H|T], D) :-
  182	depth(H, HD),
  183	depth(T, TD),
  184	(HD + 1 > TD -> D is HD + 1 ; D = TD)