{- Acknowledgements
~~~~~~~~~~~~~~~~~~~

This module has been largely copied off
    <https://hackage.haskell.org/package/formatting/docs/Formatting-Time.html>
Written by Chris Done
    <https://github.com/chrisdone>
-}

{-# LANGUAGE CPP                 #-}
{-# LANGUAGE ExplicitForAll      #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}


{- | Formatters for various time types. This module copies the structure of
@<https://hackage.haskell.org/package/formatting/docs/Formatting-Time.html Formatting.Time>@
from the @<https://hackage.haskell.org/package/formatting formatting>@ package.

Most of the time you'll want to use one of these formatters (all of the
examples below use @"2018-02-14 16:20:45.5 CST"@):

* 'dateTimeF' – full date and time:

    >>> dateTimeF t
    "Wed Feb 14 16:20:45 CST 2018"

* 'hmF' – hours and minutes:

    >>> hmF t
    "16:20"

* 'hmsF' – hours, minutes and seconds:

    >>> hmsF t
    "16:20:45"

* 'dateDashF' – date in ISO 8601 format:

    >>> dateDashF t
    "2018-02-14"

* 'diffF' – either a time period or a point in time, in a convenient for
  humans format:

    >>> diffF False 130    -- time period (130 seconds)
    "2 minutes"
    >>> diffF True 130     -- point in time (130 seconds in the future)
    "in 2 minutes"

Note that two formatters from @Formatting.Time@ are called differently here:

@
pico     -> 'picosecondF'
decimals -> 'subsecondF'
@

-}
module Fmt.Time
(
  -- * Custom
  timeF,

  -- * For 'TimeZone' (and 'ZonedTime' and 'UTCTime')
  tzF,
  tzNameF,
  dateTimeF,

  -- * For 'TimeOfDay' (and 'LocalTime' and 'ZonedTime' and 'UTCTime')
  hmF,
  hmsF,
  hmsLF,
  hmsPLF,
  dayHalfF,
  dayHalfUF,
  hour24F,
  hour12F,
  hour24SF,
  hour12SF,
  minuteF,
  secondF,
  picosecondF,
  subsecondF,

  -- * For 'UTCTime' and 'ZonedTime'
  epochF,

  -- * For 'Day' (and 'LocalTime' and 'ZonedTime' and 'UTCTime')
  dateSlashF,
  dateDashF,
  dateSlashLF,
  yearF,
  yyF,
  centuryF,
  monthNameF,
  monthNameShortF,
  monthF,
  dayOfMonthF,
  dayOfMonthOrdF,
  dayOfMonthSF,
  dayF,
  weekYearF,
  weekYYF,
  weekCenturyF,
  weekF,
  dayOfWeekF,
  dayNameShortF,
  dayNameF,
  weekFromZeroF,
  dayOfWeekFromZeroF,
  weekOfYearMonF,

  -- * Time spans, diffs, 'NominalDiffTime', 'DiffTime', etc.
  diffF,
  yearsF,
  daysF,
  hoursF,
  minutesF,
  secondsF,
)
where


import           Data.List               (find)

#if !MIN_VERSION_base(4,9,0)
import           Data.Monoid             ((<>))
#endif

import           Data.Text               (Text)
import qualified Data.Text               as T
import           Formatting.Buildable    (build)
import           Data.Text.Lazy.Builder  (Builder)
import           Data.Time

#if !MIN_VERSION_time(1,5,0)
import           Data.Time.Locale.Compat
#endif

import           Fmt.Internal.Numeric    (fixedF, ordinalF)

-- $setup
-- >>> let t = read "2018-02-14 16:20:45.5 CST" :: ZonedTime

----------------------------------------------------------------------------
-- Custom
----------------------------------------------------------------------------

-- | Format time with an arbitrary formatting string. Other formatters in
-- this module are implemented using 'timeF'.
timeF :: FormatTime a => Text -> a -> Builder
timeF :: Text -> a -> Builder
timeF Text
f = 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
. 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)

----------------------------------------------------------------------------
-- For 'TimeZone' (and 'ZonedTime' and 'UTCTime')
----------------------------------------------------------------------------

-- | Timezone offset on the format @-HHMM@.
--
-- >>> t
-- 2018-02-14 16:20:45.5 CST
-- >>> tzF t
-- "-0600"
tzF :: FormatTime a => a -> Builder
tzF :: a -> Builder
tzF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%z"

-- | Timezone name.
--
-- >>> tzNameF t
-- "CST"
tzNameF :: FormatTime a => a -> Builder
tzNameF :: a -> Builder
tzNameF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%Z"

-- | As 'dateTimeFmt' @locale@ (e.g. @%a %b %e %H:%M:%S %Z %Y@).
--
-- >>> dateTimeF t
-- "Wed Feb 14 16:20:45 CST 2018"
dateTimeF :: FormatTime a => a -> Builder
dateTimeF :: a -> Builder
dateTimeF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%c"

----------------------------------------------------------------------------
-- For 'TimeOfDay' (and 'LocalTime' and 'ZonedTime' and 'UTCTime')
----------------------------------------------------------------------------

-- | Same as @%H:%M@.
--
-- >>> hmF t
-- "16:20"
hmF :: FormatTime a => a -> Builder
hmF :: a -> Builder
hmF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%R"

-- | Same as @%H:%M:%S@.
--
-- >>> hmsF t
-- "16:20:45"
hmsF :: FormatTime a => a -> Builder
hmsF :: a -> Builder
hmsF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%T"

-- | As 'timeFmt' @locale@ (e.g. @%H:%M:%S@).
--
-- >>> hmsLF t
-- "16:20:45"
hmsLF :: FormatTime a => a -> Builder
hmsLF :: a -> Builder
hmsLF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%X"

-- | As 'time12Fmt' @locale@ (e.g. @%I:%M:%S %p@).
--
-- >>> hmsPLF t
-- "04:20:45 PM"
hmsPLF :: FormatTime a => a -> Builder
hmsPLF :: a -> Builder
hmsPLF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%r"

-- | Day half from ('amPm' @locale@), converted to lowercase, @am@, @pm@.
--
-- >>> dayHalfF t
-- "pm"
dayHalfF :: FormatTime a => a -> Builder
dayHalfF :: a -> Builder
dayHalfF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%P"

-- | Day half from ('amPm' @locale@), @AM@, @PM@.
--
-- >>> dayHalfUF t
-- "PM"
dayHalfUF :: FormatTime a => a -> Builder
dayHalfUF :: a -> Builder
dayHalfUF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%p"

-- | Hour, 24-hour, leading 0 as needed, @00@ - @23@.
--
-- >>> hour24F t
-- "16"
-- >>> hour24F midnight
-- "00"
hour24F :: FormatTime a => a -> Builder
hour24F :: a -> Builder
hour24F = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%H"

-- | Hour, 12-hour, leading 0 as needed, @01@ - @12@.
--
-- >>> hour12F t
-- "04"
-- >>> hour12F midnight
-- "12"
hour12F :: FormatTime a => a -> Builder
hour12F :: a -> Builder
hour12F = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%I"

-- | Hour, 24-hour, leading space as needed, @ 0@ - @23@.
--
-- >>> hour24SF t
-- "16"
-- >>> hour24SF midnight
-- " 0"
hour24SF :: FormatTime a => a -> Builder
hour24SF :: a -> Builder
hour24SF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%k"

-- | Hour, 12-hour, leading space as needed, @ 1@ - @12@.
--
-- >>> hour12SF t
-- " 4"
-- >>> hour12SF midnight
-- "12"
hour12SF :: FormatTime a => a -> Builder
hour12SF :: a -> Builder
hour12SF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%l"

-- | Minute, @00@ - @59@.
--
-- >>> minuteF t
-- "20"
minuteF :: FormatTime a => a -> Builder
minuteF :: a -> Builder
minuteF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%M"

-- | Second, without decimal part, @00@ - @60@.
--
-- >>> secondF t
-- "45"
secondF :: FormatTime a => a -> Builder
secondF :: a -> Builder
secondF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%S"

-- | Picosecond, including trailing zeros, @000000000000@ - @999999999999@.
--
-- >>> picosecondF t
-- "500000000000"
picosecondF :: FormatTime a => a -> Builder
picosecondF :: a -> Builder
picosecondF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%q"

-- | Decimal point of the second. Up to 12 digits, without trailing zeros.
-- For a whole number of seconds, this produces an empty string.
--
-- >>> subsecondF t
-- ".5"
subsecondF :: FormatTime a => a -> Builder
subsecondF :: a -> Builder
subsecondF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%Q"

----------------------------------------------------------------------------
-- For 'UTCTime' and 'ZonedTime'
----------------------------------------------------------------------------

-- | 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@.
--
-- >>> epochF t
-- "1518646845"
epochF :: FormatTime a => a -> Builder
epochF :: a -> Builder
epochF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%s"

----------------------------------------------------------------------------
-- For 'Day' (and 'LocalTime' and 'ZonedTime' and 'UTCTime')
----------------------------------------------------------------------------

-- | Same as @%m\/%d\/%y@.
--
-- >>> dateSlashF t
-- "02/14/18"
dateSlashF :: FormatTime a => a -> Builder
dateSlashF :: a -> Builder
dateSlashF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%D"

-- | Same as @%Y-%m-%d@.
--
-- >>> dateDashF t
-- "2018-02-14"
dateDashF :: FormatTime a => a -> Builder
dateDashF :: a -> Builder
dateDashF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%F"

-- | As 'dateFmt' @locale@ (e.g. @%m\/%d\/%y@).
--
-- >>> dateSlashLF t
-- "02/14/18"
dateSlashLF :: FormatTime a => a -> Builder
dateSlashLF :: a -> Builder
dateSlashLF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%x"

-- | Year.
--
-- >>> yearF t
-- "2018"
yearF :: FormatTime a => a -> Builder
yearF :: a -> Builder
yearF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%Y"

-- | Last two digits of year, @00@ - @99@.
--
-- >>> yyF t
-- "18"
yyF :: FormatTime a => a -> Builder
yyF :: a -> Builder
yyF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%y"

-- | Century (being the first two digits of the year), @00@ - @99@.
--
-- >>> centuryF t
-- "20"
centuryF :: FormatTime a => a -> Builder
centuryF :: a -> Builder
centuryF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%C"

-- | Month name, long form ('fst' from 'months' @locale@), @January@ -
-- @December@.
--
-- >>> monthNameF t
-- "February"
monthNameF :: FormatTime a => a -> Builder
monthNameF :: a -> Builder
monthNameF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%B"

-- | Month name, short form ('snd' from 'months' @locale@), @Jan@ - @Dec@.
--
-- >>> monthNameShortF t
-- "Feb"
monthNameShortF :: FormatTime a => a -> Builder
monthNameShortF :: a -> Builder
monthNameShortF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%b"

-- | Month of year, leading 0 as needed, @01@ - @12@.
--
-- >>> monthF t
-- "02"
monthF :: FormatTime a => a -> Builder
monthF :: a -> Builder
monthF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%m"

-- | Day of month, leading 0 as needed, @01@ - @31@.
--
-- >>> dayOfMonthF t
-- "14"
dayOfMonthF :: FormatTime a => a -> Builder
dayOfMonthF :: a -> Builder
dayOfMonthF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%d"

-- | Day of month, @1st@, @2nd@, @25th@, etc.
--
-- >>> dayOfMonthOrdF t
-- "14th"
dayOfMonthOrdF :: FormatTime a => a -> Builder
dayOfMonthOrdF :: a -> Builder
dayOfMonthOrdF = Int -> Builder
forall a. (Buildable a, Integral a) => a -> Builder
ordinalF (Int -> Builder) -> (a -> Int) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. FormatTime a => a -> Int
timeToInt
  where
    timeToInt :: FormatTime a => a -> Int
    timeToInt :: a -> Int
timeToInt = 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"

-- | Day of month, leading space as needed, @ 1@ - @31@.
dayOfMonthSF :: FormatTime a => a -> Builder
dayOfMonthSF :: a -> Builder
dayOfMonthSF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%e"

-- | Day of year for Ordinal Date format, @001@ - @366@.
--
-- >>> dayF t
-- "045"
dayF :: FormatTime a => a -> Builder
dayF :: a -> Builder
dayF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%j"

-- | Year for Week Date format e.g. @2013@.
--
-- >>> weekYearF t
-- "2018"
weekYearF :: FormatTime a => a -> Builder
weekYearF :: a -> Builder
weekYearF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%G"

-- | Last two digits of year for Week Date format, @00@ - @99@.
--
-- >>> weekYYF t
-- "18"
weekYYF :: FormatTime a => a -> Builder
weekYYF :: a -> Builder
weekYYF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%g"

-- | Century (first two digits of year) for Week Date format, @00@ - @99@.
--
-- >>> weekCenturyF t
-- "20"
weekCenturyF :: FormatTime a => a -> Builder
weekCenturyF :: a -> Builder
weekCenturyF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%f"

-- | Week for Week Date format, @01@ - @53@.
--
-- >>> weekF t
-- "07"
weekF :: FormatTime a => a -> Builder
weekF :: a -> Builder
weekF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%V"

-- | Day for Week Date format, @1@ - @7@.
--
-- >>> dayOfWeekF t
-- "3"
dayOfWeekF :: FormatTime a => a -> Builder
dayOfWeekF :: a -> Builder
dayOfWeekF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%u"

-- | Day of week, short form ('snd' from 'wDays' @locale@), @Sun@ - @Sat@.
--
-- >>> dayNameShortF t
-- "Wed"
dayNameShortF :: FormatTime a => a -> Builder
dayNameShortF :: a -> Builder
dayNameShortF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%a"

-- | Day of week, long form ('fst' from 'wDays' @locale@), @Sunday@ -
-- @Saturday@.
--
-- >>> dayNameF t
-- "Wednesday"
dayNameF :: FormatTime a => a -> Builder
dayNameF :: a -> Builder
dayNameF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%A"

-- | Week number of year, where weeks start on Sunday (as
-- 'sundayStartWeek'), @00@ - @53@.
--
-- >>> weekFromZeroF t
-- "06"
weekFromZeroF :: FormatTime a => a -> Builder
weekFromZeroF :: a -> Builder
weekFromZeroF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%U"

-- | Day of week number, @0@ (= Sunday) - @6@ (= Saturday).
--
-- >>> dayOfWeekFromZeroF t
-- "3"
dayOfWeekFromZeroF :: FormatTime a => a -> Builder
dayOfWeekFromZeroF :: a -> Builder
dayOfWeekFromZeroF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%w"

-- | Week number of year, where weeks start on Monday (as
-- 'mondayStartWeek'), @00@ - @53@.
--
-- >>> weekOfYearMonF t
-- "07"
weekOfYearMonF :: FormatTime a => a -> Builder
weekOfYearMonF :: a -> Builder
weekOfYearMonF = Text -> a -> Builder
forall a. FormatTime a => Text -> a -> Builder
timeF Text
"%W"

----------------------------------------------------------------------------
-- Time spans, diffs, 'NominalDiffTime', 'DiffTime', etc.
----------------------------------------------------------------------------

-- | Display a time span as one time relative to another. Input is assumed to
-- be seconds. Typical inputs are 'NominalDiffTime' and 'DiffTime'.
--
-- >>> diffF False 100
-- "a minute"
-- >>> diffF True 100
-- "in a minute"
diffF :: forall n . RealFrac n
      => Bool     -- ^ Whether to display the @in/ago@ prefix or not
      -> n        -- ^ Example: @3 seconds ago@, @in 2 days@
      -> Builder
diffF :: Bool -> n -> Builder
diffF Bool
fix = n -> Builder
RealFrac n => n -> Builder
diffed
  where
    diffed :: RealFrac n => n -> Builder
    diffed :: n -> Builder
diffed n
ts =
      case ((n, Int -> Builder, n) -> Bool)
-> [(n, Int -> Builder, n)] -> Maybe (n, Int -> Builder, n)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\(n
s,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, Int -> Builder, n)] -> [(n, Int -> Builder, n)]
forall a. [a] -> [a]
reverse [(n, Int -> Builder, n)]
RealFrac n => [(n, Int -> Builder, n)]
ranges) of
        Maybe (n, Int -> Builder, n)
Nothing           -> Builder
"unknown"
        Just (n
_, Int -> Builder
f, n
base) -> Builder
prefix Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
f (n -> n -> Int
RealFrac n => n -> n -> Int
toInt n
ts n
base) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
suffix
      where
        prefix :: Builder
prefix = 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 :: Builder
suffix = 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 :: RealFrac n => n -> n -> Int
    toInt :: n -> n -> Int
toInt n
ts n
base = Int -> Int
forall a. Num a => a -> a
abs (n -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (n
ts n -> n -> n
forall a. Fractional a => a -> a -> a
/ n
base))

    intF :: Builder -> Int -> Builder
    intF :: Builder -> Int -> Builder
intF Builder
t Int
n = Int -> Builder
forall p. Buildable p => p -> Builder
build Int
n Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
t

    ranges :: RealFrac n => [(n, Int -> Builder, n)]
    ranges :: [(n, Int -> Builder, n)]
ranges =
      [ (n
0           , Builder -> Int -> Builder
intF  Builder
" milliseconds" , n
0.001 )
      , (n
1           , Builder -> Int -> Builder
intF  Builder
" seconds"      , n
1     )
      , (n
minute      , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a minute"      , n
0     )
      , (n
minute n -> n -> n
forall a. Num a => a -> a -> a
* n
2  , Builder -> Int -> Builder
intF  Builder
" minutes"      , n
minute)
      , (n
minute n -> n -> n
forall a. Num a => a -> a -> a
* n
30 , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"half an hour"  , n
0     )
      , (n
minute n -> n -> n
forall a. Num a => a -> a -> a
* n
31 , Builder -> Int -> Builder
intF  Builder
" minutes"      , n
minute)
      , (n
hour        , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"an hour"       , n
0     )
      , (n
hour n -> n -> n
forall a. Num a => a -> a -> a
* n
2    , Builder -> Int -> Builder
intF  Builder
" hours"        , n
hour  )
      , (n
hour n -> n -> n
forall a. Num a => a -> a -> a
* n
3    , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a few hours"   , n
0     )
      , (n
hour n -> n -> n
forall a. Num a => a -> a -> a
* n
4    , Builder -> Int -> Builder
intF  Builder
" hours"        , n
hour  )
      , (n
day         , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a day"         , n
0     )
      , (n
day n -> n -> n
forall a. Num a => a -> a -> a
* n
2     , Builder -> Int -> Builder
intF  Builder
" days"         , n
day   )
      , (n
week        , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a week"        , n
0     )
      , (n
week n -> n -> n
forall a. Num a => a -> a -> a
* n
2    , Builder -> Int -> Builder
intF  Builder
" weeks"        , n
week  )
      , (n
month       , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a month"       , n
0     )
      , (n
month n -> n -> n
forall a. Num a => a -> a -> a
* n
2   , Builder -> Int -> Builder
intF  Builder
" months"       , n
month )
      , (n
year        , Builder -> Int -> Builder
forall a b. a -> b -> a
const Builder
"a year"        , n
0     )
      , (n
year n -> n -> n
forall a. Num a => a -> a -> a
* n
2    , Builder -> Int -> Builder
intF  Builder
" 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

-- | Display the absolute value time span in years.
--
-- >>> epochF t    -- time passed since Jan 1, 1970
-- "1518646845"
-- >>> yearsF 3 1518646845
-- "48.156"
yearsF :: RealFrac n
       => Int -- ^ Decimal places.
       -> n
       -> Builder
yearsF :: Int -> n -> Builder
yearsF Int
n = Int -> n -> Builder
forall a. Real a => Int -> a -> Builder
fixedF 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
x = a
x 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

-- | Display the absolute value time span in days.
--
-- >>> daysF 3 1518646845
-- "17576.931"
daysF :: RealFrac n
      => Int -- ^ Decimal places.
      -> n
      -> Builder
daysF :: Int -> n -> Builder
daysF Int
n = Int -> n -> Builder
forall a. Real a => Int -> a -> Builder
fixedF 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
x = a
x 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

-- | Display the absolute value time span in hours.
--
-- >>> hoursF 3 3600
-- "1.000"
hoursF :: RealFrac n
       => Int -- ^ Decimal places.
       -> n
       -> Builder
hoursF :: Int -> n -> Builder
hoursF Int
n = Int -> n -> Builder
forall a. Real a => Int -> a -> Builder
fixedF 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
x = a
x a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
60 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
60

-- | Display the absolute value time span in minutes.
--
-- >>> minutesF 3 150
-- "2.500"
minutesF :: RealFrac n
         => Int -- ^ Decimal places.
         -> n
         -> Builder
minutesF :: Int -> n -> Builder
minutesF Int
n = Int -> n -> Builder
forall a. Real a => Int -> a -> Builder
fixedF 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
x = a
x a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
60

-- | Display the absolute value time span in seconds.
--
-- >>> secondsF 3 100
-- "100.000"
secondsF :: RealFrac n
         => Int -- ^ Decimal places.
         -> n
         -> Builder
secondsF :: Int -> n -> Builder
secondsF Int
n = Int -> n -> Builder
forall a. Real a => Int -> a -> Builder
fixedF 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