{-# LANGUAGE MultiParamTypeClasses, GeneralizedNewtypeDeriving #-} -- | Simple Type: @latitudeType@ module Data.Geo.GPX.LatitudeType( LatitudeType, latitudeType ) where import Data.Geo.GPX.Accessor.Value import Data.Fixed import Text.XML.HXT.Arrow newtype LatitudeType = LatitudeType Double deriving (Eq, Ord, Enum, Num, Fractional, Floating, Real, RealFrac, RealFloat) latitudeType :: Double -- ^ The value which will be between -90 and 90 (values out of the range are truncated using a modulus operation). -> LatitudeType latitudeType n = LatitudeType ((n + 90) `mod'` 180 - 90) instance XmlPickler LatitudeType where xpickle = xpWrap (latitudeType, \(LatitudeType n) -> n) xpPrim instance Show LatitudeType where show (LatitudeType n) = show n instance Value LatitudeType Double where value (LatitudeType x) = x