{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

-- 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 Cassandra.Options where

import Data.Aeson.TH
import Imports

data Endpoint = Endpoint
  { Endpoint -> Text
host :: !Text,
    Endpoint -> Word16
port :: !Word16
  }
  deriving (Int -> Endpoint -> ShowS
[Endpoint] -> ShowS
Endpoint -> String
(Int -> Endpoint -> ShowS)
-> (Endpoint -> String) -> ([Endpoint] -> ShowS) -> Show Endpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Endpoint -> ShowS
showsPrec :: Int -> Endpoint -> ShowS
$cshow :: Endpoint -> String
show :: Endpoint -> String
$cshowList :: [Endpoint] -> ShowS
showList :: [Endpoint] -> ShowS
Show, (forall x. Endpoint -> Rep Endpoint x)
-> (forall x. Rep Endpoint x -> Endpoint) -> Generic Endpoint
forall x. Rep Endpoint x -> Endpoint
forall x. Endpoint -> Rep Endpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Endpoint -> Rep Endpoint x
from :: forall x. Endpoint -> Rep Endpoint x
$cto :: forall x. Rep Endpoint x -> Endpoint
to :: forall x. Rep Endpoint x -> Endpoint
Generic)

deriveJSON defaultOptions ''Endpoint

data CassandraOpts = CassandraOpts
  { CassandraOpts -> Endpoint
endpoint :: !Endpoint,
    CassandraOpts -> Text
keyspace :: !Text,
    -- | If this option is unset, use all available nodes.
    -- If this option is set, use only cassandra nodes in the given datacentre
    --
    -- This option is most likely only necessary during a cassandra DC migration
    -- FUTUREWORK: remove this option again, or support a datacentre migration feature
    CassandraOpts -> Maybe Text
filterNodesByDatacentre :: !(Maybe Text),
    CassandraOpts -> Maybe String
tlsCa :: Maybe FilePath
  }
  deriving (Int -> CassandraOpts -> ShowS
[CassandraOpts] -> ShowS
CassandraOpts -> String
(Int -> CassandraOpts -> ShowS)
-> (CassandraOpts -> String)
-> ([CassandraOpts] -> ShowS)
-> Show CassandraOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CassandraOpts -> ShowS
showsPrec :: Int -> CassandraOpts -> ShowS
$cshow :: CassandraOpts -> String
show :: CassandraOpts -> String
$cshowList :: [CassandraOpts] -> ShowS
showList :: [CassandraOpts] -> ShowS
Show, (forall x. CassandraOpts -> Rep CassandraOpts x)
-> (forall x. Rep CassandraOpts x -> CassandraOpts)
-> Generic CassandraOpts
forall x. Rep CassandraOpts x -> CassandraOpts
forall x. CassandraOpts -> Rep CassandraOpts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CassandraOpts -> Rep CassandraOpts x
from :: forall x. CassandraOpts -> Rep CassandraOpts x
$cto :: forall x. Rep CassandraOpts x -> CassandraOpts
to :: forall x. Rep CassandraOpts x -> CassandraOpts
Generic)

deriveFromJSON defaultOptions ''CassandraOpts