{-# LANGUAGE Safe #-}moduleData.Time.LocalTime.Internal.TimeOfDay(-- * Time of dayTimeOfDay (..),midnight ,midday ,makeTimeOfDayValid ,timeToDaysAndTimeOfDay ,daysAndTimeOfDayToTime ,utcToLocalTimeOfDay ,localToUTCTimeOfDay ,timeToTimeOfDay ,pastMidnight ,timeOfDayToTime ,sinceMidnight ,dayFractionToTimeOfDay ,timeOfDayToDayFraction ,)whereimportControl.DeepSeqimportData.DataimportData.FixedimportData.Time.Calendar.Private importData.Time.Clock.Internal.DiffTime importData.Time.Clock.Internal.NominalDiffTime importData.Time.LocalTime.Internal.TimeZone -- | Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.---- @TimeOfDay 24 0 0@ is considered invalid for the purposes of 'makeTimeOfDayValid', as well as reading and parsing,-- but valid for ISO 8601 parsing in "Data.Time.Format.ISO8601".dataTimeOfDay =TimeOfDay {TimeOfDay -> Int todHour ::Int-- ^ range 0 - 23,TimeOfDay -> Int todMin ::Int-- ^ range 0 - 59,TimeOfDay -> Pico todSec ::Pico-- ^ Note that 0 <= 'todSec' < 61, accomodating leap seconds.-- Any local minute may have a leap second, since leap seconds happen in all zones simultaneously}deriving(TimeOfDay -> TimeOfDay -> Bool (TimeOfDay -> TimeOfDay -> Bool) -> (TimeOfDay -> TimeOfDay -> Bool) -> Eq TimeOfDay forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TimeOfDay -> TimeOfDay -> Bool $c/= :: TimeOfDay -> TimeOfDay -> Bool == :: TimeOfDay -> TimeOfDay -> Bool $c== :: TimeOfDay -> TimeOfDay -> Bool Eq,Eq TimeOfDay Eq TimeOfDay -> (TimeOfDay -> TimeOfDay -> Ordering) -> (TimeOfDay -> TimeOfDay -> Bool) -> (TimeOfDay -> TimeOfDay -> Bool) -> (TimeOfDay -> TimeOfDay -> Bool) -> (TimeOfDay -> TimeOfDay -> Bool) -> (TimeOfDay -> TimeOfDay -> TimeOfDay) -> (TimeOfDay -> TimeOfDay -> TimeOfDay) -> Ord TimeOfDay TimeOfDay -> TimeOfDay -> Bool TimeOfDay -> TimeOfDay -> Ordering TimeOfDay -> TimeOfDay -> TimeOfDay forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: TimeOfDay -> TimeOfDay -> TimeOfDay $cmin :: TimeOfDay -> TimeOfDay -> TimeOfDay max :: TimeOfDay -> TimeOfDay -> TimeOfDay $cmax :: TimeOfDay -> TimeOfDay -> TimeOfDay >= :: TimeOfDay -> TimeOfDay -> Bool $c>= :: TimeOfDay -> TimeOfDay -> Bool > :: TimeOfDay -> TimeOfDay -> Bool $c> :: TimeOfDay -> TimeOfDay -> Bool <= :: TimeOfDay -> TimeOfDay -> Bool $c<= :: TimeOfDay -> TimeOfDay -> Bool < :: TimeOfDay -> TimeOfDay -> Bool $c< :: TimeOfDay -> TimeOfDay -> Bool compare :: TimeOfDay -> TimeOfDay -> Ordering $ccompare :: TimeOfDay -> TimeOfDay -> Ordering $cp1Ord :: Eq TimeOfDay Ord,Typeable TimeOfDay DataType Constr Typeable TimeOfDay -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay) -> (TimeOfDay -> Constr) -> (TimeOfDay -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay)) -> ((forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r) -> (forall u. (forall d. Data d => d -> u) -> TimeOfDay -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay) -> Data TimeOfDay TimeOfDay -> DataType TimeOfDay -> Constr (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u forall u. (forall d. Data d => d -> u) -> TimeOfDay -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) $cTimeOfDay :: Constr $tTimeOfDay :: DataType gmapMo :: (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay gmapMp :: (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay gmapM :: (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> TimeOfDay -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay $cgmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) dataTypeOf :: TimeOfDay -> DataType $cdataTypeOf :: TimeOfDay -> DataType toConstr :: TimeOfDay -> Constr $ctoConstr :: TimeOfDay -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay $cp1Data :: Typeable TimeOfDay Data,Typeable)instanceNFDataTimeOfDay wherernf :: TimeOfDay -> () rnf(TimeOfDay Int h Int m Pico s )=Int -> () forall a. NFData a => a -> () rnfInt h () -> () -> () `seq`Int -> () forall a. NFData a => a -> () rnfInt m () -> () -> () `seq`Pico -> () forall a. NFData a => a -> () rnfPico s () -> () -> () `seq`()-- | Hour zeromidnight ::TimeOfDay midnight :: TimeOfDay midnight =Int -> Int -> Pico -> TimeOfDay TimeOfDay Int 0Int 0Pico 0-- | Hour twelvemidday ::TimeOfDay midday :: TimeOfDay midday =Int -> Int -> Pico -> TimeOfDay TimeOfDay Int 12Int 0Pico 0instanceShowTimeOfDay whereshow :: TimeOfDay -> String show(TimeOfDay Int h Int m Pico s )=(Int -> String forall t. ShowPadded t => t -> String show2 Int h )String -> ShowS forall a. [a] -> [a] -> [a] ++String ":"String -> ShowS forall a. [a] -> [a] -> [a] ++(Int -> String forall t. ShowPadded t => t -> String show2 Int m )String -> ShowS forall a. [a] -> [a] -> [a] ++String ":"String -> ShowS forall a. [a] -> [a] -> [a] ++(Pico -> String show2Fixed Pico s )makeTimeOfDayValid ::Int->Int->Pico->MaybeTimeOfDay makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay makeTimeOfDayValid Int h Int m Pico s =doInt _<-Int -> Int -> Int -> Maybe Int forall t. Ord t => t -> t -> t -> Maybe t clipValid Int 0Int 23Int h Int _<-Int -> Int -> Int -> Maybe Int forall t. Ord t => t -> t -> t -> Maybe t clipValid Int 0Int 59Int m Pico _<-Pico -> Pico -> Pico -> Maybe Pico forall t. Ord t => t -> t -> t -> Maybe t clipValid Pico 0Pico 60.999999999999Pico s TimeOfDay -> Maybe TimeOfDay forall (m :: * -> *) a. Monad m => a -> m a return(Int -> Int -> Pico -> TimeOfDay TimeOfDay Int h Int m Pico s )-- | Convert a period of time into a count of days and a time of day since midnight.-- The time of day will never have a leap second.timeToDaysAndTimeOfDay ::NominalDiffTime ->(Integer,TimeOfDay )timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay) timeToDaysAndTimeOfDay NominalDiffTime dt =lets :: Pico s =NominalDiffTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFracNominalDiffTime dt (Int m ,Pico ms )=Pico -> Pico -> (Int, Pico) forall a b. (Real a, Integral b) => a -> a -> (b, a) divMod'Pico s Pico 60(Int h ,Int hm )=Int -> Int -> (Int, Int) forall a b. (Real a, Integral b) => a -> a -> (b, a) divMod'Int m Int 60(Integer d ,Int dh )=Int -> Int -> (Integer, Int) forall a b. (Real a, Integral b) => a -> a -> (b, a) divMod'Int h Int 24in(Integer d ,Int -> Int -> Pico -> TimeOfDay TimeOfDay Int dh Int hm Pico ms )-- | Convert a count of days and a time of day since midnight into a period of time.daysAndTimeOfDayToTime ::Integer->TimeOfDay ->NominalDiffTime daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime daysAndTimeOfDayToTime Integer d (TimeOfDay Int dh Int hm Pico ms )=NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (+)(Pico -> NominalDiffTime forall a b. (Real a, Fractional b) => a -> b realToFracPico ms )(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (*)NominalDiffTime 60(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (+)(Int -> NominalDiffTime forall a b. (Real a, Fractional b) => a -> b realToFracInt hm )(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (*)NominalDiffTime 60(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (+)(Int -> NominalDiffTime forall a b. (Real a, Fractional b) => a -> b realToFracInt dh )(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $NominalDiffTime -> NominalDiffTime -> NominalDiffTime forall a. Num a => a -> a -> a (*)NominalDiffTime 24(NominalDiffTime -> NominalDiffTime) -> NominalDiffTime -> NominalDiffTime forall a b. (a -> b) -> a -> b $Integer -> NominalDiffTime forall a b. (Real a, Fractional b) => a -> b realToFracInteger d -- | Convert a time of day in UTC to a time of day in some timezone, together with a day adjustment.utcToLocalTimeOfDay ::TimeZone ->TimeOfDay ->(Integer,TimeOfDay )utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) utcToLocalTimeOfDay TimeZone zone (TimeOfDay Int h Int m Pico s )=(Int -> Integer forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Int -> Int forall a. Integral a => a -> a -> a divInt h' Int 24),Int -> Int -> Pico -> TimeOfDay TimeOfDay (Int -> Int -> Int forall a. Integral a => a -> a -> a modInt h' Int 24)(Int -> Int -> Int forall a. Integral a => a -> a -> a modInt m' Int 60)Pico s )wherem' :: Int m' =Int m Int -> Int -> Int forall a. Num a => a -> a -> a +TimeZone -> Int timeZoneMinutes TimeZone zone h' :: Int h' =Int h Int -> Int -> Int forall a. Num a => a -> a -> a +(Int -> Int -> Int forall a. Integral a => a -> a -> a divInt m' Int 60)-- | Convert a time of day in some timezone to a time of day in UTC, together with a day adjustment.localToUTCTimeOfDay ::TimeZone ->TimeOfDay ->(Integer,TimeOfDay )localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) localToUTCTimeOfDay TimeZone zone =TimeZone -> TimeOfDay -> (Integer, TimeOfDay) utcToLocalTimeOfDay (Int -> TimeZone minutesToTimeZone (Int -> Int forall a. Num a => a -> a negate(TimeZone -> Int timeZoneMinutes TimeZone zone )))posixDayLength ::DiffTime posixDayLength :: DiffTime posixDayLength =Integer -> DiffTime forall a. Num a => Integer -> a fromIntegerInteger 86400-- | Get the time of day given a time since midnight.-- Time more than 24h will be converted to leap-seconds.timeToTimeOfDay ::DiffTime ->TimeOfDay timeToTimeOfDay :: DiffTime -> TimeOfDay timeToTimeOfDay DiffTime dt |DiffTime dt DiffTime -> DiffTime -> Bool forall a. Ord a => a -> a -> Bool >=DiffTime posixDayLength =Int -> Int -> Pico -> TimeOfDay TimeOfDay Int 23Int 59(Pico 60Pico -> Pico -> Pico forall a. Num a => a -> a -> a +(DiffTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFrac(DiffTime dt DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a -DiffTime posixDayLength )))timeToTimeOfDay DiffTime dt =Int -> Int -> Pico -> TimeOfDay TimeOfDay (Integer -> Int forall a. Num a => Integer -> a fromIntegerInteger h )(Integer -> Int forall a. Num a => Integer -> a fromIntegerInteger m )Pico s wheres' :: Pico s' =DiffTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFracDiffTime dt s :: Pico s =Pico -> Pico -> Pico forall a. Real a => a -> a -> a mod'Pico s' Pico 60m' :: Integer m' =Pico -> Pico -> Integer forall a b. (Real a, Integral b) => a -> a -> b div'Pico s' Pico 60m :: Integer m =Integer -> Integer -> Integer forall a. Real a => a -> a -> a mod'Integer m' Integer 60h :: Integer h =Integer -> Integer -> Integer forall a b. (Real a, Integral b) => a -> a -> b div'Integer m' Integer 60-- | Same as 'timeToTimeOfDay'.pastMidnight ::DiffTime ->TimeOfDay pastMidnight :: DiffTime -> TimeOfDay pastMidnight =DiffTime -> TimeOfDay timeToTimeOfDay -- | Get the time since midnight for a given time of day.timeOfDayToTime ::TimeOfDay ->DiffTime timeOfDayToTime :: TimeOfDay -> DiffTime timeOfDayToTime (TimeOfDay Int h Int m Pico s )=((Int -> DiffTime forall a b. (Integral a, Num b) => a -> b fromIntegralInt h )DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a *DiffTime 60DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a +(Int -> DiffTime forall a b. (Integral a, Num b) => a -> b fromIntegralInt m ))DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a *DiffTime 60DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a +(Pico -> DiffTime forall a b. (Real a, Fractional b) => a -> b realToFracPico s )-- | Same as 'timeOfDayToTime'.sinceMidnight ::TimeOfDay ->DiffTime sinceMidnight :: TimeOfDay -> DiffTime sinceMidnight =TimeOfDay -> DiffTime timeOfDayToTime -- | Get the time of day given the fraction of a day since midnight.dayFractionToTimeOfDay ::Rational->TimeOfDay dayFractionToTimeOfDay :: Rational -> TimeOfDay dayFractionToTimeOfDay Rational df =DiffTime -> TimeOfDay timeToTimeOfDay (Rational -> DiffTime forall a b. (Real a, Fractional b) => a -> b realToFrac(Rational df Rational -> Rational -> Rational forall a. Num a => a -> a -> a *Rational 86400))-- | Get the fraction of a day since midnight given a time of day.timeOfDayToDayFraction ::TimeOfDay ->RationaltimeOfDayToDayFraction :: TimeOfDay -> Rational timeOfDayToDayFraction TimeOfDay tod =DiffTime -> Rational forall a b. (Real a, Fractional b) => a -> b realToFrac(TimeOfDay -> DiffTime timeOfDayToTime TimeOfDay tod )Rational -> Rational -> Rational forall a. Fractional a => a -> a -> a /DiffTime -> Rational forall a b. (Real a, Fractional b) => a -> b realToFracDiffTime posixDayLength