Skip to content

ghcjs buildable version #52

New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Open
wants to merge 8 commits into
base: master
Choose a base branch
from
Open
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1 +1,3 @@
/dist/
dump/
.stack-work/
7 changes: 0 additions & 7 deletions include/thyme.h

This file was deleted.

156 changes: 0 additions & 156 deletions lens/Control/Lens.hs

This file was deleted.

2 changes: 1 addition & 1 deletion src/Data/Thyme/Calendar.hs
Original file line number Diff line number Diff line change
@@ -3,7 +3,7 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

#include "thyme.h"

#if HLINT
#include "cabal_macros.h"
#endif
54 changes: 21 additions & 33 deletions src/Data/Thyme/Calendar/Internal.hs
Original file line number Diff line number Diff line change
@@ -13,7 +13,6 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK hide #-}

#include "thyme.h"
#if HLINT
#include "cabal_macros.h"
#endif
@@ -59,7 +58,7 @@ type Days = Int
-- <https://en.wikipedia.org/wiki/Julian_day#Variants Modified Julian Day>
-- (MJD) epoch.
--
-- To convert a 'Day' to the corresponding 'YearMonthDay' in the W_GREGORIAN
-- To convert a 'Day' to the corresponding 'YearMonthDay' in the <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian>
-- calendar, see 'gregorian'.
--
-- @
@@ -84,7 +83,7 @@ type Days = Int
-- Other ways of viewing a 'Day' include 'ordinalDate', and 'weekDate'.
newtype Day = ModifiedJulianDay
{ toModifiedJulianDay :: Int
} deriving (INSTANCES_NEWTYPE, CoArbitrary)
} deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, CoArbitrary)

instance AffineSpace Day where
type Diff Day = Days
@@ -110,7 +109,7 @@ instance AffineSpace Day where
modifiedJulianDay :: Iso' Day Int
modifiedJulianDay = iso toModifiedJulianDay ModifiedJulianDay

-- | Conversion between a W_GREGORIAN 'OrdinalDate' and the corresponding
-- | Conversion between a <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian> 'OrdinalDate' and the corresponding
-- 'YearMonthDay'.
--
-- @
@@ -204,18 +203,14 @@ data YearMonthDay = YearMonthDay
{ ymdYear :: {-# UNPACK #-}!Year
, ymdMonth :: {-# UNPACK #-}!Month
, ymdDay :: {-# UNPACK #-}!DayOfMonth
} deriving (INSTANCES_USUAL, Show)

LENS(YearMonthDay,ymdYear,Year)
LENS(YearMonthDay,ymdMonth,Month)
LENS(YearMonthDay,ymdDay,DayOfMonth)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable YearMonthDay
instance NFData YearMonthDay

------------------------------------------------------------------------

-- | Is it a leap year according to the W_GREGORIAN calendar?
-- | Is it a leap year according to the <https://en.wikipedia.org/wiki/Gregorian_calendar Gregorian> calendar?
isLeapYear :: Year -> Bool
isLeapYear y = y .&. 3 == 0 && (r100 /= 0 || q100 .&. 3 == 0) where
(q100, r100) = y `quotRem` 100
@@ -228,10 +223,7 @@ type DayOfYear = Int
data OrdinalDate = OrdinalDate
{ odYear :: {-# UNPACK #-}!Year
, odDay :: {-# UNPACK #-}!DayOfYear
} deriving (INSTANCES_USUAL, Show)

LENS(OrdinalDate,odYear,Year)
LENS(OrdinalDate,odDay,DayOfYear)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable OrdinalDate
instance NFData OrdinalDate
@@ -368,10 +360,7 @@ randomIsoR l (x, y) = first (^. l) . randomR (l # x, l # y)
data MonthDay = MonthDay
{ mdMonth :: {-# UNPACK #-}!Month
, mdDay :: {-# UNPACK #-}!DayOfMonth
} deriving (INSTANCES_USUAL, Show)

LENS(MonthDay,mdMonth,Month)
LENS(MonthDay,mdDay,DayOfMonth)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable MonthDay
instance NFData MonthDay
@@ -512,11 +501,7 @@ data WeekDate = WeekDate
-- belong to the previous year.
, wdDay :: {-# UNPACK #-}!DayOfWeek
-- ^ /1 = Monday/ … /7 = Sunday/.
} deriving (INSTANCES_USUAL, Show)

LENS(WeekDate,wdYear,Year)
LENS(WeekDate,wdWeek,WeekOfYear)
LENS(WeekDate,wdDay,DayOfWeek)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable WeekDate
instance NFData WeekDate
@@ -602,11 +587,7 @@ data SundayWeek = SundayWeek
-- /Sunday/ of the year as the first day of week /01/.
, swDay :: {-# UNPACK #-}!DayOfWeek
-- ^ /0 = Sunday/.
} deriving (INSTANCES_USUAL, Show)

LENS(SundayWeek,swYear,Year)
LENS(SundayWeek,swWeek,WeekOfYear)
LENS(SundayWeek,swDay,DayOfWeek)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable SundayWeek
instance NFData SundayWeek
@@ -668,11 +649,7 @@ data MondayWeek = MondayWeek
-- /Monday/ of the year as the first day of week /01/.
, mwDay :: {-# UNPACK #-}!DayOfWeek
-- ^ /7 = Sunday/.
} deriving (INSTANCES_USUAL, Show)

LENS(MondayWeek,mwYear,Year)
LENS(MondayWeek,mwWeek,WeekOfYear)
LENS(MondayWeek,mwDay,DayOfWeek)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Hashable MondayWeek
instance NFData MondayWeek
@@ -748,3 +725,14 @@ derivingUnbox "MondayWeek" [t| MondayWeek -> Int |]
[| \ MondayWeek {..} -> shiftL mwYear 9 .|. shiftL mwWeek 3 .|. mwDay |]
[| \ n -> MondayWeek (shiftR n 9) (shiftR n 3 .&. 0x3f) (n .&. 0x7) |]

makeLensesFor [("ymdYear","_ymdYear"),("ymdMonth","_ymdMonth"),("ymdDay","_ymdDay")] ''YearMonthDay

makeLensesFor [("odYear","_odYear"),("odDay","_odDay")] ''OrdinalDate

makeLensesFor [("mdMonth","_mdMonth"),("mdDay","_mdDay")] ''MonthDay

makeLensesFor [("wdYear","_wdYear"),("wdWeek","_wdWeek"),("wdDay","_wdDay")] ''WeekDate

makeLensesFor [("swYear","_swYear"),("swWeek","_swWeek"),("swDay","_swDay")] ''SundayWeek

makeLensesFor [("mwYear","_mwYear"),("mwWeek","_mwWeek"),("mwDay","_mwDay")] ''MondayWeek
2 changes: 1 addition & 1 deletion src/Data/Thyme/Calendar/MonthDay.hs
Original file line number Diff line number Diff line change
@@ -2,7 +2,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

#include "thyme.h"


-- | Calendar months and day-of-months.
module Data.Thyme.Calendar.MonthDay
2 changes: 1 addition & 1 deletion src/Data/Thyme/Calendar/OrdinalDate.hs
Original file line number Diff line number Diff line change
@@ -3,7 +3,7 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

#include "thyme.h"

#if HLINT
#include "cabal_macros.h"
#endif
2 changes: 1 addition & 1 deletion src/Data/Thyme/Calendar/WeekDate.hs
Original file line number Diff line number Diff line change
@@ -6,7 +6,7 @@
{-# OPTIONS_GHC -fsimpl-tick-factor=120 #-} -- 7.6.3 only, it seems; fixes #29
#endif

#include "thyme.h"

#if HLINT
#include "cabal_macros.h"
#endif
9 changes: 2 additions & 7 deletions src/Data/Thyme/Calendar/WeekdayOfMonth.hs
Original file line number Diff line number Diff line change
@@ -7,7 +7,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

#include "thyme.h"
#if HLINT
#include "cabal_macros.h"
#endif
@@ -52,12 +51,7 @@ data WeekdayOfMonth = WeekdayOfMonth
-- last 'DayOfWeek' of the month.
, womDayOfWeek :: {-# UNPACK #-}!DayOfWeek
-- ^ Day of week. /1 = Monday, 7 = Sunday/, like ISO 8601 'WeekDate'.
} deriving (INSTANCES_USUAL, Show)

LENS(WeekdayOfMonth,womYear,Year)
LENS(WeekdayOfMonth,womMonth,Month)
LENS(WeekdayOfMonth,womNth,Int)
LENS(WeekdayOfMonth,womDayOfWeek,DayOfWeek)
} deriving (Eq, Ord, Data, Typeable, Generic, Show)

derivingUnbox "WeekdayOfMonth"
[t| WeekdayOfMonth -> Int |]
@@ -146,3 +140,4 @@ weekdayOfMonthValid (WeekdayOfMonth y m n wd) = (refDay .+^ s * offset)
wo = s * (wd - wd1)
offset = (abs n - 1) * 7 + if wo < 0 then wo + 7 else wo

makeLensesFor [("womYear","_womYear"),("womMonth","_womMonth"),("womNth","_womNth"),("womDayOfWeek","_womDayOfWeek")] ''WeekdayOfMonth
17 changes: 7 additions & 10 deletions src/Data/Thyme/Clock/Internal.hs
Original file line number Diff line number Diff line change
@@ -14,8 +14,6 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK hide #-}

#include "thyme.h"

module Data.Thyme.Clock.Internal where

import Prelude
@@ -130,7 +128,7 @@ fromSecondsIntegral _ = review microseconds . (*) 1000000 . fromIntegral
-- > 'fromSeconds'' 100 '^-^' 'fromSeconds'' 100 '^/' 4
-- 75s
-- @
newtype DiffTime = DiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
newtype DiffTime = DiffTime Micro deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary, AdditiveGroup)

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

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

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

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

-- | 'Lens'' for the calendar 'Day' component of a 'UTCView'.
LENS(UTCView,utcvDay,Day)
makeLensesFor [("utcvDay","_utcvDay")] ''UTCView

-- | 'Lens'' for the time-of-day 'DiffTime' component of a 'UTCView'.
LENS(UTCView,utcvDayTime,DiffTime)
makeLensesFor [("utcvDayTime","_utcvDayTime")] ''UTCView

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

12 changes: 7 additions & 5 deletions src/Data/Thyme/Clock/TAI.hs
Original file line number Diff line number Diff line change
@@ -9,7 +9,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

#include "thyme.h"

#if HLINT
#include "cabal_macros.h"
#endif
@@ -41,6 +41,9 @@ import Prelude
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mempty)
#endif
import Control.DeepSeq
import Control.Lens
import Control.Monad
@@ -74,7 +77,7 @@ import Test.QuickCheck
--
-- Internally this is the number of seconds since 'taiEpoch'. TAI days are
-- exactly 86400 SI seconds long.
newtype AbsoluteTime = AbsoluteTime DiffTime deriving (INSTANCES_MICRO)
newtype AbsoluteTime = AbsoluteTime DiffTime deriving (Eq, Ord, Data, Typeable, Generic, Enum, Ix, Hashable, NFData, Bounded, Random, Arbitrary, CoArbitrary)

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

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

{-# INLINE lookupLE #-}
lookupLE :: (Ord k) => k -> Map k TAIUTCRow -> TAIUTCRow
@@ -354,4 +357,3 @@ utcToTAITime = view . absoluteTime
{-# INLINE taiToUTCTime #-}
taiToUTCTime :: TAIUTCMap -> AbsoluteTime -> UTCTime
taiToUTCTime = review . absoluteTime

34 changes: 18 additions & 16 deletions src/Data/Thyme/Format.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
#include "thyme.h"

-- | Formatting and parsing for dates and times.
module Data.Thyme.Format
@@ -30,6 +30,9 @@ import Control.Applicative
#if SHOW_INTERNAL
import Control.Arrow
#endif
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mempty)
#endif
import Control.Lens
import Control.Monad.Trans
import Control.Monad.State.Strict
@@ -486,20 +489,20 @@ data TimeParse = TimeParse
, tpTimeZone :: !TimeZone
} deriving (Show)

LENS(TimeParse,tpCentury,Int)
LENS(TimeParse,tpCenturyYear,Int{-YearOfCentury-})
LENS(TimeParse,tpMonth,Month)
LENS(TimeParse,tpWeekOfYear,WeekOfYear)
LENS(TimeParse,tpDayOfMonth,DayOfMonth)
LENS(TimeParse,tpDayOfWeek,DayOfWeek)
LENS(TimeParse,tpDayOfYear,DayOfYear)
LENS(TimeParse,tpFlags,Int{-BitSet TimeFlag-})
LENS(TimeParse,tpHour,Hour)
LENS(TimeParse,tpMinute,Minute)
LENS(TimeParse,tpSecond,Int)
LENS(TimeParse,tpSecFrac,DiffTime)
LENS(TimeParse,tpPOSIXTime,POSIXTime)
LENS(TimeParse,tpTimeZone,TimeZone)
makeLensesFor [ ("tpCentury","_tpCentury")
, ("tpCenturyYear","_tpCenturyYear")
, ("tpMonth","_tpMonth")
, ("tpWeekOfYear","_tpWeekOfYear")
, ("tpDayOfMonth","_tpDayOfMonth")
, ("tpDayOfWeek","_tpDayOfWeek")
, ("tpDayOfYear","_tpDayOfYear")
, ("tpFlags","_tpFlags")
, ("tpHour","_tpHour")
, ("tpMinute","_tpMinute")
, ("tpSecond","_tpSecond")
, ("tpSecFrac","_tpSecFrac")
, ("tpPOSIXTime","_tpPOSIXTime")
, ("tpTimeZone","_tpTimeZone")] ''TimeParse

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

5 changes: 2 additions & 3 deletions src/Data/Thyme/Format/Human.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

#include "thyme.h"
#if HLINT
#include "cabal_macros.h"
#endif
@@ -36,7 +36,7 @@ data Unit = Unit
, single :: ShowS
, plural :: ShowS
}
LENS(Unit,plural,ShowS)
makeLensesFor [("plural","_plural")] ''Unit

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

4 changes: 2 additions & 2 deletions src/Data/Thyme/Internal/Micro.hs
Original file line number Diff line number Diff line change
@@ -7,7 +7,7 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

#include "thyme.h"


-- | FOR INTERNAL USE ONLY.
module Data.Thyme.Internal.Micro where
@@ -41,7 +41,7 @@ import Text.ParserCombinators.ReadP
import Text.Read
#endif

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

derivingUnbox "Micro" [t| Micro -> Int64 |]
[| \ (Micro a) -> a |] [| Micro |]
24 changes: 8 additions & 16 deletions src/Data/Thyme/LocalTime.hs
Original file line number Diff line number Diff line change
@@ -10,7 +10,6 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

#include "thyme.h"
#if HLINT
#include "cabal_macros.h"
#endif
@@ -71,11 +70,9 @@ data TimeZone = TimeZone
-- ^ Is this a summer-only (i.e. daylight savings) time zone?
, timeZoneName :: String
-- ^ The name of the zone, typically a three- or four-letter acronym.
} deriving (INSTANCES_USUAL)
} deriving (Eq, Ord, Data, Typeable, Generic)

LENS(TimeZone,timeZoneMinutes,Minutes)
LENS(TimeZone,timeZoneSummerOnly,Bool)
LENS(TimeZone,timeZoneName,String)
makeLensesFor [("timeZoneMinutes","_timeZoneMinutes"),("timeZoneSummerOnly","_timeZoneSummerOnly"),("timeZoneName","_timeZoneName")] ''TimeZone

instance Hashable TimeZone
instance NFData TimeZone
@@ -184,11 +181,9 @@ data TimeOfDay = TimeOfDay
{ todHour :: {-# UNPACK #-}!Hour
, todMin :: {-# UNPACK #-}!Minute
, todSec :: {-# UNPACK #-}!DiffTime -- ^ Second.
} deriving (INSTANCES_USUAL)
} deriving (Eq, Ord, Data, Typeable, Generic)

LENS(TimeOfDay,todHour,Hour)
LENS(TimeOfDay,todMin,Minute)
LENS(TimeOfDay,todSec,DiffTime)
makeLensesFor [("todHour","_todHour"),("todMin","_todMin"),("todSec","_todSec")] ''TimeOfDay

derivingUnbox "TimeOfDay" [t| TimeOfDay -> Int64 |]
[| \ TimeOfDay {..} -> fromIntegral (todHour .|. shiftL todMin 8)
@@ -353,10 +348,9 @@ data LocalTime = LocalTime
-- ^ Local calendar date.
, localTimeOfDay :: {-only 3 words…-} {-# UNPACK #-}!TimeOfDay
-- ^ Local time-of-day.
} deriving (INSTANCES_USUAL)
} deriving (Eq, Ord, Data, Typeable, Generic)

LENS(LocalTime,localDay,Day)
LENS(LocalTime,localTimeOfDay,TimeOfDay)
makeLensesFor [("localDay","_localDay"),("localTimeOfDay","_localTimeOfDay")] ''LocalTime

derivingUnbox "LocalTime" [t| LocalTime -> (Day, TimeOfDay) |]
[| \ LocalTime {..} -> (localDay, localTimeOfDay) |]
@@ -461,10 +455,9 @@ ut1LocalTime long = iso localise globalise where
data ZonedTime = ZonedTime
{ zonedTimeToLocalTime :: {-only 4 words…-} {-# UNPACK #-}!LocalTime
, zonedTimeZone :: !TimeZone
} deriving (INSTANCES_USUAL)
} deriving (Eq, Ord, Data, Typeable, Generic)

LENS(ZonedTime,zonedTimeToLocalTime,LocalTime)
LENS(ZonedTime,zonedTimeZone,TimeZone)
makeLensesFor [("zonedTimeToLocalTime","_zonedTimeToLocalTime"),("zonedTimeZone","_zonedTimeZone")] ''ZonedTime

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

49 changes: 8 additions & 41 deletions thyme.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: thyme
version: 0.3.5.5
version: 0.3.5.6
synopsis: A faster time library
description:
@thyme@ is a performance-optimized rewrite of the excellent
@@ -17,8 +17,6 @@ category: Data, System
build-type: Simple
cabal-version: >= 1.10
stability: experimental
extra-source-files:
include/thyme.h
tested-with:
GHC == 7.6.3, GHC == 7.8.4,
GHC == 7.10.2, GHC == 7.10.3,
@@ -34,7 +32,7 @@ flag bug-for-bug
manual: True

flag docs
description: include extra packages for Data.Thyme.Docs; implies -flens
description: include extra packages for Data.Thyme.Docs
default: False
manual: True

@@ -43,22 +41,14 @@ flag HLint
default: False
manual: True

flag lens
description: use the full lens package
default: False
manual: True

flag show-internal
description: instance Show of internal representation
default: False
manual: True

library
default-language: Haskell2010
include-dirs: include
hs-source-dirs: src
if !(flag(lens) || flag(docs))
hs-source-dirs: lens
exposed-modules:
Data.Thyme
Data.Thyme.Docs
@@ -81,8 +71,6 @@ library
Data.Thyme.Calendar.Internal
Data.Thyme.Clock.Internal
Data.Thyme.Format.Internal
if !(flag(lens) || flag(docs))
other-modules: Control.Lens
build-depends:
QuickCheck >= 2.4,
attoparsec >= 0.10,
@@ -100,16 +88,10 @@ library
true-name >= 0.1.0.1,
vector >= 0.9,
vector-th-unbox >= 0.2.1.0,
vector-space >= 0.8
vector-space >= 0.8,
lens >= 3.9
if os(windows)
build-depends: Win32
if os(darwin)
build-tools: cpphs
ghc-options: -pgmP cpphs -optP--cpp
if flag(lens) || flag(docs)
build-depends: lens >= 3.9
else
build-depends: profunctors >= 3.1.2
if flag(docs)
build-depends: integer-gmp, ghc-prim
ghc-options: -Wall
@@ -122,12 +104,8 @@ test-suite sanity
default-language: Haskell2010
type: exitcode-stdio-1.0
hs-source-dirs: tests
if !flag(lens)
hs-source-dirs: lens
main-is: sanity.hs
other-modules: Common
if !flag(lens)
other-modules: Control.Lens
build-depends:
QuickCheck,
attoparsec,
@@ -137,11 +115,8 @@ test-suite sanity
text,
thyme,
time,
vector-space
if flag(lens)
build-depends: lens
else
build-depends: profunctors, mtl
vector-space,
lens
ghc-options: -Wall

test-suite rewrite
@@ -171,12 +146,8 @@ benchmark bench
default-language: Haskell2010
type: exitcode-stdio-1.0
hs-source-dirs: tests
if !flag(lens)
hs-source-dirs: lens
main-is: bench.hs
other-modules: Common
if !flag(lens)
other-modules: Control.Lens
build-depends:
QuickCheck,
base,
@@ -187,12 +158,8 @@ benchmark bench
thyme,
time,
vector,
vector-space
if flag(lens)
build-depends: lens
else
build-depends: profunctors
vector-space,
lens
ghc-options: -Wall

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