Did you know ... Search Documentation:
Pack refactor -- prolog/ref_replace.pl
PublicShow source

This library provides the predicate replace/5, which is the basic entry point for all the refactoring scenarios.

Note for implementors/hackers:

  • Be careful with some variables, they use destructive assignment --TODO: document them.
  • format("~a", [Atom]) does not behaves as write_term(Atom, Options), since a space is not added to separate operators from the next term, for instance after rewriting :- dynamic a/1, you would get :- dynamica/1.
  • write('') is used to reset the effect of the partial(true) option
 replace(+Level, +Pattern, +Into, :Expander, :Options) is det
Given a Level of operation, in all terms of the source code that subsumes Pattern, replace each Pattern with Into, provided that Expander succeeds. Expander can be used to finalize the shape of Into as well as to veto the expansion (if fails). The Options argument is used to control the behavior and scope of the replacement.

The predicate is efficient enough to be used also as a walker to capture all matches of Term, by printing a message and failing. For example:

replace(
    sent,
    (:-use_module(X)), _,
    (refactor_message(information, format("~w", [X])), fail),
    [file(F)])

will display all the occurrences of use_module/1 declarations in the file F. This would be useful for some complex refactoring scenarios.

The levels of operations stablishes where to look for matching terms, and could take one of the following values:

  • goal Look for terms that match a given goal. This is implemented using the source reader
  • term Look for sub-terms in a given read term recursivelly.
  • sent Look for a matching term
  • head Look for matching clause heads
  • head_rec In a clause head, look for matching terms recursivelly
  • body Look for a matching clause body
  • body_rec In a clause body, look for matching terms recursivelly

    If level is sent, some special cases of Term are used to control its behavior:

  • [] Adds an extra sentence at the top of the file.
  • end_of_file Adds an extra sentence at the bottom of the file.
  • [_|_] Replace list of sentences
  • '$NODOT'(X) Print X but without the ending dot

    The term Into could contain certain hacks to control its behavior, as follows:

  • X @@ Y Print the term X with the surroundings of Y (comments, etc.). This is useful to preserve comments in Y, if Y is going to dissapear in the transformed code.
  • X $@ Y Print the term X following the format of Y.
  • $@(X) Ignore automatic formatting following the pattern
  • $$(X) Use write_term for X, this will ignore automatic formatting following the pattern and the special terms.
  • '$G'(Into, Goal) Hook to execute Goal over the transformation generated by Into.
  • '$NOOP'(X) Just Ignore, but process X to get possible expected side effects (for instance, '$G'/2 hacks).
  • '$BODY'(X, Offset) Print X as if it where the body of a clause, that is, by introducing a new line per each conjunction and indentation starting at Offset position, plus extra characters if required.
  • '$BODY'(X) Like '$BODY'(X, 0)
  • '$BODYB'(X, Offset) Like '$BODY', but adding braces if required
  • '$BODYB'(X) Like '$BODYB'(X, 0)
  • '$CLAUSE'(X, Offset) Print X as if it where a clause, starting indentation at Offset position
  • '$CLAUSE'(X) Like '$CLAUSE'(X, 0)
  • '$LIST'(L) Print each element of L
  • '$APP'(L1, L2) Print the result of append(L1, L2, L), but preserving the formats of L1 and L2 Note that if you use append/3 directly, the format of L1 will be lost
  • '$LISTC'(L) Print each element of L in a way similar to portray_clause, but skip the dot and new line for the last element
  • '$LISTC.NL'(L) Print each element of L in a way similar to portray_clause followed by a dot and a new line. If Level is sent, the tool will add this automatically if the replacement is a list, and in the case of an empty list, the sentence will be removed
  • '$LIST,'(L) Print each element of L placing a comma between them
  • '$LIST,_'(L) Print each element of L followed by a comma
  • '$LIST,NL'(L) Print each element of L followed by a comma and a new line
  • '$LISTNL'(L) Print each element of L followed by a new line.
  • '$LIST.NL'(L) Print each element of L followed by a dot and a new line without clause layout
  • '$TEXT'(T, N) Write T with higest priority and no quoted, byasing N characters to the right
  • '$TEXT'(T) like '$TEXT'(T, 0)
  • '$TEXTQ'(T, N) Like '$TEXT'(T, N) but quoted
  • '$TEXTQ'(T) like '$TEXTQ'(T, 0)
  • '$PRETXT'(Txt, T) Write Txt before T
  • '$POSTXT'(T, Txt) Write Txt after T
  • '$POS'(Name, Term) Preserves the current write position in Name, for further usage in hacks that have Offset as argument
  • '$OUTPOS' In an Offset expression, is replaced by the current write position. For example:
    '$TEXT'(T,'$OUTPOS')

    is equivalent to:

    '$POS'(my_outpos, '$TEXT'(T, my_outpos))
  • '$SEEK'(T, O) Seek O in the current output before to print T.
  • '$TAB'(T, O) Print as many spaces as needed to make O the current write position

    Specific options for this predicate are:

  • fixpoint(+Value) States that the replacement should be applied recursively, until no more modifications are caused by the replacement.

    Value=decreasing is the default, meaning that the recursion stops if the transformed term contains more terms that could potentially match. If the level is a non recursive one (see level_rec/2), such value is equivalent to none.

    Value=file means that the recursion is performed over the hole file.

    Value=term means that the recursion is performed over the transformed term.

    Value=true means that the recursion is applied up to reach the fixpoint without decreasing control. If Level is a non recursive one, the recursion is performed over the hole file, otherwise the recursion is only applied over the transformed term.

    Value=none don't apply the fixpoint algorithm.

  • decrease_metric(:Metric) is a predicate of arity 3 of the form predicate(+Term, +Pattern, -Size) to define the metric used to perform the decreasing control (by default pattern_size/3).
  • line(-Line) Unifies Line with the line number of the sentence being refactorized.
  • clause(+Ref) Apply the refactoring to the clause refered by Ref.
  • max_tries(MaxTries) Apply no more than MaxTries changes
  • conj_width(+ConjWidth) Print several conjunctions in the same line, provided that they don't surpasses ConjWidth columns. Default is 160
  • term_width(+TermWidth) Split long terms so that when printed, they don't surpasses TermWidth columns. Default is 160
  • list_width(+ListWidth) Split long lists so that when printed, they don't surpasses ListWidth columns. Default is 160
  • linearize(+Linearize) Linearize is a subset of [vars, atms], which will linearize the term to avoid bounded variables or atoms. In some refactoring scenarios this is important if we want to avoid ambiguities. For instance, supose that you want to replayce f(A, B), by f(B, A), but if one of the matching terms is f(X, X), the change will not be performed, even if the two arguments have different layouts. To avoid this we should use the option linearize([vars]). Default is [].
  • sentence(-SentPattern) Unifies SentPattern with the sentence being processed. This is useful in some refactoring scenarios.
  • expand(Expand) Apply the program transformation to let the goal_expansion hook in ref_replace.pl be called. It only have sense if the expansion level is goal, in such level the default value is yes, otherwise is no.
  • expanded(Expanded) Unifies Expanded with the current sentence after the expansion has been applied (if applicable)
  • cleanup_attributes(CleanupAttributes) Remove attributes that could potentially be present in the sentence being refactorized, in particular, if level is goal the term could contain the attribute '$var_info'. Default value is yes.
  • max_changes(Max) Maximum number of changes performed by the refactoring.
  • vars_prefix(Prefix) Prefix added to new variables. Default 'V'
  • file(AFile) Unifies AFile with the file being reinstantiated. If AFile is instantiated on call of the predicate, limits the refactoring to such file.
  • loaded(loaded) if Loaded is false (default), refactor non loaded files too.
  • subterm_boundary(+Boundary) Processed by fix_termpos/2 to stablish the boundaries of the subterms.

    Options processed by read_term/2:

  • variable_names(-VNL) Variable names
  • comments(-Comments) Comments
  • syntax_errors(SE) Default error
  • subterm_positions(-SentPos) Subterm positions
  • term_position(-Pos) Term position

    Other options are processed by the predicate option_module_files/2 and allows to select the files or modules that are going to be modified.