1:- module(gpc_demos, [britain_arrows/1]).    2
    3:- use_module(library(gpc)).    4:- use_module(library(autowin)).    5
    6:- public
    7    britain_arrows/1.
 britain_arrows(+Op) is det
Britain has two external contours: one for the mainland, England and Wales, the other for Ireland.

The default coordinate transformation needs reversing. X and Y increase downwards and to the right.

   17britain_arrows(Op) :-
   18    read_polygon(britain, Subject),
   19    read_polygon(arrows, Clip),
   20    gpc_polygon_clip(Op, Subject, Clip, Result),
   21    new(Picture, auto_sized_picture(Op)),
   22    display_polygon(Picture, Result),
   23    send(Picture, open).
   24
   25display_polygon(Picture, Polygon) :-
   26    forall(gpc_polygon_contour(Polygon, Contour),
   27           display_contour(Picture, Contour)).
   28
   29display_contour(Picture, Contour) :-
   30    Contour =.. [Hole, Vertices],
   31    hole_colour(Hole, Colour),
   32    new(Path, path),
   33    send(Path, fill_pattern, colour(Colour)),
   34    forall(member(Vertex, Vertices), display_vertex(Path, Vertex)),
   35    send(Picture, display, Path).
   36
   37hole_colour(external, orange).
   38hole_colour(hole, pink).
   39
   40display_vertex(Path, vertex(X0, Y0)) :-
   41    X is X0 - 0,
   42    Y is 0 - Y0,
   43    send(Path, append, point(X, Y)).
   44
   45read_polygon(Spec, Polygon) :-
   46    module_property(gpc_demos, file(File)),
   47    gpc_read_polygon(Spec, Polygon, [relative_to(File), extensions([gpf])])