9:- module(map, 10 [ 11 geo_map//1, 12 average_geopoints/2 13 ]). 14 15:- use_module(library(http/html_write)). 16:- use_module(library(settings)). 17 18:- use_module(weblog(info/maps/google/gmap)). 19:- use_module(weblog(info/maps/leaflet/leafletmap)). 20 21 22:- meta_predicate geo_map( , , ).
Generator is an arity n term that corresponds to an arity n+1 predicate.
geo_map//1 will repeatedly query Generator for information and build up the map. The final argument may be
provider(-Name)
one of leaflet or google. default googleid(-ID)
The map div id and javascript variable name will be set to
this. default lmap or gmap depending on provider. must be valid
javascript identifier as atom.zoom(Zoom)
The zoom level. Provider specific how this maps to a
viewport. Default 14center(Lat, Long)
center map view here. defaults to average of
pointspoint(-Lat, -Long)
A marker will be placed at this pointicon_for(+point(Lat, Long), -IconName)
icon to use for this point.
default is provider default icon.tooltip_for(+point(Lat, Long), -ToolTipText)
contents of tooltip
default is no tooltippopup_for(-HTML, +point(Lat, Long))
termerized HTML to put in popupstyle(-Style)
only meaningful for leaflet, is cloudmade style
numbermaptype(-Type)
only meaningful for google maps, is the constant for
google.maps.MapTypeId (one of 'HYBRID', 'ROADMAP', 'SATELLITE', 'TERRAIN')Defining icon types means binding an icon/3 for each type, then binding all the properties
icon(-Name, -ImageSource, -ShadowSource)
Defines an icon type name.
The actual javascript names are common for all maps with same
provider, so you should only define the icons for each map provider
once.Defining an icon requires that the following be defined for each icon type name:
icon_size(+Name, X, Y)
size of icon imageshadow_size(+Name, X, Y)
size of shadow imageicon_anchor(+Name, X, Y)
offset from UL of image to the point
touching the spot on the mapshadow_anchor(+Name, X, Y)
offset
from UL of shadow image to the point touching the spot on mappopup_anchor(+Name, X, Y)
offset from the point touching map to
where the popup appears (so, eg, Y coord is often negative)
@tbd add an example to docs
*/
90geo_map(Generator) --> 91 { 92 ( call(Generator, provider(P)) 93 ; 94 P = google 95 ) 96 }, 97 make_geo_map(P, Generator). 98 99geo_map(_Generator) --> 100 { 101 throw(error(domain_error(list, 'provider'), context(geo_map//2, 102 'invalid provider'))) 103 }, 104 html([p('error - cannot make map')]). 105 106 107make_geo_map(leaflet, Generator) --> 108 lmap(Generator). 109make_geo_map(google, Generator) --> 110 gmap(Generator).
116average_geopoints([] , point(0.0, 0.0)) :- !. 117average_geopoints(Coordinates, point(ALat, ALong)) :- 118 sum_geopoints(Coordinates, 0, SumLat, 0, SumLong), 119 length(Coordinates, Count), 120 ALat is SumLat/Count, 121 ALong is SumLong/Count. 122 123sum_geopoints([], Lat, Lat, Long, Long). 124sum_geopoints([point(Lat, Long)|T], Lat0, LatS, Long0, LongS) :- 125 Lat1 is Lat0+Lat, 126 Long1 is Long0+Long, 127 sum_geopoints(T, Lat1, LatS, Long1, LongS)
Maps display
A provider neutral maps component.
Weblog Licensed under LGPL */