1/* 2 Copyright 2015 Samer Abdallah (UCL) 3 4 This program is free software; you can redistribute it and/or 5 modify it under the terms of the GNU Lesser General Public License 6 as published by the Free Software Foundation; either version 2 7 of the License, or (at your option) any later version. 8 9 This program is distributed in the hope that it will be useful, 10 but WITHOUT ANY WARRANTY; without even the implied warranty of 11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the 12 GNU Lesser General Public License for more details. 13 14 You should have received a copy of the GNU Lesser General Public 15 License along with this library; if not, write to the Free Software 16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA 17*/ 18 19:- module(rcutils, 20 [ persistent_history/2 21 , confirm_on_halt/0 22 ]).
43user:file_search_path(home,Home) :- expand_file_name('~',[Home]). 44 45:- use_module(library(hostname)).
49confirm_on_halt :- at_halt(confirm_halt).
55confirm_halt :- 56 write('Are you sure you want to exit? [y/n] '), flush_output, 57 repeat, 58 get_single_char(C), 59 ( C=0'y -> writeln(y) 60 ; C=0'n -> cancel_halt('Exit cancelled') 61 ; fail 62 ). 63 64:- dynamic persistent_history_stream_file/2.
If called during SWI Prolog initialisation (ie in the ~/.swiplrc file, in a command line -g goal, or in a program loaded with -s on the command line) then the line editor and history mechanisms will not have been initialised yet, so you must load whichever line editor library you like (readline or editline) first.
Valid options are:
For example, the author finds it useful to add the following to his ~/.swiplrc:
:- use_module(library(hostname)). persistent_history :- hostname(Hostname), atom_concat('.swipl_history.',Hostname,HistFile), load_files(library(readline), [if(not_loaded)]), set_prolog_flag(readline, readline), % work around bug in readline foreign library persistent_history(HistFile,[interval(60)]).
This means that any program can call persistent_history/0 to get a host specific history file, which is useful when a directory is shared or synchronised across several machines.
98persistent_history(H,Opts) :- 99 current_input(S), 100 ( persistent_history_stream_file(S,H) -> true 101 ; persistent_history_stream_file(S,H1) -> throw(persistent_history_mismatch(H1,H)) 102 ; print_message(information, rcutils:history_using_file(H)), 103 ( \+current_predicate(prolog_history:prolog_history/1) 104 -> create_prolog_flag(save_history, false, [type(boolean)]) 105 ; current_prolog_flag(save_history,true) , 106 prolog_history:history_loaded(PHFile) 107 -> prolog_history:write_history(PHFile), 108 prolog_history(disable), 109 print_message(information, rcutils:closed_prolog_history(PHFile)) 110 ; set_prolog_flag(save_history,false) 111 ), 112 (exists_file(H) -> histop(S, load(H)); true), 113 assert(persistent_history_stream_file(S,H)), 114 current_prolog_flag(os_argv,ARGV), 115 atomics_to_string(ARGV," ",Command), 116 history_event('Start: ~s',[Command]), 117 at_halt(history_event('Halt',[])), 118 ( option(interval(Interval),Opts) 119 -> print_message(information, rcutils:history_save_interval(Interval)), 120 periodic_save_history(Interval) 121 ; histop(S, save(H)) 122 ) 123 ). 124 125history_event(Msg,Args) :- 126 persistent_history_stream_file(S,H), 127 get_time(Now), 128 format_time(string(Time),'%+',Now), 129 format(string(Info),Msg,Args), 130 format(atom(Line),'% ~w | ~s',[Time,Info]), 131 debug(history,'History event: ~s',[Line]), 132 histop(S, add(Line)), 133 histop(S, save(H)). 134 135 136periodic_save_history(Interval) :- 137 persistent_history_stream_file(S,H), 138 debug(history,'Saving history to "~s"...',[H]), 139 histop(S, save(H)), 140 alarm(Interval,periodic_save_history(Interval),_,[remove(true)]). 141 142histop(S,Op) :- once(prolog:history(S,Op)). 143 144prologmessage(rcutils:history_using_file(H)) --> ['Using persistent history file: "~s"'-[H]]. 145prologmessage(rcutils:history_save_interval(I)) --> ['Will save history every ~w seconds.'-[I]]. 146prologmessage(rcutils:closed_prolog_history(F)) --> ['Saved final prolog_history snapshot to ~w.'-[F]]
Utilities for your .swiplrc
This module provides confirm_on_halt/0, to make it harder to exit Prolog unintentionally due to over-enthusiastic Ctrl-D pressing, persistent_history/2, to keep and periodically save the current command line history to an arbitrary file, and defines the file_search_path/2 location 'home', which maps to the expand_file_name/2 expansion of '~'.
You might find it useful to put this in your .plrc/.swiplrc, eg === :-
if(exists_source(library(rcutils)))
:-use_module(library(rcutils))
. :-persistent_history('.swipl.history',[interval(300)])
. :- confirm_on_halt. :- endif. ===*/