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(drs_to_ascii, [
   17		drs_to_ascii/2, % +Drs, -DrsAscii
   18		display_drs/1   % +Drs
   19	]).

DRS Pretty-printer

Creates a pretty print representation of a DRS.

author
- Kaarel Kaljurand
version
- 2008-03-14 */
   31:- op(400, fx, -).   32:- op(400, fx, ~).   33:- op(500, xfx, =>).   34:- op(500, xfx, v).
 drs_to_ascii(+Drs:term, -DrsAscii:atom) is det
Arguments:
Drs- is an Attempto DRS
DrsAscii- is an ASCII-graphics representation of the DRS
   42drs_to_ascii(Drs, DrsAscii) :-
   43	drs_to_drspp(Drs, PP),
   44	with_output_to(atom(DrsAscii), pp_to_ascii(PP)).
 display_drs(+DRS)
Makes a pretty print of a DRS and writes it out on the screen.
   51display_drs(Drs):-
   52	drs_to_drspp(Drs, PP),
   53	pp_to_ascii(PP).
 drs_to_drspp(+Drs:term, -DrsPP:list) is det
Arguments:
Drs- is an Attempto DRS
DrsPP- is the DRS with indentation information
   61drs_to_drspp(Drs, PP) :-
   62	copy_term(Drs, DrsCopy),
   63	numbervars(DrsCopy, 0, _),
   64	write_drs(DrsCopy, 0, PP).
 pp_to_ascii(+PP:term) is det
   69pp_to_ascii([]).
   70
   71pp_to_ascii([(Indent, Term) | Rest]) :-
   72	with_output_to(atom(AtomTerm), format('~W', [Term, [numbervars(true)]])),
   73	PrettyIndent is Indent * 3, 
   74	writef('%r%w\n', [' ', PrettyIndent, AtomTerm]),
   75	pp_to_ascii(Rest).
 write_drs(+DRS, +Indent, -PP)
Creates a DRS in pretty print and indents it according to the value of Indent
   83write_drs(drs(Dom,[]), Indent, [(Indent,'No conditions') | PP]):-
   84	write_dom(Dom, Indent, PP),
   85	!.
   86
   87write_drs(drs(Dom,Conds),Indent,PP):-
   88	write_dom(Dom,Indent,PP1),
   89	write_conds(Conds,Indent,PP2),
   90	append(PP1,PP2,PP),
   91	!.
   92
   93write_drs(_Term,Indent,[(Indent,'ERROR')]).
 write_dom(+Dom:list, +Indent:integer, -PP:list) is det
   99write_dom(Dom, Indent, [(Indent, Dom)]).
 write_conds(+ConditionsList, +Indent)
  105write_conds([],_Indent,[]).
  106
  107write_conds([F|R],Indent,PP):-
  108	write_cond(F,Indent,PP1),
  109	write_conds(R,Indent,PP2),
  110	append(PP1,PP2,PP).
 write_cond(+Condition, +Indent)
  116write_cond(Restr => Scope,Indent,PP):-
  117	!,
  118 	NewIndent is Indent+1,
  119 	write_drs(Restr,NewIndent,PP1),
  120 	write_drs(Scope,NewIndent,PP2),
  121	append(PP1,[(NewIndent,=>)|PP2],PP).
  122
  123write_cond(Restr v Scope,Indent,PP):-
  124	!,
  125	NewIndent is Indent+1,
  126 	write_drs(Restr,NewIndent,PP1),
  127 	write_drs(Scope,NewIndent,PP2),
  128	append(PP1,[(NewIndent,v)|PP2],PP).
  129
  130write_cond([FirstCond|Conds], Indent, PP) :-
  131	!,
  132	NewIndent is Indent+1,
  133	write_conds([FirstCond|Conds], NewIndent, PP).
  134
  135write_cond(-DRS, Indent, [(NewIndent,'NOT') | PP]) :-
  136	!,
  137	NewIndent is Indent+1,
  138	write_drs(DRS,NewIndent,PP).
  139
  140write_cond(~DRS, Indent, [(NewIndent,'NAF') | PP]) :-
  141	!,
  142	NewIndent is Indent+1,
  143	write_drs(DRS, NewIndent, PP).
  144
  145write_cond(can(DRS), Indent, [(NewIndent, 'CAN') | PP]) :-
  146	!,
  147	NewIndent is Indent+1,
  148	write_drs(DRS, NewIndent, PP).
  149
  150write_cond(must(DRS), Indent, [(NewIndent, 'MUST') | PP]) :-
  151	!,
  152	NewIndent is Indent+1,
  153	write_drs(DRS, NewIndent, PP).
  154
  155write_cond(should(DRS), Indent, [(NewIndent, 'SHOULD') | PP]) :-
  156	!,
  157	NewIndent is Indent+1,
  158	write_drs(DRS, NewIndent, PP).
  159
  160write_cond(may(DRS), Indent, [(NewIndent, 'MAY') | PP]) :-
  161	!,
  162	NewIndent is Indent+1,
  163	write_drs(DRS, NewIndent, PP).
  164
  165write_cond(question(DRS), Indent, [(NewIndent, 'QUESTION') | PP]) :-
  166	!,
  167	NewIndent is Indent+1,
  168	write_drs(DRS, NewIndent, PP).
  169
  170write_cond(command(DRS), Indent, [(NewIndent, 'COMMAND') | PP]) :-
  171	!,
  172	NewIndent is Indent+1,
  173	write_drs(DRS, NewIndent, PP).
  174
  175write_cond(Label:DRS, Indent, [(NewIndent, Label) | PP]) :-
  176	!,
  177	NewIndent is Indent+1,
  178	write_drs(DRS, NewIndent, PP).
  179
  180write_cond(drs(Dom,Cond),Indent,PP):-
  181	!,
  182	NewIndent is Indent+1,
  183	write_drs(drs(Dom,Cond),NewIndent,PP).
  184
  185write_cond(Cond, Indent, [(Indent,Cond)])