-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2025 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 Test.FeatureFlags.CellsInternal where

import qualified API.GalleyInternal as Internal
import SetupHelpers
import Test.Cells (QueueConsumer (..), getMessage, watchCellsEvents)
import Test.FeatureFlags.Util
import Testlib.Prelude

testCellsInternalEvent :: (HasCallStack) => App ()
testCellsInternalEvent :: HasCallStack => App ()
testCellsInternalEvent = do
  (Value
alice, String
tid, [Value]
_) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
0
  QueueConsumer
q <- do
    QueueConsumer
q <- WatchCellsEvents -> App QueueConsumer
watchCellsEvents WatchCellsEvents
forall a. Default a => a
def
    let isEventForTeam :: Value -> App Bool
isEventForTeam Value
v = forall a b.
(MakesValue a, MakesValue b) =>
a -> String -> b -> App Bool
fieldEquals @Value Value
v String
"payload.0.team" String
tid
    -- the cells event queue is shared by tests
    -- let's hope this filter reduces the risk of tests interfering with each other
    QueueConsumer -> App QueueConsumer
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueueConsumer -> App QueueConsumer)
-> QueueConsumer -> App QueueConsumer
forall a b. (a -> b) -> a -> b
$ QueueConsumer
q {filter = isEventForTeam}
  let quota :: String
quota = String
"234723984"
      update :: Value
update = String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota}
  APIAccess -> Value -> String -> String -> Value -> App Response
setFeature APIAccess
InternalAPI Value
alice String
tid String
"cellsInternal" Value
update App Response -> (Response -> App ()) -> App ()
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HasCallStack => Response -> App ()
Response -> App ()
assertSuccess
  Value
event <- QueueConsumer -> App Value
getMessage QueueConsumer
q App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"payload.0"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"name" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"cellsInternal"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
tid
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"type" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"feature-config.update"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"data.lockStatus" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"unlocked"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"data.status" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"enabled"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"data.config.backend.url" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"https://cells-beta.wire.com"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"data.config.collabora.edition" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"COOL"
  Value
event Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"data.config.storage.teamQuotaBytes" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
quota

testCellsInternal :: (HasCallStack) => App ()
testCellsInternal :: HasCallStack => App ()
testCellsInternal = do
  (Value
alice, String
tid, [Value]
_) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
0

  Value -> (WebSocket -> App ()) -> App ()
forall w a.
(HasCallStack, ToWSConnect w) =>
w -> (WebSocket -> App a) -> App a
withWebSocket Value
alice ((WebSocket -> App ()) -> App ())
-> (WebSocket -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \WebSocket
ws -> do
    [Value] -> (Value -> App ()) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
validCellsInternalUpdates ((Value -> App ()) -> App ()) -> (Value -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ HasCallStack =>
APIAccess -> WebSocket -> String -> String -> Value -> App ()
APIAccess -> WebSocket -> String -> String -> Value -> App ()
setFlag APIAccess
InternalAPI WebSocket
ws String
tid String
"cellsInternal"
    [Value] -> (Value -> App Value) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
invalidCellsInternalUpdates ((Value -> App Value) -> App ()) -> (Value -> App Value) -> App ()
forall a b. (a -> b) -> a -> b
$ APIAccess -> Value -> String -> String -> Value -> App Response
setFeature APIAccess
InternalAPI Value
alice String
tid String
"cellsInternal" (Value -> App Response)
-> (Response -> App Value) -> Value -> App Value
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> HasCallStack => Int -> Response -> App Value
Int -> Response -> App Value
getJSON Int
400

  -- the feature does not have a public PUT endpoint
  APIAccess -> Value -> String -> String -> Value -> App Response
setFeature APIAccess
PublicAPI Value
alice String
tid String
"cellsInternal" Value
enabled App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
`bindResponse` \Response
resp -> do
    Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
    Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"label" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"no-endpoint"

validCellsInternalUpdates :: [Value]
validCellsInternalUpdates :: [Value]
validCellsInternalUpdates =
  [ String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf,
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "NO"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "COOL"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {url = "https://wire.com"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "92346832946243"}
  ]

invalidCellsInternalUpdates :: [Value]
invalidCellsInternalUpdates :: [Value]
invalidCellsInternalUpdates =
  [ String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "FOO"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {url = "http://wire.com"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "-92346832946243"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "1 TB"},
    String -> String -> CellsInternalConfig -> Value
mkFt String
"disabled" String
"unlocked" CellsInternalConfig
defConf
  ]

mkFt :: String -> String -> CellsInternalConfig -> Value
mkFt :: String -> String -> CellsInternalConfig -> Value
mkFt String
s String
ls CellsInternalConfig
c =
  [Pair] -> Value
object
    [ String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
ls,
      String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
s,
      String
"ttl" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"unlimited",
      String
"config"
        String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
          [ String
"backend" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.url],
            String
"collabora" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"edition" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.collabora],
            String
"storage" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"teamQuotaBytes" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.quota]
          ]
    ]

defConf :: CellsInternalConfig
defConf :: CellsInternalConfig
defConf =
  CellsInternalConfig
    { url :: String
url = String
"https://cells-beta.wire.com",
      collabora :: String
collabora = String
"COOL",
      quota :: String
quota = String
"1000000000000"
    }

testPatchCellsInternal :: (HasCallStack) => App ()
testPatchCellsInternal :: HasCallStack => App ()
testPatchCellsInternal = do
  [Value] -> (Value -> App ()) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
validCellsInternalUpdates ((Value -> App ()) -> App ()) -> (Value -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"cellsInternal"
  (Value
_, String
tid, [Value]
_) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
0
  [Value] -> (Value -> App ()) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"locked" CellsInternalConfig
defConf Value -> [Value] -> [Value]
forall a. a -> [a] -> [a]
: [Value]
invalidCellsInternalUpdates)
    ((Value -> App ()) -> App ()) -> (Value -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ Domain -> String -> String -> Value -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> Value -> App Response
Internal.patchTeamFeature Domain
OwnDomain String
tid String
"cellsInternal"
    (Value -> App Response) -> (Response -> App ()) -> Value -> App ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
400

data CellsInternalConfig = CellsInternalConfig
  { CellsInternalConfig -> String
url :: String,
    CellsInternalConfig -> String
collabora :: String,
    CellsInternalConfig -> String
quota :: String
  }