{-# LANGUAGE Safe #-}

module Data.Time.Format.Format.Class (
    -- * Formatting
    formatTime,
    FormatNumericPadding,
    FormatOptions (..),
    FormatTime (..),
    ShowPadded,
    PadOption,
    formatGeneral,
    formatString,
    formatNumber,
    formatNumberStd,
    showPaddedFixed,
    showPaddedFixedFraction,
    quotBy,
    remBy,
) where

import Data.Char
import Data.Fixed
import Data.Maybe
import Data.Time.Calendar.Private
import Data.Time.Format.Locale

type FormatNumericPadding = Maybe Char

data FormatOptions = MkFormatOptions
    { FormatOptions -> TimeLocale
foLocale :: TimeLocale
    , FormatOptions -> Maybe FormatNumericPadding
foPadding :: Maybe FormatNumericPadding
    , FormatOptions -> Maybe Int
foWidth :: Maybe Int
    }

-- <http://www.opengroup.org/onlinepubs/007908799/xsh/strftime.html>
class FormatTime t where
    -- | @since 1.9.1
    formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> t -> String)

-- the weird UNIX logic is here
getPadOption :: Bool -> Bool -> Int -> Char -> Maybe FormatNumericPadding -> Maybe Int -> PadOption
getPadOption :: Bool
-> Bool
-> Int
-> Char
-> Maybe FormatNumericPadding
-> Maybe Int
-> PadOption
getPadOption Bool
trunc Bool
fdef Int
idef Char
cdef Maybe FormatNumericPadding
mnpad Maybe Int
mi = let
    c :: Char
c = case Maybe FormatNumericPadding
mnpad of
        Just (Just Char
c') -> Char
c'
        Just FormatNumericPadding
Nothing -> Char
' '
        Maybe FormatNumericPadding
_ -> Char
cdef
    i :: Int
i = case Maybe Int
mi of
        Just Int
i' -> case Maybe FormatNumericPadding
mnpad of
            Just FormatNumericPadding
Nothing -> Int
i'
            Maybe FormatNumericPadding
_ ->
                if Bool
trunc
                    then Int
i'
                    else Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
i' Int
idef
        Maybe Int
Nothing -> Int
idef
    f :: Bool
f = case Maybe Int
mi of
        Just Int
_ -> Bool
True
        Maybe Int
Nothing -> case Maybe FormatNumericPadding
mnpad of
            Maybe FormatNumericPadding
Nothing -> Bool
fdef
            Just FormatNumericPadding
Nothing -> Bool
False
            Just (Just Char
_) -> Bool
True
    in if Bool
f
        then Int -> Char -> PadOption
Pad Int
i Char
c
        else PadOption
NoPad

formatGeneral ::
    Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> (FormatOptions -> t -> String)
formatGeneral :: Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
trunc Bool
fdef Int
idef Char
cdef TimeLocale -> PadOption -> t -> String
ff FormatOptions
fo =
    TimeLocale -> PadOption -> t -> String
ff (FormatOptions -> TimeLocale
foLocale FormatOptions
fo) (PadOption -> t -> String) -> PadOption -> t -> String
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Int
-> Char
-> Maybe FormatNumericPadding
-> Maybe Int
-> PadOption
getPadOption Bool
trunc Bool
fdef Int
idef Char
cdef (FormatOptions -> Maybe FormatNumericPadding
foPadding FormatOptions
fo) (FormatOptions -> Maybe Int
foWidth FormatOptions
fo)

formatString :: (TimeLocale -> t -> String) -> (FormatOptions -> t -> String)
formatString :: (TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString TimeLocale -> t -> String
ff = Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
False Bool
False Int
1 Char
' ' ((TimeLocale -> PadOption -> t -> String)
 -> FormatOptions -> t -> String)
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
locale PadOption
pado -> PadOption -> String -> String
showPadded PadOption
pado (String -> String) -> (t -> String) -> t -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> t -> String
ff TimeLocale
locale

formatNumber :: (ShowPadded i) => Bool -> Int -> Char -> (t -> i) -> (FormatOptions -> t -> String)
formatNumber :: Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
fdef Int
idef Char
cdef t -> i
ff = Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
forall t.
Bool
-> Bool
-> Int
-> Char
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
formatGeneral Bool
False Bool
fdef Int
idef Char
cdef ((TimeLocale -> PadOption -> t -> String)
 -> FormatOptions -> t -> String)
-> (TimeLocale -> PadOption -> t -> String)
-> FormatOptions
-> t
-> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ PadOption
pado -> PadOption -> i -> String
forall t. ShowPadded t => PadOption -> t -> String
showPaddedNum PadOption
pado (i -> String) -> (t -> i) -> t -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> i
ff

formatNumberStd :: Int -> (t -> Integer) -> (FormatOptions -> t -> String)
formatNumberStd :: Int -> (t -> Integer) -> FormatOptions -> t -> String
formatNumberStd Int
n = Bool
-> Int -> Char -> (t -> Integer) -> FormatOptions -> t -> String
forall i t.
ShowPadded i =>
Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String
formatNumber Bool
False Int
n Char
'0'

showPaddedFixed :: HasResolution a => PadOption -> PadOption -> Fixed a -> String
showPaddedFixed :: PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
padn PadOption
padf Fixed a
x
    | Fixed a
x Fixed a -> Fixed a -> Bool
forall a. Ord a => a -> a -> Bool
< Fixed a
0 = Char
'-' Char -> String -> String
forall a. a -> [a] -> [a]
: PadOption -> PadOption -> Fixed a -> String
forall a.
HasResolution a =>
PadOption -> PadOption -> Fixed a -> String
showPaddedFixed PadOption
padn PadOption
padf (Fixed a -> Fixed a
forall a. Num a => a -> a
negate Fixed a
x)
showPaddedFixed PadOption
padn PadOption
padf Fixed a
x = let
    ns :: String
ns = PadOption -> Integer -> String
forall t. ShowPadded t => PadOption -> t -> String
showPaddedNum PadOption
padn (Integer -> String) -> Integer -> String
forall a b. (a -> b) -> a -> b
$ (Fixed a -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor Fixed a
x :: Integer)
    fs :: String
fs = PadOption -> Fixed a -> String
forall a. HasResolution a => PadOption -> Fixed a -> String
showPaddedFixedFraction PadOption
padf Fixed a
x
    ds :: String
ds =
        if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
fs
            then String
""
            else String
"."
    in String
ns String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ds String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fs

showPaddedFixedFraction :: HasResolution a => PadOption -> Fixed a -> String
showPaddedFixedFraction :: PadOption -> Fixed a -> String
showPaddedFixedFraction PadOption
pado Fixed a
x = let
    digits :: String
digits = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Bool -> Fixed a -> String
forall k (a :: k). HasResolution a => Bool -> Fixed a -> String
showFixed Bool
True Fixed a
x
    n :: Int
n = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
digits
    in case PadOption
pado of
        PadOption
NoPad -> String
digits
        Pad Int
i Char
c ->
            if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n
                then Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
i String
digits
                else String
digits String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) Char
c

-- | Substitute various time-related information for each %-code in the string, as per 'formatCharacter'.
--
-- The general form is @%\<modifier\>\<width\>\<alternate\>\<specifier\>@, where @\<modifier\>@, @\<width\>@, and @\<alternate\>@ are optional.
--
-- == @\<modifier\>@
-- glibc-style modifiers can be used before the specifier (here marked as @z@):
--
-- [@%-z@] no padding
--
-- [@%_z@] pad with spaces
--
-- [@%0z@] pad with zeros
--
-- [@%^z@] convert to upper case
--
-- [@%#z@] convert to lower case (consistently, unlike glibc)
--
-- == @\<width\>@
-- Width digits can also be used after any modifiers and before the specifier (here marked as @z@), for example:
--
-- [@%4z@] pad to 4 characters (with default padding character)
--
-- [@%_12z@] pad with spaces to 12 characters
--
-- == @\<alternate\>@
-- An optional @E@ character indicates an alternate formatting. Currently this only affects @%Z@ and @%z@.
--
-- [@%Ez@] alternate formatting
--
-- == @\<specifier\>@
--
-- For all types (note these three are done by 'formatTime', not by 'formatCharacter'):
--
-- [@%%@] @%@
--
-- [@%t@] tab
--
-- [@%n@] newline
--
-- === 'TimeZone'
-- For 'TimeZone' (and 'ZonedTime' and 'UTCTime'):
--
-- [@%z@] timezone offset in the format @±HHMM@
--
-- [@%Ez@] timezone offset in the format @±HH:MM@
--
-- [@%Z@] timezone name (or else offset in the format @±HHMM@)
--
-- [@%EZ@] timezone name (or else offset in the format @±HH:MM@)
--
-- === 'LocalTime'
-- For 'LocalTime' (and 'ZonedTime' and 'UTCTime' and 'UniversalTime'):
--
-- [@%c@] as 'dateTimeFmt' @locale@ (e.g. @%a %b %e %H:%M:%S %Z %Y@)
--
-- === 'TimeOfDay'
-- For 'TimeOfDay' (and 'LocalTime' and 'ZonedTime' and 'UTCTime' and 'UniversalTime'):
--
-- [@%R@] same as @%H:%M@
--
-- [@%T@] same as @%H:%M:%S@
--
-- [@%X@] as 'timeFmt' @locale@ (e.g. @%H:%M:%S@)
--
-- [@%r@] as 'time12Fmt' @locale@ (e.g. @%I:%M:%S %p@)
--
-- [@%P@] day-half of day from ('amPm' @locale@), converted to lowercase, @am@, @pm@
--
-- [@%p@] day-half of day from ('amPm' @locale@), @AM@, @PM@
--
-- [@%H@] hour of day (24-hour), 0-padded to two chars, @00@ - @23@
--
-- [@%k@] hour of day (24-hour), space-padded to two chars, @ 0@ - @23@
--
-- [@%I@] hour of day-half (12-hour), 0-padded to two chars, @01@ - @12@
--
-- [@%l@] hour of day-half (12-hour), space-padded to two chars, @ 1@ - @12@
--
-- [@%M@] minute of hour, 0-padded to two chars, @00@ - @59@
--
-- [@%S@] second of minute (without decimal part), 0-padded to two chars, @00@ - @60@
--
-- [@%q@] picosecond of second, 0-padded to twelve chars, @000000000000@ - @999999999999@.
--
-- [@%Q@] decimal point and fraction of second, up to 12 second decimals, without trailing zeros.
-- For a whole number of seconds, @%Q@ omits the decimal point unless padding is specified.
--
-- === 'UTCTime' and 'ZonedTime'
-- For 'UTCTime' and 'ZonedTime':
--
-- [@%s@] number of whole seconds since the Unix epoch. For times before
-- the Unix epoch, this is a negative number. Note that in @%s.%q@ and @%s%Q@
-- the decimals are positive, not negative. For example, 0.9 seconds
-- before the Unix epoch is formatted as @-1.1@ with @%s%Q@.
--
-- === 'DayOfWeek'
-- For 'DayOfWeek' (and 'Day' and 'LocalTime' and 'ZonedTime' and 'UTCTime' and 'UniversalTime'):
--
-- [@%u@] day of week number for Week Date format, @1@ (= Monday) - @7@ (= Sunday)
--
-- [@%w@] day of week number, @0@ (= Sunday) - @6@ (= Saturday)
--
-- [@%a@] day of week, short form ('snd' from 'wDays' @locale@), @Sun@ - @Sat@
--
-- [@%A@] day of week, long form ('fst' from 'wDays' @locale@), @Sunday@ - @Saturday@
--
-- === 'Month'
-- For 'Month' (and 'Day' and 'LocalTime' and 'ZonedTime' and 'UTCTime' and 'UniversalTime'):
--
-- [@%Y@] year, no padding. Note @%0Y@ and @%_Y@ pad to four chars
--
-- [@%y@] year of century, 0-padded to two chars, @00@ - @99@
--
-- [@%C@] century, no padding. Note @%0C@ and @%_C@ pad to two chars
--
-- [@%B@] month name, long form ('fst' from 'months' @locale@), @January@ - @December@
--
-- [@%b@, @%h@] month name, short form ('snd' from 'months' @locale@), @Jan@ - @Dec@
--
-- [@%m@] month of year, 0-padded to two chars, @01@ - @12@
--
-- === 'Day'
-- For 'Day' (and 'LocalTime' and 'ZonedTime' and 'UTCTime' and 'UniversalTime'):
--
-- [@%D@] same as @%m\/%d\/%y@
--
-- [@%F@] same as @%Y-%m-%d@
--
-- [@%x@] as 'dateFmt' @locale@ (e.g. @%m\/%d\/%y@)
--
-- [@%d@] day of month, 0-padded to two chars, @01@ - @31@
--
-- [@%e@] day of month, space-padded to two chars,  @ 1@ - @31@
--
-- [@%j@] day of year, 0-padded to three chars, @001@ - @366@
--
-- [@%f@] century for Week Date format, no padding. Note @%0f@ and @%_f@ pad to two chars
--
-- [@%V@] week of year for Week Date format, 0-padded to two chars, @01@ - @53@
--
-- [@%U@] week of year where weeks start on Sunday (as 'sundayStartWeek'), 0-padded to two chars, @00@ - @53@
--
-- [@%W@] week of year where weeks start on Monday (as 'mondayStartWeek'), 0-padded to two chars, @00@ - @53@
--
-- == Duration types
-- The specifiers for 'DiffTime', 'NominalDiffTime', 'CalendarDiffDays', and 'CalendarDiffTime' are semantically
-- separate from the other types.
-- Specifiers on negative time differences will generally be negative (think 'rem' rather than 'mod').
--
-- === 'NominalDiffTime' and 'DiffTime'
-- Note that a "minute" of 'DiffTime' is simply 60 SI seconds, rather than a minute of civil time.
-- Use 'NominalDiffTime' to work with civil time, ignoring any leap seconds.
--
-- For 'NominalDiffTime' and 'DiffTime':
--
-- [@%w@] total whole weeks
--
-- [@%d@] total whole days
--
-- [@%D@] whole days of week
--
-- [@%h@] total whole hours
--
-- [@%H@] whole hours of day
--
-- [@%m@] total whole minutes
--
-- [@%M@] whole minutes of hour
--
-- [@%s@] total whole seconds
--
-- [@%Es@] total seconds, with decimal point and up to \<width\> (default 12) decimal places, without trailing zeros.
-- For a whole number of seconds, @%Es@ omits the decimal point unless padding is specified.
--
-- [@%0Es@] total seconds, with decimal point and \<width\> (default 12) decimal places.
--
-- [@%S@] whole seconds of minute
--
-- [@%ES@] seconds of minute, with decimal point and up to \<width\> (default 12) decimal places, without trailing zeros.
-- For a whole number of seconds, @%ES@ omits the decimal point unless padding is specified.
--
-- [@%0ES@] seconds of minute as two digits, with decimal point and \<width\> (default 12) decimal places.
--
-- === 'CalendarDiffDays'
-- For 'CalendarDiffDays' (and 'CalendarDiffTime'):
--
-- [@%y@] total years
--
-- [@%b@] total months
--
-- [@%B@] months of year
--
-- [@%w@] total weeks, not including months
--
-- [@%d@] total days, not including months
--
-- [@%D@] days of week
--
-- === 'CalendarDiffTime'
-- For 'CalendarDiffTime':
--
-- [@%h@] total hours, not including months
--
-- [@%H@] hours of day
--
-- [@%m@] total minutes, not including months
--
-- [@%M@] minutes of hour
--
-- [@%s@] total whole seconds, not including months
--
-- [@%Es@] total seconds, not including months, with decimal point and up to \<width\> (default 12) decimal places, without trailing zeros.
-- For a whole number of seconds, @%Es@ omits the decimal point unless padding is specified.
--
-- [@%0Es@] total seconds, not including months, with decimal point and \<width\> (default 12) decimal places.
--
-- [@%S@] whole seconds of minute
--
-- [@%ES@] seconds of minute, with decimal point and up to \<width\> (default 12) decimal places, without trailing zeros.
-- For a whole number of seconds, @%ES@ omits the decimal point unless padding is specified.
--
-- [@%0ES@] seconds of minute as two digits, with decimal point and \<width\> (default 12) decimal places.
formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String
formatTime :: TimeLocale -> String -> t -> String
formatTime TimeLocale
_ [] t
_ = String
""
formatTime TimeLocale
locale (Char
'%' : String
cs) t
t =
    case TimeLocale -> String -> t -> Maybe String
forall t. FormatTime t => TimeLocale -> String -> t -> Maybe String
formatTime1 TimeLocale
locale String
cs t
t of
        Just String
result -> String
result
        Maybe String
Nothing -> Char
'%' Char -> String -> String
forall a. a -> [a] -> [a]
: (TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
cs t
t)
formatTime TimeLocale
locale (Char
c : String
cs) t
t = Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: (TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
cs t
t)

formatTime1 :: (FormatTime t) => TimeLocale -> String -> t -> Maybe String
formatTime1 :: TimeLocale -> String -> t -> Maybe String
formatTime1 TimeLocale
locale (Char
'_' : String
cs) t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale String -> String
forall a. a -> a
id (FormatNumericPadding -> Maybe FormatNumericPadding
forall a. a -> Maybe a
Just (Char -> FormatNumericPadding
forall a. a -> Maybe a
Just Char
' ')) String
cs t
t
formatTime1 TimeLocale
locale (Char
'-' : String
cs) t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale String -> String
forall a. a -> a
id (FormatNumericPadding -> Maybe FormatNumericPadding
forall a. a -> Maybe a
Just FormatNumericPadding
forall a. Maybe a
Nothing) String
cs t
t
formatTime1 TimeLocale
locale (Char
'0' : String
cs) t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale String -> String
forall a. a -> a
id (FormatNumericPadding -> Maybe FormatNumericPadding
forall a. a -> Maybe a
Just (Char -> FormatNumericPadding
forall a. a -> Maybe a
Just Char
'0')) String
cs t
t
formatTime1 TimeLocale
locale (Char
'^' : String
cs) t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale ((Char -> Char) -> String -> String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toUpper) Maybe FormatNumericPadding
forall a. Maybe a
Nothing String
cs t
t
formatTime1 TimeLocale
locale (Char
'#' : String
cs) t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale ((Char -> Char) -> String -> String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower) Maybe FormatNumericPadding
forall a. Maybe a
Nothing String
cs t
t
formatTime1 TimeLocale
locale String
cs t
t = TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale String -> String
forall a. a -> a
id Maybe FormatNumericPadding
forall a. Maybe a
Nothing String
cs t
t

getDigit :: Char -> Maybe Int
getDigit :: Char -> Maybe Int
getDigit Char
c
    | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'0' = Maybe Int
forall a. Maybe a
Nothing
getDigit Char
c
    | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
> Char
'9' = Maybe Int
forall a. Maybe a
Nothing
getDigit Char
c = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ (Char -> Int
ord Char
c) Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Char -> Int
ord Char
'0')

pullNumber :: Maybe Int -> String -> (Maybe Int, String)
pullNumber :: Maybe Int -> String -> (Maybe Int, String)
pullNumber Maybe Int
mx [] = (Maybe Int
mx, [])
pullNumber Maybe Int
mx s :: String
s@(Char
c : String
cs) =
    case Char -> Maybe Int
getDigit Char
c of
        Just Int
i -> Maybe Int -> String -> (Maybe Int, String)
pullNumber (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 Maybe Int
mx) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
10 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i) String
cs
        Maybe Int
Nothing -> (Maybe Int
mx, String
s)

formatTime2 ::
    (FormatTime t) => TimeLocale -> (String -> String) -> Maybe FormatNumericPadding -> String -> t -> Maybe String
formatTime2 :: TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> String
-> t
-> Maybe String
formatTime2 TimeLocale
locale String -> String
recase Maybe FormatNumericPadding
mpad String
cs t
t = let
    (Maybe Int
mwidth, String
rest) = Maybe Int -> String -> (Maybe Int, String)
pullNumber Maybe Int
forall a. Maybe a
Nothing String
cs
    in TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> Maybe Int
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> Maybe Int
-> String
-> t
-> Maybe String
formatTime3 TimeLocale
locale String -> String
recase Maybe FormatNumericPadding
mpad Maybe Int
mwidth String
rest t
t

formatTime3 ::
    (FormatTime t) =>
    TimeLocale ->
    (String -> String) ->
    Maybe FormatNumericPadding ->
    Maybe Int ->
    String ->
    t ->
    Maybe String
formatTime3 :: TimeLocale
-> (String -> String)
-> Maybe FormatNumericPadding
-> Maybe Int
-> String
-> t
-> Maybe String
formatTime3 TimeLocale
locale String -> String
recase Maybe FormatNumericPadding
mpad Maybe Int
mwidth (Char
'E' : String
cs) = Bool
-> (String -> String)
-> FormatOptions
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
Bool
-> (String -> String)
-> FormatOptions
-> String
-> t
-> Maybe String
formatTime4 Bool
True String -> String
recase (TimeLocale
-> Maybe FormatNumericPadding -> Maybe Int -> FormatOptions
MkFormatOptions TimeLocale
locale Maybe FormatNumericPadding
mpad Maybe Int
mwidth) String
cs
formatTime3 TimeLocale
locale String -> String
recase Maybe FormatNumericPadding
mpad Maybe Int
mwidth String
cs = Bool
-> (String -> String)
-> FormatOptions
-> String
-> t
-> Maybe String
forall t.
FormatTime t =>
Bool
-> (String -> String)
-> FormatOptions
-> String
-> t
-> Maybe String
formatTime4 Bool
False String -> String
recase (TimeLocale
-> Maybe FormatNumericPadding -> Maybe Int -> FormatOptions
MkFormatOptions TimeLocale
locale Maybe FormatNumericPadding
mpad Maybe Int
mwidth) String
cs

formatTime4 :: (FormatTime t) => Bool -> (String -> String) -> FormatOptions -> String -> t -> Maybe String
formatTime4 :: Bool
-> (String -> String)
-> FormatOptions
-> String
-> t
-> Maybe String
formatTime4 Bool
alt String -> String
recase FormatOptions
fo (Char
c : String
cs) t
t = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ (String -> String
recase (Bool -> Char -> FormatOptions -> t -> String
forall t.
FormatTime t =>
Bool -> Char -> FormatOptions -> t -> String
formatChar Bool
alt Char
c FormatOptions
fo t
t)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ (TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime (FormatOptions -> TimeLocale
foLocale FormatOptions
fo) String
cs t
t)
formatTime4 Bool
_alt String -> String
_recase FormatOptions
_fo [] t
_t = Maybe String
forall a. Maybe a
Nothing

formatChar :: (FormatTime t) => Bool -> Char -> FormatOptions -> t -> String
formatChar :: Bool -> Char -> FormatOptions -> t -> String
formatChar Bool
_ Char
'%' = (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> t -> String) -> FormatOptions -> t -> String)
-> (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ t
_ -> String
"%"
formatChar Bool
_ Char
't' = (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> t -> String) -> FormatOptions -> t -> String)
-> (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ t
_ -> String
"\t"
formatChar Bool
_ Char
'n' = (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall t.
(TimeLocale -> t -> String) -> FormatOptions -> t -> String
formatString ((TimeLocale -> t -> String) -> FormatOptions -> t -> String)
-> (TimeLocale -> t -> String) -> FormatOptions -> t -> String
forall a b. (a -> b) -> a -> b
$ \TimeLocale
_ t
_ -> String
"\n"
formatChar Bool
alt Char
c =
    case Bool -> Char -> Maybe (FormatOptions -> t -> String)
forall t.
FormatTime t =>
Bool -> Char -> Maybe (FormatOptions -> t -> String)
formatCharacter Bool
alt Char
c of
        Just FormatOptions -> t -> String
f -> FormatOptions -> t -> String
f
        Maybe (FormatOptions -> t -> String)
_ -> \FormatOptions
_ t
_ -> String
""