[commit: packages/time] master,wip/travis: use realToFrac (dfadfd1)
git at git.haskell.org
git at git.haskell.org
Sat May 7 06:39:50 UTC 2016
Repository : ssh://git@git.haskell.org/time
On branches: master,wip/travis
Link : http://git.haskell.org/packages/time.git/commitdiff/dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2
>---------------------------------------------------------------
commit dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2
Author: Ashley Yakeley <ashley at semantic.org>
Date: Sun Mar 20 22:31:44 2005 -0800
use realToFrac
darcs-hash:20050321063144-ac6dd-a67fc28e4d4dfcabaf93e5863c79e8697254d5e5
>---------------------------------------------------------------
dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2
Data/Fixed.hs | 6 +-----
System/Time/Calendar.hs | 12 ++++++------
System/Time/Clock.hs | 8 ++++----
System/Time/TAI.hs | 5 ++---
4 files changed, 13 insertions(+), 18 deletions(-)
diff --git a/Data/Fixed.hs b/Data/Fixed.hs
index 7e90374..971a39b 100644
--- a/Data/Fixed.hs
+++ b/Data/Fixed.hs
@@ -2,7 +2,7 @@
module Data.Fixed
(
- fromReal,div',mod',divMod',
+ div',mod',divMod',
Fixed,HasResolution(..),
showFixed,
@@ -10,10 +10,6 @@ module Data.Fixed
E12,Pico
) where
--- | similar idea to "fromIntegral"
-fromReal :: (Real a,Fractional b) => a -> b
-fromReal = fromRational . toRational
-
-- | like "div", but with a more useful type
div' :: (Real a,Integral b) => a -> a -> b
div' n d = floor ((toRational n) / (toRational d))
diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs
index 9c434f6..5cc646a 100644
--- a/System/Time/Calendar.hs
+++ b/System/Time/Calendar.hs
@@ -127,7 +127,7 @@ calendarToDay (CalendarDay year month day) =
-- | convert a ToD in UTC to a ToD in some timezone, together with a day adjustment
utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay)
-utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 60) (mod m' 60) s) where
+utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where
m' = m + tz
h' = h + (div m' 60)
@@ -141,9 +141,9 @@ posixDay = fromInteger 86400
-- | get a TimeOfDay given a time since midnight
-- | time more than 24h will be converted to leap-seconds
timeToTimeOfDay :: DiffTime -> TimeOfDay
-timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + (fromReal (dt - posixDay)))
+timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + (realToFrac (dt - posixDay)))
timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) s where
- s' = fromReal dt
+ s' = realToFrac dt
s = mod' s' 60
m' = div' s' 60
m = mod' m' 60
@@ -151,7 +151,7 @@ timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) s where
-- | find out how much time since midnight a given TimeOfDay is
timeOfDayToTime :: TimeOfDay -> DiffTime
-timeOfDayToTime (TimeOfDay h m s) = ((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (fromReal s)
+timeOfDayToTime (TimeOfDay h m s) = ((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (realToFrac s)
-- | show a UTC time in a given time zone as a CalendarTime
utcToCalendar :: TimeZone -> UTCTime -> CalendarTime
@@ -166,7 +166,7 @@ calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime to
-- | get a TimeOfDay given the fraction of a day since midnight
dayFractionToTimeOfDay :: Rational -> TimeOfDay
-dayFractionToTimeOfDay df = timeToTimeOfDay (fromReal (df * 86400))
+dayFractionToTimeOfDay df = timeToTimeOfDay (realToFrac (df * 86400))
-- | 1st arg is observation meridian in degrees, positive is East
ut1ToCalendar :: Rational -> ModJulianDate -> CalendarTime
@@ -177,7 +177,7 @@ ut1ToCalendar long date = CalendarTime (dayToCalendar localDay) (dayFractionToTi
-- | get the fraction of a day since midnight given a TimeOfDay
timeOfDayToDayFraction :: TimeOfDay -> Rational
-timeOfDayToDayFraction tod = fromReal (timeOfDayToTime tod / posixDay)
+timeOfDayToDayFraction tod = realToFrac (timeOfDayToTime tod / posixDay)
-- | 1st arg is observation meridian in degrees, positive is East
calendarToUT1 :: Rational -> CalendarTime -> ModJulianDate
diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs
index 73b9bf3..c13fb61 100644
--- a/System/Time/Clock.hs
+++ b/System/Time/Clock.hs
@@ -97,18 +97,18 @@ unixEpochMJD = 40587
posixSecondsToUTCTime :: Pico -> UTCTime
posixSecondsToUTCTime i = let
(d,t) = divMod' i posixDaySeconds
- in UTCTime (d + unixEpochMJD) (fromReal t)
+ in UTCTime (d + unixEpochMJD) (realToFrac t)
utcTimeToPOSIXSeconds :: UTCTime -> Pico
utcTimeToPOSIXSeconds (UTCTime d t) =
- (fromInteger (d - unixEpochMJD) * posixDaySeconds) + min posixDaySeconds (fromReal t)
+ (fromInteger (d - unixEpochMJD) * posixDaySeconds) + min posixDaySeconds (realToFrac t)
addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime
-addUTCTime x t = posixSecondsToUTCTime ((fromReal x) + (utcTimeToPOSIXSeconds t))
+addUTCTime x t = posixSecondsToUTCTime ((realToFrac x) + (utcTimeToPOSIXSeconds t))
diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime
-diffUTCTime a b = fromReal ((utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b))
+diffUTCTime a b = realToFrac ((utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b))
-- Get current time
diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs
index b21daa6..8cd7315 100644
--- a/System/Time/TAI.hs
+++ b/System/Time/TAI.hs
@@ -14,7 +14,6 @@ module System.Time.TAI
) where
import System.Time.Clock
-import Data.Fixed
-- | TAI as DiffTime from epoch
newtype AbsoluteTime = MkAbsoluteTime DiffTime deriving (Eq,Ord)
@@ -29,11 +28,11 @@ diffAbsoluteTime (MkAbsoluteTime a) (MkAbsoluteTime b) = a - b
type LeapSecondTable = ModJulianDay -> Integer
utcDayLength :: LeapSecondTable -> ModJulianDay -> DiffTime
-utcDayLength table day = fromReal (86400 + (table (day + 1)) - (table day))
+utcDayLength table day = realToFrac (86400 + (table (day + 1)) - (table day))
utcToTAITime :: LeapSecondTable -> UTCTime -> AbsoluteTime
utcToTAITime table (UTCTime day dtime) = MkAbsoluteTime
- ((fromReal (day * 86400 + (table day))) + dtime)
+ ((realToFrac (day * 86400 + (table day))) + dtime)
taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime
taiToUTCTime table (MkAbsoluteTime t) = undefined table t
More information about the ghc-commits
mailing list