module Data.Geo.Jord.Length
(
Length
, feet
, kilometres
, metres
, nauticalMiles
, readLength
, readLengthE
, readLengthF
, toFeet
, toKilometres
, toMetres
, toNauticalMiles
) where
import Control.Applicative
import Control.Monad.Fail
import Data.Geo.Jord.Parser
import Data.Geo.Jord.Quantity
import Prelude hiding (fail, length)
import Text.ParserCombinators.ReadP
import Text.Read hiding (pfail)
newtype Length = Length
{ tenthOfMm :: Int
} deriving (Eq)
instance Read Length where
readsPrec _ = readP_to_S length
instance Show Length where
show l
| abs m <= 10000.0 = show m ++ "m"
| otherwise = show (m / 1000.0) ++ "km"
where
m = toMetres l
instance Quantity Length where
add a b = Length (tenthOfMm a + tenthOfMm b)
sub a b = Length (tenthOfMm a - tenthOfMm b)
zero = Length 0
feet :: Double -> Length
feet ft = Length (round (ft * 3048.0))
kilometres :: Double -> Length
kilometres km = Length (round (km * 10000000.0))
metres :: Double -> Length
metres m = Length (round (m * 10000.0))
nauticalMiles :: Double -> Length
nauticalMiles nm = Length (round (nm * 18520000.0))
readLength :: String -> Length
readLength s = read s :: Length
readLengthE :: String -> Either String Length
readLengthE s =
case readMaybe s of
Nothing -> Left ("couldn't read length " ++ s)
Just l -> Right l
readLengthF :: (MonadFail m) => String -> m Length
readLengthF s =
let p = readEither s
in case p of
Left e -> fail e
Right l -> return l
toFeet :: Length -> Double
toFeet (Length l) = fromIntegral l / 3048.0
toKilometres :: Length -> Double
toKilometres (Length l) = fromIntegral l / 10000000.0
toMetres :: Length -> Double
toMetres (Length l) = fromIntegral l / 10000.0
toNauticalMiles :: Length -> Double
toNauticalMiles (Length l) = fromIntegral l / 18520000.0
length :: ReadP Length
length = do
v <- number
skipSpaces
u <- string "m" <|> string "km" <|> string "nm" <|> string "ft"
case u of
"m" -> return (metres v)
"km" -> return (kilometres v)
"nm" -> return (nauticalMiles v)
"ft" -> return (feet v)
_ -> pfail