next up previous contents
Next: TRALE Output Up: ale_trale_man Previous: TRALE-EXTENSION:Installing [incr TSDB()]   Contents


Pretty-printing Hooks

[Code]
This section is intended for more advanced audiences who are proficient in Prolog and ALE .

ALE  uses a data structure that is not so easily readable without pretty-printing or access predicates. In order to make pretty-printing more customizable, hooks are provided to portray feature structures and inequations. If these hooks succeed, the pretty-printer assumes that the structure/inequation has been printed and quietly succeeds. If the hooks fail, the pretty-printer will print the structure/inequation by the default method used in previous versions of ALE . The hooks are called with every pretty-printing call to a substructure of a given feature structure. It is, therefore, important that the user's hooks use the arguments provided to mark visited substructures if the feature structure being printed is potentially cyclic, or else pretty-printing may not terminate.

Portraying feature structures

The hook for portraying feature structures is:

portray_fs(Type,FS,KeyedFeats,VisIn,VisOut,TagsIn,TagsOut,Col,
           HDIn,HDOut)

FS is the feature structure to be printed. This is ALE's internal representation of this structureD.1. It is recommended that access to information in this structure be obtained by Type and KeyedFeats although the brave of heart may wish to work with it directly. FS is also used to check token identity with structures in the Vis and Tags trees, as described below. Type is the type of FS. KeyedFeats is a list of fval/3 triples:

[fval(Feat_1,Val_1,Restr_1),..., fval(Feat_n,Val_n,Restr_n)]

where n is the number of appropriate features to Type. FS's value at Feat_i is Val_i, and the appropriate value restriction of Type at Feat_i is Restr_i.

VisIn, VisOut, TagsIn and TagsOut are AVL trees. They can be manipulated using the access predicates found in the library(assoc) module of SICStus Prolog. VisIn is a tree of the nodes visited so far in the current printing call, and TagsIn is a tree of the nodes with re-entrancies in the structure(s) currently being printed (of which FS may just be a small piece). Each node in an AVL tree has a key, used for searching, and a value. In both Vis and Tags trees, the key is a feature structure such as FS. For example, the call:

get_assoc(FS,VisIn,FSVal)

determines whether FS has been visited before. In the Vis tree, the value (FSVal in the above example) at a given key is not used by the default pretty-printer. The user may change them to anything desired. When the default pretty-printer adds a node to the Vis tree, it adds the current FS with a fresh unbound variable as the value.

In the Tags tree, the value at key FS is the numeric tag that the default pretty-printer would print in square brackets to indicate structure-sharing at that location. The user may change this value (using get_assoc/5 or put_assoc/
3
), and the default pretty-printer will use that (with a write/1 call) instead.

A hook must return a TagsOut and VisOut tree to the pretty-printer if it succeeds. At a minimum, this means binding TagsOut to TagsIn and VisOut to VisIn. If the structure being traversed is potentially cyclic, VisOut should, in general, update VisOut to record that the current node has been visited to avoid an infinite traversal.

Col is the number of columns that have already been indented before the hook was called. This is useful for formatting. HDIn and HDOut are hook data. They are not used by the default pretty-printer, and are simply passed around for the convenience of hooks to record information to pass to their next invocation. The initial top-level call to a portray_fs hook contains 0 (zero) as the value of HDIn. Thus, HDIn can also be used to distinguish the first call from subsequent calls provided that the 0 is replaced with something else in recursive calls.

The file pphooks.pl (discussed in subsection D.0.3 below) shows a simple printing hook to produce output very much as the default pretty-printer would.

When a portray_fs hook prints one of FS's feature values, it typically will call the pretty-printer rather than attempt to manipulate the data structure directly. This callback is provided by:

print_fs(VarType,FS,VisIn,VisOut,TagsIn,TagsOut,Col,HDIn,HDOut)

Note that the type and feature values of FS do not need to be supplied--those will be filled in by the system before control is passed to portray_fs or the default pretty-printer.

VarType is currently not used. The other positions are the same as in portray_fs.

Portraying inequations

The hook for inequations is:

portray_ineq(FS1,FS2,IqsIn,IqsOut,TagsIn,TagsOut,VisIn,VisOut,Col,
             HDIn,HDOut).

This is called when there is an inequation between FS1 and FS2 with IqsIn being the remaining inequations. The hook should return the remainder to consider printing next in IqsOut, which is normally bound to IqsIn. IqsIn can also be used to test whether FS1=\=FS2 is the last inequation.

Col is the number of columns that the default pretty-printer would print before printing FS1. This is different from the use of Col in potray_fs where it is the number of columns already printed. The other arguments are the same as in portray_fs.

Inequations are typically printed after all feature structures and their substructures in a top-level call to the pretty-printer have been printed. Likewise, portray_ineq is only called once portray_fs has been called on all feature structures and their substructures in a top-level call. Typically, the arguments to inequations will thus have been visited before--the only exceptions to this are inequated extensionally typed feature structures.


A sample pretty-printing hook

The following Prolog code shows how the default pretty-printer can be written as a hook. This code is available online on the ALE  web site under the name pphooks.pl.

The file has two top-level predicates: portray_fs/10 and portray_ineq/11. As mentioned above, the former is responsible for printing feature structures and the latter, for printing inequations.

The first thing that portray_fs/10 does is check whether the feature structure it is printing is tagged, i.e., whether it is structure-shared with another feature structure. This check is made using get_assoc(FS,TagsIn,Tag). If so, the tag is printed between square brackets. Then using get_assoc(FS,VisIn,_), the system determines whether the feature structure has already been printed. Should this be the case, VisOut, TagsOut and HDOut are respectively bound with VisIn, TagsIn and HDIn, and the hook succeeds with nothing else printed.

If, on the other hand, the feature structure has not been printed already, and FS is a variable, then either Type, or in case Type has at least one appropriate feature, mgsat(Type), is printed. Then, put_assoc/4 is used to update VisOut to include FS, and TagsOut and HDOut are bound to TagsIn and HDIn, respectively.

In case the feature structure is not a variable, its type is written, and a call to a recursive predicate is made to print each feature-value pair of FS in turn. Two important things to note are that (1) VisOut is updated to include FS before the call is made to avoid non-termination on cyclic structures, and (2) the feature values are actually printed with a callback to print_fs/9 (which in turn calls portray_fs/10 again).

The predicate portray_ineq/11 works similarly. Note that Col spaces are added by the hook itself, unlike portray_fs/10.

The source code of pphooks.pl is given below:

% pphooks.pl

% default printer written as hook (w/o type or feat hiding or
% FS expansion)

portray_fs(Type,FS,KeyedFeats,VisIn,VisOut,TagsIn,TagsOut,Col,
           HDIn,HDOut):-

% print Tag if shared
  ( get_assoc(FS,TagsIn,Tag)
  -> write('['),write(Tag),write('] ')
  ;  true),

% print structure if not yet visited
  ( get_assoc(FS,VisIn,_)
  -> VisOut = VisIn,
     TagsOut = TagsIn,
     HDOut = HDIn     % already printed

% variable - use Type to print
  ; var(FS) -> ( approp(_,Type,_)
               -> write('mgsat('),write(Type),write(')')
               ; write(Type)
               ),
               put_assoc(FS,VisIn,_,VisOut),
               TagsOut = TagsIn,
               HDOut = HDIn


            % otherwise print Type and recurse
            ; write(Type),
            put_assoc(FS,VisIn,_,VisMid),
            print_feats(KeyedFeats,VisMid,VisOut,TagsIn,
                        TagsOut,Col,HDIn,HDOut)
  ).

print_feats([],Vis,Vis,Tags,Tags,_Col,HD,HD).
print_feats([fval(F,Val,Restr)|Feats],VisIn,VisOut,TagsIn,
            TagsOut,Col,HDIn,HDOut) :-
  nl,tab(Col),
  write_feature(F,LengthF),  % capitalise, print and count
                             % characters
  NewCol is Col + LengthF + 1,
  print_fs(Restr,Val,VisIn,VisMid,TagsIn,TagsMid,NewCol,HDIn,
           HDMid),
  print_feats(Feats,VisMid,VisOut,TagsMid,TagsOut,Col,HDMid,
              HDOut).


portray_ineq(FS1,FS2,Rest,Rest,VisIn,VisOut,TagsIn,TagsOut,
             Col,HDIn,HDOut):-
  tab(Col),
  print_fs(bot,FS1,VisIn,VisMid,TagsIn,TagsMid,Col,HDIn,
           HDMid),
  nl,write('  =\\=  '), NewCol is Col + 7,
  print_fs(bot,FS2,VisMid,VisOut,TagsMid,TagsOut,NewCol,
           HDMid,HDOut).



Subsections
next up previous contents
Next: TRALE Output Up: ale_trale_man Previous: TRALE-EXTENSION:Installing [incr TSDB()]   Contents
TRALE User's Manual