module Data.Time.Exts.Base (
Date(..)
, Time(..)
, Zone(..)
, DateTime(..)
, DateZone(..)
, TimeZone(..)
, DateTimeZone(..)
, DateTimeMath(..)
, Duration(..)
, DateStruct(..)
, TimeStruct(..)
, DateTimeStruct(..)
, DateZoneStruct(..)
, DateTimeZoneStruct(..)
, Year(..)
, Month(..)
, Day(..)
, DayOfWeek(..)
, Hour(..)
, Minute(..)
, Second(..)
, Millis(..)
, Micros(..)
, Nanos(..)
, Picos(..)
, properFracMillis
, properFracMicros
, properFracNanos
, properFracPicos
, epochToDate
, epochToTime
, midnightToTime
, isLeapYear
, showPeriod
, showSuffix
) where
import Control.Arrow (first)
import Data.Aeson (FromJSON, ToJSON)
import Data.Int (Int32, Int64)
import qualified Data.Time.Exts.Zone as TZ (TimeZone)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Printf (PrintfArg)
import System.Random (Random(..))
class Date d where
fromDateStruct :: DateStruct -> d
toDateStruct :: d -> DateStruct
class Time t where
fromTimeStruct :: TimeStruct -> t
toTimeStruct :: t -> TimeStruct
class Zone x where
toTimeZone :: x -> TZ.TimeZone -> x
class (Date dt, Time dt) => DateTime dt where
fromDateTimeStruct :: DateTimeStruct -> dt
toDateTimeStruct :: dt -> DateTimeStruct
class Zone dz => DateZone dz where
fromDateZoneStruct :: DateZoneStruct -> dz
toDateZoneStruct :: dz -> DateZoneStruct
class Zone tz => TimeZone tz where
fromTimeZoneStruct :: TimeZoneStruct -> tz
toTimeZoneStruct :: tz -> TimeZoneStruct
class DateZone dtz => DateTimeZone dtz where
fromDateTimeZoneStruct :: DateTimeZoneStruct -> dtz
toDateTimeZoneStruct :: dtz -> DateTimeZoneStruct
class Duration x c where
duration :: x -> x -> c
class DateTimeMath x c where
plus :: x -> c -> x
data DateStruct = DateStruct {
_d_year :: !Year
, _d_mon :: !Month
, _d_mday :: !Day
, _d_wday :: !DayOfWeek
} deriving (Eq,Generic,Ord,Show,Typeable)
data TimeStruct = TimeStruct {
_t_hour :: !Hour
, _t_min :: !Minute
, _t_sec :: !Double
} deriving (Eq,Generic,Ord,Show,Typeable)
data DateTimeStruct = DateTimeStruct {
_dt_year :: !Year
, _dt_mon :: !Month
, _dt_mday :: !Day
, _dt_wday :: !DayOfWeek
, _dt_hour :: !Hour
, _dt_min :: !Minute
, _dt_sec :: !Double
} deriving (Eq,Generic,Ord,Show,Typeable)
data DateZoneStruct = DateZoneStruct {
_dz_year :: !Year
, _dz_mon :: !Month
, _dz_mday :: !Day
, _dz_wday :: !DayOfWeek
, _dz_zone :: !TZ.TimeZone
} deriving (Eq,Generic,Ord,Show,Typeable)
data TimeZoneStruct = TimeZoneStruct {
_tz_hour :: !Hour
, _tz_min :: !Minute
, _tz_sec :: !Double
, _tz_zone :: !TZ.TimeZone
} deriving (Eq,Generic,Ord,Show,Typeable)
data DateTimeZoneStruct = DateTimeZoneStruct {
_dtz_year :: !Year
, _dtz_mon :: !Month
, _dtz_mday :: !Day
, _dtz_wday :: !DayOfWeek
, _dtz_hour :: !Hour
, _dtz_min :: !Minute
, _dtz_sec :: !Double
, _dtz_zone :: !TZ.TimeZone
} deriving (Eq,Generic,Ord,Show,Typeable)
newtype Year = Year {getYear :: Int32}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
data Month =
January
| February
| March
| April
| May
| June
| July
| August
| September
| October
| November
| December
deriving (Eq,Enum,Generic,Ord,Show,Typeable)
newtype Day = Day {getDay :: Int32}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
data DayOfWeek =
Sunday
| Monday
| Tuesday
| Wednesday
| Thursday
| Friday
| Saturday
deriving (Eq,Enum,Generic,Ord,Show,Typeable)
newtype Hour = Hour {getHour :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Minute = Minute {getMinute :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Second = Second {getSecond :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Millis = Millis {getMillis :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Micros = Micros {getMicros :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Nanos = Nanos {getNanos :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
newtype Picos = Picos {getPicos :: Int64}
deriving (Bounded,Enum,Eq,FromJSON,Generic,Integral,Num,Ord,PrintfArg,Random,Real,ToJSON)
instance FromJSON DateStruct
instance FromJSON DateTimeStruct
instance FromJSON DateZoneStruct
instance FromJSON DateTimeZoneStruct
instance FromJSON DayOfWeek
instance FromJSON Month
instance Random Month where
random = first toEnum . randomR (0, 11)
randomR (a,b) = first toEnum . randomR (fromEnum a, fromEnum b)
instance Random DayOfWeek where
random = first toEnum . randomR (0, 6)
randomR (a,b) = first toEnum . randomR (fromEnum a, fromEnum b)
instance Show Year where show Year {getYear } = show getYear
instance Show Day where show Day {getDay } = show getDay
instance Show Hour where show Hour {getHour } = show getHour
instance Show Minute where show Minute {getMinute} = show getMinute
instance Show Second where show Second {getSecond} = show getSecond
instance Show Millis where show Millis {getMillis} = show getMillis
instance Show Micros where show Micros {getMicros} = show getMicros
instance Show Nanos where show Nanos {getNanos } = show getNanos
instance Show Picos where show Picos {getPicos } = show getPicos
instance ToJSON DateStruct
instance ToJSON DateTimeStruct
instance ToJSON DateZoneStruct
instance ToJSON DateTimeZoneStruct
instance ToJSON DayOfWeek
instance ToJSON Month
properFracMillis :: Floating a => RealFrac a => a -> (Second, Millis)
properFracMillis millis = if res == 1000 then (sec + 1, 0) else result
where result@(sec, res) = fmap (round . (*) 1000) $ properFraction millis
properFracMicros :: Floating a => RealFrac a => a -> (Second, Micros)
properFracMicros micros = if res == 1000000 then (sec + 1, 0) else result
where result@(sec, res) = fmap (round . (*) 1000000) $ properFraction micros
properFracNanos :: Floating a => RealFrac a => a -> (Second, Nanos)
properFracNanos nanos = if res == 1000000000 then (sec + 1, 0) else result
where result@(sec, res) = fmap (round . (*) 1000000000) $ properFraction nanos
properFracPicos :: Floating a => RealFrac a => a -> (Second, Picos)
properFracPicos picos = if res == 1000000000000 then (sec + 1, 0) else result
where result@(sec, res) = fmap (round . (*) 1000000000000) $ properFraction picos
epochToDate :: Year -> Month -> Day -> Day
epochToDate year month day =
epochToYear year + yearToMonth month leap + day 1
where leap = isLeapYear year
epochToYear :: Year -> Day
epochToYear (Year year) =
Day $ (year 1970) * 365 + (year 1969) `div` 004
(year 1901) `div` 100 + (year 1601) `div` 400
yearToMonth :: Month -> Bool -> Day
yearToMonth month leap =
if leap
then
case month of
January -> 000; February -> 031; March -> 060; April -> 091
May -> 121; June -> 152; July -> 182; August -> 213
September -> 244; October -> 274; November -> 305; December -> 335
else
case month of
January -> 000; February -> 031; March -> 059; April -> 090
May -> 120; June -> 151; July -> 181; August -> 212
September -> 243; October -> 273; November -> 304; December -> 334
epochToTime :: Year -> Month -> Day -> Hour -> Minute -> Second -> Second
epochToTime year month day hour minute second =
Second (days * 86400) + midnightToTime hour minute second
where days = fromIntegral $ epochToDate year month day
midnightToTime :: Hour -> Minute -> Second -> Second
midnightToTime (Hour hour) (Minute minute) (Second second) =
Second $ (hour * 3600) + (minute * 60) + second
isLeapYear :: Year -> Bool
isLeapYear year = year `mod` 400 == 0 || (year `mod` 100 /= 0 && year `mod` 4 == 0)
showPeriod :: Hour -> String
showPeriod hour = if hour < 12 then "AM" else "PM"
showSuffix :: Day -> String
showSuffix (Day day) =
if day < 1 || 31 < day
then error $ "showSuffix: unknown day of month"
else case day `mod` 10 of
1 | day /= 11 -> "st"
2 | day /= 12 -> "nd"
3 | day /= 13 -> "rd"
_ -> "th"