{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE Rank2Types #-}
module Naqsha.Geometry.Coordinate
(
Geo(..)
, northPole, southPole
, Latitude
, lat, north, south
, equator
, tropicOfCancer
, tropicOfCapricon
, Longitude
, lon, east, west
, greenwich
) where
import Control.Monad ( liftM )
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 Prelude
import Naqsha.Geometry.Angle
import Naqsha.Geometry.Internal
north :: Angle -> Latitude
north = lat
south :: Angle -> Latitude
south = lat . invert
equator :: Latitude
equator = lat $ degree 0
tropicOfCancer :: Latitude
tropicOfCancer = north $ degree 23.5
tropicOfCapricon :: Latitude
tropicOfCapricon = south $ degree 23.5
east :: Angle -> Longitude
east = lon
west :: Angle -> Longitude
west = lon . invert
greenwich :: Longitude
greenwich = lon $ degree 0
data Geo = Geo {-# UNPACK #-} !Latitude
{-# UNPACK #-} !Longitude
deriving Show
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
newtype instance MVector s Geo = MGeoV (MVector s (Angle,Angle))
newtype instance Vector Geo = GeoV (Vector (Angle,Angle))
instance GVM.MVector MVector Geo where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
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
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
{-# INLINE elemseq #-}
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)