Leaflet Maps display

A (for now) rudimentary leaflet maps component.

This code is part of the weblog project Licensed under LGPL */

    9:- module(leafletmap,
   10	  [ lmap//1			% +Generator
   11	  ]).   12
   13:- use_module(library(http/html_write)).   14:- use_module(library(http/html_head)).   15:- use_module(library(http/http_dispatch)).   16:- use_module(library(settings)).   17:- use_module(weblog(info/html/html_comments)).   18:- use_module(weblog(support/javascript_utils)).   19:- ensure_loaded(weblog(resources/resources)).   20
   21% this makes sure there's always a setting
   22% weblog users - do NOT change this. Copy keys/cloudmadekey.pl.example
   23% to keys/googlekey.pl and edit
   24:- setting(
   25  cloudmade_map_key,
   26  atom,
   27  notarealcloudmadekey,
   28  'Cloudmade map key.  Get one at http://account.cloudmade.com/register'
   29).   30
   31prolog:message(missing_key_file(File)) -->
   32  ['Key file ~w is missing.'-[File], nl].
   33:-
   34  % Print an error message if the keyfile is not present.
   35  (
   36    absolute_file_name(
   37      weblog('keys/cloudmadekey'),
   38      File,
   39      [access(read), file_errors(fail), file_type(prolog)]
   40    )
   41  ->
   42    load_settings(File)
   43  ;
   44% AO - 9/21/13 making this less in your face
   45%
   46%    print_message(warning, missing_key_file('cloudmadekey.pl'))
   47    debug(weblog, 'Cloudmade map key missing (keys/cloudmakekey.pl)', [])
   48  ).   49
   50% needed for some coord calc stuff
   51:- use_module(weblog(info/maps/map)).   52
   53
   54:- meta_predicate  lmap(1, ?, ?).
 lmap(+Generator)// is det
HTML component that shows Open Street Map maps, using the Leaflet library (leafletjs.com) with tiles provided by Cloudmade (cloudmade.com). Maps are generated from a closure. This is documented in map:geo_map.

Do not call this directly, call it through geo_map and pass provider(leaflet).

   68lmap(_Generator) -->
   69  {
   70    setting(cloudmade_map_key, notarealcloudmadekey)
   71  },
   72  !,
   73  html([p('Missing cloudmade key in weblog/keys/cloudmadekey.pl')]).
   74lmap(Generator) -->
   75	{
   76	    (	call(Generator, id(ID)) ; ID = lmap   )
   77	},
   78	html([
   79	      \html_requires(leaflet),
   80	      \html_post(head,
   81		\if_ie('lte IE 8',
   82                  link([ rel(stylesheet),
   83                    href('http://cdn.leafletjs.com/leaflet-0.5/leaflet.ie.css')
   84                  ]))),
   85	      div([ id(ID)
   86		 ],
   87		 [])]),
   88	define_icons(Generator),
   89	show_map(Generator),!.
   90lmap(_) -->
   91	html(p('Leaflet failed')).
   92
   93define_icons(Generator) -->
   94	{
   95	    setof(Name, A^B^call(Generator, icon(Name, A, B)), Names),!
   96	},
   97	html(script(type('text/javascript'), [
   98	     \def_icons_helper(Generator, Names) ])).
   99% fallback if no icons defined
  100define_icons(_) --> [].
  101
  102def_icons_helper(_, []) --> [].
  103def_icons_helper(Generator, [H|T]) -->
  104	{
  105	    call(Generator, icon(H, ImgSrc, MaskSrc)),
  106	    call(Generator, icon_size(H, IconSizeX, IconSizeY)),
  107	    call(Generator, shadow_size(H, ShadowSizeX, ShadowSizeY)),
  108	    call(Generator, icon_anchor(H, IconAnchorX, IconAnchorY)),
  109	    call(Generator, shadow_anchor(H, ShadowAnchorX, ShadowAnchorY)),
  110	    call(Generator, popup_anchor(H, PopupAnchorX, PopupAnchorY))
  111	},
  112	html([
  113	    'var ~wLeafIcon = L.icon({~niconUrl: \'~w\',~n'-[H, ImgSrc],
  114	    '    shadowUrl: \'~w\',~n'-[MaskSrc],
  115	    '	 iconSize:   [~w, ~w],~n'-[IconSizeX, IconSizeY],
  116	    '	 shadowSize: [~w, ~w],~n'-[ShadowSizeX, ShadowSizeY],
  117	    '    iconAnchor: [~w, ~w],~n'-[IconAnchorX, IconAnchorY],
  118	    '	 shadowAnchor: [~w, ~w],~n'-[ShadowAnchorX, ShadowAnchorY],
  119	    '    popupAnchor: [~w, ~w]~n});~n'-[PopupAnchorX, PopupAnchorY]
  120	     ]),
  121	def_icons_helper(Generator, T).
  122def_icons_helper(Generator, [H|T]) -->
  123	html(\[' // ~w could not be generated (missing values?)~n'-[H]]),
  124	def_icons_helper(Generator, T).
  125
  126show_map(Generator) -->
  127	{
  128	  (	call(Generator, id(ID)) ; ID = lmap   ),
  129	  (	call(Generator, zoom(Zoom)) ; Zoom = 14  ),
  130	    % setof fails if the goal never succeeds
  131	  (   setof(point(X,Y), call(Generator, point(X,Y)), Coordinates) ;
  132	      Coordinates = []),
  133	  setting(cloudmade_map_key, Key),
  134           Key \= notarealcloudmadekey,
  135	  (     call(Generator, center(CLat, CLong)) ; average_geopoints(Coordinates, point(CLat, CLong))),
  136	  (     call(Generator, style(Style)) ; Style = 997)
  137	},
  138	html(script(type('text/javascript'), [
  139'var ~w = L.map(\'~w\').setView([~w, ~w], ~w);\n'-[ID, ID, CLat, CLong, Zoom],
  140'L.tileLayer(\'http://{s}.tile.cloudmade.com/~w/~w/256/{z}/{x}/{y}.png\', {\n'-[Key, Style],
  141	'    maxZoom: 18,
  142	     minZoom: 2',
  143'}).addTo(~w);\nvar allmarkers = L.layerGroup().addTo(~w);\n'-[ID, ID],
  144	     \coords(Generator, Coordinates)
  145		    ])).
  146
  147% needed because var_branches doesnt suppress the error
  148:- style_check(-singleton).  149coords(_, []) --> [].
  150coords(Generator, [point(Lat, Long)|T]) -->
  151	{
  152	 (   call(Generator, tooltip_for(point(Lat, Long), ToolTip)) ; ToolTip = '' ),
  153	 (   call(Generator, id(ID)) ; ID = lmap   ),
  154	 (   call(Generator, icon_for(point(Lat, Long), N)) ->
  155	     format(codes(IconName), ', {icon: ~wLeafIcon, title: \'~w\'}', [N, ToolTip])
  156	 ;
  157	     IconName = ""
  158	),
  159    % did this to avoid having entities made
  160        format(atom(MarkerCode), 'L.marker([~w,~w]~s).addTo(allmarkers)',[Lat, Long, IconName])
  161
  162	},
  163	html([\[MarkerCode],
  164	     \decorations(Generator, point(Lat, Long)),
  165	     ';\n']),
  166	coords(Generator, T).
  167:- style_check(+singleton).  168
  169decorations(Generator, Pt) -->
  170	{
  171	   call(Generator, popup_for(HTML, Pt)),
  172	   javascript_friendly_html(HTML, JavascriptFriendlyHTML)
  173	},
  174	html('.bindPopup("'),
  175	html(\[JavascriptFriendlyHTML]),
  176	html('")'),!.
  177decorations(_, _) -->
  178	[]