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.
   40user:set_context_module(File):-
   41	setup_call_cleanup(
   42		open(File, read, S, [encoding(utf8)]),
   43		read(S, T),
   44		close(S)),
   45	(	(T = (:- module(M));  T = (:- module(M,_)))
   46	->	true
   47	;   M = user
   48	),
   49	module(M),
   50	write("\n"),
   51	write("Context module: "),
   52	write(M),
   53	write(.).
   54
   55user:log(M, X, X):- user:log(M).
   56
   57user:log(X):- getenv(snapshot, Log),
   58	open(Log, append, S),
   59	writeln(S, X),
   60	close(S).
   61
   62% Ad hoc way to get HOST and USER
   63
   64% ?- apropos(split).
   65%% forest_to_paths(+X, -Y) is det.
   66%	X is a  directory structure with path alias
   67%	for sub directories in X.
   68%   Y is a set of pairs (A=B) such that B is the absolute
   69%	file name of A such that file_search_path(A, B) becomes true.
   70
   71% ?- setup_aux:forest_to_paths([], X).
   72% ?- setup_aux:forest_to_paths([(a:b)-[]], X).
   73% ?- setup_aux:forest_to_paths([(a:b)-[(c:d)-[]]], X).
   74% ?- setup_aux:forest_to_paths([(a:b)-[(c:d)]], X).
   75% ?- setup_aux:forest_to_paths([(a:b)-[(c:d), (e:f)]], X).
   76
   77forest_to_paths([], []).
   78forest_to_paths([(P:Dir)-L|Xs], Out):-!,
   79	forest_to_paths(L, D),
   80	maplist(attach_dir_prefix(Dir), D, D0),
   81	forest_to_paths(Xs, Ys),
   82	append(D0, Ys, Zs),
   83	(	P == [] -> Out = Zs
   84	; 	Out = [P = Dir| Zs]
   85	).
   86forest_to_paths([:(Dir)-L|Xs], Out):-!, forest_to_paths([([]:Dir)-L|Xs], Out).
   87forest_to_paths([A|Xs], Out):- forest_to_paths([A-[]|Xs], Out).
   88
   89%
   90user:shot_init:- getenv(snapshot, F),
   91	(	exists_file(F)
   92	->	delete_file(F)
   93	;	true
   94	).
   95%
   96user:shot(X):- getenv(snapshot, File),
   97	setup_call_cleanup(
   98		open(File, append, S, [encoding(utf8)]),
   99		writeln(S, X),
  100		close(S)).
  101
  102% Check the log file "snapshot" at Desktop.
  103% ?- dbg(shift(true)).
  104% ?- dbg((true, shift(X=1))).
  105% ?- dbg(shift((X=1, Y=2))).
  106
  107user:dbg_init:- getenv(snapshot, F),
  108	(	exists_file(F)
  109	->	delete_file(F)
  110	;	true
  111	).
  112%
  113:- meta_predicate user:dbg(0).  114%
  115user:dbg(G):- getenv(snapshot, File),
  116	setup_call_cleanup(
  117		open(File, append, S, [encoding(utf8)]),
  118		setup_aux:dbg(G, S),
  119		close(S)).
  120%
  121:- meta_predicate dbg(:, ?).  122
  123dbg(Goal, A):- reset(Goal, PGoal, Cont),
  124	(	var(PGoal) -> true
  125	;	dbg_trace(PGoal, A)
  126	),
  127	(	Cont == 0 -> true
  128	;	dbg(Cont, A)
  129	).
  130
  131%
  132:- meta_predicate dbg_trace(0, ?).  133dbg_trace(true, _):-!.
  134dbg_trace((X,Y), A):-!, dbg_trace(X, A), dbg_trace(Y, A).
  135dbg_trace((X;Y), A):-!, (dbg_trace(X, A); dbg_trace(Y, A)).
  136dbg_trace(G, A):-  call(G),
  137	write(A, "\n"),
  138	writeln(A, G).
  139%
  140user:dshot_init:- dbg_init.
  141
  142:- meta_predicate user:dshot(0).  143user:dshot(G):- getenv(snapshot, File),
  144	setup_call_cleanup(
  145		open(File, append, S, [encoding(utf8)]),
  146		setup_aux:dbg_trace(G, S),
  147		close(S))