Skip to content

Commit

Permalink
Split Minute into MinuteOfTime & MinuteOfAngle, #249.
Browse files Browse the repository at this point in the history
  • Loading branch information
philderbeast committed Mar 16, 2019
1 parent 0a0b84d commit 679a30b
Show file tree
Hide file tree
Showing 6 changed files with 54 additions and 45 deletions.
3 changes: 2 additions & 1 deletion igc/library/Flight/Igc.hs
Expand Up @@ -27,7 +27,8 @@ module Flight.Igc
, Altitude(..)
, Degree(..)
, Hour(..)
, Minute(..)
, MinuteOfTime(..)
, MinuteOfAngle(..)
, Second(..)
, Year(..)
, Month(..)
Expand Down
8 changes: 4 additions & 4 deletions igc/library/Flight/Igc/Fix.hs
Expand Up @@ -77,19 +77,19 @@ extract HFDTE{} = Nothing
extract B{hms, pos} = Just (hms, pos)

-- | Combines date with time of day to get a @UTCTime@.
-- >>> stamp (Year 17, Month 7, Day 8) (HMS (Hour 2) (Minute "37") (Second 56))
-- >>> stamp (Year 17, Month 7, Day 8) (HMS (Hour 2) (MinuteOfTime 37) (Second 56))
-- 2017-07-08 02:37:56 UTC
--
-- >>> stamp (Year 17, Month 7, Day 8) (HMS (Hour 26) (Minute "37") (Second 56))
-- >>> stamp (Year 17, Month 7, Day 8) (HMS (Hour 26) (MinuteOfTime 37) (Second 56))
-- 2017-07-09 02:37:56 UTC
stamp :: (Year, Month, Day) -> HMS -> UTCTime
stamp (Year yy, Month mm, Day dd) (HMS (Hour hr) (Minute minute) (Second sec)) =
stamp (Year yy, Month mm, Day dd) (HMS (Hour hr) (MinuteOfTime minute) (Second sec)) =
utc
where
-- TODO: Test with an IGC file from the 20th Century.
y = 2000 + fromIntegral yy :: Integer
hr' = fromIntegral hr
minute' = read minute :: Integer
minute' = fromIntegral minute
sec' = fromIntegral sec
utc =
(fromInteger $ 60 * ((60 * hr') + minute') + sec')
Expand Down
6 changes: 3 additions & 3 deletions igc/library/Flight/Igc/Parse.hs
Expand Up @@ -39,7 +39,7 @@ line = do
timeHHMMSS :: ParsecT Void String Identity HMS
timeHHMMSS = do
hh <- Hour . read <$> count 2 digitChar
mm <- Minute <$> count 2 digitChar
mm <- MinuteOfTime . read <$> count 2 digitChar
ss <- Second . read <$> count 2 digitChar
return $ HMS hh mm ss

Expand All @@ -49,7 +49,7 @@ timeHHMMSS = do
lat :: ParsecT Void String Identity Lat
lat = do
degs <- Degree . read <$> count 2 digitChar
mins <- Minute <$> count 5 digitChar
mins <- MinuteOfAngle . read <$> count 5 digitChar
f <- const LatN <$> char 'N' <|> const LatS <$> char 'S'
return $ f degs mins

Expand All @@ -59,7 +59,7 @@ lat = do
lng :: ParsecT Void String Identity Lng
lng = do
degs <- Degree . read <$> count 3 digitChar
mins <- Minute <$> count 5 digitChar
mins <- MinuteOfAngle . read <$> count 5 digitChar
f <- const LngW <$> char 'W' <|> const LngE <$> char 'E'
return $ f degs mins

Expand Down
73 changes: 40 additions & 33 deletions igc/library/Flight/Igc/Record.hs
Expand Up @@ -10,7 +10,8 @@ module Flight.Igc.Record
, Altitude(..)
, Degree(..)
, Hour(..)
, Minute(..)
, MinuteOfTime(..)
, MinuteOfAngle(..)
, Second(..)
, Year(..)
, Month(..)
Expand All @@ -34,10 +35,12 @@ newtype Altitude = Altitude String
newtype Hour = Hour Int
deriving (Eq, Ord)

-- | A minute of time or a minute of a degree. If a minute of a degree, the
-- first two chars are whole minutes and the following chars are the decimal
-- part. No decimal point character is included.
newtype Minute = Minute String
-- | A minute of time.
newtype MinuteOfTime = MinuteOfTime Int
deriving (Eq, Ord)

-- | Thousandths of a minute of angle.
newtype MinuteOfAngle = MinuteOfAngle {unThousandths :: Int}
deriving (Eq, Ord)

-- | A second of time.
Expand All @@ -49,19 +52,19 @@ newtype Degree = Degree Int
deriving (Eq, Ord)

-- | A time with hours, minutes and seconds.
data HMS = HMS Hour Minute Second
data HMS = HMS Hour MinuteOfTime Second
deriving (Eq, Ord)

-- | A latitude with degrees and minutes.
data Lat
= LatN Degree Minute -- ^ North
| LatS Degree Minute -- ^ South
= LatN Degree MinuteOfAngle -- ^ North
| LatS Degree MinuteOfAngle -- ^ South
deriving (Eq, Ord)

-- | A longitude with degrees and minutes.
data Lng
= LngW Degree Minute -- ^ West
| LngE Degree Minute -- ^ East
= LngW Degree MinuteOfAngle -- ^ West
| LngE Degree MinuteOfAngle -- ^ East
deriving (Eq, Ord)

-- | Pressure altitude in metres
Expand Down Expand Up @@ -149,10 +152,14 @@ instance Show IgcRecord where
instance Arbitrary Hour where
arbitrary = Hour <$> arbitrary

instance Arbitrary Minute where
arbitrary = do
h :: Int <- arbitrary
return . Minute $ show h
instance Arbitrary Degree where
arbitrary = Degree <$> arbitrary

instance Arbitrary MinuteOfTime where
arbitrary = MinuteOfTime <$> arbitrary

instance Arbitrary MinuteOfAngle where
arbitrary = MinuteOfAngle <$> arbitrary

instance Arbitrary Second where
arbitrary = Second <$> arbitrary
Expand All @@ -168,27 +175,27 @@ instance Arbitrary Lat where
arbitrary =
oneof
[ do
d <- Degree <$> arbitrary
m <- Minute <$> arbitrary
d <- arbitrary
m <- arbitrary
return $ LatN d m

, do
d <- Degree <$> arbitrary
m <- Minute <$> arbitrary
d <- arbitrary
m <- arbitrary
return $ LatS d m
]

instance Arbitrary Lng where
arbitrary =
oneof
[ do
d <- Degree <$> arbitrary
m <- Minute <$> arbitrary
d <- arbitrary
m <- arbitrary
return $ LngE d m

, do
d <- Degree <$> arbitrary
m <- Minute <$> arbitrary
d <- arbitrary
m <- arbitrary
return $ LngW d m
]

Expand Down Expand Up @@ -225,10 +232,10 @@ instance Arbitrary IgcRecord where
return $ HFDTE ymd

-- |
-- >>> addHoursHms (Hour 0) (HMS (Hour 0) (Minute "0") (Second 0))
-- >>> addHoursHms (Hour 0) (HMS (Hour 0) (MinuteOfTime 0) (Second 0))
-- 00:00:00
--
-- >>> addHoursHms (Hour 24) (HMS (Hour 12) (Minute "34") (Second 56))
-- >>> addHoursHms (Hour 24) (HMS (Hour 12) (MinuteOfTime 34) (Second 56))
-- 36:34:56
addHoursHms :: Hour -> HMS -> HMS
addHoursHms
Expand All @@ -246,24 +253,24 @@ showDegreeOfLat (Degree d) = printf "%02d°" d
showDegreeOfLng :: Degree -> String
showDegreeOfLng (Degree d) = printf "%03d°" d

showMinute :: String -> String
showMinute (m0 : m1 : m) = [m0, m1] ++ "." ++ m ++ "'"
showMinute m = m
showMinute :: MinuteOfAngle -> String
showMinute (MinuteOfAngle thousandths) =
printf "%06.3f'" $ (fromIntegral thousandths :: Double) / 1000

showHMS :: HMS -> String
showHMS (HMS (Hour hh) (Minute mm) (Second ss)) =
printf "%02d:%02d:%02d" hh (read mm :: Int) ss
showHMS (HMS (Hour hh) (MinuteOfTime mm) (Second ss)) =
printf "%02d:%02d:%02d" hh mm ss

showLat :: Lat -> String
showLat (LatN d (Minute m)) =
showLat (LatN d m) =
showDegreeOfLat d ++ " " ++ showMinute m ++ " N"
showLat (LatS d (Minute m)) =
showLat (LatS d m) =
showDegreeOfLat d ++ " " ++ showMinute m ++ " S"

showLng :: Lng -> String
showLng (LngW d (Minute m)) =
showLng (LngW d m) =
showDegreeOfLng d ++ " " ++ showMinute m ++ " W"
showLng (LngE d (Minute m)) =
showLng (LngE d m) =
showDegreeOfLng d ++ " " ++ showMinute m ++ " E"

ltrimZero :: String -> String
Expand Down
8 changes: 4 additions & 4 deletions track/library/Flight/TrackLog.hs
Expand Up @@ -39,7 +39,7 @@ import System.FilePath
import qualified Flight.Kml as K
import qualified Flight.Igc as I (parse)
import Flight.Igc
( Degree(..), Minute(..)
( Degree(..), MinuteOfAngle(..)
, Lat(..), Lng(..), Altitude(..), AltGps(..), AltBaro(..)
, IgcRecord(..)
, isMark, isFix
Expand Down Expand Up @@ -224,12 +224,12 @@ toFix mark0 (t, (lat, lng, altBaro, altGps)) =
, K.fixAltBaro = readAltGps <$> altGps
}

readDegMin :: Degree -> Minute -> Rational
readDegMin (Degree d) (Minute m) =
readDegMin :: Degree -> MinuteOfAngle -> Rational
readDegMin (Degree d) MinuteOfAngle{unThousandths} =
d' % 1 + toRational m' / 60000
where
d' = fromIntegral d
m' = read m :: Double
m' = fromIntegral unThousandths :: Integer

readLat :: Lat -> K.Latitude
readLat (LatN d m) = K.Latitude $ readDegMin d m
Expand Down
1 change: 1 addition & 0 deletions track/test-suite-doctest/DocTest.hs
Expand Up @@ -9,6 +9,7 @@ arguments =
, "-XScopedTypeVariables"
, "-XTupleSections"
, "-XParallelListComp"
, "-XNamedFieldPuns"
]

main :: IO ()
Expand Down

0 comments on commit 679a30b

Please sign in to comment.