module Geodetics.LatLongParser (
degreesMinutesSeconds,
degreesMinutesSecondsUnits,
degreesDecimalMinutes,
degreesDecimalMinutesUnits,
dms7,
angle,
latitudeNS,
longitudeEW,
signedLatLong,
latLong
) where
import Control.Monad
import Data.Char
import Text.ParserCombinators.ReadP as P
natural :: ReadP Integer
natural = read <$> munch1 isDigit
minuteTick :: ReadP ()
minuteTick = void $ choice [char '\'', char '\8242']
secondTick :: ReadP ()
secondTick = void $ choice [char '"', char '\8243']
decimal :: ReadP Double
decimal = do
str1 <- munch1 isDigit
option (read str1) $ do
str2 <- char '.' *> munch1 isDigit
return $ read $ str1 ++ '.' : str2
signChar :: (Num a) =>
Char
-> Char
-> ReadP a
signChar pos neg = do
c <- char pos +++ char neg
return $ if c == pos then 1 else (-1)
signedDecimal :: ReadP Double
signedDecimal = (*) <$> option 1 (signChar '+' '-') <*> decimal
degreesMinutesSeconds :: ReadP Double
degreesMinutesSeconds = do
d <- fromIntegral <$> natural
guard $ d <= 360
skipSpaces
ms <- option 0 $ do
m <- fromIntegral <$> natural
guard $ m < 60
skipSpaces
s <- option 0 decimal
guard $ s < 60
return $ m / 60 + s / 3600
return $ d + ms
degreesMinutesSecondsUnits :: ReadP Double
degreesMinutesSecondsUnits = do
(s, a) <- gather $ do
d <- fromIntegral <$> option 0 (natural <* char '°')
guard $ d <= 360
skipSpaces
m <- fromIntegral <$> option 0 (natural <* minuteTick)
guard $ m < 60
skipSpaces
s <- option 0 (decimal <* secondTick)
guard $ s < 60
return $ d + m / 60 + s / 3600
guard $ not $ null s
return a
degreesDecimalMinutes :: ReadP Double
degreesDecimalMinutes = do
d <- fromIntegral <$> natural
skipSpaces
guard $ d <= 360
m <- option 0 decimal
guard $ m < 60
return $ d + m/60
degreesDecimalMinutesUnits :: ReadP Double
degreesDecimalMinutesUnits = do
(s, a) <- gather $ do
d <- fromIntegral <$> option 0 (natural <* char '°')
guard $ d <= 360
m <- option 0 (decimal <* minuteTick)
guard $ m < 60
return $ d + m / 60
guard $ not $ null s
return a
dms7 :: ReadP Double
dms7 = do
str <- munch1 isDigit
decs <- option "0" (char '.' *> munch1 isDigit)
let c = length str
(ds, rs) = splitAt (c-4) str
(ms,ss) = splitAt 2 rs
d = read ds
m = read ms
s = read $ ss ++ '.' : decs
guard $ c >= 5 && c <= 7
guard $ m < 60
guard $ s < 60
return $ d + m / 60 + s / 3600
angle :: ReadP Double
angle = choice [
decimal <* optional (char '°'),
degreesMinutesSeconds,
degreesMinutesSecondsUnits,
degreesDecimalMinutes,
degreesDecimalMinutesUnits,
dms7
]
latitudeNS :: ReadP Double
latitudeNS = do
ul <- angle
guard $ ul <= 90
skipSpaces
sgn <- signChar 'N' 'S'
return $ sgn * ul
longitudeEW :: ReadP Double
longitudeEW = do
ul <- angle
guard $ ul <= 180
skipSpaces
sgn <- signChar 'E' 'W'
return $ sgn * ul
signedLatLong :: ReadP (Double, Double)
signedLatLong = do
lat <- signedDecimal <* optional (char '°')
guard $ lat >= (-90)
guard $ lat <= 90
skipSpaces
P.optional $ char ',' >> skipSpaces
long <- signedDecimal <* optional (char '°')
guard $ long >= (-180)
guard $ long < 360
return (lat, if long > 180 then long-360 else long)
latLong :: ReadP (Double, Double)
latLong = latLong1 +++ longLat +++ signedLatLong
where
latLong1 = do
lat <- latitudeNS
skipSpaces
P.optional $ char ',' >> skipSpaces
long <- longitudeEW
return (lat, long)
longLat = do
long <- longitudeEW
skipSpaces
P.optional $ char ',' >> skipSpaces
lat <- latitudeNS
return (lat, long)