1:- module(input, [screen_size/2]). 2
3:- use_module(library(dcg/basics)). 4
5:- use_module(utility). 6
9screen_size(Width, Height) :-
10 process(path(xdpyinfo), [], [output(Output)]),
11 atomic_list_concat(Lines, '\n', Output),
12 member(L, Lines),
13 parse(input:size_str(Width, Height), L).
14
15size_str(Width, Height) -->
16 blanks, "dimensions:", blanks, integer(Width), "x", integer(Height), string(_).
17
18screenshot(Img) :- screenshot(_, _, _, _, Img).
19screenshot(X, Y, Width, Height, Img) :-
20 call_if_var(
21 (
22 tmp_file('screenshot', Temp),
23 atom_concat(Temp, '.bmp', Img)
24 ), Img),
25 call_if_var(X = 0, X),
26 call_if_var(Y = 0, Y),
27 call_if_var(screen_size(Width, _), Width),
28 call_if_var(screen_size(_, Height), Height),
29
30 format(atom(CropArg), '~wx~w+~w+~w', [Width, Height, X, Y]),
31
32 process(path(import), ['-window', 'root', Img, '-crop', CropArg]).
33
47