module Data.Geo.Jord.Length
    (
    
      Length(millimetres)
    
    , kilometres
    , metres
    , nauticalMiles
    
    , readLength
    , readLengthE
    , readLengthF
    
    , toKilometres
    , toMetres
    , toNauticalMiles
    
    , isZero
    ) where
import Control.Applicative
import Control.Monad.Fail
import Data.Geo.Jord.Parse
import Data.Geo.Jord.Quantity
import Prelude hiding (fail, length)
import Text.ParserCombinators.ReadP
import Text.Read hiding (pfail)
newtype Length = Length
    { millimetres :: Int
    } deriving (Eq)
instance Read Length where
    readsPrec _ = readP_to_S length
instance Show Length where
    show l
        | m <= 10000.0 = show m ++ "m"
        | otherwise = show (m / 1000.0) ++ "km"
      where
        m = toMetres l
instance Quantity Length where
    add a b = Length (millimetres a + millimetres b)
    sub a b = Length (millimetres a - millimetres b)
nauticalMiles :: Double -> Length
nauticalMiles nm = metres (nm * 1852.0)
metres :: Double -> Length
metres m = Length (round (m * 1000.0))
kilometres :: Double -> Length
kilometres km = metres (km * 1000.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
toKilometres :: Length -> Double
toKilometres l = toMetres l / 1000.0
toMetres :: Length -> Double
toMetres (Length mm) = fromIntegral mm / 1000.0
toNauticalMiles :: Length -> Double
toNauticalMiles l = toMetres l / 1852.0
isZero :: Length -> Bool
isZero (Length mm) = mm == 0
length :: ReadP Length
length = do
    v <- number
    skipSpaces
    u <- string "m" <|> string "km" <|> string "Nm"
    case u of
        "m" -> return (metres v)
        "km" -> return (kilometres v)
        "Nm" -> return (nauticalMiles v)
        _ -> pfail