Google Maps display

A (for now) rudimentary google maps component.

This code provided to weblog by Cliopatria project Licensed under LGPL */

    9:- module(gmap,
   10	  [ gmap//1			% +Coordinates
   11	  ]).   12
   13:- use_module(library(http/html_write)).   14:- use_module(library(uri)).   15:- ensure_loaded(weblog(resources/resources)).   16
   17% this makes sure there's always a setting
   18% weblog users - do NOT change this. Copy keys/googlekey.pl.example
   19% to keys/googlekey.pl and edit
   20:-   setting(
   21       google_map_key,
   22       atom,
   23       notarealgooglekey,   % don't change this here
   24       'Google map key.  "abcdefg" works for localhost (didn\'t for me -AO)'
   25).   26
   27
   28gmap_scheme(_NoScheme).
   29gmap_authority('maps.googleapis.com').
   30gmap_path('/maps/api/js').
   31gmap_fragment(_NoFragment).
   32
   33prolog:message(missing_key_file(File)) -->
   34  ['Key file ~w is missing'-[File], nl].
   35:-
   36  % Print an error message if the keyfile is not present.
   37  (
   38    absolute_file_name(
   39      weblog('keys/googlekey'),
   40      File,
   41      [access(read), file_errors(fail), file_type(prolog)]
   42    )
   43  ->
   44    load_settings(File, [undefined(error)])
   45  ;
   46% AO - 9/21/13 making this less in your face
   47%
   48% print_message(warning, missing_key_file('googlekey.pl'))
   49  debug(weblog, 'Google map key file missing (keys/googlekey.pl)', [])
   50  ).   51
   52% needed for some coord calc stuff
   53:- use_module(weblog(info/maps/map)).
 gmap(+Generator:closure)// is det
Geomap (map of Earth) component using Google Maps

Do not call this directly, call it through geo_map and bind provider(google) (or do nothing, google is the default)

Generator is an arity n term that corresponds to an arity n+1 predicate.

gmap//1 will repeatedly query Generator for information and build up the map. The final argument may be

Defining icon types means binding an icon/3 for each type, then binding all the properties

Defining an icon requires that the following be defined for each icon type name:

*/

  114gmap(_) -->
  115  {
  116    setting(google_map_key, notarealgooglekey)
  117  },
  118  !,
  119  html([p('Missing google key in weblog/keys/googlekey.pl')]).
  120gmap(Generator) -->
  121  {
  122    (call(Generator, id(ID)) ; ID = gmap),
  123    setting(google_map_key, Key),
  124    Key \= notarealgooglekey,
  125    !,
  126    gmap_scheme(Scheme),
  127    gmap_authority(Authority),
  128    gmap_path(Path),
  129    uri_query_components(Search, [key=Key, sensor=false, v=3]),
  130    uri_components(
  131      URI,
  132      uri_components(Scheme, Authority, Path, Search, _Fragment)
  133    )
  134  },
  135  html([
  136    \html_post(head, script([src(URI), type('text/javascript')], [])),
  137    \html_post(head, [\show_map(Generator)]),
  138    div(id(ID), [])
  139  ]).
  140
  141gmap(_) -->
  142	html([p('gmap failed')]).
  143
  144show_map(Generator) -->
  145	{
  146	  (	call(Generator, id(ID)) ; ID = gmap   ),
  147	  (	call(Generator, zoom(Zoom)) ; Zoom = 14  ),
  148	  (     call(Generator, maptype(MT)),
  149		member(MT, ['HYBRID', 'ROADMAP', 'SATELLITE', 'TERRAIN'])
  150	  ;
  151		MT = 'TERRAIN' ),
  152	 % setof fails if the goal always does
  153	  (   setof(point(X,Y), call(Generator, point(X,Y)), Coordinates) ;
  154	      Coordinates = []),
  155	  (
  156	        call(Generator, center(CLat, CLong))
  157	  ;     average_geopoints(Coordinates, point(CLat, CLong))
  158	  )
  159	},
  160	define_icons(Generator),
  161	html(script(type('text/javascript'), [
  162\['	var ~w;
  163	function initialize() {
  164        var mapOptions = {
  165          center: new google.maps.LatLng(~w, ~w),
  166          zoom: ~w,~n'-[ID,CLat, CLong, Zoom],
  167'          mapTypeId: google.maps.MapTypeId.~w,
  168	  mapTypeControl: false
  169        };
  170'-[MT],
  171'        ~w = new google.maps.Map(document.getElementById("~w"),
  172            mapOptions);~n'-[ID, ID],
  173         \coords(Generator, Coordinates),
  174'~n      }
  175      google.maps.event.addDomListener(window, \'load\', initialize);~n'-[ID,ID]]])).
  176
  177coords(_, []) --> [].
  178coords(Generator, [point(Lat, Long)|T]) -->
  179	{
  180	    (	call(Generator, id(ID)) ; ID = gmap   ),
  181	    (
  182	        call(Generator, icon_for(point(Lat, Long), N)),
  183		format(atom(IconAtom), ',   icon: ~wIcon,~n', [N])
  184	    ;
  185	        IconAtom = ''
  186	    ),
  187            (	call(Generator, tooltip_for(point(Lat, Long), ToolTip)),
  188		format(atom(ToolTipText), ',   title: "~w"\n',[ToolTip])
  189	    ;
  190	        ToolTipText = ''
  191	    )
  192	},
  193	html('(new google.maps.Marker({
  194    position: new google.maps.LatLng(~w, ~w)
  195~w~w
  196})).setMap(~w);~n'-[Lat, Long, IconAtom, ToolTipText, ID]),
  197	coords(Generator, T).
  198
  199define_icons(Generator) -->
  200	{
  201	    setof(Name, A^B^call(Generator, icon(Name, A, B)), Names),!
  202	},
  203	html(script(type('text/javascript'), [
  204	     \def_icons_helper(Generator, Names) ])).
  205% fallback if no icons defined
  206define_icons(_) --> [].
  207
  208def_icons_helper(_, []) --> [].
  209def_icons_helper(Generator, [H|T]) -->
  210	{
  211	    call(Generator, icon(H, ImgSrc, _)),
  212	    call(Generator, icon_size(H, IconSizeX, IconSizeY)),
  213	    call(Generator, icon_anchor(H, IconAnchorX, IconAnchorY))
  214	},
  215	html([
  216	    'var ~wIcon = {
  217    url: \'~w\',~n'-[H, ImgSrc],
  218	    '	 size:	 new google.maps.Size(~w, ~w),~n'-[IconSizeX, IconSizeY],
  219	    '    origin: new google.maps.Point(0,0),
  220   iconAnchor: new google.maps.Point(~w, ~w)
  221};~n'-[IconAnchorX, IconAnchorY]
  222	     ]),
  223	def_icons_helper(Generator, T).
  224def_icons_helper(Generator, [H|T]) -->
  225	html(\[' // ~w could not be generated (missing values?)~n'-[H]]),
  226	def_icons_helper(Generator, T)