commit ghc-hourglass for openSUSE:Factory
Hello community, here is the log from the commit of package ghc-hourglass for openSUSE:Factory checked in at 2016-02-29 09:14:45 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-hourglass (Old) and /work/SRC/openSUSE:Factory/.ghc-hourglass.new (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Package is "ghc-hourglass" Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-hourglass/ghc-hourglass.changes 2015-05-27 12:43:12.000000000 +0200 +++ /work/SRC/openSUSE:Factory/.ghc-hourglass.new/ghc-hourglass.changes 2016-02-29 09:16:14.000000000 +0100 @@ -1,0 +2,5 @@ +Sun Feb 28 21:48:31 UTC 2016 - mimi.vx@gmail.com + +- update to 0.2.10 + +------------------------------------------------------------------- Old: ---- hourglass-0.2.9.tar.gz New: ---- hourglass-0.2.10.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-hourglass.spec ++++++ --- /var/tmp/diff_new_pack.o6ZMiG/_old 2016-02-29 09:16:16.000000000 +0100 +++ /var/tmp/diff_new_pack.o6ZMiG/_new 2016-02-29 09:16:16.000000000 +0100 @@ -20,7 +20,7 @@ %bcond_with tests Name: ghc-%{pkg_name} -Version: 0.2.9 +Version: 0.2.10 Release: 0 Summary: Simple performant time related library Group: System/Libraries ++++++ hourglass-0.2.9.tar.gz -> hourglass-0.2.10.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Data/Hourglass/Compat.hs new/hourglass-0.2.10/Data/Hourglass/Compat.hs --- old/hourglass-0.2.9/Data/Hourglass/Compat.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/Data/Hourglass/Compat.hs 2016-02-27 12:23:51.000000000 +0100 @@ -29,76 +29,10 @@ -- > -- > offsetTime = H.TimezoneOffset $ fromIntegral $ T.timeZoneMinutes $ T.zonedTimeZone oldTime -- +-- This module will be depreciated in favor of Time.Compat +-- module Data.Hourglass.Compat - ( dateFromPOSIXEpoch - , dateFromTAIEpoch - , diffTimeToTimeOfDay + ( module Time.Compat ) where -import Data.Hourglass - --- | Convert an integer which represent the Number of days (To/From) POSIX Epoch --- to a Date (POSIX Epoch is 1970-01-01). -dateFromPOSIXEpoch :: Integer -- ^ number of days since POSIX Epoch - -> Date -dateFromPOSIXEpoch day = do - let sec = Elapsed $ fromIntegral $ day * 86400 - timeConvert sec - --- | Number of days between POSIX Epoch and TAI Epoch --- (between 1858-11-17 and 1970-01-01) -daysTAItoPOSIX :: Integer -daysTAItoPOSIX = 40587 - --- | Convert an integer which represents the Number of days (To/From) TAI Epoch --- This function allows use of the package time to easily convert the Day into --- the Hourglass Date representation (TAI Epoch is 1858-11-17). --- --- This function allows user to easily convert a Data.Time.Calendar.Day into Date --- --- > import qualified Data.Time.Calendar as T --- > --- > timeDay :: T.Day --- > --- > dateFromTAIEpoch $ T.toModifiedJulianDay timeDay -dateFromTAIEpoch :: Integer -- ^ number of days since TAI Epoch - -> Date -dateFromTAIEpoch dtai = - dateFromPOSIXEpoch (dtai - daysTAItoPOSIX) - --- | Convert of differential of time of a day. --- (it convers a Data.Time.Clock.DiffTime into a TimeOfDay) --- --- Example with DiffTime type from time: --- --- > import qualified Data.Time.Clock as T --- > --- > difftime :: T.DiffTime --- > --- > diffTimeToTimeOfDay difftime --- --- Example with the TimeOfDay type from time: --- --- > import qualified Data.Time.Clock as T --- > --- > timeofday :: T.TimeOfDay --- > --- > diffTimeToTimeOfDay $ T.timeOfDayToTime timeofday -diffTimeToTimeOfDay :: Real t - => t -- ^ number of seconds of the time of the day - -> TimeOfDay -diffTimeToTimeOfDay dt = do - TimeOfDay - { todHour = fromIntegral hours - , todMin = fromIntegral minutes - , todSec = fromIntegral seconds - , todNSec = fromIntegral nsecs - } - where - r :: Rational - r = toRational dt - (secs, nR) = properFraction r :: (Integer, Rational) - nsecs :: Integer - nsecs = round (nR * 1000000000) - (minsofday, seconds) = secs `divMod` 60 :: (Integer, Integer) - (hours, minutes) = minsofday `divMod` 60 :: (Integer, Integer) +import Time.Compat diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Data/Hourglass/Diff.hs new/hourglass-0.2.10/Data/Hourglass/Diff.hs --- old/hourglass-0.2.9/Data/Hourglass/Diff.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/Data/Hourglass/Diff.hs 2016-02-27 12:23:51.000000000 +0100 @@ -34,7 +34,7 @@ { periodYears :: !Int , periodMonths :: !Int , periodDays :: !Int - } deriving (Read,Eq,Ord,Data,Typeable) + } deriving (Show,Read,Eq,Ord,Data,Typeable) instance NFData Period where rnf (Period y m d) = y `seq` m `seq` d `seq` () @@ -50,7 +50,7 @@ , durationMinutes :: !Minutes -- ^ number of minutes , durationSeconds :: !Seconds -- ^ number of seconds , durationNs :: !NanoSeconds -- ^ number of nanoseconds - } deriving (Read,Eq,Ord,Data,Typeable) + } deriving (Show,Read,Eq,Ord,Data,Typeable) instance NFData Duration where rnf (Duration h m s ns) = h `seq` m `seq` s `seq` ns `seq` () @@ -86,10 +86,16 @@ where (yDiffAcc,mStartPos) = (fromEnum mOrig + mDiff) `divMod` 12 loop y m d - | d < dMonth = Date y (toEnum m) d + | d <= 0 = + let (m', y') = if m == 0 + then (11, y - 1) + else (m - 1, y) + in + loop y' m' (daysInMonth y' (toEnum m') + d) + | d <= dMonth = Date y (toEnum m) d | otherwise = let newDiff = d - dMonth - in if m == 12 + in if m == 11 then loop (y+1) 0 newDiff else loop y (m+1) newDiff where dMonth = daysInMonth y (toEnum m) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Data/Hourglass/Internal/Win.hs new/hourglass-0.2.10/Data/Hourglass/Internal/Win.hs --- old/hourglass-0.2.9/Data/Hourglass/Internal/Win.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/Data/Hourglass/Internal/Win.hs 2016-02-27 12:23:51.000000000 +0100 @@ -61,9 +61,16 @@ systemGetTimezone :: IO TimezoneOffset systemGetTimezone = do - (_,tzInfo) <- getTimeZoneInformation - return $ TimezoneOffset $ getTzOffset tzInfo - where getTzOffset tzInfo = fromIntegral (tziBias tzInfo - tziDaylightBias tzInfo) + (tzMode,tzInfo) <- getTimeZoneInformation + case tzMode of + TzIdDaylight -> return $ toTO (tziBias tzInfo + tziDaylightBias tzInfo) + TzIdStandard -> return $ toTO (tziBias tzInfo + tziStandardBias tzInfo) + TzIdUnknown -> return $ toTO (tziBias tzInfo) + where + -- a negative value represent value how to go from local to UTC, + -- whereas TimezoneOffset represent the offset to go from UTC to local. + -- here we negate the bias to get the proper value represented. + toTO = TimezoneOffset . fromIntegral . negate systemGetElapsedP :: IO ElapsedP systemGetElapsedP = toElapsedP `fmap` getSystemTimeAsFileTime diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Data/Hourglass/Types.hs new/hourglass-0.2.10/Data/Hourglass/Types.hs --- old/hourglass-0.2.9/Data/Hourglass/Types.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/Data/Hourglass/Types.hs 2016-02-27 12:23:51.000000000 +0100 @@ -14,226 +14,10 @@ -- Most units use the unix epoch referential, but by no means reduce portability. -- the unix referential works under the Windows platform or any other platforms. -- +-- This module will be depreciated in favor of Time.Types +-- module Data.Hourglass.Types - ( - -- * Time units - NanoSeconds(..) - , Seconds(..) - , Minutes(..) - , Hours(..) - , TimeInterval(..) - -- * Time enumeration - , Month(..) - , WeekDay(..) - -- * Timezone - , TimezoneOffset(..) - , timezoneOffsetToSeconds - , timezone_UTC - -- * Computer friendly format - -- ** Unix elapsed - , Elapsed(..) - , ElapsedP(..) - -- * Human friendly format - -- ** Calendar time - , Date(..) - , TimeOfDay(..) - , DateTime(..) + ( module Time.Types ) where -import Data.Int -import Data.Data -import Data.Ratio -import Control.DeepSeq -import Data.Hourglass.Utils (pad2) - --- | Represent any time interval that has an --- equivalent value to a number of seconds. -class TimeInterval i where - toSeconds :: i -> Seconds - fromSeconds :: Seconds -> (i, Seconds) - --- | Nanoseconds -newtype NanoSeconds = NanoSeconds Int64 - deriving (Read,Eq,Ord,Num,Data,Typeable,NFData) - -instance Show NanoSeconds where - show (NanoSeconds v) = shows v "ns" - -instance TimeInterval NanoSeconds where - toSeconds (NanoSeconds ns) = Seconds (ns `div` 1000000000) - fromSeconds (Seconds s) = (NanoSeconds (s * 1000000000), 0) - --- | Number of seconds without a referential. --- --- Can hold a number between [-2^63,2^63-1], which should --- be good for some billions of years. --- --- However, because of limitation in the calendar conversion --- currently used, seconds should be in the range [-2^55,2^55-1], --- which is good for only 1 billion of year. -newtype Seconds = Seconds Int64 - deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) - -instance Show Seconds where - show (Seconds s) = shows s "s" - -instance TimeInterval Seconds where - toSeconds = id - fromSeconds s = (s,0) - --- | Number of minutes without a referential. -newtype Minutes = Minutes Int64 - deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) - -instance Show Minutes where - show (Minutes s) = shows s "m" - -instance TimeInterval Minutes where - toSeconds (Minutes m) = Seconds (m * 60) - fromSeconds (Seconds s) = (Minutes m, Seconds s') - where (m, s') = s `divMod` 60 - --- | Number of hours without a referential. -newtype Hours = Hours Int64 - deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) - -instance Show Hours where - show (Hours s) = shows s "h" - -instance TimeInterval Hours where - toSeconds (Hours h) = Seconds (h * 3600) - fromSeconds (Seconds s) = (Hours h, Seconds s') - where (h, s') = s `divMod` 3600 - --- | A number of seconds elapsed since the unix epoch. -newtype Elapsed = Elapsed Seconds - deriving (Read,Eq,Ord,Num,Data,Typeable,NFData) - -instance Show Elapsed where - show (Elapsed s) = show s - --- | A number of seconds and nanoseconds elapsed since the unix epoch. -data ElapsedP = ElapsedP {-# UNPACK #-} !Elapsed {-# UNPACK #-} !NanoSeconds - deriving (Read,Eq,Ord,Data,Typeable) - -instance Show ElapsedP where - show (ElapsedP e ns) = shows e ('.' : show ns) - -instance NFData ElapsedP where rnf e = e `seq` () - -instance Num ElapsedP where - (+) = addElapsedP - (-) = subElapsedP - (ElapsedP e1 ns1) * (ElapsedP e2 ns2) = ElapsedP (e1*e2) (ns1*ns2) - negate (ElapsedP e ns) = ElapsedP (negate e) ns - abs (ElapsedP e ns) = ElapsedP (abs e) ns - signum (ElapsedP e ns) = ElapsedP (signum e) ns - fromInteger i = ElapsedP (Elapsed (fromIntegral i)) 0 - -addElapsedP :: ElapsedP -> ElapsedP -> ElapsedP -addElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) = - let notNormalizedNS = ns1 + ns2 - (retainedNS, ns) = notNormalizedNS `divMod` 1000000000 - in ElapsedP (e1 + e2 + (Elapsed $ Seconds retainedNS)) (NanoSeconds ns) - -subElapsedP :: ElapsedP -> ElapsedP -> ElapsedP -subElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) = - let notNormalizedNS = ns1 - ns2 - notNormalizedS = e1 - e2 - in if notNormalizedNS < 0 - then ElapsedP (notNormalizedS - oneSecond) (NanoSeconds (1000000000 + notNormalizedNS)) - else ElapsedP notNormalizedS (NanoSeconds notNormalizedNS) - where - oneSecond :: Elapsed - oneSecond = Elapsed $ Seconds 1 - -instance Real ElapsedP where - -- FIXME - toRational (ElapsedP (Elapsed (Seconds s)) (NanoSeconds ns)) = - fromIntegral s + (1000000000 % fromIntegral ns) - --- | Month of the year -data Month = - January - | February - | March - | April - | May - | June - | July - | August - | September - | October - | November - | December - deriving (Show,Eq,Ord,Enum,Data,Typeable) - --- | Day of the week --- --- the enumeration starts on Sunday. -data WeekDay = - Sunday - | Monday - | Tuesday - | Wednesday - | Thursday - | Friday - | Saturday - deriving (Show,Read,Eq,Ord,Enum,Data,Typeable) - --- | Offset against UTC in minutes --- --- * a positive number represent a location East of UTC. --- --- * a negative number represent a location West of UTC. --- --- LocalTime t (-300) = t represent a time at UTC-5 --- LocalTime t (+480) = t represent a time at UTC+8 --- --- should be between -11H and +14H -newtype TimezoneOffset = TimezoneOffset - { timezoneOffsetToMinutes :: Int -- ^ return the number of minutes - } deriving (Eq,Ord,Data,Typeable,NFData) - --- | Return the number of seconds associated with a timezone -timezoneOffsetToSeconds :: TimezoneOffset -> Seconds -timezoneOffsetToSeconds (TimezoneOffset ofs) = Seconds (fromIntegral ofs * 60) - -instance Show TimezoneOffset where - show (TimezoneOffset tz) = - concat [if tz < 0 then "-" else "+", pad2 tzH, pad2 tzM] - where (tzH, tzM) = abs tz `divMod` 60 - --- | The UTC timezone. offset of 0 -timezone_UTC :: TimezoneOffset -timezone_UTC = TimezoneOffset 0 - --- | human date representation using common calendar -data Date = Date - { dateYear :: {-# UNPACK #-} !Int -- ^ year (Common Era) - , dateMonth :: !Month -- ^ month of the year - , dateDay :: {-# UNPACK #-} !Int -- ^ day of the month, between 1 to 31 - } deriving (Show,Eq,Ord,Data,Typeable) - -instance NFData Date where - rnf (Date y m d) = y `seq` m `seq` d `seq` () - --- | human time representation of hour, minutes, seconds in a day. -data TimeOfDay = TimeOfDay - { todHour :: {-# UNPACK #-} !Hours -- ^ hours, between 0 and 23 - , todMin :: {-# UNPACK #-} !Minutes -- ^ minutes, between 0 and 59 - , todSec :: {-# UNPACK #-} !Seconds -- ^ seconds, between 0 and 59. 60 when having leap second */ - , todNSec :: {-# UNPACK #-} !NanoSeconds -- ^ nanoseconds, between 0 and 999999999 */ - } deriving (Show,Eq,Ord,Data,Typeable) - -instance NFData TimeOfDay where - rnf (TimeOfDay h m s ns) = h `seq` m `seq` s `seq` ns `seq` () - --- | Date and Time -data DateTime = DateTime - { dtDate :: Date - , dtTime :: TimeOfDay - } deriving (Show,Eq,Ord,Data,Typeable) - -instance NFData DateTime where - rnf (DateTime d t) = rnf d `seq` rnf t `seq` () +import Time.Types diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Data/Hourglass.hs new/hourglass-0.2.10/Data/Hourglass.hs --- old/hourglass-0.2.9/Data/Hourglass.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/Data/Hourglass.hs 2016-02-27 12:23:51.000000000 +0100 @@ -37,4 +37,4 @@ import Data.Hourglass.Types import Data.Hourglass.Local import Data.Hourglass.Zone -import Data.Hourglass.Calendar (isLeapYear, getWeekDay, getDayOfTheYear) +import Data.Hourglass.Calendar (isLeapYear, getWeekDay, getDayOfTheYear, daysInMonth) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/System/Hourglass.hs new/hourglass-0.2.10/System/Hourglass.hs --- old/hourglass-0.2.9/System/Hourglass.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/System/Hourglass.hs 2016-02-27 12:23:51.000000000 +0100 @@ -7,52 +7,10 @@ -- -- Get the system timezone and current time value in multiple formats -- +-- This module will be depreciated in favor of Time.System +-- module System.Hourglass - ( - -- * Current time in computer friendly format - timeCurrent - , timeCurrentP - -- * Current time in human friendly DateTime format - , dateCurrent - , localDateCurrent - , localDateCurrentAt - -- * System timezone - , timezoneCurrent + ( module Time.System ) where -import Control.Applicative -import Data.Hourglass.Types -import Data.Hourglass.Time -import Data.Hourglass.Local -import Data.Hourglass.Internal (systemGetElapsedP, systemGetElapsed, systemGetTimezone) - --- | Get the current elapsed seconds since epoch -timeCurrent :: IO Elapsed -timeCurrent = systemGetElapsed - --- | Get the current elapsed seconds (precise to the nanosecond) since epoch -timeCurrentP :: IO ElapsedP -timeCurrentP = systemGetElapsedP - --- | Get the current global date --- --- This is equivalent to: --- --- > timeGetDateTimeOfDay `fmap` timeCurrentP -dateCurrent :: IO DateTime -dateCurrent = timeGetDateTimeOfDay <$> timeCurrentP - --- | Get the localized date by using 'timezoneCurrent' and 'dateCurrent' -localDateCurrent :: IO (LocalTime DateTime) -localDateCurrent = localTimeSetTimezone <$> timezoneCurrent - <*> (localTimeFromGlobal <$> dateCurrent) - --- | Get the localized date at a specific timezone offset. -localDateCurrentAt :: TimezoneOffset -> IO (LocalTime DateTime) -localDateCurrentAt tz = localTimeSetTimezone tz . localTimeFromGlobal <$> dateCurrent - --- | Get the current timezone offset --- --- This include daylight saving time when in operation. -timezoneCurrent :: IO TimezoneOffset -timezoneCurrent = systemGetTimezone +import Time.System diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Time/Compat.hs new/hourglass-0.2.10/Time/Compat.hs --- old/hourglass-0.2.9/Time/Compat.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/hourglass-0.2.10/Time/Compat.hs 2016-02-27 12:23:51.000000000 +0100 @@ -0,0 +1,104 @@ +-- | +-- Module : Time.Compat +-- License : BSD-style +-- Maintainer : Nicolas DI PRIMA <nicolas@di-prima.fr> +-- +-- Basic Time conversion compatibility. +-- +-- This module aims to help conversion between the types from the package +-- time to the package hourglass. +-- +-- Example of use (extracted from file Example/Time/Compat.hs): +-- +-- > import Data.Hourglass as H +-- > import Data.Hourglass.Compat as C +-- > import Data.Time as T +-- > +-- > transpose :: T.ZonedTime +-- > -> H.LocalTime H.DateTime +-- > transpose oldTime = +-- > H.localTime +-- > offsetTime +-- > (H.DateTime newDate timeofday) +-- > where +-- > newDate :: H.Date +-- > newDate = C.dateFromTAIEpoch $ T.toModifiedJulianDay $ T.localDay $ T.zonedTimeToLocalTime oldTime +-- > +-- > timeofday :: H.TimeOfDay +-- > timeofday = C.diffTimeToTimeOfDay $ T.timeOfDayToTime $ T.localTimeOfDay $ T.zonedTimeToLocalTime oldTime +-- > +-- > offsetTime = H.TimezoneOffset $ fromIntegral $ T.timeZoneMinutes $ T.zonedTimeZone oldTime +-- +module Time.Compat + ( dateFromPOSIXEpoch + , dateFromTAIEpoch + , diffTimeToTimeOfDay + ) where + +import Data.Hourglass + +-- | Convert an integer which represent the Number of days (To/From) POSIX Epoch +-- to a Date (POSIX Epoch is 1970-01-01). +dateFromPOSIXEpoch :: Integer -- ^ number of days since POSIX Epoch + -> Date +dateFromPOSIXEpoch day = do + let sec = Elapsed $ fromIntegral $ day * 86400 + timeConvert sec + +-- | Number of days between POSIX Epoch and TAI Epoch +-- (between 1858-11-17 and 1970-01-01) +daysTAItoPOSIX :: Integer +daysTAItoPOSIX = 40587 + +-- | Convert an integer which represents the Number of days (To/From) TAI Epoch +-- This function allows use of the package time to easily convert the Day into +-- the Hourglass Date representation (TAI Epoch is 1858-11-17). +-- +-- This function allows user to easily convert a Data.Time.Calendar.Day into Date +-- +-- > import qualified Data.Time.Calendar as T +-- > +-- > timeDay :: T.Day +-- > +-- > dateFromTAIEpoch $ T.toModifiedJulianDay timeDay +dateFromTAIEpoch :: Integer -- ^ number of days since TAI Epoch + -> Date +dateFromTAIEpoch dtai = + dateFromPOSIXEpoch (dtai - daysTAItoPOSIX) + +-- | Convert of differential of time of a day. +-- (it convers a Data.Time.Clock.DiffTime into a TimeOfDay) +-- +-- Example with DiffTime type from time: +-- +-- > import qualified Data.Time.Clock as T +-- > +-- > difftime :: T.DiffTime +-- > +-- > diffTimeToTimeOfDay difftime +-- +-- Example with the TimeOfDay type from time: +-- +-- > import qualified Data.Time.Clock as T +-- > +-- > timeofday :: T.TimeOfDay +-- > +-- > diffTimeToTimeOfDay $ T.timeOfDayToTime timeofday +diffTimeToTimeOfDay :: Real t + => t -- ^ number of seconds of the time of the day + -> TimeOfDay +diffTimeToTimeOfDay dt = do + TimeOfDay + { todHour = fromIntegral hours + , todMin = fromIntegral minutes + , todSec = fromIntegral seconds + , todNSec = fromIntegral nsecs + } + where + r :: Rational + r = toRational dt + (secs, nR) = properFraction r :: (Integer, Rational) + nsecs :: Integer + nsecs = round (nR * 1000000000) + (minsofday, seconds) = secs `divMod` 60 :: (Integer, Integer) + (hours, minutes) = minsofday `divMod` 60 :: (Integer, Integer) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Time/System.hs new/hourglass-0.2.10/Time/System.hs --- old/hourglass-0.2.9/Time/System.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/hourglass-0.2.10/Time/System.hs 2016-02-27 12:23:51.000000000 +0100 @@ -0,0 +1,58 @@ +-- | +-- Module : Time.System +-- License : BSD-style +-- Maintainer : Vincent Hanquez <vincent@snarc.org> +-- Stability : experimental +-- Portability : unknown +-- +-- Get the system timezone and current time value in multiple formats +-- +module Time.System + ( + -- * Current time in computer friendly format + timeCurrent + , timeCurrentP + -- * Current time in human friendly DateTime format + , dateCurrent + , localDateCurrent + , localDateCurrentAt + -- * System timezone + , timezoneCurrent + ) where + +import Control.Applicative +import Time.Types +import Data.Hourglass.Time +import Data.Hourglass.Local +import Data.Hourglass.Internal (systemGetElapsedP, systemGetElapsed, systemGetTimezone) + +-- | Get the current elapsed seconds since epoch +timeCurrent :: IO Elapsed +timeCurrent = systemGetElapsed + +-- | Get the current elapsed seconds (precise to the nanosecond) since epoch +timeCurrentP :: IO ElapsedP +timeCurrentP = systemGetElapsedP + +-- | Get the current global date +-- +-- This is equivalent to: +-- +-- > timeGetDateTimeOfDay `fmap` timeCurrentP +dateCurrent :: IO DateTime +dateCurrent = timeGetDateTimeOfDay <$> timeCurrentP + +-- | Get the localized date by using 'timezoneCurrent' and 'dateCurrent' +localDateCurrent :: IO (LocalTime DateTime) +localDateCurrent = localTimeSetTimezone <$> timezoneCurrent + <*> (localTimeFromGlobal <$> dateCurrent) + +-- | Get the localized date at a specific timezone offset. +localDateCurrentAt :: TimezoneOffset -> IO (LocalTime DateTime) +localDateCurrentAt tz = localTimeSetTimezone tz . localTimeFromGlobal <$> dateCurrent + +-- | Get the current timezone offset +-- +-- This include daylight saving time when in operation. +timezoneCurrent :: IO TimezoneOffset +timezoneCurrent = systemGetTimezone diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/Time/Types.hs new/hourglass-0.2.10/Time/Types.hs --- old/hourglass-0.2.9/Time/Types.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/hourglass-0.2.10/Time/Types.hs 2016-02-27 12:23:51.000000000 +0100 @@ -0,0 +1,244 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveDataTypeable #-} +-- | +-- Module : Time.Types +-- License : BSD-style +-- Maintainer : Vincent Hanquez <vincent@snarc.org> +-- +-- Basic times units and types. +-- +-- While pratically some units could hold infinite values, for practical +-- and efficient purpose they are limited to int64 types for seconds +-- and int types for years. +-- +-- Most units use the unix epoch referential, but by no means reduce portability. +-- the unix referential works under the Windows platform or any other platforms. +-- +module Time.Types + ( + -- * Time units + NanoSeconds(..) + , Seconds(..) + , Minutes(..) + , Hours(..) + , TimeInterval(..) + -- * Time enumeration + , Month(..) + , WeekDay(..) + -- * Timezone + , TimezoneOffset(..) + , timezoneOffsetToSeconds + , timezone_UTC + -- * Computer friendly format + -- ** Unix elapsed + , Elapsed(..) + , ElapsedP(..) + -- * Human friendly format + -- ** Calendar time + , Date(..) + , TimeOfDay(..) + , DateTime(..) + ) where + +import Data.Int +import Data.Data +import Data.Ratio +import Control.DeepSeq +import Data.Hourglass.Utils (pad2) + +-- | Represent any time interval that has an +-- equivalent value to a number of seconds. +class TimeInterval i where + toSeconds :: i -> Seconds + fromSeconds :: Seconds -> (i, Seconds) + +-- | Nanoseconds +newtype NanoSeconds = NanoSeconds Int64 + deriving (Read,Eq,Ord,Num,Data,Typeable,NFData) + +instance Show NanoSeconds where + show (NanoSeconds v) = shows v "ns" + +instance TimeInterval NanoSeconds where + toSeconds (NanoSeconds ns) = Seconds (ns `div` 1000000000) + fromSeconds (Seconds s) = (NanoSeconds (s * 1000000000), 0) + +-- | Number of seconds without a referential. +-- +-- Can hold a number between [-2^63,2^63-1], which should +-- be good for some billions of years. +-- +-- However, because of limitation in the calendar conversion +-- currently used, seconds should be in the range [-2^55,2^55-1], +-- which is good for only 1 billion of year. +newtype Seconds = Seconds Int64 + deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) + +instance Show Seconds where + show (Seconds s) = shows s "s" + +instance TimeInterval Seconds where + toSeconds = id + fromSeconds s = (s,0) + +-- | Number of minutes without a referential. +newtype Minutes = Minutes Int64 + deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) + +instance Show Minutes where + show (Minutes s) = shows s "m" + +instance TimeInterval Minutes where + toSeconds (Minutes m) = Seconds (m * 60) + fromSeconds (Seconds s) = (Minutes m, Seconds s') + where (m, s') = s `divMod` 60 + +-- | Number of hours without a referential. +newtype Hours = Hours Int64 + deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData) + +instance Show Hours where + show (Hours s) = shows s "h" + +instance TimeInterval Hours where + toSeconds (Hours h) = Seconds (h * 3600) + fromSeconds (Seconds s) = (Hours h, Seconds s') + where (h, s') = s `divMod` 3600 + +-- | A number of seconds elapsed since the unix epoch. +newtype Elapsed = Elapsed Seconds + deriving (Read,Eq,Ord,Num,Data,Typeable,NFData) + +instance Show Elapsed where + show (Elapsed s) = show s + +-- | A number of seconds and nanoseconds elapsed since the unix epoch. +data ElapsedP = ElapsedP {-# UNPACK #-} !Elapsed {-# UNPACK #-} !NanoSeconds + deriving (Read,Eq,Ord,Data,Typeable) + +instance Show ElapsedP where + show (ElapsedP e ns) = shows e ('.' : show ns) + +instance NFData ElapsedP where rnf e = e `seq` () + +instance Num ElapsedP where + (+) = addElapsedP + (-) = subElapsedP + (ElapsedP e1 ns1) * (ElapsedP e2 ns2) = ElapsedP (e1*e2) (ns1*ns2) + negate (ElapsedP e ns) = ElapsedP (negate e) ns + abs (ElapsedP e ns) = ElapsedP (abs e) ns + signum (ElapsedP e ns) = ElapsedP (signum e) ns + fromInteger i = ElapsedP (Elapsed (fromIntegral i)) 0 + +addElapsedP :: ElapsedP -> ElapsedP -> ElapsedP +addElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) = + let notNormalizedNS = ns1 + ns2 + (retainedNS, ns) = notNormalizedNS `divMod` 1000000000 + in ElapsedP (e1 + e2 + (Elapsed $ Seconds retainedNS)) (NanoSeconds ns) + +subElapsedP :: ElapsedP -> ElapsedP -> ElapsedP +subElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) = + let notNormalizedNS = ns1 - ns2 + notNormalizedS = e1 - e2 + in if notNormalizedNS < 0 + then ElapsedP (notNormalizedS - oneSecond) (NanoSeconds (1000000000 + notNormalizedNS)) + else ElapsedP notNormalizedS (NanoSeconds notNormalizedNS) + where + oneSecond :: Elapsed + oneSecond = Elapsed $ Seconds 1 + +instance Real ElapsedP where + -- FIXME + toRational (ElapsedP (Elapsed (Seconds s)) (NanoSeconds ns)) = + fromIntegral s + (1000000000 % fromIntegral ns) + +-- | Month of the year +data Month = + January + | February + | March + | April + | May + | June + | July + | August + | September + | October + | November + | December + deriving (Show,Read,Eq,Ord,Enum,Data,Typeable,Bounded) + +-- | Day of the week +-- +-- the enumeration starts on Sunday. +data WeekDay = + Sunday + | Monday + | Tuesday + | Wednesday + | Thursday + | Friday + | Saturday + deriving (Show,Read,Eq,Ord,Enum,Data,Typeable,Bounded) + +-- | Offset against UTC in minutes to obtain from UTC time, local time. +-- +-- * a positive number represent a location East of UTC. +-- +-- * a negative number represent a location West of UTC. +-- +-- LocalTime t (-300) = t represent a time at UTC-5 +-- LocalTime t (+480) = t represent a time at UTC+8 +-- +-- should be between -11H and +14H +-- +-- Example: +-- in AUSEDT (UTC+1000 with daylight = UTC+1100), local time is 15:47; +-- Thus, UTC time is 04:47, and TimezoneOffset is +660 (minutes) +-- +newtype TimezoneOffset = TimezoneOffset + { timezoneOffsetToMinutes :: Int -- ^ return the number of minutes + } deriving (Eq,Ord,Data,Typeable,NFData) + +-- | Return the number of seconds associated with a timezone +timezoneOffsetToSeconds :: TimezoneOffset -> Seconds +timezoneOffsetToSeconds (TimezoneOffset ofs) = Seconds (fromIntegral ofs * 60) + +instance Show TimezoneOffset where + show (TimezoneOffset tz) = + concat [if tz < 0 then "-" else "+", pad2 tzH, pad2 tzM] + where (tzH, tzM) = abs tz `divMod` 60 + +-- | The UTC timezone. offset of 0 +timezone_UTC :: TimezoneOffset +timezone_UTC = TimezoneOffset 0 + +-- | human date representation using common calendar +data Date = Date + { dateYear :: {-# UNPACK #-} !Int -- ^ year (Common Era) + , dateMonth :: !Month -- ^ month of the year + , dateDay :: {-# UNPACK #-} !Int -- ^ day of the month, between 1 to 31 + } deriving (Show,Read,Eq,Ord,Data,Typeable) + +instance NFData Date where + rnf (Date y m d) = y `seq` m `seq` d `seq` () + +-- | human time representation of hour, minutes, seconds in a day. +data TimeOfDay = TimeOfDay + { todHour :: {-# UNPACK #-} !Hours -- ^ hours, between 0 and 23 + , todMin :: {-# UNPACK #-} !Minutes -- ^ minutes, between 0 and 59 + , todSec :: {-# UNPACK #-} !Seconds -- ^ seconds, between 0 and 59. 60 when having leap second */ + , todNSec :: {-# UNPACK #-} !NanoSeconds -- ^ nanoseconds, between 0 and 999999999 */ + } deriving (Show,Read,Eq,Ord,Data,Typeable) + +instance NFData TimeOfDay where + rnf (TimeOfDay h m s ns) = h `seq` m `seq` s `seq` ns `seq` () + +-- | Date and Time +data DateTime = DateTime + { dtDate :: Date + , dtTime :: TimeOfDay + } deriving (Show,Read,Eq,Ord,Data,Typeable) + +instance NFData DateTime where + rnf (DateTime d t) = rnf d `seq` rnf t `seq` () diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/hourglass.cabal new/hourglass-0.2.10/hourglass.cabal --- old/hourglass-0.2.9/hourglass.cabal 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/hourglass.cabal 2016-02-27 12:23:51.000000000 +0100 @@ -1,5 +1,5 @@ Name: hourglass -Version: 0.2.9 +Version: 0.2.10 Synopsis: simple performant time related library Description: Simple time library focusing on simple but powerful and performant API @@ -23,7 +23,10 @@ , tests/TimeDB.hs Library - Exposed-modules: Data.Hourglass + Exposed-modules: Time.Types + , Time.System + , Time.Compat + , Data.Hourglass , Data.Hourglass.Types , Data.Hourglass.Epoch , Data.Hourglass.Compat diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hourglass-0.2.9/tests/Tests.hs new/hourglass-0.2.10/tests/Tests.hs --- old/hourglass-0.2.9/tests/Tests.hs 2015-04-01 16:53:50.000000000 +0200 +++ new/hourglass-0.2.10/tests/Tests.hs 2016-02-27 12:23:51.000000000 +0100 @@ -51,6 +51,15 @@ (h' , mi') = dt' `divMod` 60 (DateTime (Date y m d) (TimeOfDay h mi sec _)) = localTimeToGlobal localtime +-- | The @Date@ type is able to represent some values that aren't actually legal, +-- specifically dates with a day field outside of the range of dates in the +-- month. This function validates a @Date@. It is conservative; it only verifies +-- that the day is less than 31. TODO: It would be nice to tighten this up a +-- bit. There's a daysInMonth function we could use for this, +-- but Data.Hourglass.Calendar, but it isn't exposed. +isValidDate :: Date -> Bool +isValidDate (Date _ _ d) = d > 0 && d <= 31 + -- windows native functions to convert time cannot handle time before year 1601 #ifdef WINDOWS loElapsed = -11644473600 -- ~ year 1601 @@ -183,6 +192,8 @@ (toEnum ((fromEnum m+1) `mod` 12) `eq` m') && (if m == December then (y+1) `eq` y' else y `eq` y') -} + , testProperty "dateAddPeriod" $ (\date period -> + isValidDate (date `dateAddPeriod` period)) ] , testGroup "formating" [ testProperty "iso8601 date" $ \(e :: Elapsed) ->
participants (1)
-
root@hilbert.suse.de