Skip to content

Commit 988d3ee

Browse files
committed
cleaning up cpp needs
Signed-off-by: buckie <[email protected]>
1 parent eb9c1c6 commit 988d3ee

File tree

7 files changed

+25
-31
lines changed

7 files changed

+25
-31
lines changed

include/thyme.h

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1 @@
1-
#define INSTANCES_USUAL Eq, Ord, Data, Typeable, Generic
2-
#define INSTANCES_NEWTYPE INSTANCES_USUAL, Enum, Ix, Hashable, NFData
3-
#define INSTANCES_MICRO INSTANCES_NEWTYPE, Bounded, Random, Arbitrary, CoArbitrary
4-
#define LensP Lens'
5-
#define LENS(S,F,A) {-# INLINE _/**/F #-}; _/**/F :: LensP S A; _/**/F = lens F $ \ S {..} F/**/_ -> S {F = F/**/_, ..}
6-
7-
#define W_GREGORIAN <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian>
1+
#define LENS(S,F,A) {-# INLINE _/**/F #-}; _/**/F :: Lens' S A; _/**/F = lens F $ \ S {..} F/**/_ -> S {F = F/**/_, ..}

src/Data/Thyme/Calendar/Internal.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ type Days = Int
5959
-- <https://en.wikipedia.org/wiki/Julian_day#Variants Modified Julian Day>
6060
-- (MJD) epoch.
6161
--
62-
-- To convert a 'Day' to the corresponding 'YearMonthDay' in the W_GREGORIAN
62+
-- To convert a 'Day' to the corresponding 'YearMonthDay' in the <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian>
6363
-- calendar, see 'gregorian'.
6464
--
6565
-- @
@@ -84,7 +84,7 @@ type Days = Int
8484
-- Other ways of viewing a 'Day' include 'ordinalDate', and 'weekDate'.
8585
newtype Day = ModifiedJulianDay
8686
{ toModifiedJulianDay :: Int
87-
} deriving (INSTANCES_NEWTYPE, CoArbitrary)
87+
} deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, CoArbitrary)
8888

8989
instance AffineSpace Day where
9090
type Diff Day = Days
@@ -110,7 +110,7 @@ instance AffineSpace Day where
110110
modifiedJulianDay :: Iso' Day Int
111111
modifiedJulianDay = iso toModifiedJulianDay ModifiedJulianDay
112112

113-
-- | Conversion between a W_GREGORIAN 'OrdinalDate' and the corresponding
113+
-- | Conversion between a <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian> 'OrdinalDate' and the corresponding
114114
-- 'YearMonthDay'.
115115
--
116116
-- @
@@ -204,7 +204,7 @@ data YearMonthDay = YearMonthDay
204204
{ ymdYear :: {-# UNPACK #-}!Year
205205
, ymdMonth :: {-# UNPACK #-}!Month
206206
, ymdDay :: {-# UNPACK #-}!DayOfMonth
207-
} deriving (INSTANCES_USUAL, Show)
207+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
208208

209209
LENS(YearMonthDay,ymdYear,Year)
210210
LENS(YearMonthDay,ymdMonth,Month)
@@ -215,7 +215,7 @@ instance NFData YearMonthDay
215215

216216
------------------------------------------------------------------------
217217

218-
-- | Is it a leap year according to the W_GREGORIAN calendar?
218+
-- | Is it a leap year according to the <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian> calendar?
219219
isLeapYear :: Year -> Bool
220220
isLeapYear y = y .&. 3 == 0 && (r100 /= 0 || q100 .&. 3 == 0) where
221221
(q100, r100) = y `quotRem` 100
@@ -228,7 +228,7 @@ type DayOfYear = Int
228228
data OrdinalDate = OrdinalDate
229229
{ odYear :: {-# UNPACK #-}!Year
230230
, odDay :: {-# UNPACK #-}!DayOfYear
231-
} deriving (INSTANCES_USUAL, Show)
231+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
232232

233233
LENS(OrdinalDate,odYear,Year)
234234
LENS(OrdinalDate,odDay,DayOfYear)
@@ -368,7 +368,7 @@ randomIsoR l (x, y) = first (^. l) . randomR (l # x, l # y)
368368
data MonthDay = MonthDay
369369
{ mdMonth :: {-# UNPACK #-}!Month
370370
, mdDay :: {-# UNPACK #-}!DayOfMonth
371-
} deriving (INSTANCES_USUAL, Show)
371+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
372372

373373
LENS(MonthDay,mdMonth,Month)
374374
LENS(MonthDay,mdDay,DayOfMonth)
@@ -512,7 +512,7 @@ data WeekDate = WeekDate
512512
-- belong to the previous year.
513513
, wdDay :: {-# UNPACK #-}!DayOfWeek
514514
-- ^ /1 = Monday/ … /7 = Sunday/.
515-
} deriving (INSTANCES_USUAL, Show)
515+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
516516

517517
LENS(WeekDate,wdYear,Year)
518518
LENS(WeekDate,wdWeek,WeekOfYear)
@@ -602,7 +602,7 @@ data SundayWeek = SundayWeek
602602
-- /Sunday/ of the year as the first day of week /01/.
603603
, swDay :: {-# UNPACK #-}!DayOfWeek
604604
-- ^ /0 = Sunday/.
605-
} deriving (INSTANCES_USUAL, Show)
605+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
606606

607607
LENS(SundayWeek,swYear,Year)
608608
LENS(SundayWeek,swWeek,WeekOfYear)
@@ -668,7 +668,7 @@ data MondayWeek = MondayWeek
668668
-- /Monday/ of the year as the first day of week /01/.
669669
, mwDay :: {-# UNPACK #-}!DayOfWeek
670670
-- ^ /7 = Sunday/.
671-
} deriving (INSTANCES_USUAL, Show)
671+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
672672

673673
LENS(MondayWeek,mwYear,Year)
674674
LENS(MondayWeek,mwWeek,WeekOfYear)

src/Data/Thyme/Calendar/WeekdayOfMonth.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ data WeekdayOfMonth = WeekdayOfMonth
5252
-- last 'DayOfWeek' of the month.
5353
, womDayOfWeek :: {-# UNPACK #-}!DayOfWeek
5454
-- ^ Day of week. /1 = Monday, 7 = Sunday/, like ISO 8601 'WeekDate'.
55-
} deriving (INSTANCES_USUAL, Show)
55+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
5656

5757
LENS(WeekdayOfMonth,womYear,Year)
5858
LENS(WeekdayOfMonth,womMonth,Month)

src/Data/Thyme/Clock/Internal.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ fromSecondsIntegral _ = review microseconds . (*) 1000000 . fromIntegral
130130
-- > 'fromSeconds'' 100 '^-^' 'fromSeconds'' 100 '^/' 4
131131
-- 75s
132132
-- @
133-
newtype DiffTime = DiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
133+
newtype DiffTime = DiffTime Micro deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary, AdditiveGroup)
134134

135135
derivingUnbox "DiffTime" [t| DiffTime -> Micro |]
136136
[| \ (DiffTime a) -> a |] [| DiffTime |]
@@ -188,7 +188,7 @@ instance TimeDiff DiffTime where
188188
-- @
189189
--
190190
-- See also: 'UTCTime'.
191-
newtype NominalDiffTime = NominalDiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
191+
newtype NominalDiffTime = NominalDiffTime Micro deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary, AdditiveGroup)
192192

193193
derivingUnbox "NominalDiffTime" [t| NominalDiffTime -> Micro |]
194194
[| \ (NominalDiffTime a) -> a |] [| NominalDiffTime |]
@@ -239,7 +239,7 @@ posixDayLength = microseconds # 86400000000
239239
--
240240
-- The difference between UT1 and UTC is
241241
-- <http://en.wikipedia.org/wiki/DUT1 DUT1>.
242-
newtype UniversalTime = UniversalRep NominalDiffTime deriving (INSTANCES_MICRO)
242+
newtype UniversalTime = UniversalRep NominalDiffTime deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary)
243243

244244
derivingUnbox "UniversalTime" [t| UniversalTime -> NominalDiffTime |]
245245
[| \ (UniversalRep a) -> a |] [| UniversalRep |]
@@ -313,7 +313,7 @@ pattern UniversalTime mjd <- (view modJulianDate -> mjd)
313313
-- If leap seconds matter, use 'Data.Thyme.Clock.TAI.AbsoluteTime' from
314314
-- "Data.Thyme.Clock.TAI" instead, along with
315315
-- 'Data.Thyme.Clock.TAI.absoluteTime'' and 'UTCView' for presentation.
316-
newtype UTCTime = UTCRep NominalDiffTime deriving (INSTANCES_MICRO)
316+
newtype UTCTime = UTCRep NominalDiffTime deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary)
317317

318318
derivingUnbox "UTCTime" [t| UTCTime -> NominalDiffTime |]
319319
[| \ (UTCRep a) -> a |] [| UTCRep |]
@@ -326,7 +326,7 @@ data UTCView = UTCView
326326
-- ^ Calendar date.
327327
, utcvDayTime :: {-# UNPACK #-}!DiffTime
328328
-- ^ Time elapsed since midnight; /0/ ≤ 'utcvDayTime' < /86401s/.
329-
} deriving (INSTANCES_USUAL, Show)
329+
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
330330

331331
-- | 'Lens'' for the calendar 'Day' component of a 'UTCView'.
332332
LENS(UTCView,utcvDay,Day)

src/Data/Thyme/Clock/TAI.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ import Test.QuickCheck
7474
--
7575
-- Internally this is the number of seconds since 'taiEpoch'. TAI days are
7676
-- exactly 86400 SI seconds long.
77-
newtype AbsoluteTime = AbsoluteTime DiffTime deriving (INSTANCES_MICRO)
77+
newtype AbsoluteTime = AbsoluteTime DiffTime deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary)
7878

7979
derivingUnbox "AbsoluteTime" [t| AbsoluteTime -> DiffTime |]
8080
[| \ (AbsoluteTime a) -> a |] [| AbsoluteTime |]
@@ -107,7 +107,7 @@ instance AffineSpace AbsoluteTime where
107107
-- program shipped with such a table could become out-of-date in as little
108108
-- as 6 months. See 'parseTAIUTCDAT' for details.
109109
data TAIUTCMap = TAIUTCMap (Map UTCTime TAIUTCRow) (Map AbsoluteTime TAIUTCRow)
110-
deriving (INSTANCES_USUAL, Show)
110+
deriving (Eq, Ord, Data, Typeable, Generic, Show)
111111

112112
-- | Each line of TAIUTCDAT (see 'parseTAIUTCDAT') specifies the difference
113113
-- between TAI and UTC for a particular period. For example:
@@ -161,7 +161,7 @@ data TAIUTCMap = TAIUTCMap (Map UTCTime TAIUTCRow) (Map AbsoluteTime TAIUTCRow)
161161
data TAIUTCRow = TAIUTCRow !DiffTime !UTCTime !Rational
162162
-- ^ Each row comprises of an /additive/ component, the /base/ of the
163163
-- scaled component, and the /coefficient/ of the scaled component.
164-
deriving (INSTANCES_USUAL, Show)
164+
deriving (Eq, Ord, Data, Typeable, Generic, Show)
165165

166166
{-# INLINE lookupLE #-}
167167
lookupLE :: (Ord k) => k -> Map k TAIUTCRow -> TAIUTCRow

src/Data/Thyme/Internal/Micro.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import Text.ParserCombinators.ReadP
4141
import Text.Read
4242
#endif
4343

44-
newtype Micro = Micro Int64 deriving (INSTANCES_MICRO)
44+
newtype Micro = Micro Int64 deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary)
4545

4646
derivingUnbox "Micro" [t| Micro -> Int64 |]
4747
[| \ (Micro a) -> a |] [| Micro |]

src/Data/Thyme/LocalTime.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ data TimeZone = TimeZone
7171
-- ^ Is this a summer-only (i.e. daylight savings) time zone?
7272
, timeZoneName :: String
7373
-- ^ The name of the zone, typically a three- or four-letter acronym.
74-
} deriving (INSTANCES_USUAL)
74+
} deriving (Eq, Ord, Data, Typeable, Generic)
7575

7676
LENS(TimeZone,timeZoneMinutes,Minutes)
7777
LENS(TimeZone,timeZoneSummerOnly,Bool)
@@ -184,7 +184,7 @@ data TimeOfDay = TimeOfDay
184184
{ todHour :: {-# UNPACK #-}!Hour
185185
, todMin :: {-# UNPACK #-}!Minute
186186
, todSec :: {-# UNPACK #-}!DiffTime -- ^ Second.
187-
} deriving (INSTANCES_USUAL)
187+
} deriving (Eq, Ord, Data, Typeable, Generic)
188188

189189
LENS(TimeOfDay,todHour,Hour)
190190
LENS(TimeOfDay,todMin,Minute)
@@ -353,7 +353,7 @@ data LocalTime = LocalTime
353353
-- ^ Local calendar date.
354354
, localTimeOfDay :: {-only 3 words…-} {-# UNPACK #-}!TimeOfDay
355355
-- ^ Local time-of-day.
356-
} deriving (INSTANCES_USUAL)
356+
} deriving (Eq, Ord, Data, Typeable, Generic)
357357

358358
LENS(LocalTime,localDay,Day)
359359
LENS(LocalTime,localTimeOfDay,TimeOfDay)
@@ -461,7 +461,7 @@ ut1LocalTime long = iso localise globalise where
461461
data ZonedTime = ZonedTime
462462
{ zonedTimeToLocalTime :: {-only 4 words…-} {-# UNPACK #-}!LocalTime
463463
, zonedTimeZone :: !TimeZone
464-
} deriving (INSTANCES_USUAL)
464+
} deriving (Eq, Ord, Data, Typeable, Generic)
465465

466466
LENS(ZonedTime,zonedTimeToLocalTime,LocalTime)
467467
LENS(ZonedTime,zonedTimeZone,TimeZone)

0 commit comments

Comments
 (0)