module IP2Location (Meta, IP2LocationRecord(..), getAPIVersion, doInit, doQuery) where
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Char8 as BS8
import Data.Word
import Data.Bits
import Data.Binary.Get
import Data.IP
import Control.Exception
import System.Exit
data IP2LocationRecord = IP2LocationRecord {
IP2LocationRecord -> String
country_short :: String,
IP2LocationRecord -> String
country_long :: String,
IP2LocationRecord -> String
region :: String,
IP2LocationRecord -> String
city :: String,
IP2LocationRecord -> String
isp :: String,
IP2LocationRecord -> Float
latitude :: Float,
IP2LocationRecord -> Float
longitude :: Float,
IP2LocationRecord -> String
domain :: String,
IP2LocationRecord -> String
zipcode :: String,
IP2LocationRecord -> String
timezone :: String,
IP2LocationRecord -> String
netspeed :: String,
IP2LocationRecord -> String
iddcode :: String,
IP2LocationRecord -> String
areacode :: String,
IP2LocationRecord -> String
weatherstationcode :: String,
IP2LocationRecord -> String
weatherstationname :: String,
IP2LocationRecord -> String
mcc :: String,
IP2LocationRecord -> String
mnc :: String,
IP2LocationRecord -> String
mobilebrand :: String,
IP2LocationRecord -> Float
elevation :: Float,
IP2LocationRecord -> String
usagetype :: String,
IP2LocationRecord -> String
addresstype :: String,
IP2LocationRecord -> String
category :: String,
IP2LocationRecord -> String
district :: String,
IP2LocationRecord -> String
asn :: String,
IP2LocationRecord -> String
as :: String
} deriving (Int -> IP2LocationRecord -> ShowS
[IP2LocationRecord] -> ShowS
IP2LocationRecord -> String
(Int -> IP2LocationRecord -> ShowS)
-> (IP2LocationRecord -> String)
-> ([IP2LocationRecord] -> ShowS)
-> Show IP2LocationRecord
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IP2LocationRecord -> ShowS
showsPrec :: Int -> IP2LocationRecord -> ShowS
$cshow :: IP2LocationRecord -> String
show :: IP2LocationRecord -> String
$cshowList :: [IP2LocationRecord] -> ShowS
showList :: [IP2LocationRecord] -> ShowS
Show)
data Meta = Meta {
Meta -> Int
databasetype :: Int,
Meta -> Int
databasecolumn :: Int,
Meta -> Int
databaseyear :: Int,
Meta -> Int
databasemonth :: Int,
Meta -> Int
databaseday :: Int,
Meta -> Int
ipv4databasecount :: Int,
Meta -> Int
ipv4databaseaddr :: Int,
Meta -> Int
ipv6databasecount :: Int,
Meta -> Int
ipv6databaseaddr :: Int,
Meta -> Int
ipv4indexbaseaddr :: Int,
Meta -> Int
ipv6indexbaseaddr :: Int,
Meta -> Int
ipv4columnsize :: Int,
Meta -> Int
ipv6columnsize :: Int,
Meta -> Int
wrongbin :: Int
} deriving (Int -> Meta -> ShowS
[Meta] -> ShowS
Meta -> String
(Int -> Meta -> ShowS)
-> (Meta -> String) -> ([Meta] -> ShowS) -> Show Meta
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Meta -> ShowS
showsPrec :: Int -> Meta -> ShowS
$cshow :: Meta -> String
show :: Meta -> String
$cshowList :: [Meta] -> ShowS
showList :: [Meta] -> ShowS
Show)
getMeta :: Get Meta
getMeta = do
Word8
databasetype <- Get Word8
getWord8
Word8
databasecolumn <- Get Word8
getWord8
Word8
databaseyear <- Get Word8
getWord8
Word8
databasemonth <- Get Word8
getWord8
Word8
databaseday <- Get Word8
getWord8
Word32
ipv4databasecount <- Get Word32
getWord32le
Word32
ipv4databaseaddr <- Get Word32
getWord32le
Word32
ipv6databasecount <- Get Word32
getWord32le
Word32
ipv6databaseaddr <- Get Word32
getWord32le
Word32
ipv4indexbaseaddr <- Get Word32
getWord32le
Word32
ipv6indexbaseaddr <- Get Word32
getWord32le
Word8
productcode <- Get Word8
getWord8
Word8
producttype <- Get Word8
getWord8
Word32
filesize <- Get Word32
getWord32le
let wrongbin :: Int
wrongbin = if (Word8
productcode Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
1 Bool -> Bool -> Bool
&& Word8
databaseyear Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
21) Bool -> Bool -> Bool
|| (Word8
databasetype Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
80 Bool -> Bool -> Bool
&& Word8
databasecolumn Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
75)
then do
Int
1
else do
Int
0
let ipv4columnsize :: Int
ipv4columnsize = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databasecolumn Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
let ipv6columnsize :: Int
ipv6columnsize = Int
16 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databasecolumn Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2)
let meta :: Meta
meta = Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Meta
Meta (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databasetype) (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databasecolumn) (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databaseyear) (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databasemonth) (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
databaseday) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv4databasecount) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv4databaseaddr) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv6databasecount) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv6databaseaddr) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv4indexbaseaddr) (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
ipv6indexbaseaddr) Int
ipv4columnsize Int
ipv6columnsize Int
wrongbin
Meta -> Get Meta
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
meta
getAPIVersion :: String
getAPIVersion :: String
getAPIVersion = String
"8.5.1"
ipToOcts :: IP -> [Int]
ipToOcts :: IP -> [Int]
ipToOcts (IPv4 IPv4
ip) = IPv4 -> [Int]
fromIPv4 IPv4
ip
ipToOcts (IPv6 IPv6
ip) = IPv6 -> [Int]
fromIPv6b IPv6
ip
ipToInteger :: IP -> Integer
ipToInteger :: IP -> Integer
ipToInteger = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Integer] -> Integer) -> (IP -> [Integer]) -> IP -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Integer, Int) -> Integer) -> [(Integer, Int)] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (\(Integer
n,Int
o) -> Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
o Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
256 Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
n) ([(Integer, Int)] -> [Integer])
-> (IP -> [(Integer, Int)]) -> IP -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> [Int] -> [(Integer, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] ([Int] -> [(Integer, Int)])
-> (IP -> [Int]) -> IP -> [(Integer, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> (IP -> [Int]) -> IP -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IP -> [Int]
ipToOcts
ipStringToInteger :: String -> Integer
ipStringToInteger :: String -> Integer
ipStringToInteger = IP -> Integer
ipToInteger (IP -> Integer) -> (String -> IP) -> String -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IP
forall a. Read a => String -> a
read
doInit :: String -> IO Meta
doInit :: String -> IO Meta
doInit String
myfile = do
ByteString
contents <- String -> IO ByteString
BS.readFile String
myfile
let stuff :: Meta
stuff = Get Meta -> ByteString -> Meta
forall a. Get a -> ByteString -> a
runGet Get Meta
getMeta ByteString
contents
let iswrong :: String
iswrong = (Int -> String
forall a. Show a => a -> String
show (Meta -> Int
wrongbin Meta
stuff))
if String
iswrong String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"1"
then do
String -> IO Meta
forall a. String -> IO a
die(ShowS
forall a. Show a => a -> String
show String
"Incorrect IP2Location BIN file format. Please make sure that you are using the latest IP2Location BIN file.")
else do
Meta -> IO Meta
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Meta -> IO Meta) -> Meta -> IO Meta
forall a b. (a -> b) -> a -> b
$ Meta
stuff
readuint8 :: BS.ByteString -> Int -> Int
readuint8 :: ByteString -> Int -> Int
readuint8 ByteString
contents Int
startpos = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Get Word8 -> ByteString -> Word8
forall a. Get a -> ByteString -> a
runGet Get Word8
getWord8 (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) ByteString
contents))
readuint32 :: BS.ByteString -> Int -> Int
readuint32 :: ByteString -> Int -> Int
readuint32 ByteString
contents Int
startpos = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Get Word32 -> ByteString -> Word32
forall a. Get a -> ByteString -> a
runGet Get Word32
getWord32le (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) ByteString
contents))
readuint32row :: BS.ByteString -> Int -> Int
readuint32row :: ByteString -> Int -> Int
readuint32row ByteString
row Int
startpos = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Get Word32 -> ByteString -> Word32
forall a. Get a -> ByteString -> a
runGet Get Word32
getWord32le (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos) ByteString
row))
getuint128 :: Get Integer
getuint128 = do
Word64
uint64A <- Get Word64
getWord64le
Word64
uint64B <- Get Word64
getWord64le
let uint128 :: Integer
uint128 = (Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
uint64A) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ ((Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
uint64B) Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateL` Int
64)
Integer -> Get Integer
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
uint128
readuint128 :: BS.ByteString -> Int -> Integer
readuint128 :: ByteString -> Int -> Integer
readuint128 ByteString
contents Int
startpos = Get Integer -> ByteString -> Integer
forall a. Get a -> ByteString -> a
runGet Get Integer
getuint128 (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) ByteString
contents)
readfloatrow :: BS.ByteString -> Int -> Float
readfloatrow :: ByteString -> Int -> Float
readfloatrow ByteString
row Int
startpos = Get Float -> ByteString -> Float
forall a. Get a -> ByteString -> a
runGet Get Float
getFloatle (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos) ByteString
row)
readstr :: BS.ByteString -> Int -> String
readstr :: ByteString -> Int -> String
readstr ByteString
contents Int
startpos = do
let len :: Word8
len = Get Word8 -> ByteString -> Word8
forall a. Get a -> ByteString -> a
runGet Get Word8
getWord8 (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos) ByteString
contents)
Char
str <- ByteString -> String
BS8.unpack (Int64 -> ByteString -> ByteString
BS.take (Word8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
len) (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startpos Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) ByteString
contents))
Char -> String
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return Char
str
readcolcountry :: BS.ByteString -> Int -> Int -> [Int] -> (String, String)
readcolcountry :: ByteString -> Int -> Int -> [Int] -> (String, String)
readcolcountry ByteString
contents Int
dbtype Int
rowoffset [Int]
col = do
let x :: String
x = String
"This parameter is unavailable for selected data file. Please upgrade the data file."
let [Int
colpos] = Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
col)
if Int
colpos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
(String
x, String
x)
else do
let coloffset :: Int
coloffset = (Int
colpos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
let x0 :: Int
x0 = ByteString -> Int -> Int
readuint32 ByteString
contents (Int
rowoffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
coloffset)
let x1 :: String
x1 = ByteString -> Int -> String
readstr ByteString
contents Int
x0
let x2 :: String
x2 = ByteString -> Int -> String
readstr ByteString
contents (Int
x0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
(String
x1, String
x2)
readcolcountryrow :: BS.ByteString -> BS.ByteString -> Int -> [Int] -> (String, String)
readcolcountryrow :: ByteString -> ByteString -> Int -> [Int] -> (String, String)
readcolcountryrow ByteString
contents ByteString
row Int
dbtype [Int]
col = do
let x :: String
x = String
"This parameter is unavailable for selected data file. Please upgrade the data file."
let [Int
colpos] = Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
col)
if Int
colpos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
(String
x, String
x)
else do
let coloffset :: Int
coloffset = (Int
colpos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
let x0 :: Int
x0 = ByteString -> Int -> Int
readuint32row ByteString
row Int
coloffset
let x1 :: String
x1 = ByteString -> Int -> String
readstr ByteString
contents Int
x0
let x2 :: String
x2 = ByteString -> Int -> String
readstr ByteString
contents (Int
x0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
(String
x1, String
x2)
readcolstringrow :: BS.ByteString -> BS.ByteString -> Int -> [Int] -> String
readcolstringrow :: ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
col = do
let [Int
colpos] = Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
col)
if Int
colpos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
String
"This parameter is unavailable for selected data file. Please upgrade the data file."
else do
let coloffset :: Int
coloffset = (Int
colpos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
ByteString -> Int -> String
readstr ByteString
contents (ByteString -> Int -> Int
readuint32row ByteString
row Int
coloffset)
readcolfloatrow :: BS.ByteString -> Int -> [Int] -> Float
readcolfloatrow :: ByteString -> Int -> [Int] -> Float
readcolfloatrow ByteString
row Int
dbtype [Int]
col = do
let [Int
colpos] = Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
col)
if Int
colpos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
Float
0.0
else do
let coloffset :: Int
coloffset = (Int
colpos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
ByteString -> Int -> Float
readfloatrow ByteString
row Int
coloffset
readcolfloatstringrow :: BS.ByteString -> BS.ByteString -> Int -> [Int] -> Float
readcolfloatstringrow :: ByteString -> ByteString -> Int -> [Int] -> Float
readcolfloatstringrow ByteString
contents ByteString
row Int
dbtype [Int]
col = do
let [Int
colpos] = Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
col)
if Int
colpos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
Float
0.0
else do
let coloffset :: Int
coloffset = (Int
colpos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
let n :: String
n = ByteString -> Int -> String
readstr ByteString
contents (ByteString -> Int -> Int
readuint32row ByteString
row Int
coloffset)
String -> Float
forall a. Read a => String -> a
read String
n :: Float
countif :: (a -> Bool) -> [a] -> Int
countif :: forall a. (a -> Bool) -> [a] -> Int
countif a -> Bool
f = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> ([a] -> [a]) -> [a] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter a -> Bool
f
readrecord :: BS.ByteString -> Int -> Int -> IP2LocationRecord
readrecord :: ByteString -> Int -> Int -> IP2LocationRecord
readrecord ByteString
contents Int
dbtype Int
rowoffset = do
let country_position :: [Int]
country_position = [Int
0, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2, Int
2]
let region_position :: [Int]
region_position = [Int
0, Int
0, Int
0, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3, Int
3]
let city_position :: [Int]
city_position = [Int
0, Int
0, Int
0, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4, Int
4]
let isp_position :: [Int]
isp_position = [Int
0, Int
0, Int
3, Int
0, Int
5, Int
0, Int
7, Int
5, Int
7, Int
0, Int
8, Int
0, Int
9, Int
0, Int
9, Int
0, Int
9, Int
0, Int
9, Int
7, Int
9, Int
0, Int
9, Int
7, Int
9, Int
9, Int
9]
let latitude_position :: [Int]
latitude_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
5, Int
5, Int
0, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5, Int
5]
let longitude_position :: [Int]
longitude_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
6, Int
6, Int
0, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6, Int
6]
let domain_position :: [Int]
domain_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
6, Int
8, Int
0, Int
9, Int
0, Int
10,Int
0, Int
10, Int
0, Int
10, Int
0, Int
10, Int
8, Int
10, Int
0, Int
10, Int
8, Int
10, Int
10, Int
10]
let zipcode_position :: [Int]
zipcode_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
7, Int
7, Int
7, Int
7, Int
0, Int
7, Int
7, Int
7, Int
0, Int
7, Int
0, Int
7, Int
7, Int
7, Int
0, Int
7, Int
7, Int
7]
let timezone_position :: [Int]
timezone_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
8, Int
8, Int
7, Int
8, Int
8, Int
8, Int
7, Int
8, Int
0, Int
8, Int
8, Int
8, Int
0, Int
8, Int
8, Int
8]
let netspeed_position :: [Int]
netspeed_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
8, Int
11,Int
0, Int
11,Int
8, Int
11, Int
0, Int
11, Int
0, Int
11, Int
0, Int
11, Int
11, Int
11]
let iddcode_position :: [Int]
iddcode_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
9, Int
12, Int
0, Int
12, Int
0, Int
12, Int
9, Int
12, Int
0, Int
12, Int
12, Int
12]
let areacode_position :: [Int]
areacode_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
10 ,Int
13 ,Int
0, Int
13, Int
0, Int
13, Int
10, Int
13, Int
0, Int
13, Int
13, Int
13]
let weatherstationcode_position :: [Int]
weatherstationcode_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
9, Int
14, Int
0, Int
14, Int
0, Int
14, Int
0, Int
14, Int
14, Int
14]
let weatherstationname_position :: [Int]
weatherstationname_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
10, Int
15, Int
0, Int
15, Int
0, Int
15, Int
0, Int
15, Int
15, Int
15]
let mcc_position :: [Int]
mcc_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
9, Int
16, Int
0, Int
16, Int
9, Int
16, Int
16, Int
16]
let mnc_position :: [Int]
mnc_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
10,Int
17, Int
0, Int
17, Int
10, Int
17, Int
17, Int
17]
let mobilebrand_position :: [Int]
mobilebrand_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
11,Int
18, Int
0, Int
18, Int
11, Int
18, Int
18, Int
18]
let elevation_position :: [Int]
elevation_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
11, Int
19, Int
0, Int
19, Int
19, Int
19]
let usagetype_position :: [Int]
usagetype_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
12, Int
20, Int
20, Int
20]
let addresstype_position :: [Int]
addresstype_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
21, Int
21]
let category_position :: [Int]
category_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
22, Int
22]
let district_position :: [Int]
district_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
23]
let asn_position :: [Int]
asn_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
24]
let as_position :: [Int]
as_position = [Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
0, Int
25]
let allcols :: [Int]
allcols = (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
country_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
region_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
city_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
isp_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
latitude_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
longitude_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
domain_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
zipcode_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
timezone_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
netspeed_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
iddcode_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
areacode_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
weatherstationcode_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
weatherstationname_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
mcc_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
mnc_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
mobilebrand_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
elevation_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
usagetype_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
addresstype_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
category_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
district_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
asn_position)) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
drop Int
dbtype [Int]
as_position))
let cols :: Int
cols = ((Int -> Bool) -> [Int] -> Int
forall a. (a -> Bool) -> [a] -> Int
countif (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
0) [Int]
allcols) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2
let row :: ByteString
row = Int64 -> ByteString -> ByteString
BS.take (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cols) (Int64 -> ByteString -> ByteString
BS.drop (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
rowoffset Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) ByteString
contents)
let (String
country_short, String
country_long) = ByteString -> ByteString -> Int -> [Int] -> (String, String)
readcolcountryrow ByteString
contents ByteString
row Int
dbtype [Int]
country_position
let region :: String
region = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
region_position
let city :: String
city = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
city_position
let isp :: String
isp = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
isp_position
let latitude :: Float
latitude = ByteString -> Int -> [Int] -> Float
readcolfloatrow ByteString
row Int
dbtype [Int]
latitude_position
let longitude :: Float
longitude = ByteString -> Int -> [Int] -> Float
readcolfloatrow ByteString
row Int
dbtype [Int]
longitude_position
let domain :: String
domain = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
domain_position
let zipcode :: String
zipcode = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
zipcode_position
let timezone :: String
timezone = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
timezone_position
let netspeed :: String
netspeed = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
netspeed_position
let iddcode :: String
iddcode = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
iddcode_position
let areacode :: String
areacode = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
areacode_position
let weatherstationcode :: String
weatherstationcode = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
weatherstationcode_position
let weatherstationname :: String
weatherstationname = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
weatherstationname_position
let mcc :: String
mcc = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
mcc_position
let mnc :: String
mnc = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
mnc_position
let mobilebrand :: String
mobilebrand = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
mobilebrand_position
let elevation :: Float
elevation = ByteString -> ByteString -> Int -> [Int] -> Float
readcolfloatstringrow ByteString
contents ByteString
row Int
dbtype [Int]
elevation_position
let usagetype :: String
usagetype = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
usagetype_position
let addresstype :: String
addresstype = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
addresstype_position
let category :: String
category = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
category_position
let district :: String
district = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
district_position
let asn :: String
asn = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
asn_position
let as :: String
as = ByteString -> ByteString -> Int -> [Int] -> String
readcolstringrow ByteString
contents ByteString
row Int
dbtype [Int]
as_position
String
-> String
-> String
-> String
-> String
-> Float
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> IP2LocationRecord
IP2LocationRecord String
country_short String
country_long String
region String
city String
isp Float
latitude Float
longitude String
domain String
zipcode String
timezone String
netspeed String
iddcode String
areacode String
weatherstationcode String
weatherstationname String
mcc String
mnc String
mobilebrand Float
elevation String
usagetype String
addresstype String
category String
district String
asn String
as
searchtree :: BS.ByteString -> Integer -> Int -> Int -> Int -> Int -> Int -> Int -> IP2LocationRecord
searchtree :: ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum Int
dbtype Int
low Int
high Int
baseaddr Int
colsize Int
iptype = do
if Int
low Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
high
then do
let mid :: Int
mid = ((Int
low Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
high) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
let rowoffset :: Int
rowoffset = Int
baseaddr Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
mid Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
colsize)
let rowoffset2 :: Int
rowoffset2 = Int
rowoffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
colsize
let ipfrom :: Integer
ipfrom = if (Int
iptype Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4)
then Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> Int
readuint32 ByteString
contents Int
rowoffset
else ByteString -> Int -> Integer
readuint128 ByteString
contents Int
rowoffset
let ipto :: Integer
ipto = if (Int
iptype Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4)
then Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> Int
readuint32 ByteString
contents Int
rowoffset2
else ByteString -> Int -> Integer
readuint128 ByteString
contents Int
rowoffset2
if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
ipfrom Bool -> Bool -> Bool
&& Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
ipto
then do
if Int
iptype Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4
then
ByteString -> Int -> Int -> IP2LocationRecord
readrecord ByteString
contents Int
dbtype (Int
rowoffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
else
ByteString -> Int -> Int -> IP2LocationRecord
readrecord ByteString
contents Int
dbtype (Int
rowoffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
16)
else if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
ipfrom
then
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum Int
dbtype Int
low (Int
mid Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
baseaddr Int
colsize Int
iptype
else
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum Int
dbtype (Int
mid Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
high Int
baseaddr Int
colsize Int
iptype
else do
let x :: String
x = String
"IP address not found."
String
-> String
-> String
-> String
-> String
-> Float
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> IP2LocationRecord
IP2LocationRecord String
x String
x String
x String
x String
x Float
0.0 Float
0.0 String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x Float
0.0 String
x String
x String
x String
x String
x String
x
search4 :: BS.ByteString -> Integer -> Int -> Int -> Int -> Int -> Int -> Int -> IP2LocationRecord
search4 :: ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search4 ByteString
contents Integer
ipnum Int
dbtype Int
low Int
high Int
baseaddr Int
indexbaseaddr Int
colsize = do
let ipnum2 :: Integer
ipnum2 = if (Integer
ipnum Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
4294967295)
then Integer
ipnum Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1
else Integer
ipnum
if Int
indexbaseaddr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then do
let indexpos :: Int
indexpos = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (((Integer
ipnum2 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateR` Int
16) Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateL` Int
3) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
indexbaseaddr))
let low2 :: Int
low2 = ByteString -> Int -> Int
readuint32 ByteString
contents Int
indexpos
let high2 :: Int
high2 = ByteString -> Int -> Int
readuint32 ByteString
contents (Int
indexpos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum2 Int
dbtype Int
low2 Int
high2 Int
baseaddr Int
colsize Int
4
else
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum2 Int
dbtype Int
low Int
high Int
baseaddr Int
colsize Int
4
search6 :: BS.ByteString -> Integer -> Int -> Int -> Int -> Int -> Int -> Int -> IP2LocationRecord
search6 :: ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search6 ByteString
contents Integer
ipnum Int
dbtype Int
low Int
high Int
baseaddr Int
indexbaseaddr Int
colsize = do
let ipnum2 :: Integer
ipnum2 = if (Integer
ipnum Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
340282366920938463463374607431768211455)
then Integer
ipnum Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1
else Integer
ipnum
if Int
indexbaseaddr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then do
let indexpos :: Int
indexpos = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (((Integer
ipnum2 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateR` Int
112) Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateL` Int
3) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
indexbaseaddr))
let low2 :: Int
low2 = ByteString -> Int -> Int
readuint32 ByteString
contents Int
indexpos
let high2 :: Int
high2 = ByteString -> Int -> Int
readuint32 ByteString
contents (Int
indexpos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum2 Int
dbtype Int
low2 Int
high2 Int
baseaddr Int
colsize Int
6
else
ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
searchtree ByteString
contents Integer
ipnum2 Int
dbtype Int
low Int
high Int
baseaddr Int
colsize Int
6
tryfirst :: String -> IO Integer
tryfirst String
myIP = do
Either SomeException Integer
result <- IO Integer -> IO (Either SomeException Integer)
forall e a. Exception e => IO a -> IO (Either e a)
try (Integer -> IO Integer
forall a. a -> IO a
evaluate (String -> Integer
ipStringToInteger String
myIP)) :: IO (Either SomeException Integer)
case Either SomeException Integer
result of
Left SomeException
ex -> Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> IO Integer) -> Integer -> IO Integer
forall a b. (a -> b) -> a -> b
$ Integer -> Integer
forall a. Integral a => a -> Integer
toInteger (Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
2)
Right Integer
val -> Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
val
doQuery :: String -> Meta -> String -> IO IP2LocationRecord
doQuery :: String -> Meta -> String -> IO IP2LocationRecord
doQuery String
myfile Meta
meta String
myip = do
ByteString
contents <- String -> IO ByteString
BS.readFile String
myfile
let fromV4Mapped :: Integer
fromV4Mapped = Integer
281470681743360
let toV4Mapped :: Integer
toV4Mapped = Integer
281474976710655
let fromV4Compatible :: Integer
fromV4Compatible = Integer
0
let toV4Compatible :: Integer
toV4Compatible = Integer
4294967295
let from6To4 :: Integer
from6To4 = Integer
42545680458834377588178886921629466624
let to6To4 :: Integer
to6To4 = Integer
42550872755692912415807417417958686719
let fromTeredo :: Integer
fromTeredo = Integer
42540488161975842760550356425300246528
let toTeredo :: Integer
toTeredo = Integer
42540488241204005274814694018844196863
let last32Bits :: Integer
last32Bits = Integer
4294967295
Integer
ipnum <- String -> IO Integer
tryfirst String
myip
if Integer
ipnum Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== -Integer
1
then do
let x :: String
x = String
"Invalid IP address."
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ String
-> String
-> String
-> String
-> String
-> Float
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> IP2LocationRecord
IP2LocationRecord String
x String
x String
x String
x String
x Float
0.0 Float
0.0 String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x Float
0.0 String
x String
x String
x String
x String
x String
x
else if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
fromV4Mapped Bool -> Bool -> Bool
&& Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
toV4Mapped
then do
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search4 ByteString
contents (Integer
ipnum Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- (Integer -> Integer
forall a. Integral a => a -> Integer
toInteger Integer
fromV4Mapped)) (Meta -> Int
databasetype Meta
meta) Int
0 (Meta -> Int
ipv4databasecount Meta
meta) (Meta -> Int
ipv4databaseaddr Meta
meta) (Meta -> Int
ipv4indexbaseaddr Meta
meta) (Meta -> Int
ipv4columnsize Meta
meta)
else if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
from6To4 Bool -> Bool -> Bool
&& Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
to6To4
then do
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search4 ByteString
contents ((Integer
ipnum Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`rotateR` Int
80) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
last32Bits) (Meta -> Int
databasetype Meta
meta) Int
0 (Meta -> Int
ipv4databasecount Meta
meta) (Meta -> Int
ipv4databaseaddr Meta
meta) (Meta -> Int
ipv4indexbaseaddr Meta
meta) (Meta -> Int
ipv4columnsize Meta
meta)
else if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
fromTeredo Bool -> Bool -> Bool
&& Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
toTeredo
then do
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search4 ByteString
contents ((Integer -> Integer
forall a. Bits a => a -> a
complement Integer
ipnum) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
last32Bits) (Meta -> Int
databasetype Meta
meta) Int
0 (Meta -> Int
ipv4databasecount Meta
meta) (Meta -> Int
ipv4databaseaddr Meta
meta) (Meta -> Int
ipv4indexbaseaddr Meta
meta) (Meta -> Int
ipv4columnsize Meta
meta)
else if Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
fromV4Compatible Bool -> Bool -> Bool
&& Integer
ipnum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
toV4Compatible
then do
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search4 ByteString
contents Integer
ipnum (Meta -> Int
databasetype Meta
meta) Int
0 (Meta -> Int
ipv4databasecount Meta
meta) (Meta -> Int
ipv4databaseaddr Meta
meta) (Meta -> Int
ipv4indexbaseaddr Meta
meta) (Meta -> Int
ipv4columnsize Meta
meta)
else if (Meta -> Int
ipv6databasecount Meta
meta) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
let x :: String
x = String
"IPv6 address missing in IPv4 BIN."
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ String
-> String
-> String
-> String
-> String
-> Float
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> String
-> Float
-> String
-> String
-> String
-> String
-> String
-> String
-> IP2LocationRecord
IP2LocationRecord String
x String
x String
x String
x String
x Float
0.0 Float
0.0 String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x String
x Float
0.0 String
x String
x String
x String
x String
x String
x
else do
IP2LocationRecord -> IO IP2LocationRecord
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IP2LocationRecord -> IO IP2LocationRecord)
-> IP2LocationRecord -> IO IP2LocationRecord
forall a b. (a -> b) -> a -> b
$ ByteString
-> Integer
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IP2LocationRecord
search6 ByteString
contents Integer
ipnum (Meta -> Int
databasetype Meta
meta) Int
0 (Meta -> Int
ipv6databasecount Meta
meta) (Meta -> Int
ipv6databaseaddr Meta
meta) (Meta -> Int
ipv6indexbaseaddr Meta
meta) (Meta -> Int
ipv6columnsize Meta
meta)