1:- module(bc_image, [
    2    bc_image_dimensions/3 % +Path, -Width, -Height
    3]).

Helper module to obtain image dimensions */

    7:- use_module(library(process)).    8:- use_module(library(dcg/basics)).    9
   10% Extracts image dimensions. Fails when
   11% ImageMagick's identify command is not
   12% found in PATH or outputs unexpected data.
   13
   14bc_image_dimensions(Path, Width, Height):-
   15    catch(absolute_file_name(path(identify),
   16        Identify, [access(execute)]), _, fail),
   17    setup_call_cleanup(
   18        process_create(Identify,
   19            ['-format', '%[fx:w]x%[fx:h]', Path], [stdout(pipe(Out))]),
   20        read_stream_to_codes(Out, Codes),
   21        close(Out)),
   22    parse_dimensions(Codes, Width, Height),
   23    Width > 0, Height > 0.
   24
   25parse_dimensions(Codes, Width, Height):-
   26    phrase(dcg_dimensions(Width, Height), Codes, _), !.
   27
   28dcg_dimensions(Width, Height) -->
   29    integer(Width), "x", integer(Height)