{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
module Formatting.Time
( tz
, tzName
, datetime
, hm
, hms
, hmsL
, hmsPL
, dayHalf
, dayHalfU
, hour24
, hour12
, hour24S
, hour12S
, minute
, second
, pico
, decimals
, epoch
, dateSlash
, dateDash
, dateSlashL
, year
, yy
, century
, monthName
, monthNameShort
, month
, dayOfMonth
, dayOfMonthOrd
, dayOfMonthS
, day
, weekYear
, weekYY
, weekCentury
, week
, dayOfWeek
, dayNameShort
, dayName
, weekFromZero
, dayOfWeekFromZero
, weekOfYearMon
, diff
, years
, days
, hours
, minutes
, seconds
, diffComponents
, customDiffComponents
, fmt
, customTimeFmt
) where
import Data.List
import Data.Tuple
import Formatting.Formatters hiding (build, base)
import Formatting.Internal
import Data.Text (Text)
import qualified Data.Text as T
import Formatting.Buildable
import Data.Time (FormatTime, formatTime, defaultTimeLocale)
#if MIN_VERSION_time(1,5,0)
import System.Locale ()
#else
import System.Locale
#endif
import Control.Monad.Trans.State.Strict
tz :: FormatTime a => Format r (a -> r)
tz = later (build . fmt "%z")
tzName :: FormatTime a => Format r (a -> r)
tzName = later (build . fmt "%Z")
datetime :: FormatTime a => Format r (a -> r)
datetime = later (build . fmt "%c")
hm :: FormatTime a => Format r (a -> r)
hm = later (build . fmt "%R")
hms :: FormatTime a => Format r (a -> r)
hms = later (build . fmt "%T")
hmsL :: FormatTime a => Format r (a -> r)
hmsL = later (build . fmt "%X")
hmsPL :: FormatTime a => Format r (a -> r)
hmsPL = later (build . fmt "%r")
dayHalf :: FormatTime a => Format r (a -> r)
dayHalf = later (build . fmt "%P")
dayHalfU :: FormatTime a => Format r (a -> r)
dayHalfU = later (build . fmt "%p")
hour24 :: FormatTime a => Format r (a -> r)
hour24 = later (build . fmt "%H")
hour12 :: FormatTime a => Format r (a -> r)
hour12 = later (build . fmt "%I")
hour24S :: FormatTime a => Format r (a -> r)
hour24S = later (build . fmt "%k")
hour12S :: FormatTime a => Format r (a -> r)
hour12S = later (build . fmt "%l")
minute :: FormatTime a => Format r (a -> r)
minute = later (build . fmt "%M")
second :: FormatTime a => Format r (a -> r)
second = later (build . fmt "%S")
pico :: FormatTime a => Format r (a -> r)
pico = later (build . fmt "%q")
decimals :: FormatTime a => Format r (a -> r)
decimals = later (build . fmt "%Q")
epoch :: FormatTime a => Format r (a -> r)
epoch = later (build . fmt "%s")
dateSlash :: FormatTime a => Format r (a -> r)
dateSlash = later (build . fmt "%D")
dateDash :: FormatTime a => Format r (a -> r)
dateDash = later (build . fmt "%F")
dateSlashL :: FormatTime a => Format r (a -> r)
dateSlashL = later (build . fmt "%x")
year :: FormatTime a => Format r (a -> r)
year = later (build . fmt "%Y")
yy :: FormatTime a => Format r (a -> r)
yy = later (build . fmt "%y")
century :: FormatTime a => Format r (a -> r)
century = later (build . fmt "%C")
monthName :: FormatTime a => Format r (a -> r)
monthName = later (build . fmt "%B")
monthNameShort :: FormatTime a => Format r (a -> r)
monthNameShort = later (build . fmt "%b")
month :: FormatTime a => Format r (a -> r)
month = later (build . fmt "%m")
dayOfMonth :: FormatTime a => Format r (a -> r)
dayOfMonth = later (build . fmt "%d")
dayOfMonthOrd :: FormatTime a => Format r (a -> r)
dayOfMonthOrd = later (bprint ords . toInt)
where toInt :: FormatTime a => a -> Int
toInt = read . formatTime defaultTimeLocale "%d"
dayOfMonthS :: FormatTime a => Format r (a -> r)
dayOfMonthS = later (build . fmt "%e")
day :: FormatTime a => Format r (a -> r)
day = later (build . fmt "%j")
weekYear :: FormatTime a => Format r (a -> r)
weekYear = later (build . fmt "%G")
weekYY :: FormatTime a => Format r (a -> r)
weekYY = later (build . fmt "%g")
weekCentury :: FormatTime a => Format r (a -> r)
weekCentury = later (build . fmt "%f")
week :: FormatTime a => Format r (a -> r)
week = later (build . fmt "%V")
dayOfWeek :: FormatTime a => Format r (a -> r)
dayOfWeek = later (build . fmt "%u")
dayNameShort :: FormatTime a => Format r (a -> r)
dayNameShort = later (build . fmt "%a")
dayName :: FormatTime a => Format r (a -> r)
dayName = later (build . fmt "%A")
weekFromZero :: FormatTime a => Format r (a -> r)
weekFromZero = later (build . fmt "%U")
dayOfWeekFromZero :: FormatTime a => Format r (a -> r)
dayOfWeekFromZero = later (build . fmt "%w")
weekOfYearMon :: FormatTime a => Format r (a -> r)
weekOfYearMon = later (build . fmt "%W")
diff :: (RealFrac n)
=> Bool
-> Format r (n -> r)
diff fix =
later diffed
where
diffed ts =
case find (\(s,_,_) -> abs ts >= s) (reverse ranges) of
Nothing -> "unknown"
Just (_,f,base) -> bprint (prefix % f % suffix) (toInt ts base)
where prefix = now (if fix && ts > 0 then "in " else "")
suffix = now (if fix && ts < 0 then " ago" else "")
toInt ts base = abs (round (ts / base)) :: Int
ranges =
[(0,int % " milliseconds",0.001)
,(1,int % " seconds",1)
,(minute',fconst "a minute",0)
,(minute'*2,int % " minutes",minute')
,(minute'*30,fconst "half an hour",0)
,(minute'*31,int % " minutes",minute')
,(hour',fconst "an hour",0)
,(hour'*2,int % " hours",hour')
,(hour'*3,fconst "a few hours",0)
,(hour'*4,int % " hours",hour')
,(day',fconst "a day",0)
,(day'*2,int % " days",day')
,(week',fconst "a week",0)
,(week'*2,int % " weeks",week')
,(month',fconst "a month",0)
,(month'*2,int % " months",month')
,(year',fconst "a year",0)
,(year'*2,int % " years",year')]
where year' = month' * 12
month' = day' * 30
week' = day' * 7
day' = hour' * 24
hour' = minute' * 60
minute' = 60
years :: (RealFrac n)
=> Int
-> Format r (n -> r)
years n = later (bprint (fixed n) . abs . count)
where count n' = n' / 365 / 24 / 60 / 60
days :: (RealFrac n)
=> Int
-> Format r (n -> r)
days n = later (bprint (fixed n) . abs . count)
where count n' = n' / 24 / 60 / 60
hours :: (RealFrac n)
=> Int
-> Format r (n -> r)
hours n = later (bprint (fixed n) . abs . count)
where count n' = n' / 60 / 60
minutes :: (RealFrac n)
=> Int
-> Format r (n -> r)
minutes n = later (bprint (fixed n) . abs . count)
where count n' = n' / 60
seconds :: (RealFrac n)
=> Int
-> Format r (n -> r)
seconds n = later (bprint (fixed n) . abs . count)
where count n' = n'
diffComponents :: (RealFrac n) => Format r (n -> r)
diffComponents = customDiffComponents (left 2 '0' % ":" % left 2 '0' % ":" % left 2 '0' % ":" % left 2 '0')
customDiffComponents :: (RealFrac n) => (forall r'. Format r' (Integer -> Integer -> Integer -> Integer -> r')) -> Format r (n -> r)
customDiffComponents subFormat = later builder' where
builder' diffTime = flip evalState (round diffTime) $ do
seconds' <- state (swap . flip divMod 60)
minutes' <- state (swap . flip divMod 60)
hours' <- state (swap . flip divMod 24)
days' <- get
return (bprint subFormat days' hours' minutes' seconds')
fmt :: FormatTime a => Text -> a -> Text
fmt f = T.pack . formatTime defaultTimeLocale (T.unpack f)
customTimeFmt :: FormatTime a => Text -> Format r (a -> r)
customTimeFmt f = later (build . fmt f)