Skip to content

Commit 50f8b14

Browse files
committed
removed cpp defs because they break ghcjs and are unneccessary
Signed-off-by: buckie <[email protected]>
1 parent 988d3ee commit 50f8b14

File tree

8 files changed

+75
-64
lines changed

8 files changed

+75
-64
lines changed

include/thyme.h

Lines changed: 0 additions & 1 deletion
This file was deleted.

src/Data/Thyme/Calendar/Internal.hs

Lines changed: 22 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -206,9 +206,10 @@ data YearMonthDay = YearMonthDay
206206
, ymdDay :: {-# UNPACK #-}!DayOfMonth
207207
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
208208

209-
LENS(YearMonthDay,ymdYear,Year)
210-
LENS(YearMonthDay,ymdMonth,Month)
211-
LENS(YearMonthDay,ymdDay,DayOfMonth)
209+
makeLensesFor [("ymdYear","_ymdYear"),("ymdMonth","_ymdMonth"),("ymdDay","_ymdDay")] ''YearMonthDay
210+
{-# INLINE _ymdYear #-}
211+
{-# INLINE _ymdMonth #-}
212+
{-# INLINE _ymdDay #-}
212213

213214
instance Hashable YearMonthDay
214215
instance NFData YearMonthDay
@@ -230,8 +231,9 @@ data OrdinalDate = OrdinalDate
230231
, odDay :: {-# UNPACK #-}!DayOfYear
231232
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
232233

233-
LENS(OrdinalDate,odYear,Year)
234-
LENS(OrdinalDate,odDay,DayOfYear)
234+
makeLensesFor [("odYear","_odYear"),("odDay","_odDay")] ''OrdinalDate
235+
{-# INLINE _odYear #-}
236+
{-# INLINE _odDay #-}
235237

236238
instance Hashable OrdinalDate
237239
instance NFData OrdinalDate
@@ -370,8 +372,9 @@ data MonthDay = MonthDay
370372
, mdDay :: {-# UNPACK #-}!DayOfMonth
371373
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
372374

373-
LENS(MonthDay,mdMonth,Month)
374-
LENS(MonthDay,mdDay,DayOfMonth)
375+
makeLensesFor [("mdMonth","_mdMonth"),("mdDay","_mdDay")] ''MonthDay
376+
{-# INLINE _mdMonth #-}
377+
{-# INLINE _mdDay #-}
375378

376379
instance Hashable MonthDay
377380
instance NFData MonthDay
@@ -514,9 +517,10 @@ data WeekDate = WeekDate
514517
-- ^ /1 = Monday/ … /7 = Sunday/.
515518
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
516519

517-
LENS(WeekDate,wdYear,Year)
518-
LENS(WeekDate,wdWeek,WeekOfYear)
519-
LENS(WeekDate,wdDay,DayOfWeek)
520+
makeLensesFor [("wdYear","_wdYear"),("wdWeek","_wdWeek"),("wdDay","_wdDay")] ''WeekDate
521+
{-# INLINE _wdYear #-}
522+
{-# INLINE _wdWeek #-}
523+
{-# INLINE _wdDay #-}
520524

521525
instance Hashable WeekDate
522526
instance NFData WeekDate
@@ -604,9 +608,10 @@ data SundayWeek = SundayWeek
604608
-- ^ /0 = Sunday/.
605609
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
606610

607-
LENS(SundayWeek,swYear,Year)
608-
LENS(SundayWeek,swWeek,WeekOfYear)
609-
LENS(SundayWeek,swDay,DayOfWeek)
611+
makeLensesFor [("swYear","_swYear"),("swWeek","_swWeek"),("swDay","_swDay")] ''SundayWeek
612+
{-# INLINE _swYear #-}
613+
{-# INLINE _swWeek #-}
614+
{-# INLINE _swDay #-}
610615

611616
instance Hashable SundayWeek
612617
instance NFData SundayWeek
@@ -670,9 +675,10 @@ data MondayWeek = MondayWeek
670675
-- ^ /7 = Sunday/.
671676
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
672677

673-
LENS(MondayWeek,mwYear,Year)
674-
LENS(MondayWeek,mwWeek,WeekOfYear)
675-
LENS(MondayWeek,mwDay,DayOfWeek)
678+
makeLensesFor [("mwYear","_mwYear"),("mwWeek","_mwWeek"),("mwDay","_mwDay")] ''MondayWeek
679+
{-# INLINE _mwYear #-}
680+
{-# INLINE _mwWeek #-}
681+
{-# INLINE _mwDay #-}
676682

677683
instance Hashable MondayWeek
678684
instance NFData MondayWeek
@@ -747,4 +753,3 @@ derivingUnbox "SundayWeek" [t| SundayWeek -> Int |]
747753
derivingUnbox "MondayWeek" [t| MondayWeek -> Int |]
748754
[| \ MondayWeek {..} -> shiftL mwYear 9 .|. shiftL mwWeek 3 .|. mwDay |]
749755
[| \ n -> MondayWeek (shiftR n 9) (shiftR n 3 .&. 0x3f) (n .&. 0x7) |]
750-

src/Data/Thyme/Calendar/WeekdayOfMonth.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE TypeFamilies #-}
88
{-# LANGUAGE ViewPatterns #-}
99

10-
#include "thyme.h"
1110
#if HLINT
1211
#include "cabal_macros.h"
1312
#endif
@@ -54,10 +53,11 @@ data WeekdayOfMonth = WeekdayOfMonth
5453
-- ^ Day of week. /1 = Monday, 7 = Sunday/, like ISO 8601 'WeekDate'.
5554
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
5655

57-
LENS(WeekdayOfMonth,womYear,Year)
58-
LENS(WeekdayOfMonth,womMonth,Month)
59-
LENS(WeekdayOfMonth,womNth,Int)
60-
LENS(WeekdayOfMonth,womDayOfWeek,DayOfWeek)
56+
makeLensesFor [("womYear","_womYear"),("womMonth","_womMonth"),("womNth","_womNth"),("womDayOfWeek","_womDayOfWeek")] ''WeekdayOfMonth
57+
{-# INLINE _womYear #-}
58+
{-# INLINE _womMonth #-}
59+
{-# INLINE _womNth #-}
60+
{-# INLINE _womDayOfWeek #-}
6161

6262
derivingUnbox "WeekdayOfMonth"
6363
[t| WeekdayOfMonth -> Int |]
@@ -145,4 +145,3 @@ weekdayOfMonthValid (WeekdayOfMonth y m n wd) = (refDay .+^ s * offset)
145145
s = signum n
146146
wo = s * (wd - wd1)
147147
offset = (abs n - 1) * 7 + if wo < 0 then wo + 7 else wo
148-

src/Data/Thyme/Clock/Internal.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,6 @@
1414
{-# LANGUAGE ViewPatterns #-}
1515
{-# OPTIONS_HADDOCK hide #-}
1616

17-
#include "thyme.h"
18-
1917
module Data.Thyme.Clock.Internal where
2018

2119
import Prelude
@@ -329,10 +327,12 @@ data UTCView = UTCView
329327
} deriving (Eq, Ord, Data, Typeable, Generic, Show)
330328

331329
-- | 'Lens'' for the calendar 'Day' component of a 'UTCView'.
332-
LENS(UTCView,utcvDay,Day)
330+
makeLensesFor [("utcvDay","_utcvDay")] ''UTCView
331+
{-# INLINE _utcvDay #-}
333332

334333
-- | 'Lens'' for the time-of-day 'DiffTime' component of a 'UTCView'.
335-
LENS(UTCView,utcvDayTime,DiffTime)
334+
makeLensesFor [("utcvDayTime","_utcvDayTime")] ''UTCView
335+
{-# INLINE _utcvDayTime #-}
336336

337337
derivingUnbox "UTCView" [t| UTCView -> (Day, DiffTime) |]
338338
[| \ UTCView {..} -> (utcvDay, utcvDayTime) |]
@@ -431,4 +431,3 @@ mkUTCTime :: Year -> Month -> DayOfMonth -> Hour -> Minute -> Double -> UTCTime
431431
mkUTCTime yy mm dd h m s = utcTime # UTCView
432432
(gregorian # YearMonthDay yy mm dd)
433433
(fromSeconds (3600 * h + 60 * m) ^+^ fromSeconds s)
434-

src/Data/Thyme/Format.hs

Lines changed: 28 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
{-# LANGUAGE StandaloneDeriving #-}
55
{-# LANGUAGE ViewPatterns #-}
66
{-# OPTIONS_GHC -fno-warn-orphans #-}
7-
#include "thyme.h"
87

98
-- | Formatting and parsing for dates and times.
109
module Data.Thyme.Format
@@ -486,20 +485,34 @@ data TimeParse = TimeParse
486485
, tpTimeZone :: !TimeZone
487486
} deriving (Show)
488487

489-
LENS(TimeParse,tpCentury,Int)
490-
LENS(TimeParse,tpCenturyYear,Int{-YearOfCentury-})
491-
LENS(TimeParse,tpMonth,Month)
492-
LENS(TimeParse,tpWeekOfYear,WeekOfYear)
493-
LENS(TimeParse,tpDayOfMonth,DayOfMonth)
494-
LENS(TimeParse,tpDayOfWeek,DayOfWeek)
495-
LENS(TimeParse,tpDayOfYear,DayOfYear)
496-
LENS(TimeParse,tpFlags,Int{-BitSet TimeFlag-})
497-
LENS(TimeParse,tpHour,Hour)
498-
LENS(TimeParse,tpMinute,Minute)
499-
LENS(TimeParse,tpSecond,Int)
500-
LENS(TimeParse,tpSecFrac,DiffTime)
501-
LENS(TimeParse,tpPOSIXTime,POSIXTime)
502-
LENS(TimeParse,tpTimeZone,TimeZone)
488+
makeLensesFor [ ("tpCentury","_tpCentury")
489+
, ("tpCenturyYear","_tpCenturyYear")
490+
, ("tpMonth","_tpMonth")
491+
, ("tpWeekOfYear","_tpWeekOfYear")
492+
, ("tpDayOfMonth","_tpDayOfMonth")
493+
, ("tpDayOfWeek","_tpDayOfWeek")
494+
, ("tpDayOfYear","_tpDayOfYear")
495+
, ("tpFlags","_tpFlags")
496+
, ("tpHour","_tpHour")
497+
, ("tpMinute","_tpMinute")
498+
, ("tpSecond","_tpSecond")
499+
, ("tpSecFrac","_tpSecFrac")
500+
, ("tpPOSIXTime","_tpPOSIXTime")
501+
, ("tpTimeZone","_tpTimeZone")] ''TimeParse
502+
{-# INLINE _tpCentury #-}
503+
{-# INLINE _tpCenturyYear #-}
504+
{-# INLINE _tpMonth #-}
505+
{-# INLINE _tpWeekOfYear #-}
506+
{-# INLINE _tpDayOfMonth #-}
507+
{-# INLINE _tpDayOfWeek #-}
508+
{-# INLINE _tpDayOfYear #-}
509+
{-# INLINE _tpFlags #-}
510+
{-# INLINE _tpHour #-}
511+
{-# INLINE _tpMinute #-}
512+
{-# INLINE _tpSecond #-}
513+
{-# INLINE _tpSecFrac #-}
514+
{-# INLINE _tpPOSIXTime #-}
515+
{-# INLINE _tpTimeZone #-}
503516

504517
{-# INLINE flag #-}
505518
flag :: TimeFlag -> Lens' TimeParse Bool
@@ -985,4 +998,3 @@ timeZoneParser = zone "TAI" 0 False <|> zone "UT1" 0 False
985998
zone name offset dst = TimeZone offset dst name <$ P.string (S.pack name)
986999
($+) h m = h * 60 + m
9871000
($-) h m = negate (h * 60 + m)
988-

src/Data/Thyme/Format/Human.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
{-# LANGUAGE RecordWildCards #-}
44
{-# LANGUAGE ViewPatterns #-}
55

6-
#include "thyme.h"
76
#if HLINT
87
#include "cabal_macros.h"
98
#endif
@@ -36,7 +35,8 @@ data Unit = Unit
3635
, single :: ShowS
3736
, plural :: ShowS
3837
}
39-
LENS(Unit,plural,ShowS)
38+
makeLensesFor [("plural","_plural")] ''Unit
39+
{-# INLINE _plural #-}
4040

4141
-- | Display 'DiffTime' or 'NominalDiffTime' in a human-readable form.
4242
{-# INLINE humanTimeDiff #-}
@@ -91,4 +91,3 @@ units = scanl (&)
9191
times :: String -> Rational -> Unit -> Unit
9292
times ((++) . (:) ' ' -> single) r Unit {unit}
9393
= Unit {unit = r *^ unit, plural = single . (:) 's', ..}
94-

src/Data/Thyme/LocalTime.hs

Lines changed: 14 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@
1010
{-# LANGUAGE ViewPatterns #-}
1111
{-# OPTIONS_GHC -fno-warn-orphans #-}
1212

13-
#include "thyme.h"
1413
#if HLINT
1514
#include "cabal_macros.h"
1615
#endif
@@ -73,9 +72,10 @@ data TimeZone = TimeZone
7372
-- ^ The name of the zone, typically a three- or four-letter acronym.
7473
} deriving (Eq, Ord, Data, Typeable, Generic)
7574

76-
LENS(TimeZone,timeZoneMinutes,Minutes)
77-
LENS(TimeZone,timeZoneSummerOnly,Bool)
78-
LENS(TimeZone,timeZoneName,String)
75+
makeLensesFor [("timeZoneMinutes","_timeZoneMinutes"),("timeZoneSummerOnly","_timeZoneSummerOnly"),("timeZoneName","_timeZoneName")] ''TimeZone
76+
{-# INLINE _timeZoneMinutes #-}
77+
{-# INLINE _timeZoneSummerOnly #-}
78+
{-# INLINE _timeZoneName #-}
7979

8080
instance Hashable TimeZone
8181
instance NFData TimeZone
@@ -186,9 +186,10 @@ data TimeOfDay = TimeOfDay
186186
, todSec :: {-# UNPACK #-}!DiffTime -- ^ Second.
187187
} deriving (Eq, Ord, Data, Typeable, Generic)
188188

189-
LENS(TimeOfDay,todHour,Hour)
190-
LENS(TimeOfDay,todMin,Minute)
191-
LENS(TimeOfDay,todSec,DiffTime)
189+
makeLensesFor [("todHour","_todHour"),("todMin","_todMin"),("todSec","_todSec")] ''TimeOfDay
190+
{-# INLINE _todHour #-}
191+
{-# INLINE _todMin #-}
192+
{-# INLINE _todSec #-}
192193

193194
derivingUnbox "TimeOfDay" [t| TimeOfDay -> Int64 |]
194195
[| \ TimeOfDay {..} -> fromIntegral (todHour .|. shiftL todMin 8)
@@ -355,8 +356,9 @@ data LocalTime = LocalTime
355356
-- ^ Local time-of-day.
356357
} deriving (Eq, Ord, Data, Typeable, Generic)
357358

358-
LENS(LocalTime,localDay,Day)
359-
LENS(LocalTime,localTimeOfDay,TimeOfDay)
359+
makeLensesFor [("localDay","_localDay"),("localTimeOfDay","_localTimeOfDay")] ''LocalTime
360+
{-# INLINE _localDay #-}
361+
{-# INLINE _localTimeOfDay #-}
360362

361363
derivingUnbox "LocalTime" [t| LocalTime -> (Day, TimeOfDay) |]
362364
[| \ LocalTime {..} -> (localDay, localTimeOfDay) |]
@@ -463,8 +465,9 @@ data ZonedTime = ZonedTime
463465
, zonedTimeZone :: !TimeZone
464466
} deriving (Eq, Ord, Data, Typeable, Generic)
465467

466-
LENS(ZonedTime,zonedTimeToLocalTime,LocalTime)
467-
LENS(ZonedTime,zonedTimeZone,TimeZone)
468+
makeLensesFor [("zonedTimeToLocalTime","_zonedTimeToLocalTime"),("zonedTimeZone","_zonedTimeZone")] ''ZonedTime
469+
{-# INLINE _zonedTimeToLocalTime #-}
470+
{-# INLINE _zonedTimeZone #-}
468471

469472
instance Hashable ZonedTime
470473
instance NFData ZonedTime where
@@ -668,4 +671,3 @@ utcToZonedTime z t = view zonedTime (z, t)
668671
{-# INLINE zonedTimeToUTC #-}
669672
zonedTimeToUTC :: ZonedTime -> UTCTime
670673
zonedTimeToUTC = snd . review zonedTime
671-

thyme.cabal

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,6 @@ category: Data, System
1717
build-type: Simple
1818
cabal-version: >= 1.10
1919
stability: experimental
20-
extra-source-files:
21-
include/thyme.h
2220
tested-with:
2321
GHC == 7.6.3, GHC == 7.8.4,
2422
GHC == 7.10.2, GHC == 7.10.3,
@@ -55,7 +53,6 @@ flag show-internal
5553

5654
library
5755
default-language: Haskell2010
58-
include-dirs: include
5956
hs-source-dirs: src
6057
if !(flag(lens) || flag(docs))
6158
hs-source-dirs: lens
@@ -195,4 +192,3 @@ benchmark bench
195192
ghc-options: -Wall
196193

197194
-- vim: et sw=4 ts=4 sts=4:
198-

0 commit comments

Comments
 (0)