1:- module(glatlong, [gaddr_latlong/6]).

Lat/long from street address

Calls Google api to get latlong info for street address.

*/

    9:- use_module(library(http/http_open)).   10:- use_module(library(http/json)).   11:- use_module(library(url)).   12
   13:- dynamic(country_location/2).
 gaddr_latlong(+Name:codes, -FormattedAddress:atom_or_codes, -Type:atom, -Bounds:box, -Location:point, -ViewPort:box) is det
box is a term of form box(NELat, NELong, SWLat, SWLong) point is a term of form point(Lat, Long)

type is an atom - known responses include

*/

   32gaddr_latlong(Name,
   33	      FA,
   34	      TYPE,
   35	      box(BoundNELat, BoundNELong, BoundSWLat, BoundSWLong),
   36	      point(Loc_Lat, Loc_Long),
   37	      box(View_NELat, View_NELong, View_SWLat, View_SWLong)
   38	      ) :-
   39	(   is_list(Name) -> atom_codes(AName , Name) ; AName = Name),
   40	www_form_encode(AName , FEName),
   41	atom_concat('http://maps.googleapis.com/maps/api/geocode/json?address=',
   42		    FEName , PreReq),
   43	atom_concat(PreReq, '&sensor=false', Req),
   44	http_open(Req, Stream, []),
   45	json_read(Stream , Term),
   46	close(Stream),
   47	json([results=[json(Results)|_],status='OK']) = Term,
   48	(   member(formatted_address=FA, Results) ; FA=Name),
   49	(   member(types=[TYPE|_], Results) ; TYPE=unknown),
   50	member(geometry=json(GEO), Results),
   51	member(bounds=json([
   52                    northeast=json([lat=BoundNELat,lng=BoundNELong]),
   53                    southwest=json([lat=BoundSWLat,lng=BoundSWLong])]), GEO),
   54	member(location=json([lat=Loc_Lat, lng=Loc_Long]), GEO),
   55	member(viewport=json([
   56                    northeast=json([lat=View_NELat,lng=View_NELong]),
   57                    southwest=json([lat=View_SWLat,lng=View_SWLong])]), GEO)