1:- module(setup_aux, [mk_file_search_path/1, setup_env/1
    2					 ]).    3
    4setup_env(X=E):- eval_concat(E, V), setenv(X, V).
    5%
    6eval_concat($(V), U):-!, getenv(V, U).
    7eval_concat(X+Y, V):-!, eval_concat(X, U),
    8	eval_concat(Y, W),
    9	atom_concat(U, W, V).
   10eval_concat(V, V).
   11
   12mk_file_search_path(DirStr):-
   13	getenv(pac_root, Dir),
   14	file_directory_name(Dir, RootName),
   15	mk_file_search_path(RootName, DirStr),
   16	getenv(home, H),
   17	concat_atom([H, '/.config'], Configs),
   18	assert(user:file_search_path(configs, Configs)).
   19%
   20mk_file_search_path(Root, DirStr):-
   21	forest_to_paths(DirStr, Eqs),
   22	maplist(attach_dir_prefix(Root), Eqs, Eqs0),
   23	maplist(assert_search_path, Eqs0).
   24
   25% Remarck: [] means empty string "" to avoid "//" in paths.
   26attach_dir_prefix([], E, E):-!.
   27attach_dir_prefix(A, P = [], P = A):-!.
   28attach_dir_prefix(A, P = B, P = C):-
   29	concat_atom([A, /, B], C).
   30%
   31assert_search_path(A = B):-
   32	(	string(B) -> atom_string(B0, B)
   33	;   B0 = B
   34	),
   35	assert(user:file_search_path(A, B0)).
of the buffer-file.
   39user:set_context_module(File):-
   40	setup_call_cleanup(
   41		open(File, read, S, [encoding(utf8)]),
   42		read(S, T),
   43		close(S)),
   44	(	(T = (:- module(M));  T = (:- module(M,_)))
   45	->	true
   46	;   M = user
   47	),
   48	module(M),
   49	write("\n"),
   50	write("Context module: "),
   51	write(M),
   52	write(.).
   53
   54user:log(M, X, X):- user:log(M).
   55
   56user:log(X):- getenv(snapshot, Log),
   57	open(Log, append, S),
   58	writeln(S, X),
   59	close(S).
   60
   61% Ad hoc way to get HOST and USER
   62
   63% ?- apropos(split).
   64%% forest_to_paths(+X, -Y) is det.
   65%	X is a  directory structure with path alias
   66%	for sub directories in X.
   67%   Y is a set of pairs (A=B) such that B is the absolute
   68%	file name of A such that file_search_path(A, B) becomes true.
   69
   70% ?- setup_aux:forest_to_paths([], X).
   71% ?- setup_aux:forest_to_paths([(a:b)-[]], X).
   72% ?- setup_aux:forest_to_paths([(a:b)-[(c:d)-[]]], X).
   73% ?- setup_aux:forest_to_paths([(a:b)-[(c:d)]], X).
   74% ?- setup_aux:forest_to_paths([(a:b)-[(c:d), (e:f)]], X).
   75
   76forest_to_paths([], []).
   77forest_to_paths([(P:Dir)-L|Xs], Out):-!,
   78	forest_to_paths(L, D),
   79	maplist(attach_dir_prefix(Dir), D, D0),
   80	forest_to_paths(Xs, Ys),
   81	append(D0, Ys, Zs),
   82	(	P == [] -> Out = Zs
   83	; 	Out = [P = Dir| Zs]
   84	).
   85forest_to_paths([:(Dir)-L|Xs], Out):-!, forest_to_paths([([]:Dir)-L|Xs], Out).
   86forest_to_paths([A|Xs], Out):- forest_to_paths([A-[]|Xs], Out).
   87
   88%
   89user:shot_init:- getenv(snapshot, F),
   90	(	exists_file(F)
   91	->	delete_file(F)
   92	;	true
   93	).
   94%
   95user:shot(X):- getenv(snapshot, File),
   96	setup_call_cleanup(
   97		open(File, append, S, [encoding(utf8)]),
   98		writeln(S, X),
   99		close(S)).
  100
  101% Check the log file "snapshot" at Desktop.
  102% ?- dbg(shift(true)).
  103% ?- dbg((true, shift(X=1))).
  104% ?- dbg(shift((X=1, Y=2))).
  105
  106user:dbg_init:- getenv(snapshot, F),
  107	(	exists_file(F)
  108	->	delete_file(F)
  109	;	true
  110	).
  111%
  112:- meta_predicate user:dbg(0).  113%
  114user:dbg(G):- getenv(snapshot, File),
  115	setup_call_cleanup(
  116		open(File, append, S, [encoding(utf8)]),
  117		setup_aux:dbg(G, S),
  118		close(S)).
  119%
  120:- meta_predicate dbg(:, ?).  121
  122dbg(Goal, A):- reset(Goal, PGoal, Cont),
  123	(	var(PGoal) -> true
  124	;	dbg_trace(PGoal, A)
  125	),
  126	(	Cont == 0 -> true
  127	;	dbg(Cont, A)
  128	).
  129
  130%
  131:- meta_predicate dbg_trace(0, ?).  132dbg_trace(true, _):-!.
  133dbg_trace((X,Y), A):-!, dbg_trace(X, A), dbg_trace(Y, A).
  134dbg_trace((X;Y), A):-!, (dbg_trace(X, A); dbg_trace(Y, A)).
  135dbg_trace(G, A):-  call(G),
  136	write(A, "\n"),
  137	writeln(A, G).
  138%
  139user:dshot_init:- dbg_init.
  140
  141:- meta_predicate user:dshot(0).  142user:dshot(G):- getenv(snapshot, File),
  143	setup_call_cleanup(
  144		open(File, append, S, [encoding(utf8)]),
  145		setup_aux:dbg_trace(G, S),
  146		close(S))