Skip to content

Commit

Permalink
1.2.0
Browse files Browse the repository at this point in the history
Added plotmap function.
  • Loading branch information
ip2location committed Feb 2, 2023
1 parent d99a41e commit e34115b
Show file tree
Hide file tree
Showing 10 changed files with 420 additions and 16 deletions.
7 changes: 3 additions & 4 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,16 +1,15 @@
Package: ip2proxy
Type: Package
Title: Lookup for IP Address Proxy Information
Version: 1.0.0
Version: 1.2.0
Author: IP2Location
Maintainer: IP2Location <[email protected]>
Description: A R package to find the IP addresses which are used as VPN anonymizer, open proxies, web proxies and Tor exits.
The package lookup the proxy IP address from IP2Proxy BIN Data file. You may visit <https://lite.ip2location.com> for free database download.
License: MIT + file LICENSE
Encoding: UTF-8
Depends: R (>= 3.2.3)
Imports: reticulate (>= 1.13), stringr (>= 1.4.0), jsonlite (>= 1.6)
LazyData: true
Imports: reticulate (>= 1.13), jsonlite (>= 1.6), ggplot2 (>= 3.4), maps (>= 3.4.1), scales (>= 1.2.1)
SystemRequirements: IP2Proxy Python library
<https://www.ip2location.com/development-libraries/ip2proxy/python>
RoxygenNote: 7.1.1
RoxygenNote: 7.2.3
6 changes: 6 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,12 @@

export(get_all)
export(is_proxy)
export(lookup_web_service)
export(open)
export(plot_map)
import(ggplot2)
import(jsonlite)
import(maps)
import(reticulate)
import(scales)
import(utils)
38 changes: 32 additions & 6 deletions R/IP2Proxy.r
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
#' @return NULL
#' @import reticulate
#' @export
#' @examples \donttest{
#' @examples \dontrun{
#' open("~/IP-COUNTRY.BIN")
#' }
#'
Expand All @@ -19,14 +19,14 @@ open <- function(bin_location){

#' @title Lookup for IP address proxy information
#'
#' @description Find the country, region, city, ISP, domain name, usage types, asn, as name, last seen and threat type. The return values will be depending on the BIN data loaded.
#' @description Find the country, region, city, ISP, domain name, usage types, asn, as name, last seen, threat type and provider. The return values will be depending on the BIN data loaded.
#' @param ip IPv4 or IPv6 address
#' @return Return all the proxy information about the IP address
#' @import reticulate
#' @import jsonlite
#' @export
#' @examples \donttest{
#' get_all("8.8.8.8")
#' @examples \dontrun{
#' get_all("1.0.241.135")
#' }
#'

Expand All @@ -45,8 +45,8 @@ get_all <- function(ip){
#' @import reticulate
#' @import jsonlite
#' @export
#' @examples \donttest{
#' is_proxy("8.8.8.8")
#' @examples \dontrun{
#' is_proxy("1.0.241.135")
#' }
#'

Expand All @@ -59,3 +59,29 @@ is_proxy <- function(ip){
result = fromJSON(py$j1)
return(result['is_proxy'])
}

#' @title Lookup for IP address proxy information using IP2Proxy web service.
#' @param api_key IP2Proxy web service API key
#' @param ip IPv4 or IPv6 address
#' @param package Package to use for IP2Proxy web service.
#' @description Find the country, region, city, ISP, domain name, usage types, asn, as name, last seen, threat type and provider. The return values will be depending on the IP2Proxy web service package used.
#' @return Return all the proxy information about the IP address
#' @import reticulate
#' @import jsonlite
#' @export
#' @examples \dontrun{
#' lookup_web_service("1.0.241.135","PX1")
#' }
#'

lookup_web_service <- function(api_key, ip, package = 'PX1'){
py_run_string("import IP2Proxy")
py_run_string("import json")
ws_initialize = paste("ws = IP2Proxy.IP2ProxyWebService('", api_key, "','", package, "',True)", sep = "")
py_run_string(ws_initialize)
API_result = paste("rec = ws.lookup('", ip, "')", sep = "")
py_run_string(API_result)
py_run_string("j = json.dumps(rec)")
result = fromJSON(py$j)
return(result)
}
76 changes: 76 additions & 0 deletions R/IP2Proxy_plotmap.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,76 @@
if(getRversion() >= "2.15.1") utils::globalVariables(c("long", "lat", "group", "prop"))

#' @title Plot map using IP2Location data.
#'
#' @description Plot the country on the map based on IP addresses and its IP2Location country data.
#' @param ips A vector of IP addresses to be plot on
#' @return NULL
#' @import maps
#' @import ggplot2
#' @import scales
#' @import utils
#' @export
#' @examples \dontrun{
#' plot_map(c("1.0.241.135", "1.2.3.4"))
#' }
#'

plot_map <- function(ips){
countries = c()
mapData = map_data("world")
for ( i in ips ) {
result = ip2proxy::get_all(i)
countries = append(countries, toString(result["country_long"]))
}

country_table <- table(countries)
ipData <- data.frame(country_table)

variable1 = deparse(substitute(countries))
variable1 = strsplit(variable1, "\\$")[[1]][2]

if(ncol(ipData) == 2) {
names(ipData) <- c(variable1, "n")
} else if(ncol(ipData) > 2){
names(ipData)[length(ipData)] <- "n"
}

prop <- as.vector(country_table)/sum(country_table)
ipData <- data.frame(ipData, prop)

table.prop <- as.vector(country_table)/sum(country_table)
table.perc <- format(round(table.prop*100, 1), nsmall = 1)
table.perc <- gsub("$", "%", table.perc)
ipData <- data.frame(ipData, table.perc)

names(ipData)[1] = "group"

path = find.package("ip2proxy")

#data <- read.csv("inst\\countrynames_mapping.txt", header=TRUE)
data <- read.csv(paste(path, '/countrynames_mapping.txt', sep = ""), header=TRUE)

data$matched_country_name[data$matched_country_name == ''] <- NA

for(i in 1:nrow(data)){
if(!is.na(data[i, "matched_country_name"])){
old.name <- paste(data[i, "country_name"])
new.name <- paste(data[i, "matched_country_name"])
ipData[, "group"] <- gsub(old.name, new.name, ipData[, "group"])
}
}

worldMapIPs <- merge(mapData, ipData, by.x = "region", by.y = "group", all.x = TRUE)
worldMapIPs <- worldMapIPs[order(worldMapIPs[, "order"]), ]
worldMapIPs[is.na(worldMapIPs)] <- 0
world <- map_data("world")
p <- ggplot() +
geom_polygon(data=world, aes(x=long, y=lat, group = group),
colour = "#595959", fill = "white") + theme(panel.background = element_rect(fill = "#b2cce5"), plot.background = element_rect(fill = "#b2cce5"))

mapcolors = c("black", "#d6d6d6", "white")
mapvalues = c(1, .025, 0)


p + geom_polygon(data=worldMapIPs, aes(x=long, y=lat, group = group, fill = prop)) + geom_path(data=worldMapIPs, aes(x=long, y=lat, group=group), color="#595959", size=0.05) + scale_fill_gradientn(colours= mapcolors, values= mapvalues, labels = percent_format(), limits = c(0,1)) + theme(plot.title = element_text(size = 20, colour = "black", family = "sans", margin = unit(c(0, 0, 5, 0), "mm"))) + scale_y_continuous(name=NULL, breaks=NULL, expand = c(0,0)) + scale_x_continuous(name=NULL, breaks=NULL, expand = c(0,0)) + theme(legend.justification = c(0, 0), legend.position = c(0, 0.32), legend.background = element_blank(), legend.title = element_blank(), legend.text = element_text(size = rel(1.1), colour = "black", family = "sans")) + guides(fill = guide_colorbar(barwidth = rel(0.5), barheight = rel(5.0), ticks = F))
}
Loading

0 comments on commit e34115b

Please sign in to comment.