36
37:- module(shell,
38 [ shell/0,
39 ls/0,
40 ls/1, 41 cd/0,
42 cd/1, 43 pushd/0,
44 pushd/1, 45 dirs/0,
46 pwd/0,
47 popd/0,
48 mv/2, 49 rm/1 50 ]). 51:- use_module(library(lists), [nth1/3]). 52:- use_module(library(error)). 53:- use_module(library(apply)). 54:- set_prolog_flag(generate_debug_info, false). 55
62
75
76shell :-
77 interective_shell(Shell),
78 access_file(Shell, execute),
79 !,
80 shell(Shell).
81shell :-
82 existence_error(config, shell).
83
84interective_shell(Shell) :-
85 current_prolog_flag(shell, Shell).
86interective_shell(Shell) :-
87 getenv('SHELL', Shell).
88interective_shell(Shell) :-
89 current_prolog_flag(posix_shell, Shell).
90interective_shell(Shell) :-
91 current_prolog_flag(windows, true),
92 getenv(comspec, Shell). 93
94
99
100cd :-
101 cd(~).
102
103cd(Dir) :-
104 name_to_file(Dir, Name),
105 working_directory(_, Name).
106
119
120:- dynamic
121 stack/1. 122
123pushd :-
124 pushd(+1).
125
126pushd(N) :-
127 integer(N),
128 !,
129 findall(D, stack(D), Ds),
130 ( nth1(N, Ds, Go),
131 retract(stack(Go))
132 -> pushd(Go),
133 print_message(information, shell(directory(Go)))
134 ; warning('Directory stack not that deep', []),
135 fail
136 ).
137pushd(Dir) :-
138 name_to_file(Dir, Name),
139 working_directory(Old, Name),
140 asserta(stack(Old)).
141
142popd :-
143 retract(stack(Dir)),
144 !,
145 working_directory(_, Dir),
146 print_message(information, shell(directory(Dir))).
147popd :-
148 warning('Directory stack empty', []),
149 fail.
150
151dirs :-
152 working_directory(WD, WD),
153 findall(D, stack(D), Dirs),
154 maplist(dir_name, [WD|Dirs], Results),
155 print_message(information, shell(file_set(Results))).
156
160
161pwd :-
162 working_directory(WD, WD),
163 print_message(information, format('~w', [WD])).
164
165dir_name('/', '/') :- !.
166dir_name(Path, Name) :-
167 atom_concat(P, /, Path),
168 !,
169 dir_name(P, Name).
170dir_name(Path, Name) :-
171 current_prolog_flag(unix, true),
172 expand_file_name('~', [Home0]),
173 ( atom_concat(Home, /, Home0)
174 -> true
175 ; Home = Home0
176 ),
177 atom_concat(Home, FromHome, Path),
178 !,
179 atom_concat('~', FromHome, Name).
180dir_name(Path, Path).
181
186
187ls :-
188 ls('.').
189
190ls(Spec) :-
191 name_to_files(Spec, Matches),
192 ls_(Matches).
193
194ls_([]) :-
195 !,
196 warning('No Match', []).
197ls_([Dir]) :-
198 exists_directory(Dir),
199 !,
200 atom_concat(Dir, '/*', Pattern),
201 expand_file_name(Pattern, Files),
202 maplist(tagged_file_in_dir, Files, Results),
203 print_message(information, shell(file_set(Results))).
204ls_(Files) :-
205 maplist(tag_file, Files, Results),
206 print_message(information, shell(file_set(Results))).
207
208tagged_file_in_dir(File, Result) :-
209 file_base_name(File, Base),
210 ( exists_directory(File)
211 -> atom_concat(Base, /, Result)
212 ; Result = Base
213 ).
214
215tag_file(File, Dir) :-
216 exists_directory(File),
217 !,
218 atom_concat(File, /, Dir).
219tag_file(File, File).
220
225
226mv(From, To) :-
227 name_to_files(From, Src),
228 name_to_new_file(To, Dest),
229 mv_(Src, Dest).
230
231mv_([One], Dest) :-
232 \+ exists_directory(Dest),
233 !,
234 rename_file(One, Dest).
235mv_(Multi, Dest) :-
236 ( exists_directory(Dest)
237 -> maplist(mv_to_dir(Dest), Multi)
238 ; print_message(warning, format('Not a directory: ~w', [Dest])),
239 fail
240 ).
241
242mv_to_dir(Dest, Src) :-
243 file_base_name(Src, Name),
244 atomic_list_concat([Dest, Name], /, Target),
245 rename_file(Src, Target).
246
250
251rm(File) :-
252 name_to_file(File, A),
253 delete_file(A).
254
255
259
260name_to_file(Spec, File) :-
261 name_to_files(Spec, Files),
262 ( Files = [File]
263 -> true
264 ; print_message(warning, format('Ambiguous: ~w', [Spec])),
265 fail
266 ).
267
268name_to_new_file(Spec, File) :-
269 name_to_files(Spec, Files, false),
270 ( Files = [File]
271 -> true
272 ; print_message(warning, format('Ambiguous: ~w', [Spec])),
273 fail
274 ).
275
276name_to_files(Spec, Files) :-
277 name_to_files(Spec, Files, true).
278name_to_files(Spec, Files, Exists) :-
279 name_to_files_(Spec, Files, Exists),
280 ( Files == []
281 -> print_message(warning, format('No match: ~w', [Spec])),
282 fail
283 ; true
284 ).
285
286name_to_files_(Spec, Files, _) :-
287 compound(Spec),
288 compound_name_arity(Spec, _Alias, 1),
289 !,
290 findall(File,
291 ( absolute_file_name(Spec, File,
292 [ access(exist),
293 file_type(directory),
294 file_errors(fail),
295 solutions(all)
296 ])
297 ; absolute_file_name(Spec, File,
298 [ access(exist),
299 file_errors(fail),
300 solutions(all)
301 ])
302 ),
303 Files).
304name_to_files_(Spec, Files, Exists) :-
305 file_name_to_atom(Spec, S1),
306 expand_file_name(S1, Files0),
307 ( Exists == true,
308 Files0 == [S1],
309 \+ access_file(S1, exist)
310 -> warning('"~w" does not exist', [S1]),
311 fail
312 ; Files = Files0
313 ).
314
315file_name_to_atom(Spec, File) :-
316 atomic(Spec),
317 !,
318 atom_string(File, Spec).
319file_name_to_atom(Spec, File) :-
320 phrase(segments(Spec), L),
321 atomic_list_concat(L, /, File).
322
323segments(Var) -->
324 { var(Var),
325 !,
326 instantiation_error(Var)
327 }.
328segments(A/B) -->
329 !,
330 segments(A),
331 segments(B).
332segments(A) -->
333 { must_be(atomic, A) },
334 [ A ].
335
337
338warning(Fmt, Args) :-
339 print_message(warning, format(Fmt, Args)).
340
341:- multifile prolog:message//1. 342
343prolog:message(shell(file_set(Files))) -->
344 { catch(tty_size(_, Width), _, Width = 80)
345 },
346 table(Files, Width).
347prolog:message(shell(directory(Path))) -->
348 { dir_name(Path, Name) },
349 [ '~w'-[Name] ].
350
361
362table(List, Width) -->
363 { table_layout(List, Width, Layout),
364 compound_name_arguments(Array, a, List)
365 },
366 table(0, Array, Layout).
367
368table(I, Array, Layout) -->
369 { Cols = Layout.cols,
370 Index is I // Cols + (I mod Cols) * Layout.rows + 1,
371 ( (I+1) mod Cols =:= 0
372 -> NL = true
373 ; NL = false
374 )
375 },
376 ( { arg(Index, Array, Atom) }
377 -> ( { NL == false }
378 -> [ '~|~w~t~*+'-[Atom, Layout.col_width] ]
379 ; [ '~w'-[Atom] ]
380 )
381 ; []
382 ),
383 ( { I2 is I+1,
384 I2 < Cols*Layout.rows
385 }
386 -> ( { NL == true }
387 -> [ nl ]
388 ; []
389 ),
390 table(I2, Array, Layout)
391 ; []
392 ).
393
394table_layout(Atoms, Width, _{cols:Cols, rows:Rows, col_width:ColWidth}) :-
395 length(Atoms, L),
396 longest(Atoms, Longest),
397 Cols is max(1, Width // (Longest + 3)),
398 Rows is integer(L / Cols + 0.49999), 399 ColWidth is Width // Cols.
400
401longest(List, Longest) :-
402 longest(List, 0, Longest).
403
404longest([], M, M) :- !.
405longest([H|T], Sofar, M) :-
406 atom_length(H, L),
407 L >= Sofar,
408 !,
409 longest(T, L, M).
410longest([_|T], S, M) :-
411 longest(T, S, M)