{-# LANGUAGE Safe #-}
{-# OPTIONS -fno-warn-orphans #-}
module Data.Time.Format.Format.Instances (
    ) where
import Control.Applicative ((<|>))
import Data.Char
import Data.Fixed
import Data.Time.Calendar.CalendarDiffDays
import Data.Time.Calendar.Days
import Data.Time.Calendar.Gregorian
import Data.Time.Calendar.Month
import Data.Time.Calendar.OrdinalDate
import Data.Time.Calendar.Private
import Data.Time.Calendar.Week
import Data.Time.Calendar.WeekDate
import Data.Time.Clock.Internal.DiffTime
import Data.Time.Clock.Internal.NominalDiffTime
import Data.Time.Clock.Internal.UTCTime
import Data.Time.Clock.Internal.UniversalTime
import Data.Time.Clock.POSIX
import Data.Time.Format.Format.Class
import Data.Time.Format.Locale
import Data.Time.LocalTime.Internal.CalendarDiffTime
import Data.Time.LocalTime.Internal.LocalTime
import Data.Time.LocalTime.Internal.TimeOfDay
import Data.Time.LocalTime.Internal.TimeZone
import Data.Time.LocalTime.Internal.ZonedTime
mapFormatCharacter :: (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String)
mapFormatCharacter :: forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter b -> a
ba = ((FormatOptions -> a -> String) -> FormatOptions -> b -> String)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((FormatOptions -> a -> String) -> FormatOptions -> b -> String)
 -> Maybe (FormatOptions -> a -> String)
 -> Maybe (FormatOptions -> b -> String))
-> ((FormatOptions -> a -> String) -> FormatOptions -> b -> String)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
forall a b. (a -> b) -> a -> b
$ ((a -> String) -> b -> String)
-> (FormatOptions -> a -> String) -> FormatOptions -> b -> String
forall a b. (a -> b) -> (FormatOptions -> a) -> FormatOptions -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((a -> String) -> b -> String)
 -> (FormatOptions -> a -> String) -> FormatOptions -> b -> String)
-> ((a -> String) -> b -> String)
-> (FormatOptions -> a -> String)
-> FormatOptions
-> b
-> String
forall a b. (a -> b) -> a -> b
$ \a -> String
as -> a -> String
as (a -> String) -> (b -> a) -> b -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a
ba
instance FormatTime LocalTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String)
formatCharacter Bool
_ Char
'c' = (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> LocalTime -> String)
 -> Maybe (FormatOptions -> LocalTime -> String))
-> (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
forall a b. (a -> b) -> a -> b
$ \FormatOptions
fo -> TimeLocale -> String -> LocalTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime (FormatOptions -> TimeLocale
foLocale FormatOptions
fo) (String -> LocalTime -> String) -> String -> LocalTime -> String
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String
dateTimeFmt (TimeLocale -> String) -> TimeLocale -> String
forall a b. (a -> b) -> a -> b
$ FormatOptions -> TimeLocale
foLocale FormatOptions
fo
    formatCharacter Bool
alt Char
c =
        (LocalTime -> Day)
-> Maybe (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter LocalTime -> Day
localDay (Bool -> Char -> Maybe (FormatOptions -> Day -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c)
            Maybe (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (LocalTime -> TimeOfDay)
-> Maybe (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> LocalTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter LocalTime -> TimeOfDay
localTimeOfDay (Bool -> Char -> Maybe (FormatOptions -> TimeOfDay -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c)
todAMPM :: TimeLocale -> TimeOfDay -> String
todAMPM :: TimeLocale -> TimeOfDay -> String
todAMPM TimeLocale
locale TimeOfDay
day = let
    (String
am, String
pm) = TimeLocale -> (String, String)
amPm TimeLocale
locale
    in if (TimeOfDay -> Int
todHour TimeOfDay
day) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
12
        then String
am
        else String
pm
tod12Hour :: TimeOfDay -> Int
tod12Hour :: TimeOfDay -> Int
tod12Hour TimeOfDay
day = (Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (TimeOfDay -> Int
todHour TimeOfDay
day Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
12) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
instance FormatTime TimeOfDay where
    
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeOfDay -> String)
formatCharacter Bool
_ Char
'R' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> TimeOfDay -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
"%H:%M"
    formatCharacter Bool
_ Char
'T' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> TimeOfDay -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
"%H:%M:%S"
    formatCharacter Bool
_ Char
'X' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> TimeOfDay -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale (TimeLocale -> String
timeFmt TimeLocale
locale)
    formatCharacter Bool
_ Char
'r' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> TimeOfDay -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale (TimeLocale -> String
time12Fmt TimeLocale
locale)
    
    formatCharacter Bool
_ Char
'P' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (String -> String) -> (TimeOfDay -> String) -> TimeOfDay -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> TimeOfDay -> String
todAMPM TimeLocale
locale
    formatCharacter Bool
_ Char
'p' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> TimeOfDay -> String)
-> FormatOptions -> TimeOfDay -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> TimeOfDay -> String
todAMPM TimeLocale
locale
    
    formatCharacter Bool
_ Char
'H' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' TimeOfDay -> Int
todHour
    formatCharacter Bool
_ Char
'I' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' TimeOfDay -> Int
tod12Hour
    formatCharacter Bool
_ Char
'k' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
' ' TimeOfDay -> Int
todHour
    formatCharacter Bool
_ Char
'l' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
' ' TimeOfDay -> Int
tod12Hour
    
    formatCharacter Bool
_ Char
'M' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' TimeOfDay -> Int
todMin
    
    formatCharacter Bool
_ Char
'S' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (TimeOfDay -> Int)
-> FormatOptions
-> TimeOfDay
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String)
-> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String
forall a b. (a -> b) -> a -> b
$ (Pico -> Int
forall b. Integral b => Pico -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (Pico -> Int) -> (TimeOfDay -> Pico) -> TimeOfDay -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeOfDay -> Pico
todSec :: TimeOfDay -> Int)
    formatCharacter Bool
_ Char
'q' = (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
True Int
12 Char
'0' ((TimeLocale -> PadOption -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> PadOption -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
pado -> PadOption -> Pico -> String
forall a. HasResolution a => PadOption -> Fixed a -> String
showPaddedFixedFraction PadOption
pado (Pico -> String) -> (TimeOfDay -> Pico) -> TimeOfDay -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeOfDay -> Pico
todSec
    formatCharacter Bool
_ Char
'Q' =
        (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeOfDay -> String)
 -> Maybe (FormatOptions -> TimeOfDay -> String))
-> (FormatOptions -> TimeOfDay -> String)
-> Maybe (FormatOptions -> TimeOfDay -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
False Int
12 Char
'0' ((TimeLocale -> PadOption -> TimeOfDay -> String)
 -> FormatOptions -> TimeOfDay -> String)
-> (TimeLocale -> PadOption -> TimeOfDay -> String)
-> FormatOptions
-> TimeOfDay
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
pado -> String -> String
dotNonEmpty (String -> String) -> (TimeOfDay -> String) -> TimeOfDay -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PadOption -> Pico -> String
forall a. HasResolution a => PadOption -> Fixed a -> String
showPaddedFixedFraction PadOption
pado (Pico -> String) -> (TimeOfDay -> Pico) -> TimeOfDay -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeOfDay -> Pico
todSec
      where
        dotNonEmpty :: String -> String
dotNonEmpty String
"" = String
""
        dotNonEmpty String
s = Char
'.' Char -> String -> String
forall a. a -> [a] -> [a]
: String
s
    
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> TimeOfDay -> String)
forall a. Maybe a
Nothing
instance FormatTime ZonedTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String)
formatCharacter Bool
_ Char
'c' = (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> ZonedTime -> String)
 -> Maybe (FormatOptions -> ZonedTime -> String))
-> (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> ZonedTime -> String)
-> FormatOptions -> ZonedTime -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> ZonedTime -> String)
 -> FormatOptions -> ZonedTime -> String)
-> (TimeLocale -> ZonedTime -> String)
-> FormatOptions
-> ZonedTime
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> ZonedTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale (TimeLocale -> String
dateTimeFmt TimeLocale
locale)
    formatCharacter Bool
_ Char
's' =
        (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> ZonedTime -> String)
 -> Maybe (FormatOptions -> ZonedTime -> String))
-> (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (ZonedTime -> Integer)
-> FormatOptions
-> ZonedTime
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
1 Char
'0' ((ZonedTime -> Integer) -> FormatOptions -> ZonedTime -> String)
-> (ZonedTime -> Integer) -> FormatOptions -> ZonedTime -> String
forall a b. (a -> b) -> a -> b
$ (POSIXTime -> Integer
forall b. Integral b => POSIXTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Integer)
-> (ZonedTime -> POSIXTime) -> ZonedTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> POSIXTime)
-> (ZonedTime -> UTCTime) -> ZonedTime -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZonedTime -> UTCTime
zonedTimeToUTC :: ZonedTime -> Integer)
    formatCharacter Bool
alt Char
c =
        (ZonedTime -> LocalTime)
-> Maybe (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter ZonedTime -> LocalTime
zonedTimeToLocalTime (Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c)
            Maybe (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ZonedTime -> TimeZone)
-> Maybe (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> ZonedTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter ZonedTime -> TimeZone
zonedTimeZone (Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c)
instance FormatTime TimeZone where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String)
formatCharacter Bool
False Char
'z' = (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeZone -> String)
 -> Maybe (FormatOptions -> TimeZone -> String))
-> (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> TimeZone -> String)
-> FormatOptions
-> TimeZone
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
False Bool
True Int
4 Char
'0' ((TimeLocale -> PadOption -> TimeZone -> String)
 -> FormatOptions -> TimeZone -> String)
-> (TimeLocale -> PadOption -> TimeZone -> String)
-> FormatOptions
-> TimeZone
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ -> Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
False
    formatCharacter Bool
True Char
'z' = (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeZone -> String)
 -> Maybe (FormatOptions -> TimeZone -> String))
-> (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> TimeZone -> String)
-> FormatOptions
-> TimeZone
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
False Bool
True Int
5 Char
'0' ((TimeLocale -> PadOption -> TimeZone -> String)
 -> FormatOptions -> TimeZone -> String)
-> (TimeLocale -> PadOption -> TimeZone -> String)
-> FormatOptions
-> TimeZone
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ -> Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
True
    formatCharacter Bool
alt Char
'Z' =
        (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> TimeZone -> String)
 -> Maybe (FormatOptions -> TimeZone -> String))
-> (FormatOptions -> TimeZone -> String)
-> Maybe (FormatOptions -> TimeZone -> String)
forall a b. (a -> b) -> a -> b
$ \FormatOptions
fo TimeZone
z -> let
            n :: String
n = TimeZone -> String
timeZoneName TimeZone
z
            idef :: Int
idef =
                if Bool
alt
                    then Int
5
                    else Int
4
            in if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
n
                then Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> TimeZone -> String)
-> FormatOptions
-> TimeZone
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
False Bool
True Int
idef Char
'0' (\TimeLocale
_ -> Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
alt) FormatOptions
fo TimeZone
z
                else (TimeLocale -> TimeZone -> String)
-> FormatOptions -> TimeZone -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString (\TimeLocale
_ -> TimeZone -> String
timeZoneName) FormatOptions
fo TimeZone
z
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> TimeZone -> String)
forall a. Maybe a
Nothing
instance FormatTime DayOfWeek where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DayOfWeek -> String)
formatCharacter Bool
_ Char
'u' = (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DayOfWeek -> String)
 -> Maybe (FormatOptions -> DayOfWeek -> String))
-> (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (DayOfWeek -> Int)
-> FormatOptions
-> DayOfWeek
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
1 Char
'0' ((DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String)
-> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String
forall a b. (a -> b) -> a -> b
$ DayOfWeek -> Int
forall a. Enum a => a -> Int
fromEnum
    formatCharacter Bool
_ Char
'w' = (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DayOfWeek -> String)
 -> Maybe (FormatOptions -> DayOfWeek -> String))
-> (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (DayOfWeek -> Int)
-> FormatOptions
-> DayOfWeek
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
1 Char
'0' ((DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String)
-> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String
forall a b. (a -> b) -> a -> b
$ \DayOfWeek
wd -> (Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (DayOfWeek -> Int
forall a. Enum a => a -> Int
fromEnum DayOfWeek
wd) Int
7)
    formatCharacter Bool
_ Char
'a' = (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DayOfWeek -> String)
 -> Maybe (FormatOptions -> DayOfWeek -> String))
-> (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> DayOfWeek -> String)
-> FormatOptions -> DayOfWeek -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> DayOfWeek -> String)
 -> FormatOptions -> DayOfWeek -> String)
-> (TimeLocale -> DayOfWeek -> String)
-> FormatOptions
-> DayOfWeek
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale DayOfWeek
wd -> (String, String) -> String
forall a b. (a, b) -> b
snd ((String, String) -> String) -> (String, String) -> String
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> [(String, String)]
wDays TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!! (Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (DayOfWeek -> Int
forall a. Enum a => a -> Int
fromEnum DayOfWeek
wd) Int
7)
    formatCharacter Bool
_ Char
'A' = (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DayOfWeek -> String)
 -> Maybe (FormatOptions -> DayOfWeek -> String))
-> (FormatOptions -> DayOfWeek -> String)
-> Maybe (FormatOptions -> DayOfWeek -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> DayOfWeek -> String)
-> FormatOptions -> DayOfWeek -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> DayOfWeek -> String)
 -> FormatOptions -> DayOfWeek -> String)
-> (TimeLocale -> DayOfWeek -> String)
-> FormatOptions
-> DayOfWeek
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale DayOfWeek
wd -> (String, String) -> String
forall a b. (a, b) -> a
fst ((String, String) -> String) -> (String, String) -> String
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> [(String, String)]
wDays TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!! (Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (DayOfWeek -> Int
forall a. Enum a => a -> Int
fromEnum DayOfWeek
wd) Int
7)
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> DayOfWeek -> String)
forall a. Maybe a
Nothing
instance FormatTime Month where
    
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> Month -> String)
formatCharacter Bool
_ Char
'Y' = (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Month -> Integer)
-> FormatOptions
-> Month
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
False Int
4 Char
'0' ((Month -> Integer) -> FormatOptions -> Month -> String)
-> (Month -> Integer) -> FormatOptions -> Month -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonth Integer
y Int
_) -> Integer
y
    formatCharacter Bool
_ Char
'y' = (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Month -> Integer)
-> FormatOptions
-> Month
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Month -> Integer) -> FormatOptions -> Month -> String)
-> (Month -> Integer) -> FormatOptions -> Month -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonth Integer
y Int
_) -> Integer -> Integer
forall i. Integral i => i -> i
mod100 Integer
y
    formatCharacter Bool
_ Char
'C' = (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Month -> Integer)
-> FormatOptions
-> Month
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
False Int
2 Char
'0' ((Month -> Integer) -> FormatOptions -> Month -> String)
-> (Month -> Integer) -> FormatOptions -> Month -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonth Integer
y Int
_) -> Integer -> Integer
forall i. Integral i => i -> i
div100 Integer
y
    
    formatCharacter Bool
_ Char
'B' =
        (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Month -> String)
 -> FormatOptions -> Month -> String)
-> (TimeLocale -> Month -> String)
-> FormatOptions
-> Month
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale (YearMonth Integer
_ Int
my) -> (String, String) -> String
forall a b. (a, b) -> a
fst ((String, String) -> String) -> (String, String) -> String
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> [(String, String)]
months TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
my Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    formatCharacter Bool
_ Char
'b' =
        (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Month -> String)
 -> FormatOptions -> Month -> String)
-> (TimeLocale -> Month -> String)
-> FormatOptions
-> Month
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale (YearMonth Integer
_ Int
my) -> (String, String) -> String
forall a b. (a, b) -> b
snd ((String, String) -> String) -> (String, String) -> String
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> [(String, String)]
months TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
my Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    formatCharacter Bool
_ Char
'h' =
        (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Month -> String)
 -> FormatOptions -> Month -> String)
-> (TimeLocale -> Month -> String)
-> FormatOptions
-> Month
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale (YearMonth Integer
_ Int
my) -> (String, String) -> String
forall a b. (a, b) -> b
snd ((String, String) -> String) -> (String, String) -> String
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> [(String, String)]
months TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
my Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    formatCharacter Bool
_ Char
'm' = (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Month -> String))
-> (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Month -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Month -> Int)
-> FormatOptions
-> Month
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Month -> Int) -> FormatOptions -> Month -> String)
-> (Month -> Int) -> FormatOptions -> Month -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonth Integer
_ Int
m) -> Int
m
    
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> Month -> String)
forall a. Maybe a
Nothing
instance FormatTime Day where
    
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> Day -> String)
formatCharacter Bool
_ Char
'D' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String)
-> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> Day -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
"%m/%d/%y"
    formatCharacter Bool
_ Char
'F' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String)
-> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> Day -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
"%Y-%m-%d"
    formatCharacter Bool
_ Char
'x' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String)
-> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> TimeLocale -> String -> Day -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale (TimeLocale -> String
dateFmt TimeLocale
locale)
    
    formatCharacter Bool
_ Char
'd' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonthDay Integer
_ Int
_ Int
dm) -> Int
dm
    formatCharacter Bool
_ Char
'e' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
' ' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearMonthDay Integer
_ Int
_ Int
dm) -> Int
dm
    
    formatCharacter Bool
_ Char
'j' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
3 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearDay Integer
_ Int
dy) -> Int
dy
    
    formatCharacter Bool
_ Char
'G' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Day -> Integer)
-> FormatOptions
-> Day
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
False Int
4 Char
'0' ((Day -> Integer) -> FormatOptions -> Day -> String)
-> (Day -> Integer) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearWeekDay Integer
y Int
_ DayOfWeek
_) -> Integer
y
    formatCharacter Bool
_ Char
'g' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Day -> Integer)
-> FormatOptions
-> Day
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Day -> Integer) -> FormatOptions -> Day -> String)
-> (Day -> Integer) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearWeekDay Integer
y Int
_ DayOfWeek
_) -> Integer -> Integer
forall i. Integral i => i -> i
mod100 Integer
y
    formatCharacter Bool
_ Char
'f' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int
-> Char
-> (Day -> Integer)
-> FormatOptions
-> Day
-> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
False Int
2 Char
'0' ((Day -> Integer) -> FormatOptions -> Day -> String)
-> (Day -> Integer) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearWeekDay Integer
y Int
_ DayOfWeek
_) -> Integer -> Integer
forall i. Integral i => i -> i
div100 Integer
y
    formatCharacter Bool
_ Char
'V' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearWeekDay Integer
_ Int
wy DayOfWeek
_) -> Int
wy
    formatCharacter Bool
_ Char
'u' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
1 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \(YearWeekDay Integer
_ Int
_ DayOfWeek
dw) -> DayOfWeek -> Int
forall a. Enum a => a -> Int
fromEnum DayOfWeek
dw
    
    formatCharacter Bool
_ Char
'a' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String)
-> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> (String, String) -> String
forall a b. (a, b) -> b
snd ((String, String) -> String)
-> (Day -> (String, String)) -> Day -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TimeLocale -> [(String, String)]
wDays TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!!) (Int -> (String, String))
-> (Day -> Int) -> Day -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> (Int, Int)
sundayStartWeek
    formatCharacter Bool
_ Char
'A' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String)
-> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale -> (String, String) -> String
forall a b. (a, b) -> a
fst ((String, String) -> String)
-> (Day -> (String, String)) -> Day -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TimeLocale -> [(String, String)]
wDays TimeLocale
locale) [(String, String)] -> Int -> (String, String)
forall a. HasCallStack => [a] -> Int -> a
!!) (Int -> (String, String))
-> (Day -> Int) -> Day -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> (Int, Int)
sundayStartWeek
    formatCharacter Bool
_ Char
'U' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int
forall a b. (a, b) -> a
fst ((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> (Int, Int)
sundayStartWeek
    formatCharacter Bool
_ Char
'w' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
1 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> (Int, Int)
sundayStartWeek
    formatCharacter Bool
_ Char
'W' = (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> Day -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> (FormatOptions -> Day -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
True Int
2 Char
'0' ((Day -> Int) -> FormatOptions -> Day -> String)
-> (Day -> Int) -> FormatOptions -> Day -> String
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int
forall a b. (a, b) -> a
fst ((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> (Int, Int)
mondayStartWeek
    
    formatCharacter Bool
alt Char
c = (Day -> Month)
-> Maybe (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Day -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter (\(MonthDay Month
m Int
_) -> Month
m) (Maybe (FormatOptions -> Month -> String)
 -> Maybe (FormatOptions -> Day -> String))
-> Maybe (FormatOptions -> Month -> String)
-> Maybe (FormatOptions -> Day -> String)
forall a b. (a -> b) -> a -> b
$ Bool -> Char -> Maybe (FormatOptions -> Month -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c
instance FormatTime UTCTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> UTCTime -> String)
formatCharacter Bool
alt Char
c = (UTCTime -> ZonedTime)
-> Maybe (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> UTCTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter (TimeZone -> UTCTime -> ZonedTime
utcToZonedTime TimeZone
utc) (Maybe (FormatOptions -> ZonedTime -> String)
 -> Maybe (FormatOptions -> UTCTime -> String))
-> Maybe (FormatOptions -> ZonedTime -> String)
-> Maybe (FormatOptions -> UTCTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c
instance FormatTime UniversalTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> UniversalTime -> String)
formatCharacter Bool
alt Char
c = (UniversalTime -> LocalTime)
-> Maybe (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> UniversalTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter (Rational -> UniversalTime -> LocalTime
ut1ToLocalTime Rational
0) (Maybe (FormatOptions -> LocalTime -> String)
 -> Maybe (FormatOptions -> UniversalTime -> String))
-> Maybe (FormatOptions -> LocalTime -> String)
-> Maybe (FormatOptions -> UniversalTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c
instance FormatTime NominalDiffTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> POSIXTime -> String)
formatCharacter Bool
_ Char
'w' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy (POSIXTime -> POSIXTime -> Integer)
-> POSIXTime -> POSIXTime -> Integer
forall a b. (a -> b) -> a -> b
$ POSIXTime
7 POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
* POSIXTime
86400
    formatCharacter Bool
_ Char
'd' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
86400
    formatCharacter Bool
_ Char
'D' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
7 (Integer -> Integer)
-> (POSIXTime -> Integer) -> POSIXTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
86400
    formatCharacter Bool
_ Char
'h' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
3600
    formatCharacter Bool
_ Char
'H' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
24 (Integer -> Integer)
-> (POSIXTime -> Integer) -> POSIXTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
3600
    formatCharacter Bool
_ Char
'm' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
60
    formatCharacter Bool
_ Char
'M' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
60 (Integer -> Integer)
-> (POSIXTime -> Integer) -> POSIXTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
60
    formatCharacter Bool
False Char
's' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
1
    formatCharacter Bool
True Char
's' =
        (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> POSIXTime -> String)
-> FormatOptions
-> POSIXTime
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
False Int
12 Char
'0' ((TimeLocale -> PadOption -> POSIXTime -> String)
 -> FormatOptions -> POSIXTime -> String)
-> (TimeLocale -> PadOption -> POSIXTime -> String)
-> FormatOptions
-> POSIXTime
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
padf POSIXTime
t -> PadOption -> PadOption -> Pico -> String
forall a.
HasResolution a =>
PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
NoPad PadOption
padf (POSIXTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac POSIXTime
t :: Pico)
    formatCharacter Bool
False Char
'S' = (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String)
-> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
60 (Integer -> Integer)
-> (POSIXTime -> Integer) -> POSIXTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> POSIXTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy POSIXTime
1
    formatCharacter Bool
True Char
'S' =
        (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> POSIXTime -> String))
-> (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> POSIXTime -> String)
forall a b. (a -> b) -> a -> b
$
            Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> POSIXTime -> String)
-> FormatOptions
-> POSIXTime
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
False Int
12 Char
'0' ((TimeLocale -> PadOption -> POSIXTime -> String)
 -> FormatOptions -> POSIXTime -> String)
-> (TimeLocale -> PadOption -> POSIXTime -> String)
-> FormatOptions
-> POSIXTime
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
padf POSIXTime
t -> let
                padn :: PadOption
padn = case PadOption
padf of
                    PadOption
NoPad -> PadOption
NoPad
                    Pad Int
_ Char
c -> Int -> Char -> PadOption
Pad Int
2 Char
c
                in PadOption -> PadOption -> Pico -> String
forall a.
HasResolution a =>
PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
padn PadOption
padf (POSIXTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac (POSIXTime -> Pico) -> POSIXTime -> Pico
forall a b. (a -> b) -> a -> b
$ POSIXTime -> POSIXTime -> POSIXTime
forall a. Real a => a -> a -> a
remBy POSIXTime
60 POSIXTime
t :: Pico)
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> POSIXTime -> String)
forall a. Maybe a
Nothing
instance FormatTime DiffTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DiffTime -> String)
formatCharacter Bool
_ Char
'w' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy (DiffTime -> DiffTime -> Integer)
-> DiffTime -> DiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ DiffTime
7 DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* DiffTime
86400
    formatCharacter Bool
_ Char
'd' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
86400
    formatCharacter Bool
_ Char
'D' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
7 (Integer -> Integer)
-> (DiffTime -> Integer) -> DiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
86400
    formatCharacter Bool
_ Char
'h' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
3600
    formatCharacter Bool
_ Char
'H' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
24 (Integer -> Integer)
-> (DiffTime -> Integer) -> DiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
3600
    formatCharacter Bool
_ Char
'm' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
60
    formatCharacter Bool
_ Char
'M' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
60 (Integer -> Integer)
-> (DiffTime -> Integer) -> DiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
60
    formatCharacter Bool
False Char
's' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
1
    formatCharacter Bool
True Char
's' =
        (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> DiffTime -> String)
-> FormatOptions
-> DiffTime
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
False Int
12 Char
'0' ((TimeLocale -> PadOption -> DiffTime -> String)
 -> FormatOptions -> DiffTime -> String)
-> (TimeLocale -> PadOption -> DiffTime -> String)
-> FormatOptions
-> DiffTime
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
padf DiffTime
t -> PadOption -> PadOption -> Pico -> String
forall a.
HasResolution a =>
PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
NoPad PadOption
padf (DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac DiffTime
t :: Pico)
    formatCharacter Bool
False Char
'S' = (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String)
-> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
60 (Integer -> Integer)
-> (DiffTime -> Integer) -> DiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffTime -> DiffTime -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy DiffTime
1
    formatCharacter Bool
True Char
'S' =
        (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> DiffTime -> String)
 -> Maybe (FormatOptions -> DiffTime -> String))
-> (FormatOptions -> DiffTime -> String)
-> Maybe (FormatOptions -> DiffTime -> String)
forall a b. (a -> b) -> a -> b
$
            Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> DiffTime -> String)
-> FormatOptions
-> DiffTime
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
True Bool
False Int
12 Char
'0' ((TimeLocale -> PadOption -> DiffTime -> String)
 -> FormatOptions -> DiffTime -> String)
-> (TimeLocale -> PadOption -> DiffTime -> String)
-> FormatOptions
-> DiffTime
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
padf DiffTime
t -> let
                padn :: PadOption
padn = case PadOption
padf of
                    PadOption
NoPad -> PadOption
NoPad
                    Pad Int
_ Char
c -> Int -> Char -> PadOption
Pad Int
2 Char
c
                in PadOption -> PadOption -> Pico -> String
forall a.
HasResolution a =>
PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
padn PadOption
padf (DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac (DiffTime -> Pico) -> DiffTime -> Pico
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime -> DiffTime
forall a. Real a => a -> a -> a
remBy DiffTime
60 DiffTime
t :: Pico)
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> DiffTime -> String)
forall a. Maybe a
Nothing
instance FormatTime CalendarDiffDays where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffDays -> String)
formatCharacter Bool
_ Char
'y' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy Integer
12 (Integer -> Integer)
-> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffDays -> Integer
cdMonths
    formatCharacter Bool
_ Char
'b' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ CalendarDiffDays -> Integer
cdMonths
    formatCharacter Bool
_ Char
'B' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
12 (Integer -> Integer)
-> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffDays -> Integer
cdMonths
    formatCharacter Bool
_ Char
'w' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy Integer
7 (Integer -> Integer)
-> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffDays -> Integer
cdDays
    formatCharacter Bool
_ Char
'd' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ CalendarDiffDays -> Integer
cdDays
    formatCharacter Bool
_ Char
'D' = (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffDays -> String)
 -> Maybe (FormatOptions -> CalendarDiffDays -> String))
-> (FormatOptions -> CalendarDiffDays -> String)
-> Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffDays -> Integer)
 -> FormatOptions -> CalendarDiffDays -> String)
-> (CalendarDiffDays -> Integer)
-> FormatOptions
-> CalendarDiffDays
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
7 (Integer -> Integer)
-> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffDays -> Integer
cdDays
    formatCharacter Bool
_ Char
_ = Maybe (FormatOptions -> CalendarDiffDays -> String)
forall a. Maybe a
Nothing
instance FormatTime CalendarDiffTime where
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffTime -> String)
formatCharacter Bool
_ Char
'y' = (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffTime -> String)
 -> Maybe (FormatOptions -> CalendarDiffTime -> String))
-> (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffTime -> Integer)
 -> FormatOptions -> CalendarDiffTime -> String)
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a b. (Real a, Integral b) => a -> a -> b
quotBy Integer
12 (Integer -> Integer)
-> (CalendarDiffTime -> Integer) -> CalendarDiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffTime -> Integer
ctMonths
    formatCharacter Bool
_ Char
'b' = (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffTime -> String)
 -> Maybe (FormatOptions -> CalendarDiffTime -> String))
-> (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
1 ((CalendarDiffTime -> Integer)
 -> FormatOptions -> CalendarDiffTime -> String)
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall a b. (a -> b) -> a -> b
$ CalendarDiffTime -> Integer
ctMonths
    formatCharacter Bool
_ Char
'B' = (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a. a -> Maybe a
Just ((FormatOptions -> CalendarDiffTime -> String)
 -> Maybe (FormatOptions -> CalendarDiffTime -> String))
-> (FormatOptions -> CalendarDiffTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Int
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
2 ((CalendarDiffTime -> Integer)
 -> FormatOptions -> CalendarDiffTime -> String)
-> (CalendarDiffTime -> Integer)
-> FormatOptions
-> CalendarDiffTime
-> String
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Real a => a -> a -> a
remBy Integer
12 (Integer -> Integer)
-> (CalendarDiffTime -> Integer) -> CalendarDiffTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDiffTime -> Integer
ctMonths
    formatCharacter Bool
alt Char
c = (CalendarDiffTime -> POSIXTime)
-> Maybe (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall b a.
(b -> a)
-> Maybe (FormatOptions -> a -> String)
-> Maybe (FormatOptions -> b -> String)
mapFormatCharacter CalendarDiffTime -> POSIXTime
ctTime (Maybe (FormatOptions -> POSIXTime -> String)
 -> Maybe (FormatOptions -> CalendarDiffTime -> String))
-> Maybe (FormatOptions -> POSIXTime -> String)
-> Maybe (FormatOptions -> CalendarDiffTime -> String)
forall a b. (a -> b) -> a -> b
$ Bool -> Char -> Maybe (FormatOptions -> POSIXTime -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c