module Data.Geo.Jord.LatLong
(
LatLong
, latitude
, longitude
, latLong
, latLongE
, latLongF
, decimalLatLong
, decimalLatLongE
, decimalLatLongF
, readLatLong
, readLatLongE
, readLatLongF
, toDecimalDegrees'
) where
import Control.Applicative hiding (many)
import Control.Monad.Fail
import Data.Char
import Data.Geo.Jord.Angle
import Data.Geo.Jord.Parser
import Data.Maybe
import Prelude hiding (fail)
import Text.ParserCombinators.ReadP
import Text.Read hiding (pfail)
data LatLong = LatLong
{ latitude :: Angle
, longitude :: Angle
} deriving (Eq)
instance Read LatLong where
readsPrec _ = readP_to_S ll
instance Show LatLong where
show (LatLong lat lon) = showLat lat ++ "," ++ showLon lon
latLong :: Angle -> Angle -> LatLong
latLong lat lon =
fromMaybe
(error ("Invalid latitude=" ++ show lat ++ " or longitude=" ++ show lon))
(latLongF lat lon)
latLongE :: Angle -> Angle -> Either String LatLong
latLongE lat lon
| not (isWithin lat (decimalDegrees (-90)) (decimalDegrees 90)) =
Left ("Invalid latitude=" ++ show lat)
| not (isWithin lon (decimalDegrees (-180)) (decimalDegrees 180)) =
Left ("Invalid longitude=" ++ show lon)
| otherwise = Right (LatLong lat lon)
latLongF :: (MonadFail m) => Angle -> Angle -> m LatLong
latLongF lat lon =
case e of
Left err -> fail err
Right g -> return g
where
e = latLongE lat lon
decimalLatLong :: Double -> Double -> LatLong
decimalLatLong lat lon = latLong (decimalDegrees lat) (decimalDegrees lon)
decimalLatLongE :: Double -> Double -> Either String LatLong
decimalLatLongE lat lon = latLongE (decimalDegrees lat) (decimalDegrees lon)
decimalLatLongF :: (MonadFail m) => Double -> Double -> m LatLong
decimalLatLongF lat lon = latLongF (decimalDegrees lat) (decimalDegrees lon)
readLatLong :: String -> LatLong
readLatLong s = read s :: LatLong
readLatLongE :: String -> Either String LatLong
readLatLongE s =
case readMaybe s of
Nothing -> Left ("couldn't read geo pos " ++ s)
Just g -> Right g
readLatLongF :: (MonadFail m) => String -> m LatLong
readLatLongF s =
let pg = readLatLongE s
in case pg of
Left e -> fail e
Right g -> return g
toDecimalDegrees' :: LatLong -> (Double, Double)
toDecimalDegrees' g = (toDecimalDegrees (latitude g), toDecimalDegrees (longitude g))
ll :: ReadP LatLong
ll = block <|> human
block :: ReadP LatLong
block = do
lat <- blat
lon <- blon
latLongF lat lon
blat :: ReadP Angle
blat = do
d' <- digits 2
(m', s') <- option (0, 0) (ms <|> m)
h <- hemisphere
if h == 'N'
then dmsF d' m' s' 0
else dmsF (-d') m' s' 0
blon :: ReadP Angle
blon = do
d' <- digits 3
(m', s') <- option (0, 0) (ms <|> m)
m'' <- meridian
if m'' == 'E'
then dmsF d' m' s' 0
else dmsF (-d') m' s' 0
hemisphere :: ReadP Char
hemisphere = char 'N' <|> char 'S'
meridian :: ReadP Char
meridian = char 'E' <|> char 'W'
ms :: ReadP (Int, Int)
ms = do
m' <- digits 2
s' <- digits 2
return (m', s')
m :: ReadP (Int, Int)
m = do
m' <- digits 2
return (m', 0)
human :: ReadP LatLong
human = do
lat <- hlat
_ <- char ' ' <|> char ','
lon <- hlon
latLongF lat lon
hlat :: ReadP Angle
hlat = do
lat <- angle
h <- hemisphere
if h == 'N'
then return lat
else return (negate' lat)
hlon :: ReadP Angle
hlon = do
lon <- angle
m' <- meridian
if m' == 'E'
then return lon
else return (negate' lon)
showLat :: Angle -> String
showLat lat
| isNegative lat = show (negate' lat) ++ "S"
| otherwise = show lat ++ "N"
showLon :: Angle -> String
showLon lon
| isNegative lon = show (negate' lon) ++ "W"
| otherwise = show lon ++ "E"