module Naqsha.Position
(
Geo(..)
, northPole, southPole
, Latitude
, north, south, lat
, equator
, tropicOfCancer
, tropicOfCapricon
, Longitude
, east, west, lon
, greenwich
) where
import Control.Monad ( liftM )
import Data.Default
import Data.Fixed
import Data.Monoid
import Data.Group
import Data.Vector.Unboxed ( MVector(..), Vector)
import qualified Data.Vector.Generic as GV
import qualified Data.Vector.Generic.Mutable as GVM
import Text.Read
import Prelude
import Naqsha.Geometry.Angle
newtype Latitude = Latitude { unLat :: Angle } deriving (Eq, Ord)
lat :: Angle -> Latitude
lat = Latitude . normLat
north :: Angle -> Latitude
north = lat
south :: Angle -> Latitude
south = lat . invert
instance Angular Latitude where
toAngle = unLat
instance Show Latitude where
show = show . (toDegree :: Angle -> Nano) . unLat
instance Read Latitude where
readPrec = conv <$> readPrec
where conv = lat . degree . (toRational :: Nano -> Rational)
instance Default Latitude where
def = equator
equator :: Latitude
equator = lat $ degree 0
tropicOfCancer :: Latitude
tropicOfCancer = north $ degree 23.5
tropicOfCapricon :: Latitude
tropicOfCapricon = south $ degree 23.5
instance Bounded Latitude where
maxBound = lat $ degree 90
minBound = lat $ degree (90)
newtype Longitude = Longitude { unLong :: Angle }
deriving (Eq, Bounded, Default, Angular, Ord, Monoid, Group)
instance Show Longitude where
show = show . (toDegree :: Angle -> Nano) . unLong
instance Read Longitude where
readPrec = conv <$> readPrec
where conv = lon . degree . (toRational :: Nano -> Rational)
lon :: Angle -> Longitude
lon = Longitude
east :: Angle -> Longitude
east = lon
west :: Angle -> Longitude
west = lon . invert
greenwich :: Longitude
greenwich = lon $ degree 0
data Geo = Geo !Latitude
!Longitude
deriving Show
instance Default Geo where
def = Geo def def
northPole :: Geo
northPole = Geo maxBound $ lon $ degree 0
southPole :: Geo
southPole = Geo minBound $ lon $ degree 0
instance Eq Geo where
(==) (Geo xlat xlong) (Geo ylat ylong)
| xlat == maxBound = ylat == maxBound
| xlat == minBound = ylat == minBound
| otherwise = xlat == ylat && xlong == ylong
normLat :: Angle -> Angle
normLat ang | degree (90) <= ang && ang < degree 90 = ang
| ang > degree 90 = succ (maxBound <> invert ang)
| otherwise = minBound <> invert ang
newtype instance MVector s Latitude = MLatV (MVector s Angle)
newtype instance Vector Latitude = LatV (Vector Angle)
newtype instance MVector s Longitude = MLongV (MVector s Angle)
newtype instance Vector Longitude = LongV (Vector Angle)
newtype instance MVector s Geo = MGeoV (MVector s (Angle,Angle))
newtype instance Vector Geo = GeoV (Vector (Angle,Angle))
instance GVM.MVector MVector Latitude where
basicLength (MLatV v) = GVM.basicLength v
basicUnsafeSlice i n (MLatV v) = MLatV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MLatV v1) (MLatV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MLatV v) i = Latitude `liftM` GVM.basicUnsafeRead v i
basicUnsafeWrite (MLatV v) i (Latitude x) = GVM.basicUnsafeWrite v i x
basicClear (MLatV v) = GVM.basicClear v
basicSet (MLatV v) (Latitude x) = GVM.basicSet v x
basicUnsafeNew n = MLatV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Latitude x) = MLatV `liftM` GVM.basicUnsafeReplicate n x
basicUnsafeCopy (MLatV v1) (MLatV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MLatV v) n = MLatV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MLatV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Latitude where
basicUnsafeFreeze (MLatV v) = LatV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (LatV v) = MLatV `liftM` GV.basicUnsafeThaw v
basicLength (LatV v) = GV.basicLength v
basicUnsafeSlice i n (LatV v) = LatV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (LatV v) i = Latitude `liftM` GV.basicUnsafeIndexM v i
basicUnsafeCopy (MLatV mv) (LatV v) = GV.basicUnsafeCopy mv v
elemseq _ (Latitude x) = GV.elemseq (undefined :: Vector a) x
instance GVM.MVector MVector Longitude where
basicLength (MLongV v) = GVM.basicLength v
basicUnsafeSlice i n (MLongV v) = MLongV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MLongV v1) (MLongV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MLongV v) i = Longitude `liftM` GVM.basicUnsafeRead v i
basicUnsafeWrite (MLongV v) i (Longitude x) = GVM.basicUnsafeWrite v i x
basicClear (MLongV v) = GVM.basicClear v
basicSet (MLongV v) (Longitude x) = GVM.basicSet v x
basicUnsafeNew n = MLongV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Longitude x) = MLongV `liftM` GVM.basicUnsafeReplicate n x
basicUnsafeCopy (MLongV v1) (MLongV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MLongV v) n = MLongV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MLongV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Longitude where
basicUnsafeFreeze (MLongV v) = LongV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (LongV v) = MLongV `liftM` GV.basicUnsafeThaw v
basicLength (LongV v) = GV.basicLength v
basicUnsafeSlice i n (LongV v) = LongV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (LongV v) i = Longitude `liftM` GV.basicUnsafeIndexM v i
basicUnsafeCopy (MLongV mv) (LongV v) = GV.basicUnsafeCopy mv v
elemseq _ (Longitude x) = GV.elemseq (undefined :: Vector a) x
instance GVM.MVector MVector Geo where
basicLength (MGeoV v) = GVM.basicLength v
basicUnsafeSlice i n (MGeoV v) = MGeoV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MGeoV v1) (MGeoV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MGeoV v) i = do (x,y) <- GVM.basicUnsafeRead v i
return $ Geo (Latitude x) $ Longitude y
basicUnsafeWrite (MGeoV v) i (Geo x y) = GVM.basicUnsafeWrite v i (unLat x, unLong y)
basicClear (MGeoV v) = GVM.basicClear v
basicSet (MGeoV v) (Geo x y) = GVM.basicSet v (unLat x, unLong y)
basicUnsafeNew n = MGeoV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Geo x y) = MGeoV `liftM` GVM.basicUnsafeReplicate n (unLat x, unLong y)
basicUnsafeCopy (MGeoV v1) (MGeoV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MGeoV v) n = MGeoV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MGeoV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Geo where
basicUnsafeFreeze (MGeoV v) = GeoV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (GeoV v) = MGeoV `liftM` GV.basicUnsafeThaw v
basicLength (GeoV v) = GV.basicLength v
basicUnsafeSlice i n (GeoV v) = GeoV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (GeoV v) i =do (x,y) <- GV.basicUnsafeIndexM v i
return $ Geo (Latitude x) $ Longitude y
basicUnsafeCopy (MGeoV mv) (GeoV v) = GV.basicUnsafeCopy mv v
elemseq _ (Geo x y) = GV.elemseq (undefined :: Vector a) (unLat x, unLong y)