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