module Data.Time.Format
(
module Data.Time.Format,
module Data.Time.Format.Parse
) where
import Data.Time.Format.Parse
import Data.Time.LocalTime
import Data.Time.Calendar.WeekDate
import Data.Time.Calendar.OrdinalDate
import Data.Time.Calendar
import Data.Time.Calendar.Private
import Data.Time.Clock
import Data.Time.Clock.POSIX
import System.Locale
import Data.Maybe
import Data.Char
import Data.Fixed
class FormatTime t where
formatCharacter :: Char -> Maybe (TimeLocale -> t -> String)
formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String
formatTime _ [] _ = ""
formatTime locale ('%':c:cs) t = (formatChar c) ++ (formatTime locale cs t) where
formatChar '%' = "%"
formatChar 't' = "\t"
formatChar 'n' = "\n"
formatChar _ = case (formatCharacter c) of
Just f -> f locale t
_ -> ""
formatTime locale (c:cs) t = c:(formatTime locale cs t)
instance FormatTime LocalTime where
formatCharacter 'c' = Just (\locale -> formatTime locale (dateTimeFmt locale))
formatCharacter c = case (formatCharacter c) of
Just f -> Just (\locale dt -> f locale (localDay dt))
Nothing -> case (formatCharacter c) of
Just f -> Just (\locale dt -> f locale (localTimeOfDay dt))
Nothing -> Nothing
instance FormatTime TimeOfDay where
formatCharacter 'R' = Just (\locale -> formatTime locale "%H:%M")
formatCharacter 'T' = Just (\locale -> formatTime locale "%H:%M:%S")
formatCharacter 'X' = Just (\locale -> formatTime locale (timeFmt locale))
formatCharacter 'r' = Just (\locale -> formatTime locale (time12Fmt locale))
formatCharacter 'P' = Just (\locale day -> map toLower ((if (todHour day) < 12 then fst else snd) (amPm locale)))
formatCharacter 'p' = Just (\locale day -> (if (todHour day) < 12 then fst else snd) (amPm locale))
formatCharacter 'H' = Just (\_ -> show2 . todHour)
formatCharacter 'I' = Just (\_ -> show2 . (\h -> (mod (h 1) 12) + 1) . todHour)
formatCharacter 'k' = Just (\_ -> show2Space . todHour)
formatCharacter 'l' = Just (\_ -> show2Space . (\h -> (mod (h 1) 12) + 1) . todHour)
formatCharacter 'M' = Just (\_ -> show2 . todMin)
formatCharacter 'S' = Just (\_ -> (show2 :: Int -> String) . truncate . todSec)
formatCharacter 'q' = Just (\_ -> drop 1 . dropWhile (/='.') . showFixed False . todSec)
formatCharacter 'Q' = Just (\_ -> dropWhile (/='.') . showFixed True . todSec)
formatCharacter _ = Nothing
instance FormatTime ZonedTime where
formatCharacter 'c' = Just (\locale -> formatTime locale (dateTimeFmt locale))
formatCharacter 's' = Just (\_ zt -> show (floor (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer))
formatCharacter c = case (formatCharacter c) of
Just f -> Just (\locale dt -> f locale (zonedTimeToLocalTime dt))
Nothing -> case (formatCharacter c) of
Just f -> Just (\locale dt -> f locale (zonedTimeZone dt))
Nothing -> Nothing
instance FormatTime TimeZone where
formatCharacter 'z' = Just (\_ -> timeZoneOffsetString)
formatCharacter 'Z' =
Just (\_ z -> let n = timeZoneName z
in if null n then timeZoneOffsetString z else n)
formatCharacter _ = Nothing
instance FormatTime Day where
formatCharacter 'D' = Just (\locale -> formatTime locale "%m/%d/%y")
formatCharacter 'F' = Just (\locale -> formatTime locale "%Y-%m-%d")
formatCharacter 'x' = Just (\locale -> formatTime locale (dateFmt locale))
formatCharacter 'Y' = Just (\_ -> show . fst . toOrdinalDate)
formatCharacter 'y' = Just (\_ -> show2 . mod100 . fst . toOrdinalDate)
formatCharacter 'C' = Just (\_ -> show2 . div100 . fst . toOrdinalDate)
formatCharacter 'B' = Just (\locale -> fst . (\(_,m,_) -> (months locale) !! (m 1)) . toGregorian)
formatCharacter 'b' = Just (\locale -> snd . (\(_,m,_) -> (months locale) !! (m 1)) . toGregorian)
formatCharacter 'h' = Just (\locale -> snd . (\(_,m,_) -> (months locale) !! (m 1)) . toGregorian)
formatCharacter 'm' = Just (\_ -> show2 . (\(_,m,_) -> m) . toGregorian)
formatCharacter 'd' = Just (\_ -> show2 . (\(_,_,d) -> d) . toGregorian)
formatCharacter 'e' = Just (\_ -> show2Space . (\(_,_,d) -> d) . toGregorian)
formatCharacter 'j' = Just (\_ -> show3 . snd . toOrdinalDate)
formatCharacter 'G' = Just (\_ -> show . (\(y,_,_) -> y) . toWeekDate)
formatCharacter 'g' = Just (\_ -> show2 . mod100 . (\(y,_,_) -> y) . toWeekDate)
formatCharacter 'f' = Just (\_ -> show2 . div100 . (\(y,_,_) -> y) . toWeekDate)
formatCharacter 'V' = Just (\_ -> show2 . (\(_,w,_) -> w) . toWeekDate)
formatCharacter 'u' = Just (\_ -> show . (\(_,_,d) -> d) . toWeekDate)
formatCharacter 'a' = Just (\locale -> snd . ((wDays locale) !!) . snd . sundayStartWeek)
formatCharacter 'A' = Just (\locale -> fst . ((wDays locale) !!) . snd . sundayStartWeek)
formatCharacter 'U' = Just (\_ -> show2 . fst . sundayStartWeek)
formatCharacter 'w' = Just (\_ -> show . snd . sundayStartWeek)
formatCharacter 'W' = Just (\_ -> show2 . fst . mondayStartWeek)
formatCharacter _ = Nothing
instance FormatTime UTCTime where
formatCharacter c = fmap (\f locale t -> f locale (utcToZonedTime utc t)) (formatCharacter c)