module Data.Geo.Geodetic.Sphere(
Sphere
, AsSphere(..)
, earthMean
) where
import Prelude(Double, Eq, Show(..), Ord(..), id, (++), showParen, showString)
import Control.Lens(Optic', Profunctor, iso)
import Data.Functor(Functor)
import Text.Printf(printf)
newtype Sphere =
Sphere Double
deriving (Eq, Ord)
instance Show Sphere where
showsPrec n (Sphere d) =
showParen (n > 10) (showString ("Sphere " ++ printf "%0.4f" d))
earthMean ::
Sphere
earthMean =
Sphere 6367450
class AsSphere p f s where
_Sphere ::
Optic' p f s Sphere
instance AsSphere p f Sphere where
_Sphere =
id
instance (Functor f, Profunctor p) => AsSphere p f Double where
_Sphere =
iso
Sphere
(\(Sphere d) -> d)