Skip to content

Commit 49948de

Browse files
ondraptmcgilchrist
authored andcommitted
Compatibility tweaks for older GHC versions.
1 parent be5ca29 commit 49948de

File tree

7 files changed

+33
-12
lines changed

7 files changed

+33
-12
lines changed

src/Data/Thyme/Calendar/WeekDate.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
{-# LANGUAGE ViewPatterns #-}
44
{-# OPTIONS_GHC -fno-warn-orphans #-}
55
#if __GLASGOW_HASKELL__ == 706
6-
{-# OPTIONS_GHC -fsimpl-tick-factor=120 #-} -- 7.6.3 only, it seems; fixes #29
6+
{-# OPTIONS_GHC -fsimpl-tick-factor=180 #-} -- 7.6.3 only, it seems; fixes #29
77
#endif
88

99
#include "thyme.h"
@@ -120,4 +120,3 @@ fromWeekDate y w d = weekDate # WeekDate y w d
120120
{-# INLINE fromWeekDateValid #-}
121121
fromWeekDateValid :: Year -> WeekOfYear -> DayOfWeek -> Maybe Day
122122
fromWeekDateValid y w d = weekDateValid (WeekDate y w d)
123-

src/Data/Thyme/Clock/TAI.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,9 @@ module Data.Thyme.Clock.TAI
4040
import Prelude
4141
#if !MIN_VERSION_base(4,8,0)
4242
import Control.Applicative
43+
import Data.Monoid (mempty)
4344
#endif
45+
4446
import Control.DeepSeq
4547
import Control.Lens
4648
import Control.Monad
@@ -353,5 +355,4 @@ utcToTAITime m = view (absoluteTime m)
353355
-- @
354356
{-# INLINE taiToUTCTime #-}
355357
taiToUTCTime :: TAIUTCMap -> AbsoluteTime -> UTCTime
356-
taiToUTCTime m = review (absoluteTime m)
357-
358+
taiToUTCTime m = review (absoluteTime m)

src/Data/Thyme/Format.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,9 @@ import Control.Applicative
3131
#if SHOW_INTERNAL
3232
import Control.Arrow
3333
#endif
34+
#if !MIN_VERSION_base(4,8,0)
35+
import Data.Monoid (mempty)
36+
#endif
3437
import Control.Lens
3538
import Control.Monad.Trans
3639
import Control.Monad.State.Strict
@@ -986,4 +989,3 @@ timeZoneParser = zone "TAI" 0 False <|> zone "UT1" 0 False
986989
zone name offset dst = TimeZone offset dst name <$ P.string (S.pack name)
987990
($+) h m = h * 60 + m
988991
($-) h m = negate (h * 60 + m)
989-

src/Data/Thyme/Format/Aeson.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -99,11 +99,14 @@ instance FromJSON ZonedTime where
9999
parseJSON v = typeMismatch "ZonedTime" v
100100

101101
instance ToJSON UTCTime where
102+
#if MIN_VERSION_aeson(0,11,2)
102103
toEncoding t = unsafeToEncoding $ quote (utcTimeBuilder t)
103104
{-# INLINE toEncoding #-}
105+
#endif
104106
toJSON t = String $ decodeUtf8 $ toStrict $ toLazyByteString (utcTimeBuilder t)
105107
{-# INLINE toJSON #-}
106108

109+
-- For some unexaplainable reason the fast Scanner parser doesn't seem to work on 7.6
107110
instance FromJSON UTCTime where
108111
parseJSON = withText "UTCTime" $ parseFastUtc
109112
{-# INLINE parseJSON #-}

src/Data/Thyme/Format/DateFast.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# OPTIONS_HADDOCK hide #-}
@@ -6,6 +7,9 @@ module Data.Thyme.Format.DateFast (
67
parseFastUtc
78
) where
89

10+
#if !MIN_VERSION_base(4,8,0)
11+
import Control.Applicative
12+
#endif
913
import Control.Lens (from, view)
1014
import Control.Monad (unless, void)
1115
import qualified Data.ByteString as BS
@@ -105,10 +109,10 @@ parserRfc = do
105109
- offset * 1000000 :: Int64
106110
tdiff = view (from microseconds) totalMicro
107111
tday = fromGregorian year month dayofmonth
108-
return $ UTCTime tday tdiff
112+
return $ view (from utcTime) (UTCView tday tdiff)
109113

110114
parseFastUtc :: Monad m => T.Text -> m UTCTime
111115
parseFastUtc t =
112116
case S.scanOnly parserRfc (encodeUtf8 t) of
113-
Right d -> pure d
117+
Right d -> return d
114118
Left err -> fail $ "could not parse ISO-8601 date: " ++ err

tests/sanity.hs

Lines changed: 16 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,9 @@
77

88
import Prelude
99

10+
#if !MIN_VERSION_base(4,8,0)
11+
import Control.Applicative
12+
#endif
1013
import Control.Arrow
1114
import Control.Lens
1215
import qualified Data.Attoparsec.ByteString.Char8 as P
@@ -51,16 +54,24 @@ prop_toOrdinalDate :: Day -> Bool
5154
prop_toOrdinalDate day =
5255
fromIntegral `first` toOrdinalDate day == T.toOrdinalDate (thyme # day)
5356

54-
newtype AcUTCTime = AcUTCTime { getAc :: UTCTime } deriving (Show)
57+
newtype AcUTCTime = AcUTCTime UTCTime deriving (Show)
5558
instance Arbitrary AcUTCTime where
5659
arbitrary = AcUTCTime <$> (arbitrary `suchThat` (\d -> d >= year1 && d < yearMax))
5760
where
58-
year1 = UTCTime (fromGregorian 1 1 1) 0
59-
yearMax = UTCTime (fromGregorian 10000 1 1) 0
61+
year1 = view (from utcTime) $ UTCView (fromGregorian 1 1 1) 0
62+
yearMax = view (from utcTime) $ UTCView (fromGregorian 10000 1 1) 0
6063
shrink (AcUTCTime a) = map AcUTCTime (shrink a)
6164

62-
prop_aeson :: AcUTCTime -> Bool
63-
prop_aeson a = AE.decode (AE.encode (getAc a)) == Just (getAc a)
65+
prop_aeson :: AcUTCTime -> Property
66+
prop_aeson (AcUTCTime t') =
67+
#if MIN_VERSION_QuickCheck(2,7,0)
68+
counterexample desc (t == Just [t'])
69+
#else
70+
printTestCase desc (t == Just [t'])
71+
#endif
72+
where
73+
t = AE.decode (AE.encode [t'])
74+
desc = "Orig: " ++ show t' ++ ", Aeson: " ++ show (AE.encode t') ++ ", BackOrig: " ++ show t
6475

6576
prop_formatTime :: Spec -> RecentTime -> Property
6677
prop_formatTime (Spec spec) (RecentTime t@(review thyme -> t'))

thyme.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -91,6 +91,7 @@ library
9191
aeson >= 0.6,
9292
base >= 4.5 && < 5,
9393
bytestring >= 0.9,
94+
bytestring-builder,
9495
containers >= 0.5,
9596
deepseq >= 1.2,
9697
hashable >= 1.2,

0 commit comments

Comments
 (0)