{-# LANGUAGE TemplateHaskell #-}

-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

module Wire.Sem.Now
  ( Now (..),
    get,
    boolTTL,
  )
where

import Data.Time.Clock
import Imports
import Polysemy
import Polysemy.Check (deriveGenericK)
import Wire.Sem.FromUTC

data Now m a where
  Get :: Now m UTCTime

makeSem ''Now
deriveGenericK ''Now

deriving instance Show (Now m a)

-- | Check a time against 'Now', checking if it's still alive (hasn't occurred yet.)
boolTTL ::
  forall t r a.
  (Member Now r, Ord t, FromUTC t) =>
  -- | The value to return if the TTL is expired
  a ->
  -- | The value to return if the TTL is alive
  a ->
  t -> -- The time to check
  Sem r a
boolTTL :: forall t (r :: EffectRow) a.
(Member Now r, Ord t, FromUTC t) =>
a -> a -> t -> Sem r a
boolTTL a
f a
t t
time = do
  t
now <- UTCTime -> t
forall a. FromUTC a => UTCTime -> a
fromUTCTime (UTCTime -> t) -> Sem r UTCTime -> Sem r t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Sem r UTCTime
forall (r :: EffectRow). Member Now r => Sem r UTCTime
get
  a -> Sem r a
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Sem r a) -> a -> Sem r a
forall a b. (a -> b) -> a -> b
$ a -> a -> Bool -> a
forall a. a -> a -> Bool -> a
bool a
f a
t (Bool -> a) -> Bool -> a
forall a b. (a -> b) -> a -> b
$ t
now t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
time