-- | -- Module: Data.Geo.Jord.GeoPos -- Copyright: (c) 2018 Cedric Liegeois -- License: BSD3 -- Maintainer: Cedric Liegeois -- Stability: experimental -- Portability: portable -- -- Types to represent a geographic position by its latitude and longitude. -- module Data.Geo.Jord.GeoPos ( -- * The 'GeoPos' type GeoPos(latitude, longitude) -- * Smart constructors , latLong , latLongE , latLongF , latLongDecimal , latLongDecimalE , latLongDecimalF -- * read , readGeoPos , readGeoPosE , readGeoPosF -- * Misc. , toDecimalDegrees' ) where import Control.Applicative hiding (many) import Control.Monad.Fail import Data.Char import Data.Geo.Jord.Angle import Data.Geo.Jord.Parse import Data.Maybe import Prelude hiding (fail) import Text.ParserCombinators.ReadP import Text.Read hiding (pfail) -- | A geographic position (latitude and longitude). data GeoPos = GeoPos { latitude :: Angle , longitude :: Angle } deriving (Eq) -- | See 'readGeoPos'. instance Read GeoPos where readsPrec _ = readP_to_S geo -- | Produced string format: d°(m')(s'')[N|S],d°(m')(s'')[E|W] - e.g. 55°36'21''N,13°0'2''E. instance Show GeoPos where show (GeoPos lat lon) = showLat lat ++ "," ++ showLon lon -- | 'GeoPos' from given latitude and longitude. -- 'error's if given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLong :: Angle -> Angle -> GeoPos latLong lat lon = fromMaybe (error ("Invalid latitude=" ++ show lat ++ " or longitude=" ++ show lon)) (latLongF lat lon) -- | 'GeoPos' from given latitude and longitude. -- A 'Left' indicates that the given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLongE :: Angle -> Angle -> Either String GeoPos 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 (GeoPos lat lon) -- | 'GeoPos' from given latitude and longitude. -- 'fail's if given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLongF :: (MonadFail m) => Angle -> Angle -> m GeoPos latLongF lat lon = case e of Left err -> fail err Right g -> return g where e = latLongE lat lon -- | 'GeoPos' from given latitude and longitude in decimal degrees. -- 'error's if given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLongDecimal :: Double -> Double -> GeoPos latLongDecimal lat lon = latLong (decimalDegrees lat) (decimalDegrees lon) -- | 'GeoPos' from given latitude and longitude in decimal degrees. -- A 'Left' indicates that the given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLongDecimalE :: Double -> Double -> Either String GeoPos latLongDecimalE lat lon = latLongE (decimalDegrees lat) (decimalDegrees lon) -- | 'GeoPos' from given latitude and longitude in decimal degrees. -- 'fail's if given latitude is outisde [-90..90]° and/or -- given longitude is outisde [-180..180]°. latLongDecimalF :: (MonadFail m) => Double -> Double -> m GeoPos latLongDecimalF lat lon = latLongF (decimalDegrees lat) (decimalDegrees lon) -- | Obtains a 'GeoPos' from the given string formatted as either: -- -- * DD(MM)(SS)[N|S]DDD(MM)(SS)[E|W] - e.g. 553621N0130002E or 0116S03649E or 47N122W -- -- * 'Angle'[N|S] 'Angle'[E|W] - e.g. 55°36'21''N 13°0'02''E or 11°16'S 36°49'E or 47°N 122°W -- -- This simply calls @read s :: GeoPos@ so 'error' should be handled at the call site. -- readGeoPos :: String -> GeoPos readGeoPos s = read s :: GeoPos -- | Same as 'readGeoPos' but returns a 'Either'. readGeoPosE :: String -> Either String GeoPos readGeoPosE s = case readMaybe s of Nothing -> Left ("couldn't read geo pos " ++ s) Just g -> Right g -- | Same as 'readGeoPos' but returns a 'MonadFail'. readGeoPosF :: (MonadFail m) => String -> m GeoPos readGeoPosF s = let pg = readGeoPosE s in case pg of Left e -> fail e Right g -> return g -- | Converts the given 'GeoPos' to tuple of latitude and longitude in decimal degrees. toDecimalDegrees' :: GeoPos -> (Double, Double) toDecimalDegrees' g = (toDecimalDegrees (latitude g), toDecimalDegrees (longitude g)) -- | Parses and returns a 'GeoPos'. geo :: ReadP GeoPos geo = block <|> human -- | Parses and returns a 'GeoPos' - DD(D)MMSS. block :: ReadP GeoPos block = do lat <- blat lon <- blon latLongF lat lon -- | Parses and returns a latitude, DDMMSS expected. 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 -- | Parses and returns a longitude, DDDMMSS expected. 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 -- | Parses N or S char. hemisphere :: ReadP Char hemisphere = char 'N' <|> char 'S' -- | Parses E or W char. meridian :: ReadP Char meridian = char 'E' <|> char 'W' -- | Parses minutes and seconds. ms :: ReadP (Int, Int) ms = do m' <- digits 2 s' <- digits 2 return (m', s') -- | Parses minutes. m :: ReadP (Int, Int) m = do m' <- digits 2 return (m', 0) -- | Parses and returns a 'GeoPos' from a human friendly text - see 'Angle'. human :: ReadP GeoPos human = do lat <- hlat _ <- char ' ' <|> char ',' lon <- hlon latLongF lat lon -- | Parses and returns a latitude, 'Angle'N|S expected. hlat :: ReadP Angle hlat = do lat <- angle h <- hemisphere if h == 'N' then return lat else return (negate' lat) -- | Parses and returns a longitude, 'Angle'E|W expected. hlon :: ReadP Angle hlon = do lon <- angle m' <- meridian if m' == 'E' then return lon else return (negate' lon) -- | Latitude to string. showLat :: Angle -> String showLat lat | isNegative lat = show (negate' lat) ++ "S" | otherwise = show lat ++ "N" -- | Longitude to string. showLon :: Angle -> String showLon lon | isNegative lon = show (negate' lon) ++ "W" | otherwise = show lon ++ "E"