{-# LANGUAGE Safe #-}moduleData.Time.Format.ISO8601(-- * FormatFormat ,formatShowM ,formatShow ,formatReadP ,formatParseM -- * Common formats,ISO8601 (..),iso8601Show ,iso8601ParseM -- * All formats,FormatExtension (..),formatReadPExtension ,parseFormatExtension ,calendarFormat ,yearMonthFormat ,yearFormat ,centuryFormat ,expandedCalendarFormat ,expandedYearMonthFormat ,expandedYearFormat ,expandedCenturyFormat ,ordinalDateFormat ,expandedOrdinalDateFormat ,weekDateFormat ,yearWeekFormat ,expandedWeekDateFormat ,expandedYearWeekFormat ,timeOfDayFormat ,hourMinuteFormat ,hourFormat ,withTimeDesignator ,withUTCDesignator ,timeOffsetFormat ,timeOfDayAndOffsetFormat ,localTimeFormat ,zonedTimeFormat ,utcTimeFormat ,dayAndTimeFormat ,timeAndOffsetFormat ,durationDaysFormat ,durationTimeFormat ,alternativeDurationDaysFormat ,alternativeDurationTimeFormat ,intervalFormat ,recurringIntervalFormat )whereimportControl.Monad.FailimportData.FixedimportData.Format importData.RatioimportData.Time importData.Time.Calendar.OrdinalDate importData.Time.Calendar.Private importData.Time.Calendar.WeekDate importPreludehiding(fail)importText.ParserCombinators.ReadPdataFormatExtension =-- | ISO 8601:2004(E) sec. 2.3.4. Use hyphens and colons.ExtendedFormat -- | ISO 8601:2004(E) sec. 2.3.3. Omit hyphens and colons. "The basic format should be avoided in plain text."|BasicFormat -- | Read a value in either extended or basic formatformatReadPExtension ::(FormatExtension ->Format t )->ReadPt formatReadPExtension :: (FormatExtension -> Format t) -> ReadP t formatReadPExtension FormatExtension -> Format t ff =Format t -> ReadP t forall t. Format t -> ReadP t formatReadP (FormatExtension -> Format t ff FormatExtension ExtendedFormat )ReadP t -> ReadP t -> ReadP t forall a. ReadP a -> ReadP a -> ReadP a +++Format t -> ReadP t forall t. Format t -> ReadP t formatReadP (FormatExtension -> Format t ff FormatExtension BasicFormat )-- | Parse a value in either extended or basic formatparseFormatExtension ::(MonadFailm )=>(FormatExtension ->Format t )->String->m t parseFormatExtension :: (FormatExtension -> Format t) -> String -> m t parseFormatExtension FormatExtension -> Format t ff =ReadP t -> String -> m t forall (m :: * -> *) t. MonadFail m => ReadP t -> String -> m t parseReader (ReadP t -> String -> m t) -> ReadP t -> String -> m t forall a b. (a -> b) -> a -> b $(FormatExtension -> Format t) -> ReadP t forall t. (FormatExtension -> Format t) -> ReadP t formatReadPExtension FormatExtension -> Format t ff sepFormat ::String->Format a ->Format b ->Format (a ,b )sepFormat :: String -> Format a -> Format b -> Format (a, b) sepFormat String sep Format a fa Format b fb =(Format a fa Format a -> Format () -> Format a forall (f :: * -> *) a. Productish f => f a -> f () -> f a <** String -> Format () literalFormat String sep )Format a -> Format b -> Format (a, b) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Format b fb dashFormat ::Format a ->Format b ->Format (a ,b )dashFormat :: Format a -> Format b -> Format (a, b) dashFormat =String -> Format a -> Format b -> Format (a, b) forall a b. String -> Format a -> Format b -> Format (a, b) sepFormat String "-"colnFormat ::Format a ->Format b ->Format (a ,b )colnFormat :: Format a -> Format b -> Format (a, b) colnFormat =String -> Format a -> Format b -> Format (a, b) forall a b. String -> Format a -> Format b -> Format (a, b) sepFormat String ":"extDashFormat ::FormatExtension ->Format a ->Format b ->Format (a ,b )extDashFormat :: FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension ExtendedFormat =Format a -> Format b -> Format (a, b) forall a b. Format a -> Format b -> Format (a, b) dashFormat extDashFormat FormatExtension BasicFormat =Format a -> Format b -> Format (a, b) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) (<**>) extColonFormat ::FormatExtension ->Format a ->Format b ->Format (a ,b )extColonFormat :: FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension ExtendedFormat =Format a -> Format b -> Format (a, b) forall a b. Format a -> Format b -> Format (a, b) colnFormat extColonFormat FormatExtension BasicFormat =Format a -> Format b -> Format (a, b) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) (<**>) expandedYearFormat' ::Int->Format IntegerexpandedYearFormat' :: Int -> Format Integer expandedYearFormat' Int n =SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption PosNegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt n )yearFormat' ::Format IntegeryearFormat' :: Format Integer yearFormat' =SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 4)monthFormat ::Format IntmonthFormat :: Format Int monthFormat =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)dayOfMonthFormat ::Format IntdayOfMonthFormat :: Format Int dayOfMonthFormat =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)dayOfYearFormat ::Format IntdayOfYearFormat :: Format Int dayOfYearFormat =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 3)weekOfYearFormat ::Format IntweekOfYearFormat :: Format Int weekOfYearFormat =String -> Format () literalFormat String "W"Format () -> Format Int -> Format Int forall (f :: * -> *) a. Productish f => f () -> f a -> f a **> SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)dayOfWeekFormat ::Format IntdayOfWeekFormat :: Format Int dayOfWeekFormat =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 1)hourFormat' ::Format InthourFormat' :: Format Int hourFormat' =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)dataE14 instanceHasResolutionE14 whereresolution :: p E14 -> Integer resolutionp E14 _=Integer 100000000000000dataE16 instanceHasResolutionE16 whereresolution :: p E16 -> Integer resolution p E16 _=Integer 10000000000000000hourDecimalFormat ::Format (FixedE16 )-- need four extra decimal places for hourshourDecimalFormat :: Format (Fixed E16) hourDecimalFormat =SignOption -> Maybe Int -> Format (Fixed E16) forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t decimalFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)minuteFormat ::Format IntminuteFormat :: Format Int minuteFormat =SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)minuteDecimalFormat ::Format (FixedE14 )-- need two extra decimal places for minutesminuteDecimalFormat :: Format (Fixed E14) minuteDecimalFormat =SignOption -> Maybe Int -> Format (Fixed E14) forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t decimalFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)secondFormat ::Format PicosecondFormat :: Format Pico secondFormat =SignOption -> Maybe Int -> Format Pico forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t decimalFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)mapGregorian ::Format (Integer,(Int,Int))->Format Day mapGregorian :: Format (Integer, (Int, Int)) -> Format Day mapGregorian =((Integer, (Int, Int)) -> Maybe Day) -> (Day -> Maybe (Integer, (Int, Int))) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat (\(Integer y ,(Int m ,Int d ))->Integer -> Int -> Int -> Maybe Day fromGregorianValid Integer y Int m Int d )(\Day day ->(\(Integer y ,Int m ,Int d )->(Integer, (Int, Int)) -> Maybe (Integer, (Int, Int)) forall a. a -> Maybe a Just(Integer y ,(Int m ,Int d )))((Integer, Int, Int) -> Maybe (Integer, (Int, Int))) -> (Integer, Int, Int) -> Maybe (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $Day -> (Integer, Int, Int) toGregorian Day day )mapOrdinalDate ::Format (Integer,Int)->Format Day mapOrdinalDate :: Format (Integer, Int) -> Format Day mapOrdinalDate =((Integer, Int) -> Maybe Day) -> (Day -> Maybe (Integer, Int)) -> Format (Integer, Int) -> Format Day forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat (\(Integer y ,Int d )->Integer -> Int -> Maybe Day fromOrdinalDateValid Integer y Int d )((Integer, Int) -> Maybe (Integer, Int) forall a. a -> Maybe a Just((Integer, Int) -> Maybe (Integer, Int)) -> (Day -> (Integer, Int)) -> Day -> Maybe (Integer, Int) forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Integer, Int) toOrdinalDate )mapWeekDate ::Format (Integer,(Int,Int))->Format Day mapWeekDate :: Format (Integer, (Int, Int)) -> Format Day mapWeekDate =((Integer, (Int, Int)) -> Maybe Day) -> (Day -> Maybe (Integer, (Int, Int))) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat (\(Integer y ,(Int w ,Int d ))->Integer -> Int -> Int -> Maybe Day fromWeekDateValid Integer y Int w Int d )(\Day day ->(\(Integer y ,Int w ,Int d )->(Integer, (Int, Int)) -> Maybe (Integer, (Int, Int)) forall a. a -> Maybe a Just(Integer y ,(Int w ,Int d )))((Integer, Int, Int) -> Maybe (Integer, (Int, Int))) -> (Integer, Int, Int) -> Maybe (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $Day -> (Integer, Int, Int) toWeekDate Day day )mapTimeOfDay ::Format (Int,(Int,Pico))->Format TimeOfDay mapTimeOfDay :: Format (Int, (Int, Pico)) -> Format TimeOfDay mapTimeOfDay =((Int, (Int, Pico)) -> Maybe TimeOfDay) -> (TimeOfDay -> Maybe (Int, (Int, Pico))) -> Format (Int, (Int, Pico)) -> Format TimeOfDay forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat (\(Int h ,(Int m ,Pico s ))->Int -> Int -> Pico -> Maybe TimeOfDay makeTimeOfDayValid Int h Int m Pico s )(\(TimeOfDay Int h Int m Pico s )->(Int, (Int, Pico)) -> Maybe (Int, (Int, Pico)) forall a. a -> Maybe a Just(Int h ,(Int m ,Pico s )))-- | ISO 8601:2004(E) sec. 4.1.2.2calendarFormat ::FormatExtension ->Format Day calendarFormat :: FormatExtension -> Format Day calendarFormat FormatExtension fe =Format (Integer, (Int, Int)) -> Format Day mapGregorian (Format (Integer, (Int, Int)) -> Format Day) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Integer yearFormat (Format (Int, Int) -> Format (Integer, (Int, Int))) -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Int -> Format (Int, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Int monthFormat Format Int dayOfMonthFormat -- | ISO 8601:2004(E) sec. 4.1.2.3(a)yearMonthFormat ::Format (Integer,Int)yearMonthFormat :: Format (Integer, Int) yearMonthFormat =Format Integer yearFormat Format Integer -> Format Int -> Format (Integer, Int) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> String -> Format () literalFormat String "-"Format () -> Format Int -> Format Int forall (f :: * -> *) a. Productish f => f () -> f a -> f a **> Format Int monthFormat -- | ISO 8601:2004(E) sec. 4.1.2.3(b)yearFormat ::Format IntegeryearFormat :: Format Integer yearFormat =Format Integer yearFormat' -- | ISO 8601:2004(E) sec. 4.1.2.3(c)centuryFormat ::Format IntegercenturyFormat :: Format Integer centuryFormat =SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2)-- | ISO 8601:2004(E) sec. 4.1.2.4(a)expandedCalendarFormat ::Int->FormatExtension ->Format Day expandedCalendarFormat :: Int -> FormatExtension -> Format Day expandedCalendarFormat Int n FormatExtension fe =Format (Integer, (Int, Int)) -> Format Day mapGregorian (Format (Integer, (Int, Int)) -> Format Day) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe (Int -> Format Integer expandedYearFormat Int n )(Format (Int, Int) -> Format (Integer, (Int, Int))) -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Int -> Format (Int, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Int monthFormat Format Int dayOfMonthFormat -- | ISO 8601:2004(E) sec. 4.1.2.4(b)expandedYearMonthFormat ::Int->Format (Integer,Int)expandedYearMonthFormat :: Int -> Format (Integer, Int) expandedYearMonthFormat Int n =Format Integer -> Format Int -> Format (Integer, Int) forall a b. Format a -> Format b -> Format (a, b) dashFormat (Int -> Format Integer expandedYearFormat Int n )Format Int monthFormat -- | ISO 8601:2004(E) sec. 4.1.2.4(c)expandedYearFormat ::Int->Format IntegerexpandedYearFormat :: Int -> Format Integer expandedYearFormat =Int -> Format Integer expandedYearFormat' -- | ISO 8601:2004(E) sec. 4.1.2.4(d)expandedCenturyFormat ::Int->Format IntegerexpandedCenturyFormat :: Int -> Format Integer expandedCenturyFormat Int n =SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption PosNegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt n )-- | ISO 8601:2004(E) sec. 4.1.3.2ordinalDateFormat ::FormatExtension ->Format Day ordinalDateFormat :: FormatExtension -> Format Day ordinalDateFormat FormatExtension fe =Format (Integer, Int) -> Format Day mapOrdinalDate (Format (Integer, Int) -> Format Day) -> Format (Integer, Int) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format Int -> Format (Integer, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Integer yearFormat Format Int dayOfYearFormat -- | ISO 8601:2004(E) sec. 4.1.3.3expandedOrdinalDateFormat ::Int->FormatExtension ->Format Day expandedOrdinalDateFormat :: Int -> FormatExtension -> Format Day expandedOrdinalDateFormat Int n FormatExtension fe =Format (Integer, Int) -> Format Day mapOrdinalDate (Format (Integer, Int) -> Format Day) -> Format (Integer, Int) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format Int -> Format (Integer, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe (Int -> Format Integer expandedYearFormat Int n )Format Int dayOfYearFormat -- | ISO 8601:2004(E) sec. 4.1.4.2weekDateFormat ::FormatExtension ->Format Day weekDateFormat :: FormatExtension -> Format Day weekDateFormat FormatExtension fe =Format (Integer, (Int, Int)) -> Format Day mapWeekDate (Format (Integer, (Int, Int)) -> Format Day) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Integer yearFormat (Format (Int, Int) -> Format (Integer, (Int, Int))) -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Int -> Format (Int, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Int weekOfYearFormat Format Int dayOfWeekFormat -- | ISO 8601:2004(E) sec. 4.1.4.3yearWeekFormat ::FormatExtension ->Format (Integer,Int)yearWeekFormat :: FormatExtension -> Format (Integer, Int) yearWeekFormat FormatExtension fe =FormatExtension -> Format Integer -> Format Int -> Format (Integer, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Integer yearFormat Format Int weekOfYearFormat -- | ISO 8601:2004(E) sec. 4.1.4.2expandedWeekDateFormat ::Int->FormatExtension ->Format Day expandedWeekDateFormat :: Int -> FormatExtension -> Format Day expandedWeekDateFormat Int n FormatExtension fe =Format (Integer, (Int, Int)) -> Format Day mapWeekDate (Format (Integer, (Int, Int)) -> Format Day) -> Format (Integer, (Int, Int)) -> Format Day forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe (Int -> Format Integer expandedYearFormat Int n )(Format (Int, Int) -> Format (Integer, (Int, Int))) -> Format (Int, Int) -> Format (Integer, (Int, Int)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Int -> Format (Int, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe Format Int weekOfYearFormat Format Int dayOfWeekFormat -- | ISO 8601:2004(E) sec. 4.1.4.3expandedYearWeekFormat ::Int->FormatExtension ->Format (Integer,Int)expandedYearWeekFormat :: Int -> FormatExtension -> Format (Integer, Int) expandedYearWeekFormat Int n FormatExtension fe =FormatExtension -> Format Integer -> Format Int -> Format (Integer, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe (Int -> Format Integer expandedYearFormat Int n )Format Int weekOfYearFormat -- | ISO 8601:2004(E) sec. 4.2.2.2, 4.2.2.4(a)timeOfDayFormat ::FormatExtension ->Format TimeOfDay timeOfDayFormat :: FormatExtension -> Format TimeOfDay timeOfDayFormat FormatExtension fe =Format (Int, (Int, Pico)) -> Format TimeOfDay mapTimeOfDay (Format (Int, (Int, Pico)) -> Format TimeOfDay) -> Format (Int, (Int, Pico)) -> Format TimeOfDay forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format (Int, Pico) -> Format (Int, (Int, Pico)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe Format Int hourFormat' (Format (Int, Pico) -> Format (Int, (Int, Pico))) -> Format (Int, Pico) -> Format (Int, (Int, Pico)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Pico -> Format (Int, Pico) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe Format Int minuteFormat Format Pico secondFormat -- workaround for the 'fromRational' in 'Fixed', which uses 'floor' instead of 'round'fromRationalRound ::Rational->NominalDiffTime fromRationalRound :: Rational -> NominalDiffTime fromRationalRound Rational r =Rational -> NominalDiffTime forall a. Fractional a => Rational -> a fromRational(Rational -> NominalDiffTime) -> Rational -> NominalDiffTime forall a b. (a -> b) -> a -> b $Rational -> Integer forall a b. (RealFrac a, Integral b) => a -> b round(Rational r Rational -> Rational -> Rational forall a. Num a => a -> a -> a *Rational 1000000000000)Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a %Integer 1000000000000-- | ISO 8601:2004(E) sec. 4.2.2.3(a), 4.2.2.4(b)hourMinuteFormat ::FormatExtension ->Format TimeOfDay hourMinuteFormat :: FormatExtension -> Format TimeOfDay hourMinuteFormat FormatExtension fe =lettoTOD :: (a, a) -> Maybe TimeOfDay toTOD (a h ,a m )=caseNominalDiffTime -> (Integer, TimeOfDay) timeToDaysAndTimeOfDay (NominalDiffTime -> (Integer, TimeOfDay)) -> NominalDiffTime -> (Integer, TimeOfDay) forall a b. (a -> b) -> a -> b $Rational -> NominalDiffTime fromRationalRound (Rational -> NominalDiffTime) -> Rational -> NominalDiffTime forall a b. (a -> b) -> a -> b $a -> Rational forall a. Real a => a -> Rational toRational(a -> Rational) -> a -> Rational forall a b. (a -> b) -> a -> b $(a -> a forall a b. (Integral a, Num b) => a -> b fromIntegrala h )a -> a -> a forall a. Num a => a -> a -> a *a 3600a -> a -> a forall a. Num a => a -> a -> a +a m a -> a -> a forall a. Num a => a -> a -> a *a 60of(Integer 0,TimeOfDay tod )->TimeOfDay -> Maybe TimeOfDay forall a. a -> Maybe a JustTimeOfDay tod (Integer, TimeOfDay) _->Maybe TimeOfDay forall a. Maybe a NothingfromTOD :: TimeOfDay -> Maybe (b, a) fromTOD TimeOfDay tod =letmm :: a mm =(NominalDiffTime -> a forall a b. (Real a, Fractional b) => a -> b realToFrac(NominalDiffTime -> a) -> NominalDiffTime -> a forall a b. (a -> b) -> a -> b $Integer -> TimeOfDay -> NominalDiffTime daysAndTimeOfDayToTime Integer 0TimeOfDay tod )a -> a -> a forall a. Fractional a => a -> a -> a /a 60in(b, a) -> Maybe (b, a) forall a. a -> Maybe a Just((b, a) -> Maybe (b, a)) -> (b, a) -> Maybe (b, a) forall a b. (a -> b) -> a -> b $a -> a -> (b, a) forall a b. (Real a, Integral b) => a -> a -> (b, a) quotRemBy a 60a mm in((Int, Fixed E14) -> Maybe TimeOfDay) -> (TimeOfDay -> Maybe (Int, Fixed E14)) -> Format (Int, Fixed E14) -> Format TimeOfDay forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat (Int, Fixed E14) -> Maybe TimeOfDay forall a a. (Integral a, Real a) => (a, a) -> Maybe TimeOfDay toTOD TimeOfDay -> Maybe (Int, Fixed E14) forall b a. (Integral b, Real a, Fractional a) => TimeOfDay -> Maybe (b, a) fromTOD (Format (Int, Fixed E14) -> Format TimeOfDay) -> Format (Int, Fixed E14) -> Format TimeOfDay forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format (Fixed E14) -> Format (Int, Fixed E14) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe Format Int hourFormat' (Format (Fixed E14) -> Format (Int, Fixed E14)) -> Format (Fixed E14) -> Format (Int, Fixed E14) forall a b. (a -> b) -> a -> b $Format (Fixed E14) minuteDecimalFormat -- | ISO 8601:2004(E) sec. 4.2.2.3(b), 4.2.2.4(c)hourFormat ::Format TimeOfDay hourFormat :: Format TimeOfDay hourFormat =lettoTOD :: a -> Maybe TimeOfDay toTOD a h =caseNominalDiffTime -> (Integer, TimeOfDay) timeToDaysAndTimeOfDay (NominalDiffTime -> (Integer, TimeOfDay)) -> NominalDiffTime -> (Integer, TimeOfDay) forall a b. (a -> b) -> a -> b $Rational -> NominalDiffTime fromRationalRound (Rational -> NominalDiffTime) -> Rational -> NominalDiffTime forall a b. (a -> b) -> a -> b $a -> Rational forall a. Real a => a -> Rational toRational(a -> Rational) -> a -> Rational forall a b. (a -> b) -> a -> b $a h a -> a -> a forall a. Num a => a -> a -> a *a 3600of(Integer 0,TimeOfDay tod )->TimeOfDay -> Maybe TimeOfDay forall a. a -> Maybe a JustTimeOfDay tod (Integer, TimeOfDay) _->Maybe TimeOfDay forall a. Maybe a NothingfromTOD :: TimeOfDay -> Maybe a fromTOD TimeOfDay tod =a -> Maybe a forall a. a -> Maybe a Just(a -> Maybe a) -> a -> Maybe a forall a b. (a -> b) -> a -> b $(NominalDiffTime -> a forall a b. (Real a, Fractional b) => a -> b realToFrac(NominalDiffTime -> a) -> NominalDiffTime -> a forall a b. (a -> b) -> a -> b $Integer -> TimeOfDay -> NominalDiffTime daysAndTimeOfDayToTime Integer 0TimeOfDay tod )a -> a -> a forall a. Fractional a => a -> a -> a /a 3600in(Fixed E16 -> Maybe TimeOfDay) -> (TimeOfDay -> Maybe (Fixed E16)) -> Format (Fixed E16) -> Format TimeOfDay forall a b. (a -> Maybe b) -> (b -> Maybe a) -> Format a -> Format b mapMFormat Fixed E16 -> Maybe TimeOfDay forall a. Real a => a -> Maybe TimeOfDay toTOD TimeOfDay -> Maybe (Fixed E16) forall a. Fractional a => TimeOfDay -> Maybe a fromTOD (Format (Fixed E16) -> Format TimeOfDay) -> Format (Fixed E16) -> Format TimeOfDay forall a b. (a -> b) -> a -> b $Format (Fixed E16) hourDecimalFormat -- | ISO 8601:2004(E) sec. 4.2.2.5withTimeDesignator ::Format t ->Format t withTimeDesignator :: Format t -> Format t withTimeDesignator Format t f =String -> Format () literalFormat String "T"Format () -> Format t -> Format t forall (f :: * -> *) a. Productish f => f () -> f a -> f a **> Format t f -- | ISO 8601:2004(E) sec. 4.2.4withUTCDesignator ::Format t ->Format t withUTCDesignator :: Format t -> Format t withUTCDesignator Format t f =Format t f Format t -> Format () -> Format t forall (f :: * -> *) a. Productish f => f a -> f () -> f a <** String -> Format () literalFormat String "Z"-- | ISO 8601:2004(E) sec. 4.2.5.1timeOffsetFormat ::FormatExtension ->Format TimeZone timeOffsetFormat :: FormatExtension -> Format TimeZone timeOffsetFormat FormatExtension fe =lettoTimeZone :: (Int, (Int, Int)) -> TimeZone toTimeZone (Int sign ,(Int h ,Int m ))=Int -> TimeZone minutesToTimeZone (Int -> TimeZone) -> Int -> TimeZone forall a b. (a -> b) -> a -> b $Int sign Int -> Int -> Int forall a. Num a => a -> a -> a *(Int h Int -> Int -> Int forall a. Num a => a -> a -> a *Int 60Int -> Int -> Int forall a. Num a => a -> a -> a +Int m )fromTimeZone :: TimeZone -> (Int, (Int, Int)) fromTimeZone TimeZone tz =letmm :: Int mm =TimeZone -> Int timeZoneMinutes TimeZone tz hm :: (Int, Int) hm =Int -> Int -> (Int, Int) forall a. Integral a => a -> a -> (a, a) quotRem(Int -> Int forall a. Num a => a -> a absInt mm )Int 60in(Int -> Int forall a. Num a => a -> a signumInt mm ,(Int, Int) hm )in((Int, (Int, Int)) -> TimeZone) -> (TimeZone -> (Int, (Int, Int))) -> Format (Int, (Int, Int)) -> Format TimeZone forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (Int, (Int, Int)) -> TimeZone toTimeZone TimeZone -> (Int, (Int, Int)) fromTimeZone (Format (Int, (Int, Int)) -> Format TimeZone) -> Format (Int, (Int, Int)) -> Format TimeZone forall a b. (a -> b) -> a -> b $Format Int forall t. (Eq t, Num t) => Format t mandatorySignFormat Format Int -> Format (Int, Int) -> Format (Int, (Int, Int)) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> FormatExtension -> Format Int -> Format Int -> Format (Int, Int) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe (SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2))(SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2))-- | ISO 8601:2004(E) sec. 4.2.5.2timeOfDayAndOffsetFormat ::FormatExtension ->Format (TimeOfDay ,TimeZone )timeOfDayAndOffsetFormat :: FormatExtension -> Format (TimeOfDay, TimeZone) timeOfDayAndOffsetFormat FormatExtension fe =FormatExtension -> Format TimeOfDay timeOfDayFormat FormatExtension fe Format TimeOfDay -> Format TimeZone -> Format (TimeOfDay, TimeZone) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> FormatExtension -> Format TimeZone timeOffsetFormat FormatExtension fe -- | ISO 8601:2004(E) sec. 4.3.2localTimeFormat ::Format Day ->Format TimeOfDay ->Format LocalTime localTimeFormat :: Format Day -> Format TimeOfDay -> Format LocalTime localTimeFormat Format Day fday Format TimeOfDay ftod =((Day, TimeOfDay) -> LocalTime) -> (LocalTime -> (Day, TimeOfDay)) -> Format (Day, TimeOfDay) -> Format LocalTime forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (\(Day day ,TimeOfDay tod )->Day -> TimeOfDay -> LocalTime LocalTime Day day TimeOfDay tod )(\(LocalTime Day day TimeOfDay tod )->(Day day ,TimeOfDay tod ))(Format (Day, TimeOfDay) -> Format LocalTime) -> Format (Day, TimeOfDay) -> Format LocalTime forall a b. (a -> b) -> a -> b $Format Day fday Format Day -> Format TimeOfDay -> Format (Day, TimeOfDay) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Format TimeOfDay -> Format TimeOfDay forall t. Format t -> Format t withTimeDesignator Format TimeOfDay ftod -- | ISO 8601:2004(E) sec. 4.3.2zonedTimeFormat ::Format Day ->Format TimeOfDay ->FormatExtension ->Format ZonedTime zonedTimeFormat :: Format Day -> Format TimeOfDay -> FormatExtension -> Format ZonedTime zonedTimeFormat Format Day fday Format TimeOfDay ftod FormatExtension fe =((LocalTime, TimeZone) -> ZonedTime) -> (ZonedTime -> (LocalTime, TimeZone)) -> Format (LocalTime, TimeZone) -> Format ZonedTime forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (\(LocalTime lt ,TimeZone tz )->LocalTime -> TimeZone -> ZonedTime ZonedTime LocalTime lt TimeZone tz )(\(ZonedTime LocalTime lt TimeZone tz )->(LocalTime lt ,TimeZone tz ))(Format (LocalTime, TimeZone) -> Format ZonedTime) -> Format (LocalTime, TimeZone) -> Format ZonedTime forall a b. (a -> b) -> a -> b $Format LocalTime -> FormatExtension -> Format (LocalTime, TimeZone) forall t. Format t -> FormatExtension -> Format (t, TimeZone) timeAndOffsetFormat (Format Day -> Format TimeOfDay -> Format LocalTime localTimeFormat Format Day fday Format TimeOfDay ftod )FormatExtension fe -- | ISO 8601:2004(E) sec. 4.3.2utcTimeFormat ::Format Day ->Format TimeOfDay ->Format UTCTime utcTimeFormat :: Format Day -> Format TimeOfDay -> Format UTCTime utcTimeFormat Format Day fday Format TimeOfDay ftod =(LocalTime -> UTCTime) -> (UTCTime -> LocalTime) -> Format LocalTime -> Format UTCTime forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (TimeZone -> LocalTime -> UTCTime localTimeToUTC TimeZone utc )(TimeZone -> UTCTime -> LocalTime utcToLocalTime TimeZone utc )(Format LocalTime -> Format UTCTime) -> Format LocalTime -> Format UTCTime forall a b. (a -> b) -> a -> b $Format LocalTime -> Format LocalTime forall t. Format t -> Format t withUTCDesignator (Format LocalTime -> Format LocalTime) -> Format LocalTime -> Format LocalTime forall a b. (a -> b) -> a -> b $Format Day -> Format TimeOfDay -> Format LocalTime localTimeFormat Format Day fday Format TimeOfDay ftod -- | ISO 8601:2004(E) sec. 4.3.3dayAndTimeFormat ::Format Day ->Format time ->Format (Day ,time )dayAndTimeFormat :: Format Day -> Format time -> Format (Day, time) dayAndTimeFormat Format Day fday Format time ft =Format Day fday Format Day -> Format time -> Format (Day, time) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Format time -> Format time forall t. Format t -> Format t withTimeDesignator Format time ft -- | ISO 8601:2004(E) sec. 4.3.3timeAndOffsetFormat ::Format t ->FormatExtension ->Format (t ,TimeZone )timeAndOffsetFormat :: Format t -> FormatExtension -> Format (t, TimeZone) timeAndOffsetFormat Format t ft FormatExtension fe =Format t ft Format t -> Format TimeZone -> Format (t, TimeZone) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> FormatExtension -> Format TimeZone timeOffsetFormat FormatExtension fe intDesignator ::(Eqt ,Showt ,Readt ,Numt )=>Char->Format t intDesignator :: Char -> Format t intDesignator Char c =t -> Format t -> Format t forall a. Eq a => a -> Format a -> Format a optionalFormat t 0(Format t -> Format t) -> Format t -> Format t forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format t forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign Maybe Int forall a. Maybe a NothingFormat t -> Format () -> Format t forall (f :: * -> *) a. Productish f => f a -> f () -> f a <** String -> Format () literalFormat [Char c ]decDesignator ::(Eqt ,Showt ,Readt ,Numt )=>Char->Format t decDesignator :: Char -> Format t decDesignator Char c =t -> Format t -> Format t forall a. Eq a => a -> Format a -> Format a optionalFormat t 0(Format t -> Format t) -> Format t -> Format t forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format t forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t decimalFormat SignOption NoSign Maybe Int forall a. Maybe a NothingFormat t -> Format () -> Format t forall (f :: * -> *) a. Productish f => f a -> f () -> f a <** String -> Format () literalFormat [Char c ]daysDesigs ::Format CalendarDiffDays daysDesigs :: Format CalendarDiffDays daysDesigs =lettoCD :: (Integer, (Integer, (Integer, Integer))) -> CalendarDiffDays toCD (Integer y ,(Integer m ,(Integer w ,Integer d )))=Integer -> Integer -> CalendarDiffDays CalendarDiffDays (Integer y Integer -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 12Integer -> Integer -> Integer forall a. Num a => a -> a -> a +Integer m )(Integer w Integer -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 7Integer -> Integer -> Integer forall a. Num a => a -> a -> a +Integer d )fromCD :: CalendarDiffDays -> (Integer, (Integer, (a, Integer))) fromCD (CalendarDiffDays Integer mm Integer d )=(Integer -> Integer -> Integer forall a. Integral a => a -> a -> a quotInteger mm Integer 12,(Integer -> Integer -> Integer forall a. Integral a => a -> a -> a remInteger mm Integer 12,(a 0,Integer d )))in((Integer, (Integer, (Integer, Integer))) -> CalendarDiffDays) -> (CalendarDiffDays -> (Integer, (Integer, (Integer, Integer)))) -> Format (Integer, (Integer, (Integer, Integer))) -> Format CalendarDiffDays forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (Integer, (Integer, (Integer, Integer))) -> CalendarDiffDays toCD CalendarDiffDays -> (Integer, (Integer, (Integer, Integer))) forall a. Num a => CalendarDiffDays -> (Integer, (Integer, (a, Integer))) fromCD (Format (Integer, (Integer, (Integer, Integer))) -> Format CalendarDiffDays) -> Format (Integer, (Integer, (Integer, Integer))) -> Format CalendarDiffDays forall a b. (a -> b) -> a -> b $Char -> Format Integer forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'Y'Format Integer -> Format (Integer, (Integer, Integer)) -> Format (Integer, (Integer, (Integer, Integer))) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Char -> Format Integer forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'M'Format Integer -> Format (Integer, Integer) -> Format (Integer, (Integer, Integer)) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Char -> Format Integer forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'W'Format Integer -> Format Integer -> Format (Integer, Integer) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Char -> Format Integer forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'D'-- | ISO 8601:2004(E) sec. 4.4.3.2durationDaysFormat ::Format CalendarDiffDays durationDaysFormat :: Format CalendarDiffDays durationDaysFormat =Format () -> Format CalendarDiffDays -> Format CalendarDiffDays forall (f :: * -> *) a. Productish f => f () -> f a -> f a (**>) (String -> Format () literalFormat String "P")(Format CalendarDiffDays -> Format CalendarDiffDays) -> Format CalendarDiffDays -> Format CalendarDiffDays forall a b. (a -> b) -> a -> b $(CalendarDiffDays, String) -> Format CalendarDiffDays -> Format CalendarDiffDays forall a. Eq a => (a, String) -> Format a -> Format a specialCaseShowFormat (CalendarDiffDays forall a. Monoid a => a mempty,String "0D")(Format CalendarDiffDays -> Format CalendarDiffDays) -> Format CalendarDiffDays -> Format CalendarDiffDays forall a b. (a -> b) -> a -> b $Format CalendarDiffDays daysDesigs -- | ISO 8601:2004(E) sec. 4.4.3.2durationTimeFormat ::Format CalendarDiffTime durationTimeFormat :: Format CalendarDiffTime durationTimeFormat =lettoCT :: (CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime toCT (CalendarDiffDays cd ,(Int h ,(Int m ,Pico s )))=CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime forall a. Monoid a => a -> a -> a mappend(CalendarDiffDays -> CalendarDiffTime calendarTimeDays CalendarDiffDays cd )(NominalDiffTime -> CalendarDiffTime calendarTimeTime (NominalDiffTime -> CalendarDiffTime) -> NominalDiffTime -> CalendarDiffTime forall a b. (a -> b) -> a -> b $Integer -> TimeOfDay -> NominalDiffTime daysAndTimeOfDayToTime Integer 0(TimeOfDay -> NominalDiffTime) -> TimeOfDay -> NominalDiffTime forall a b. (a -> b) -> a -> b $Int -> Int -> Pico -> TimeOfDay TimeOfDay Int h Int m Pico s )fromCT :: CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico))) fromCT (CalendarDiffTime Integer mm NominalDiffTime t )=let(Integer d ,TimeOfDay Int h Int m Pico s )=NominalDiffTime -> (Integer, TimeOfDay) timeToDaysAndTimeOfDay NominalDiffTime t in(Integer -> Integer -> CalendarDiffDays CalendarDiffDays Integer mm Integer d ,(Int h ,(Int m ,Pico s )))inFormat () -> Format CalendarDiffTime -> Format CalendarDiffTime forall (f :: * -> *) a. Productish f => f () -> f a -> f a (**>) (String -> Format () literalFormat String "P")(Format CalendarDiffTime -> Format CalendarDiffTime) -> Format CalendarDiffTime -> Format CalendarDiffTime forall a b. (a -> b) -> a -> b $(CalendarDiffTime, String) -> Format CalendarDiffTime -> Format CalendarDiffTime forall a. Eq a => (a, String) -> Format a -> Format a specialCaseShowFormat (CalendarDiffTime forall a. Monoid a => a mempty,String "0D")(Format CalendarDiffTime -> Format CalendarDiffTime) -> Format CalendarDiffTime -> Format CalendarDiffTime forall a b. (a -> b) -> a -> b $((CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime) -> (CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico)))) -> Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime toCT CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico))) fromCT (Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime) -> Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime forall a b. (a -> b) -> a -> b $Format CalendarDiffDays -> Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico))) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) (<**>) Format CalendarDiffDays daysDesigs (Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico)))) -> Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico))) forall a b. (a -> b) -> a -> b $(Int, (Int, Pico)) -> Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico)) forall a. Eq a => a -> Format a -> Format a optionalFormat (Int 0,(Int 0,Pico 0))(Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico))) -> Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico)) forall a b. (a -> b) -> a -> b $String -> Format () literalFormat String "T"Format () -> Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico)) forall (f :: * -> *) a. Productish f => f () -> f a -> f a **> Char -> Format Int forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'H'Format Int -> Format (Int, Pico) -> Format (Int, (Int, Pico)) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Char -> Format Int forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t intDesignator Char 'M'Format Int -> Format Pico -> Format (Int, Pico) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) <**> Char -> Format Pico forall t. (Eq t, Show t, Read t, Num t) => Char -> Format t decDesignator Char 'S'-- | ISO 8601:2004(E) sec. 4.4.3.3alternativeDurationDaysFormat ::FormatExtension ->Format CalendarDiffDays alternativeDurationDaysFormat :: FormatExtension -> Format CalendarDiffDays alternativeDurationDaysFormat FormatExtension fe =lettoCD :: (Integer, (Integer, Integer)) -> CalendarDiffDays toCD (Integer y ,(Integer m ,Integer d ))=Integer -> Integer -> CalendarDiffDays CalendarDiffDays (Integer y Integer -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 12Integer -> Integer -> Integer forall a. Num a => a -> a -> a +Integer m )Integer d fromCD :: CalendarDiffDays -> (Integer, (Integer, Integer)) fromCD (CalendarDiffDays Integer mm Integer d )=(Integer -> Integer -> Integer forall a. Integral a => a -> a -> a quotInteger mm Integer 12,(Integer -> Integer -> Integer forall a. Integral a => a -> a -> a remInteger mm Integer 12,Integer d ))in((Integer, (Integer, Integer)) -> CalendarDiffDays) -> (CalendarDiffDays -> (Integer, (Integer, Integer))) -> Format (Integer, (Integer, Integer)) -> Format CalendarDiffDays forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (Integer, (Integer, Integer)) -> CalendarDiffDays toCD CalendarDiffDays -> (Integer, (Integer, Integer)) fromCD (Format (Integer, (Integer, Integer)) -> Format CalendarDiffDays) -> Format (Integer, (Integer, Integer)) -> Format CalendarDiffDays forall a b. (a -> b) -> a -> b $Format () -> Format (Integer, (Integer, Integer)) -> Format (Integer, (Integer, Integer)) forall (f :: * -> *) a. Productish f => f () -> f a -> f a (**>) (String -> Format () literalFormat String "P")(Format (Integer, (Integer, Integer)) -> Format (Integer, (Integer, Integer))) -> Format (Integer, (Integer, Integer)) -> Format (Integer, (Integer, Integer)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format (Integer, Integer) -> Format (Integer, (Integer, Integer)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe ((Integer, Integer) -> Format Integer -> Format Integer forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Integer 0,Integer 9999)(Format Integer -> Format Integer) -> Format Integer -> Format Integer forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Maybe Int -> Format Integer) -> Maybe Int -> Format Integer forall a b. (a -> b) -> a -> b $Int -> Maybe Int forall a. a -> Maybe a JustInt 4)(Format (Integer, Integer) -> Format (Integer, (Integer, Integer))) -> Format (Integer, Integer) -> Format (Integer, (Integer, Integer)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Integer -> Format Integer -> Format (Integer, Integer) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extDashFormat FormatExtension fe ((Integer, Integer) -> Format Integer -> Format Integer forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Integer 0,Integer 12)(Format Integer -> Format Integer) -> Format Integer -> Format Integer forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Maybe Int -> Format Integer) -> Maybe Int -> Format Integer forall a b. (a -> b) -> a -> b $Int -> Maybe Int forall a. a -> Maybe a JustInt 2)(Format Integer -> Format (Integer, Integer)) -> Format Integer -> Format (Integer, Integer) forall a b. (a -> b) -> a -> b $((Integer, Integer) -> Format Integer -> Format Integer forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Integer 0,Integer 30)(Format Integer -> Format Integer) -> Format Integer -> Format Integer forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Integer forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Maybe Int -> Format Integer) -> Maybe Int -> Format Integer forall a b. (a -> b) -> a -> b $Int -> Maybe Int forall a. a -> Maybe a JustInt 2)-- | ISO 8601:2004(E) sec. 4.4.3.3alternativeDurationTimeFormat ::FormatExtension ->Format CalendarDiffTime alternativeDurationTimeFormat :: FormatExtension -> Format CalendarDiffTime alternativeDurationTimeFormat FormatExtension fe =lettoCT :: (CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime toCT (CalendarDiffDays cd ,(Int h ,(Int m ,Pico s )))=CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime forall a. Monoid a => a -> a -> a mappend(CalendarDiffDays -> CalendarDiffTime calendarTimeDays CalendarDiffDays cd )(NominalDiffTime -> CalendarDiffTime calendarTimeTime (NominalDiffTime -> CalendarDiffTime) -> NominalDiffTime -> CalendarDiffTime forall a b. (a -> b) -> a -> b $Integer -> TimeOfDay -> NominalDiffTime daysAndTimeOfDayToTime Integer 0(TimeOfDay -> NominalDiffTime) -> TimeOfDay -> NominalDiffTime forall a b. (a -> b) -> a -> b $Int -> Int -> Pico -> TimeOfDay TimeOfDay Int h Int m Pico s )fromCT :: CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico))) fromCT (CalendarDiffTime Integer mm NominalDiffTime t )=let(Integer d ,TimeOfDay Int h Int m Pico s )=NominalDiffTime -> (Integer, TimeOfDay) timeToDaysAndTimeOfDay NominalDiffTime t in(Integer -> Integer -> CalendarDiffDays CalendarDiffDays Integer mm Integer d ,(Int h ,(Int m ,Pico s )))in((CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime) -> (CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico)))) -> Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (CalendarDiffDays, (Int, (Int, Pico))) -> CalendarDiffTime toCT CalendarDiffTime -> (CalendarDiffDays, (Int, (Int, Pico))) fromCT (Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime) -> Format (CalendarDiffDays, (Int, (Int, Pico))) -> Format CalendarDiffTime forall a b. (a -> b) -> a -> b $Format CalendarDiffDays -> Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico))) forall (f :: * -> *) a b. Productish f => f a -> f b -> f (a, b) (<**>) (FormatExtension -> Format CalendarDiffDays alternativeDurationDaysFormat FormatExtension fe )(Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico)))) -> Format (Int, (Int, Pico)) -> Format (CalendarDiffDays, (Int, (Int, Pico))) forall a b. (a -> b) -> a -> b $Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico)) forall t. Format t -> Format t withTimeDesignator (Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico))) -> Format (Int, (Int, Pico)) -> Format (Int, (Int, Pico)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format (Int, Pico) -> Format (Int, (Int, Pico)) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe ((Int, Int) -> Format Int -> Format Int forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Int 0,Int 24)(Format Int -> Format Int) -> Format Int -> Format Int forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2))(Format (Int, Pico) -> Format (Int, (Int, Pico))) -> Format (Int, Pico) -> Format (Int, (Int, Pico)) forall a b. (a -> b) -> a -> b $FormatExtension -> Format Int -> Format Pico -> Format (Int, Pico) forall a b. FormatExtension -> Format a -> Format b -> Format (a, b) extColonFormat FormatExtension fe ((Int, Int) -> Format Int -> Format Int forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Int 0,Int 60)(Format Int -> Format Int) -> Format Int -> Format Int forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2))(Format Pico -> Format (Int, Pico)) -> Format Pico -> Format (Int, Pico) forall a b. (a -> b) -> a -> b $((Pico, Pico) -> Format Pico -> Format Pico forall a. Ord a => (a, a) -> Format a -> Format a clipFormat (Pico 0,Pico 60)(Format Pico -> Format Pico) -> Format Pico -> Format Pico forall a b. (a -> b) -> a -> b $SignOption -> Maybe Int -> Format Pico forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t decimalFormat SignOption NegSign (Int -> Maybe Int forall a. a -> Maybe a JustInt 2))-- | ISO 8601:2004(E) sec. 4.4.4.1intervalFormat ::Format a ->Format b ->Format (a ,b )intervalFormat :: Format a -> Format b -> Format (a, b) intervalFormat =String -> Format a -> Format b -> Format (a, b) forall a b. String -> Format a -> Format b -> Format (a, b) sepFormat String "/"-- | ISO 8601:2004(E) sec. 4.5recurringIntervalFormat ::Format a ->Format b ->Format (Int,a ,b )recurringIntervalFormat :: Format a -> Format b -> Format (Int, a, b) recurringIntervalFormat Format a fa Format b fb =((Int, (a, b)) -> (Int, a, b)) -> ((Int, a, b) -> (Int, (a, b))) -> Format (Int, (a, b)) -> Format (Int, a, b) forall (f :: * -> *) a b. IsoVariant f => (a -> b) -> (b -> a) -> f a -> f b isoMap (\(Int r ,(a a ,b b ))->(Int r ,a a ,b b ))(\(Int r ,a a ,b b )->(Int r ,(a a ,b b )))(Format (Int, (a, b)) -> Format (Int, a, b)) -> Format (Int, (a, b)) -> Format (Int, a, b) forall a b. (a -> b) -> a -> b $String -> Format Int -> Format (a, b) -> Format (Int, (a, b)) forall a b. String -> Format a -> Format b -> Format (a, b) sepFormat String "/"(String -> Format () literalFormat String "R"Format () -> Format Int -> Format Int forall (f :: * -> *) a. Productish f => f () -> f a -> f a **> SignOption -> Maybe Int -> Format Int forall t. (Show t, Read t, Num t) => SignOption -> Maybe Int -> Format t integerFormat SignOption NoSign Maybe Int forall a. Maybe a Nothing)(Format (a, b) -> Format (Int, (a, b))) -> Format (a, b) -> Format (Int, (a, b)) forall a b. (a -> b) -> a -> b $Format a -> Format b -> Format (a, b) forall a b. Format a -> Format b -> Format (a, b) intervalFormat Format a fa Format b fb classISO8601 t where-- | The most commonly used ISO 8601 format for this type.iso8601Format ::Format t -- | Show in the most commonly used ISO 8601 format.iso8601Show ::ISO8601 t =>t ->Stringiso8601Show :: t -> String iso8601Show =Format t -> t -> String forall t. Format t -> t -> String formatShow Format t forall t. ISO8601 t => Format t iso8601Format -- | Parse the most commonly used ISO 8601 format.iso8601ParseM ::(MonadFailm ,ISO8601 t )=>String->m t iso8601ParseM :: String -> m t iso8601ParseM =Format t -> String -> m t forall (m :: * -> *) t. MonadFail m => Format t -> String -> m t formatParseM Format t forall t. ISO8601 t => Format t iso8601Format -- | @yyyy-mm-dd@ (ISO 8601:2004(E) sec. 4.1.2.2 extended format)instanceISO8601 Day whereiso8601Format :: Format Day iso8601Format =FormatExtension -> Format Day calendarFormat FormatExtension ExtendedFormat -- | @hh:mm:ss[.sss]@ (ISO 8601:2004(E) sec. 4.2.2.2, 4.2.2.4(a) extended format)instanceISO8601 TimeOfDay whereiso8601Format :: Format TimeOfDay iso8601Format =FormatExtension -> Format TimeOfDay timeOfDayFormat FormatExtension ExtendedFormat -- | @±hh:mm@ (ISO 8601:2004(E) sec. 4.2.5.1 extended format)instanceISO8601 TimeZone whereiso8601Format :: Format TimeZone iso8601Format =FormatExtension -> Format TimeZone timeOffsetFormat FormatExtension ExtendedFormat -- | @yyyy-mm-ddThh:mm:ss[.sss]@ (ISO 8601:2004(E) sec. 4.3.2 extended format)instanceISO8601 LocalTime whereiso8601Format :: Format LocalTime iso8601Format =Format Day -> Format TimeOfDay -> Format LocalTime localTimeFormat Format Day forall t. ISO8601 t => Format t iso8601Format Format TimeOfDay forall t. ISO8601 t => Format t iso8601Format -- | @yyyy-mm-ddThh:mm:ss[.sss]±hh:mm@ (ISO 8601:2004(E) sec. 4.3.2 extended format)instanceISO8601 ZonedTime whereiso8601Format :: Format ZonedTime iso8601Format =Format Day -> Format TimeOfDay -> FormatExtension -> Format ZonedTime zonedTimeFormat Format Day forall t. ISO8601 t => Format t iso8601Format Format TimeOfDay forall t. ISO8601 t => Format t iso8601Format FormatExtension ExtendedFormat -- | @yyyy-mm-ddThh:mm:ss[.sss]Z@ (ISO 8601:2004(E) sec. 4.3.2 extended format)instanceISO8601 UTCTime whereiso8601Format :: Format UTCTime iso8601Format =Format Day -> Format TimeOfDay -> Format UTCTime utcTimeFormat Format Day forall t. ISO8601 t => Format t iso8601Format Format TimeOfDay forall t. ISO8601 t => Format t iso8601Format -- | @PyYmMdD@ (ISO 8601:2004(E) sec. 4.4.3.2)instanceISO8601 CalendarDiffDays whereiso8601Format :: Format CalendarDiffDays iso8601Format =Format CalendarDiffDays durationDaysFormat -- | @PyYmMdDThHmMs[.sss]S@ (ISO 8601:2004(E) sec. 4.4.3.2)instanceISO8601 CalendarDiffTime whereiso8601Format :: Format CalendarDiffTime iso8601Format =Format CalendarDiffTime durationTimeFormat