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