View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2011-2025, VU University Amsterdam
    7                              CWI, Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(prolog_history,
   38          [ prolog_history/1
   39          ]).   40:- autoload(library(base32),[base32/2]).   41
   42:- multifile
   43    prolog:history/2.

Per-directory persistent commandline history

This module implements persistency of the commandline history over Prolog sessions on Prolog installations that are based on the GNU readline library (default for the development version on Unix systems).

The history is stored in the directory <config>/dir-history. For each directory for which it keeps the history, there is file whose name is the base32 encoding of the directory path.

This file is normally loaded when Prolog is started if user_input is a terminal and the system supports history. */

   59:- create_prolog_flag(save_history, true, [type(boolean)]).
 history_directory(-Dir) is semidet
Dir is the directory where the per-directory history databases are stored.
   66history_directory(Dir) :-
   67    absolute_file_name(user_app_config('dir-history'),
   68                       Dir,
   69                       [ access(write),
   70                         file_type(directory),
   71                         file_errors(fail)
   72                       ]),
   73    !.
   74history_directory(Dir) :-
   75    absolute_file_name(user_app_config('.'),
   76                       ConfigDir,
   77                       [ access(write),
   78                         file_type(directory),
   79                         file_errors(fail)
   80                       ]),
   81    atom_concat(ConfigDir, '/dir-history', Dir),
   82    (   exists_directory(Dir)
   83    ->  '$my_file'(Dir)
   84    ;   file_directory_name(Dir, Parent),
   85        '$my_file'(Parent),
   86        make_directory(Dir)
   87    ).
 dir_history_file(+Dir, -File) is det
dir_history_file(?Dir, ?File) is nondet
File is the history file for a Prolog session running in Dir.
   94dir_history_file(Dir, File) :-
   95    nonvar(Dir),
   96    !,
   97    history_directory(Base),
   98    absolute_file_name(Dir, Path),
   99    base32(Path, Encoded),
  100    atomic_list_concat([Base, Encoded], /, File).
  101dir_history_file(Dir, File) :-
  102    history_directory(HDir),
  103    directory_files(HDir, Files),
  104    '$member'(Base32, Files),
  105    base32(Dir, Base32),
  106    !,
  107    atomic_list_concat([Dir, Base32], /, File).
  108
  109write_history(File) :-
  110    current_prolog_flag(save_history, true),
  111    catch(prolog:history(user_input, save(File)), _, true), !.
  112write_history(_).
 prolog_history(+Action) is det
Execute Action on the history. Action is one of
enable
Enable history. First loads history for the current directory. Loading the history is done at most once.
disable
Sets the Prolog flag save_history to false, such that the history is not saved on halt.
save
If there is a history loaded from a file, save the current history back into that file if save_history is true
  129:- thread_local history_loaded/1.  130
  131load_dir_history(File) :-
  132    (   exists_file(File),
  133        prolog:history(user_input, load(File))
  134    ->  assertz(history_loaded(File))
  135    ;   true
  136    ).
  137
  138prolog_history(enable) =>
  139    (   history_loaded(_)
  140    ->  true
  141    ;   catch(dir_history_file('.', File), E,
  142              (print_message(warning, E),fail)),
  143        catch(load_dir_history(File), E,
  144              print_message(warning, E)),
  145        (   thread_self(main)
  146        ->  at_halt(write_history(File))
  147        ;   true
  148        ),
  149        set_prolog_flag(save_history, true)
  150    ).
  151prolog_history(disable) =>
  152    set_prolog_flag(save_history, false).
  153prolog_history(save) =>
  154    (   history_loaded(File)
  155    ->  write_history(File)
  156    ;   true
  157    )