34
   35:- module(ref_shell,
   36          [ rcommit/0,
   37            rdiff/0,
   38            rdiff/1,
   39            rdiff/2,
   40            rreset/0,
   41            rsave/1,
   42            rshow/0
   43          ]).   44
   45:- use_module(library(lists)).   46:- use_module(library(readutil)).   47:- use_module(library(trim_utils)).   48:- use_module(library(file_changes)).   49:- use_module(library(ref_changes)).   50:- use_module(library(ref_command)).
   58ref_commit :-
   59    once(pending_change(Index)),
   60    rdiff(save, 0, Index),
   61    reset_changes.
   62
   63rshow :-
   64    once(pending_change(Index)),
   65    rdiff(show, 0, Index).
   66
   67rsave(Diff) :-
   68    tell(Diff),
   69    rshow,
   70    told.
   71
   72rdiff :-
   73    once(rdiff(_)).
   74
   75rdiff(Index) :-
   76    pending_change(Index),
   77    succ(Index1, Index),
   78    rdiff(show, Index1, Index).
   79
   80rdiff(Index1, Index) :-
   81    rdiff(show, Index1, Index).
   82
   83rdiff(Action, Index1, Index) :-
   84    findall(File, (pending_change(IdxI, File, _), IdxI=<Index), FileU),
   85    sort(FileU, FileL),
   86    forall(member(File, FileL),
   87           apply_diff(Action, Index1, File)).
   88
   89trim_content(RawContent, Content) :-
   90    atomics_to_string(RawList, "\n", RawContent),
   91    maplist(string_right_trim, RawList, List),
   92    atomics_to_string(List, "\n", Content).
   93
   94apply_diff(Action, Index1, File) :-
   95    once(pending_change(_, File, RawContent)),    96    trim_content(RawContent, Content),    97    ( pending_change(Idx1, File, Content1),
   98      Idx1 =< Index1
   99    ->setup_call_cleanup(tmp_file_stream(text, File1, Stream),
  100                         format(Stream, '~s', [Content1]),
  101                         close(Stream)),
  102      TmpFile = true
  103    ; File1 = File,
  104      TmpFile = fail,
  105      ( access_file(File, read)
  106      ->read_file_to_string(File, Content1, [])
  107      ; Content1 = []
  108      )
  109    ),
  110    ( Content1 \= Content
  111    ->do_file_change(Action, File1, File, Content)
  112    ; true
  113    ),
  114    ( TmpFile = true
  115    ->delete_file(File1)
  116    ; true
  117    ).
  118
  119rcommit :-
  120    ref_commit,
  121    reset_commands.
  122
  123rreset :-
  124    reset_changes,
  125    reset_commands
 
Pending changes management
This library provides tools to manage the stack of pending changes of the refactoring tool, as well as to apply those changes to the files. */