[nhc-bugs] nhc 1.10 bugs
Lennart Augustsson
augustss@augustsson.net
Fri, 26 Oct 2001 13:53:25 +0200 (MEST)
Here are some Time related bugs and fixes.
tdPicosec misspelled, diffClockTimes and addClockTimes not implemeted
-- Lennart
------
module Time where
data TimeDiff = TimeDiff {
tdYear, tdMonth, tdDay, tdHour, tdMin, tdSec :: Int,
tdPicosec :: Integer
} deriving (Eq, Ord, Read, Show)
------
module Time where
import DClockTime
import DTimeDiff
diffClockTimes :: ClockTime -> ClockTime -> TimeDiff
diffClockTimes (CT t) (CT t') = TimeDiff { tdYear = 0, tdMon = 0, tdDay = dd, tdHour = dh, tdMin = dm, tdSec = ds, tdPicosec = 0 }
where ts = t-t'
(tm, ds) = quotRem ts 60
(th, dm) = quotRem tm 60
(dd, dh) = quotRem th 24
-- tdMon and tdYear make no sense, so ignore them
-----
module Time where
import DTimeDiff
import DClockTime
addToClockTime :: TimeDiff -> ClockTime -> ClockTime
addToClockTime td (CT i) = CT (i+d)
-- tdYear and tdMonth make no sense, ignore them
where d = ((tdDay td * 24 + tdHour td) * 60 + tdMin td) * 60 + tdSec td
------