88--
99------------------------------------------------------------------------------
1010
11- {-# LANGUAGE DeriveDataTypeable, DeriveFunctor #-}
11+ {-# LANGUAGE DeriveDataTypeable, DeriveFunctor, CPP #-}
1212
1313module Database.PostgreSQL.Simple.Time.Implementation where
1414
@@ -27,8 +27,28 @@ import qualified Data.Attoparsec.ByteString.Char8 as A
2727import Database.PostgreSQL.Simple.Compat ((<>) )
2828import Data.Monoid (Monoid (.. ))
2929import Data.Fixed (Pico )
30+ #if !MIN_VERSION_base(4,7,0)
31+ -- A kludge to work around the fact that Data.Fixed isn't very fast and
32+ -- previously didn't give me access to the MkFixed constructor.
33+
3034import Unsafe.Coerce
3135
36+ mkPico :: Integer -> Pico
37+ mkPico = unsafeCoerce
38+
39+ fromPico :: Pico -> Integer
40+ fromPico = unsafeCoerce
41+ #else
42+ import Data.Fixed (Fixed (MkPico ))
43+
44+ mkPico :: Integer -> Pico
45+ mkPico = MkFixed
46+
47+ fromPico :: Pico -> Integer
48+ fromPico (MkFixed x) = x
49+ #endif
50+
51+
3252data Unbounded a
3353 = NegInfinity
3454 | Finite ! a
@@ -124,9 +144,8 @@ getTimeOfDay = do
124144 decimal secs = do
125145 _ <- A. satisfy (\ c -> c == ' .' || c == ' ,' )
126146 digits <- B. take 12 <$> A. takeWhile1 A. isDigit
127- -- A kludge to work around the fact that Data.Fixed isn't very fast and
128- -- doesn't give me access to the MkFixed constructor.
129- return $! unsafeCoerce (toNum_ secs digits * 10 ^ (12 - B. length digits))
147+
148+ return $! mkPico (toNum_ secs digits * 10 ^ (12 - B. length digits))
130149
131150getLocalTime :: A. Parser LocalTime
132151getLocalTime = LocalTime <$> getDay <*> (todSeparator *> getTimeOfDay)
@@ -274,10 +293,8 @@ nominalDiffTimeToBuilder xyz
274293 | yz < 500000 = sign <> integerDec x
275294 | otherwise = sign <> integerDec x <> char8 ' .' <> showD6 y
276295 where
277- -- A kludge to work around the fact that Data.Fixed isn't very fast and
278- -- doesn't give me access to the MkFixed constructor.
279296 sign = if xyz >= 0 then mempty else char8 ' -'
280- (x,yz) = ((unsafeCoerce (abs xyz) :: Integer ) + 500000 ) `quotRem` 1000000000000
297+ (x,yz) = (fromPico (abs xyz) + 500000 ) `quotRem` 1000000000000
281298 (fromIntegral -> y, _z) = yz `quotRem` 1000000
282299
283300showSeconds :: Pico -> Builder
@@ -288,7 +305,7 @@ showSeconds xyz
288305 where
289306 -- A kludge to work around the fact that Data.Fixed isn't very fast and
290307 -- doesn't give me access to the MkFixed constructor.
291- (x_,yz) = (unsafeCoerce xyz :: Integer ) `quotRem` 1000000000000
308+ (x_,yz) = fromPico xyz `quotRem` 1000000000000
292309 x = fromIntegral x_ :: Int
293310 (fromIntegral -> y, fromIntegral -> z) = yz `quotRem` 1000000
294311
0 commit comments