{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RecordWildCards #-}

module Text.Time.Pretty.Render
  ( renderDaysAgoAuto,
    renderTimeAgoAuto,
  )
where

import Text.Time.Pretty.TimeAgo

renderDaysAgoAuto :: DaysAgo -> String
renderDaysAgoAuto :: DaysAgo -> String
renderDaysAgoAuto DaysAgo {Integer
Ordering
daysAgoDays :: DaysAgo -> Integer
daysAgoWeeks :: DaysAgo -> Integer
daysAgoMonths :: DaysAgo -> Integer
daysAgoYears :: DaysAgo -> Integer
daysAgoSign :: DaysAgo -> Ordering
daysAgoDays :: Integer
daysAgoWeeks :: Integer
daysAgoMonths :: Integer
daysAgoYears :: Integer
daysAgoSign :: Ordering
..} =
  case Ordering
daysAgoSign of
    Ordering
GT ->
      if
          | Integer
daysAgoYears Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoYears String
"year" String
"years", String
"ago"]
          | Integer
daysAgoMonths Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoMonths String
"month" String
"months", String
"ago"]
          | Integer
daysAgoWeeks Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoWeeks String
"week" String
"weeks", String
"ago"]
          | Integer
daysAgoDays Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1 -> String
"yesterday"
          | Integer
daysAgoDays Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoDays String
"day" String
"days", String
"ago"]
          | Bool
otherwise -> String
"today"
    Ordering
EQ -> String
"today"
    Ordering
LT ->
      if
          | Integer
daysAgoYears Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoYears String
"year" String
"years"]
          | Integer
daysAgoMonths Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoMonths String
"month" String
"months"]
          | Integer
daysAgoWeeks Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoWeeks String
"week" String
"weeks"]
          | Integer
daysAgoDays Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1 -> String
"tomorrow"
          | Integer
daysAgoDays Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
daysAgoDays String
"day" String
"days"]
          | Bool
otherwise -> String
"today"

renderTimeAgoAuto :: TimeAgo -> String
renderTimeAgoAuto :: TimeAgo -> String
renderTimeAgoAuto TimeAgo {Integer
Ordering
DaysAgo
timeAgoPicoSeconds :: TimeAgo -> Integer
timeAgoSeconds :: TimeAgo -> Integer
timeAgoMinutes :: TimeAgo -> Integer
timeAgoHours :: TimeAgo -> Integer
timeAgoDaysAgo :: TimeAgo -> DaysAgo
timeAgoSign :: TimeAgo -> Ordering
timeAgoPicoSeconds :: Integer
timeAgoSeconds :: Integer
timeAgoMinutes :: Integer
timeAgoHours :: Integer
timeAgoDaysAgo :: DaysAgo
timeAgoSign :: Ordering
..} =
  case Ordering
timeAgoSign of
    Ordering
GT ->
      if
          | DaysAgo -> Integer
daysAgoToDays DaysAgo
timeAgoDaysAgo Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1 -> String
"1 day ago"
          | DaysAgo -> Integer
daysAgoToDays DaysAgo
timeAgoDaysAgo Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 ->
            DaysAgo -> String
renderDaysAgoAuto (DaysAgo
timeAgoDaysAgo {daysAgoSign :: Ordering
daysAgoSign = Ordering
timeAgoSign})
          | Integer
timeAgoHours Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoHours String
"hour" String
"hours", String
"ago"]
          | Integer
timeAgoMinutes Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoMinutes String
"minute" String
"minutes", String
"ago"]
          | Integer
timeAgoSeconds Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoSeconds String
"second" String
"seconds", String
"ago"]
          | Bool
otherwise -> String
"just now"
    Ordering
EQ -> String
"just now"
    Ordering
LT ->
      if
          | DaysAgo -> Integer
daysAgoToDays DaysAgo
timeAgoDaysAgo Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1 -> String
"in 1 day"
          | DaysAgo -> Integer
daysAgoToDays DaysAgo
timeAgoDaysAgo Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 ->
            DaysAgo -> String
renderDaysAgoAuto (DaysAgo
timeAgoDaysAgo {daysAgoSign :: Ordering
daysAgoSign = Ordering
timeAgoSign})
          | Integer
timeAgoHours Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoHours String
"hour" String
"hours"]
          | Integer
timeAgoMinutes Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoMinutes String
"minute" String
"minutes"]
          | Integer
timeAgoSeconds Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 -> [String] -> String
unwords [String
"in", Integer -> String -> String -> String
forall a. (Show a, Integral a) => a -> String -> String -> String
plural Integer
timeAgoSeconds String
"second" String
"seconds"]
          | Bool
otherwise -> String
"just now"

plural :: (Show a, Integral a) => a -> String -> String -> String
plural :: a -> String -> String -> String
plural a
1 String
sing String
_ = String
"1 " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
sing
plural a
n String
_ String
plur = a -> String
forall a. Show a => a -> String
show a
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
plur