module GPolyline (encodeline,encodeunsigned,decodeline,decodeunsigned) where
import Data.Word
import Data.Bits
import Data.Char
import Data.List.Split
type Point = (Double,Double)
example_decoded = [(38.5, 120.2), (40.7, 120.95), (43.252, 126.453)]
example_encoded = "_p~iF~ps|U_ulLnnqC_mqNvxq`@"
example_encoded2 = "ctteJe{{b@EESCKWAWCMAEGSQQ]Yo@"
example_decoded2 = [(58.765620000000006,5.88227),(58.76565000000001,5.8823),(58.76575000000001,5.88232),(58.76581000000001,5.88244),(58.76582000000001,5.88256),(58.76584000000001,5.88263),(58.765850000000015,5.88266),(58.76589000000001,5.882759999999999),(58.76598000000001,5.8828499999999995),(58.76613000000001,5.88298),(58.76637000000001,5.88298)]
example_encoded3 = "ctteJe{{b@E?E?SCK?WAWCMAEGSQQ]Yo@"
encodeline :: [Point] -> String
encodeline points = concatMap encodepoint rels
where rels = transform points calcoffsets
encodepoint (latoff,lngoff) = encodefloat latoff ++ encodefloat lngoff
decodeline :: String -> [Point]
decodeline str = transform points calcoffsets'
where chunks = chunkinput $ prepareinput str
floats = map (decodefloat) chunks
points = pairup floats
decodeunsigned :: String -> Int
decodeunsigned str = fromIntegral $ createvalue 5 (clrthem (prepareinput str))
encodeunsigned :: Int -> String
encodeunsigned off =
map (\b -> chr (fromIntegral(b+63))) w32l
where w32l = shorten $ thedrop (chunkvalue 5 (fromIntegral off))
shorten wrd
| null wrd = [0]
| otherwise = orthem $ reverse wrd
thedrop wrd = dropWhile (==0) (reverse wrd)
pairup :: [a] -> [(a,a)]
pairup [] = []
pairup (x:[]) = []
pairup (x:y:xs) = (x,y) : pairup xs
transform :: [Point] -> (Point -> [Point] -> [Point]) -> [Point]
transform [] _ = []
transform (x:xs) transformer
| null xs = [x]
| otherwise = x : transformer x xs
calcoffsets :: Point -> [Point] -> [Point]
calcoffsets _ [] = []
calcoffsets (xprev,yprev) lst =
(xxprev,yyprev) : calcoffsets (x,y) (tail lst)
where (x,y) = head lst
calcoffsets' :: Point -> [Point] -> [Point]
calcoffsets' _ [] = []
calcoffsets' (xprev,yprev) lst =
(x+xprev,y+yprev) : calcoffsets' (x+xprev,y+yprev) (tail lst)
where (x,y) = head lst
encodefloat :: Double -> String
encodefloat off =
map (\b -> chr (fromIntegral(b+63))) w32l
where w32l = shorten $ thedrop (chunkvalue 5 (preparefloat off))
shorten wrd
| null wrd = [0]
| otherwise = orthem $ reverse wrd
thedrop wrd = dropWhile (==0) (reverse wrd)
decodefloat :: [Word32] -> Double
decodefloat lst = 0.00001 * res
where val = createvalue 5 (clrthem lst)
num = shiftR val 1
res
| testBit val 0 = fromIntegral (num+1)
| otherwise = fromIntegral num
orthem :: [Word32] -> [Word32]
orthem [] = []
orthem (x:[]) = [x]
orthem (x:xs) = (x .|. 32) : orthem xs
clrthem :: [Word32] -> [Word32]
clrthem [] = []
clrthem (x:[]) = [x]
clrthem (x:xs) = (clearBit x 5) : clrthem xs
chunkvalue :: Int -> Word32 -> [Word32]
chunkvalue bitspersegment wrd =
[(shiftR wrd b) .&. mask | b <- [0,bitspersegment..maxbits]]
where mask = (bit bitspersegment) 1
maxbits = 25
createvalue :: Int -> [Word32] -> Word32
createvalue bitspersegment chunks =
sum $ zipWith (*) chunks [mul^e | e <- [0..]]
where mul = bit bitspersegment :: Word32
preparefloat :: Double -> Word32
preparefloat val = bin3
where int = round (val * 100000)
bin = fromIntegral int :: Word32
bin2 = shiftL bin 1
bin3
| val < 0 = complement bin2
| otherwise = bin2
chunkinput :: [Word32] -> [[Word32]]
chunkinput vals = splt (\v -> not $ testBit v 5) vals
where splt = split . keepDelimsR . whenElt
prepareinput :: String -> [Word32]
prepareinput str = map fromIntegral vals
where vals = map (\c -> (63) + ord c) str