37
38:- module(shell,
39 [ shell/0,
40 ls/0,
41 ls/1, 42 cd/0,
43 cd/1, 44 pushd/0,
45 pushd/1, 46 dirs/0,
47 pwd/0,
48 popd/0,
49 mv/2, 50 rm/1 51 ]). 52:- autoload(library(apply),[maplist/3,maplist/2]). 53:- autoload(library(error),
54 [existence_error/2,instantiation_error/1,must_be/2]). 55:- autoload(library(lists),[nth1/3]). 56
57:- multifile
58 file_style/2. 59
60
61:- set_prolog_flag(generate_debug_info, false). 62
69
82
83shell :-
84 interective_shell(Shell),
85 access_file(Shell, execute),
86 !,
87 shell(Shell).
88shell :-
89 existence_error(config, shell).
90
91interective_shell(Shell) :-
92 current_prolog_flag(shell, Shell).
93interective_shell(Shell) :-
94 getenv('SHELL', Shell).
95interective_shell(Shell) :-
96 current_prolog_flag(posix_shell, Shell).
97interective_shell(Shell) :-
98 current_prolog_flag(windows, true),
99 getenv(comspec, Shell). 100
101
106
107cd :-
108 cd(~).
109
110cd(Dir) :-
111 name_to_file(Dir, Name),
112 working_directory(_, Name).
113
126
127:- dynamic
128 stack/1. 129
130pushd :-
131 pushd(+1).
132
133pushd(N) :-
134 integer(N),
135 !,
136 findall(D, stack(D), Ds),
137 ( nth1(N, Ds, Go),
138 retract(stack(Go))
139 -> pushd(Go),
140 print_message(information, shell(directory(Go)))
141 ; warning('Directory stack not that deep', []),
142 fail
143 ).
144pushd(Dir) :-
145 name_to_file(Dir, Name),
146 working_directory(Old, Name),
147 asserta(stack(Old)).
148
149popd :-
150 retract(stack(Dir)),
151 !,
152 working_directory(_, Dir),
153 print_message(information, shell(directory(Dir))).
154popd :-
155 warning('Directory stack empty', []),
156 fail.
157
158dirs :-
159 working_directory(WD, WD),
160 findall(D, stack(D), Dirs),
161 maplist(dir_name, [WD|Dirs], Results),
162 print_message(information, shell(file_set(Results))).
163
167
168pwd :-
169 working_directory(WD, WD),
170 print_message(information, format('~w', [WD])).
171
172dir_name('/', '/') :- !.
173dir_name(Path, Name) :-
174 atom_concat(P, /, Path),
175 !,
176 dir_name(P, Name).
177dir_name(Path, Name) :-
178 current_prolog_flag(unix, true),
179 expand_file_name('~', [Home0]),
180 ( atom_concat(Home, /, Home0)
181 -> true
182 ; Home = Home0
183 ),
184 atom_concat(Home, FromHome, Path),
185 !,
186 atom_concat('~', FromHome, Name).
187dir_name(Path, Path).
188
193
194ls :-
195 ls('.').
196
197ls(Spec) :-
198 name_to_files(Spec, Matches),
199 ls_(Matches).
200
201ls_([]) :-
202 !,
203 warning('No Match', []).
204ls_([Dir]) :-
205 exists_directory(Dir),
206 !,
207 atom_concat(Dir, '/*', Pattern),
208 expand_file_name(Pattern, Files),
209 maplist(tagged_file_in_dir, Files, Results),
210 print_message(information, shell(file_set(Results))).
211ls_(Files) :-
212 maplist(tag_file, Files, Results),
213 print_message(information, shell(file_set(Results))).
214
215tagged_file_in_dir(File, Result) :-
216 file_base_name(File, Base),
217 ( exists_directory(File)
218 -> atom_concat(Base, /, Label),
219 Result = dir(File, Label)
220 ; Result = file(File, Base)
221 ).
222
223tag_file(File, dir(File, Label)) :-
224 exists_directory(File),
225 !,
226 atom_concat(File, /, Label).
227tag_file(File, file(File,File)).
228
233
234mv(From, To) :-
235 name_to_files(From, Src),
236 name_to_new_file(To, Dest),
237 mv_(Src, Dest).
238
239mv_([One], Dest) :-
240 \+ exists_directory(Dest),
241 !,
242 rename_file(One, Dest).
243mv_(Multi, Dest) :-
244 ( exists_directory(Dest)
245 -> maplist(mv_to_dir(Dest), Multi)
246 ; print_message(warning, format('Not a directory: ~w', [Dest])),
247 fail
248 ).
249
250mv_to_dir(Dest, Src) :-
251 file_base_name(Src, Name),
252 atomic_list_concat([Dest, Name], /, Target),
253 rename_file(Src, Target).
254
258
259rm(File) :-
260 name_to_file(File, A),
261 delete_file(A).
262
263
267
268name_to_file(Spec, File) :-
269 name_to_files(Spec, Files),
270 ( Files = [File]
271 -> true
272 ; print_message(warning, format('Ambiguous: ~w', [Spec])),
273 fail
274 ).
275
276name_to_new_file(Spec, File) :-
277 name_to_files(Spec, Files, false),
278 ( Files = [File]
279 -> true
280 ; print_message(warning, format('Ambiguous: ~w', [Spec])),
281 fail
282 ).
283
284name_to_files(Spec, Files) :-
285 name_to_files(Spec, Files, true).
286name_to_files(Spec, Files, Exists) :-
287 name_to_files_(Spec, Files, Exists),
288 ( Files == []
289 -> print_message(warning, format('No match: ~w', [Spec])),
290 fail
291 ; true
292 ).
293
294name_to_files_(Spec, Files, _) :-
295 compound(Spec),
296 compound_name_arity(Spec, _Alias, 1),
297 !,
298 findall(File,
299 ( absolute_file_name(Spec, File,
300 [ access(exist),
301 file_type(directory),
302 file_errors(fail),
303 solutions(all)
304 ])
305 ; absolute_file_name(Spec, File,
306 [ access(exist),
307 file_errors(fail),
308 solutions(all)
309 ])
310 ),
311 Files).
312name_to_files_(Spec, Files, Exists) :-
313 file_name_to_atom(Spec, S1),
314 expand_file_name(S1, Files0),
315 ( Exists == true,
316 Files0 == [S1],
317 \+ access_file(S1, exist)
318 -> warning('"~w" does not exist', [S1]),
319 fail
320 ; Files = Files0
321 ).
322
323file_name_to_atom(Spec, File) :-
324 atomic(Spec),
325 !,
326 atom_string(File, Spec).
327file_name_to_atom(Spec, File) :-
328 phrase(segments(Spec), L),
329 atomic_list_concat(L, /, File).
330
331segments(Var) -->
332 { var(Var),
333 !,
334 instantiation_error(Var)
335 }.
336segments(A/B) -->
337 !,
338 segments(A),
339 segments(B).
340segments(A) -->
341 { must_be(atomic, A) },
342 [ A ].
343
345
346warning(Fmt, Args) :-
347 print_message(warning, format(Fmt, Args)).
348
349:- multifile prolog:message//1. 350
351prolog:message(shell(file_set(Files))) -->
352 { catch(tty_size(_, Width), _, Width = 80)
353 },
354 table(Files, Width).
355prolog:message(shell(directory(Path))) -->
356 { dir_name(Path, Name) },
357 [ '~w'-[Name] ].
358
369
370table(List, Width) -->
371 { table_layout(List, Width, Layout),
372 compound_name_arguments(Array, a, List)
373 },
374 table(0, Array, Layout).
375
376table(I, Array, Layout) -->
377 { Cols = Layout.cols,
378 Index is I // Cols + (I mod Cols) * Layout.rows + 1,
379 ( (I+1) mod Cols =:= 0
380 -> NL = true
381 ; NL = false
382 )
383 },
384 ( { arg(Index, Array, Item) }
385 -> table_cell(Item, Layout.col_width, NL)
386 ; []
387 ),
388 ( { I2 is I+1,
389 I2 < Cols*Layout.rows
390 }
391 -> ( { NL == true }
392 -> [ nl ]
393 ; []
394 ),
395 table(I2, Array, Layout)
396 ; []
397 ).
398
399table_cell(Item, ColWidth, false) -->
400 { label_length(Item, Len),
401 Spaces is ColWidth - Len
402 },
403 table_cell_value(Item),
404 [ '~|~t~*+'-[Spaces] ].
405table_cell(Item, _ColWidth, true) -->
406 table_cell_value(Item).
407
408table_cell_value(dir(_, Label)) ==>
409 [ '~w'-[Label] ].
410table_cell_value(file(File, Label)) ==>
411 ( { file_style(File, Style) }
412 -> ( { Style == url }
413 -> [ url(File,Label) ]
414 ; [ ansi(Style, '~w', [Label]) ]
415 )
416 ; [ '~w'-[Label] ]
417 ).
418
426
427file_style(File, url) :-
428 file_name_extension(_, Ext, File),
429 link_file_extension(Ext),
430 !.
431
432link_file_extension(Ext) :-
433 user:prolog_file_type(Ext,source).
434
439
440table_layout(Atoms, Width, _{cols:Cols, rows:Rows, col_width:ColWidth}) :-
441 length(Atoms, L),
442 longest(Atoms, Longest),
443 Cols is max(1, Width // (Longest + 3)),
444 Rows is integer(L / Cols + 0.49999), 445 ColWidth is Width // Cols.
446
447longest(List, Longest) :-
448 longest(List, 0, Longest).
449
450longest([], M, M) :- !.
451longest([H|T], Sofar, M) :-
452 label_length(H, L),
453 L >= Sofar,
454 !,
455 longest(T, L, M).
456longest([_|T], S, M) :-
457 longest(T, S, M).
458
459label_length(dir(_, Label), Len) =>
460 atom_length(Label, Len).
461label_length(file(_, Label), Len) =>
462 atom_length(Label, Len)