-- 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/>.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Wire.API.MLS.Lifetime where

import Data.Time.Clock.POSIX
import Imports
import Test.QuickCheck
import Wire.API.MLS.Serialisation
import Wire.Arbitrary

-- | Seconds since the UNIX epoch.
newtype Timestamp = Timestamp {Timestamp -> Word64
timestampSeconds :: Word64}
  deriving newtype (Timestamp -> Timestamp -> Bool
(Timestamp -> Timestamp -> Bool)
-> (Timestamp -> Timestamp -> Bool) -> Eq Timestamp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Timestamp -> Timestamp -> Bool
== :: Timestamp -> Timestamp -> Bool
$c/= :: Timestamp -> Timestamp -> Bool
/= :: Timestamp -> Timestamp -> Bool
Eq, Int -> Timestamp -> ShowS
[Timestamp] -> ShowS
Timestamp -> String
(Int -> Timestamp -> ShowS)
-> (Timestamp -> String)
-> ([Timestamp] -> ShowS)
-> Show Timestamp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Timestamp -> ShowS
showsPrec :: Int -> Timestamp -> ShowS
$cshow :: Timestamp -> String
show :: Timestamp -> String
$cshowList :: [Timestamp] -> ShowS
showList :: [Timestamp] -> ShowS
Show, Gen Timestamp
Gen Timestamp -> (Timestamp -> [Timestamp]) -> Arbitrary Timestamp
Timestamp -> [Timestamp]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen Timestamp
arbitrary :: Gen Timestamp
$cshrink :: Timestamp -> [Timestamp]
shrink :: Timestamp -> [Timestamp]
Arbitrary, Get Timestamp
Get Timestamp -> ParseMLS Timestamp
forall a. Get a -> ParseMLS a
$cparseMLS :: Get Timestamp
parseMLS :: Get Timestamp
ParseMLS, Timestamp -> Put
(Timestamp -> Put) -> SerialiseMLS Timestamp
forall a. (a -> Put) -> SerialiseMLS a
$cserialiseMLS :: Timestamp -> Put
serialiseMLS :: Timestamp -> Put
SerialiseMLS)

tsPOSIX :: Timestamp -> POSIXTime
tsPOSIX :: Timestamp -> POSIXTime
tsPOSIX = Word64 -> POSIXTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> POSIXTime)
-> (Timestamp -> Word64) -> Timestamp -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Timestamp -> Word64
timestampSeconds

-- | https://messaginglayersecurity.rocks/mls-protocol/draft-ietf-mls-protocol-20/draft-ietf-mls-protocol.html#section-7.2-2
data Lifetime = Lifetime
  { Lifetime -> Timestamp
ltNotBefore :: Timestamp,
    Lifetime -> Timestamp
ltNotAfter :: Timestamp
  }
  deriving stock (Lifetime -> Lifetime -> Bool
(Lifetime -> Lifetime -> Bool)
-> (Lifetime -> Lifetime -> Bool) -> Eq Lifetime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Lifetime -> Lifetime -> Bool
== :: Lifetime -> Lifetime -> Bool
$c/= :: Lifetime -> Lifetime -> Bool
/= :: Lifetime -> Lifetime -> Bool
Eq, Int -> Lifetime -> ShowS
[Lifetime] -> ShowS
Lifetime -> String
(Int -> Lifetime -> ShowS)
-> (Lifetime -> String) -> ([Lifetime] -> ShowS) -> Show Lifetime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Lifetime -> ShowS
showsPrec :: Int -> Lifetime -> ShowS
$cshow :: Lifetime -> String
show :: Lifetime -> String
$cshowList :: [Lifetime] -> ShowS
showList :: [Lifetime] -> ShowS
Show, (forall x. Lifetime -> Rep Lifetime x)
-> (forall x. Rep Lifetime x -> Lifetime) -> Generic Lifetime
forall x. Rep Lifetime x -> Lifetime
forall x. Lifetime -> Rep Lifetime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Lifetime -> Rep Lifetime x
from :: forall x. Lifetime -> Rep Lifetime x
$cto :: forall x. Rep Lifetime x -> Lifetime
to :: forall x. Rep Lifetime x -> Lifetime
Generic)
  deriving (Gen Lifetime
Gen Lifetime -> (Lifetime -> [Lifetime]) -> Arbitrary Lifetime
Lifetime -> [Lifetime]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen Lifetime
arbitrary :: Gen Lifetime
$cshrink :: Lifetime -> [Lifetime]
shrink :: Lifetime -> [Lifetime]
Arbitrary) via GenericUniform Lifetime

instance ParseMLS Lifetime where
  parseMLS :: Get Lifetime
parseMLS = Timestamp -> Timestamp -> Lifetime
Lifetime (Timestamp -> Timestamp -> Lifetime)
-> Get Timestamp -> Get (Timestamp -> Lifetime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Timestamp
forall a. ParseMLS a => Get a
parseMLS Get (Timestamp -> Lifetime) -> Get Timestamp -> Get Lifetime
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Timestamp
forall a. ParseMLS a => Get a
parseMLS

instance SerialiseMLS Lifetime where
  serialiseMLS :: Lifetime -> Put
serialiseMLS Lifetime
lt = do
    Timestamp -> Put
forall a. SerialiseMLS a => a -> Put
serialiseMLS Lifetime
lt.ltNotBefore
    Timestamp -> Put
forall a. SerialiseMLS a => a -> Put
serialiseMLS Lifetime
lt.ltNotAfter