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