1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2014, VU University, Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(geoip,
   31	  [ geoip_open/2,			% +Name, -Handle
   32	    geoip_open/3,			% +File, +Mode, -Handle
   33	    geoip_close/1,			% +Handle
   34	    geoip_close/0,
   35	    geoip_lookup/2,			% +From, -Result
   36	    geoip_lookup/3			% +Handle, +From, -Result
   37	  ]).   38:- use_module(library(apply)).   39:- use_foreign_library(foreign(geoip4pl)).   40
   41:- multifile user:file_search_path/2.   42
   43user:file_search_path(geoip, '/usr/share/GeoIP').

GeoIP lookup

This library provides a minimal interface to the public GeoIP library from MAXMIND

It has been tested with the Ubuntu package libgeoip-dev with the databases from the package geoip-database-contrib, which are by default installed in =/usr/share/GeoIP=. A simple usage is:

?- tcp_host_to_address('www.swi-prolog.org', IP),
   geoip_lookup(IP, R).
R = geoip{city:'Amsterdam',
          continent_code:'EU',
          country_code:'NL',
          country_code3:'NLD',
          country_name:'Netherlands',
          latitude:52.349998474121094,
          longitude:4.9166998863220215,
          netmask:16,
          region:'07'}.
To be done
- Implement more of the GeoIP library API. */
   72:- dynamic
   73	geoip_db/2.				% +Name, -Handle
 geoip_open(+Name, -Handle) is det
True when Handle is a handle to the GeoIP database Name. The database file is searched for using the pattern geoip(Name.dat). Subsequent calls to this predicate return the handle to the already opened database.
   82geoip_open(Name, Handle) :-
   83	geoip_db(Name, Handle), !.
   84geoip_open(Name, Handle) :-
   85	with_mutex(geoip,
   86		   geoip_open_sync(Name, Handle)).
   87
   88geoip_open_sync(Name, Handle) :-
   89	geoip_db(Name, Handle), !.
   90geoip_open_sync(Name, Handle) :-
   91	file_name_extension(Name, dat, File),
   92	geoip_open(geoip(File), standard, Handle),
   93	assertz(geoip_db(Name, Handle)).
 geoip_open(+File, +Mode, -Handle) is det
Open the GeoIP database file File in Mode and return a handle for it. File may use alias patterns. The default configuration provides the alias geoip, pointing to ='/usr/share/GeoIP=. Mode is one of standard, memory_cache, check_cache, index_cache or mmap_cache. Consult the library documentation for the meaning of these constants. For example:
?- geoip_open(geoip('GeoIPCity.dat'), standard, H).
H = <geoip>(0x1f3ae30).

Database handles are subject to (atom) garbage collection. If a database handle is garbage collected, the underlying database is closed.

 geoip_close is det
 geoip_close(?NameOrHandle) is det
Close all databases or those matching NameOrHandle.
  118geoip_close :-
  119	geoip_close(_).
  120
  121geoip_close(Name) :-
  122	( var(Name) ; atom(Name) ), !,
  123	forall(retract(geoip_db(Name, Handle)),
  124	       geoip_close_(Handle)).
  125geoip_close(Handle) :-
  126	geoip_close_(Handle).
 geoip_lookup(+From, -Result) is semidet
 geoip_lookup(+Handle, +From, -Result) is semidet
Find a record from the GeoIP database. The predicate geoip_lookup/2 uses geoip_open('GeoIPCity', Handle) to get a handle to the GeoIP city database. Result is a dict, containing a subset of the following keys: country_code, country_code3, country_name, region, city, postal_code, continent_code, latitude, longitude, netmask or area_code. This predicate uses GeoIP_record_by_ipnum() from the GeoIP library.
Arguments:
From- is either a term ip(A,B,C,D) or a dotted string or atom containing an ip4 address or hostname. If From is a hostname, tcp_host_to_address/2 is used to lookup the IP address.
  145geoip_lookup(From, Result) :-
  146	geoip_open('GeoIPCity', Handle),
  147	geoip_lookup(Handle, From, Result).
  148
  149geoip_lookup(Handle, From, Result) :-
  150	to_ip(From, IP),
  151	geoip_lookup_(Handle, IP, Pairs),
  152	Pairs \== [],
  153	dict_pairs(Result, geoip, Pairs).
  154
  155to_ip(Atomic, IP) :-
  156	atomic(Atomic), !,
  157	split_string(Atomic, ".", "", Parts),
  158	(   length(Parts, 4),
  159	    maplist(byte_string, Bytes, Parts)
  160	->  IP =.. [ip|Bytes]
  161	;   tcp_host_to_address(Atomic, IP)
  162	).
  163to_ip(IP, IP).
  164
  165byte_string(Byte, String) :-
  166	number_string(Byte, String),
  167	integer(Byte),
  168	between(0, 255, Byte)