1:-module(geonames_weather, [geo_weather_widget//1]).

Geonames implementation of weather

this returns the astergdem height at that point 10 ?- http_get('http://api.geonames.org/astergdemJSON?lat=50.01&lng=10.2&username=anniepoo&style=full', Reply, []). Reply = json([astergdem=192,lng=10.2,lat=50.01]).

*/

   12:- use_module(library(http/http_client)).   13:- use_module(library(http/http_json)).   14:- use_module(library(http/html_write)).   15:- use_module(library(uri)).   16
   17:- ensure_loaded(weblog(resources/resources)).   18
   19% TBD - this has a defect. settings are per-module, but
   20% we want all settings shared for geonames
   21%
   22:- setting(
   23  geonames_username,
   24  atom,
   25  'notarealgeonameskey',
   26  'Geonames key.  Get one at http://www.geonames.org/'
   27).   28
   29prolog:message(missing_key_file(File)) -->
   30  ['Key file ~w is missing.'-[File], nl].
   31:-
   32  % Print an error message if the keyfile is not present.
   33  (
   34    absolute_file_name(
   35      weblog('keys/geonameskey'),
   36      File,
   37      [access(read), file_errors(fail), file_type(prolog)]
   38    )
   39  ->
   40    load_settings(File)
   41  ;
   42    debug(weblog, 'Geonames key missing', [])
   43  ).   44
   45geo_weather_widget(_) -->
   46  {
   47    setting(geonames_username, notarealgeonameskey)
   48  },
   49  !,
   50  html([p('Missing geonames key in weblog/keys/geonameskey.pl')]).
   51geo_weather_widget(Generator) -->
   52	{
   53	    setting(geonames_username, UserName),
   54	    (	call(Generator, id(ID)) ; ID = weather),
   55	    generator_lat_long(Generator, Lat, Lng),
   56            uri_query_components(Qs, [lat(Lat), lng(Lng), username(UserName)]),
   57            format(atom(URI), 'http://api.geonames.org/astergdemJSON?~w', [Qs]),
   58            http_get(URI, _Reply, [])
   59        },
   60	html(div([id=ID, class=[weblog, 'weather-widget']],
   61		 p('someday a weather widget')
   62		)).
   63
   64generator_lat_long(Generator, Lat, Lng) :-
   65	call(Generator, point(Lat, Lng))