-- 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.API.Federation.API.Cargohold where

import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Id
import Data.OpenApi
import Data.Proxy
import Imports
import Servant.API
import Servant.OpenApi (HasOpenApi (toOpenApi))
import Wire.API.Asset
import Wire.API.Federation.Endpoint
import Wire.API.Routes.AssetBody
import Wire.API.Util.Aeson
import Wire.Arbitrary (Arbitrary, GenericUniform (..))

data GetAsset = GetAsset
  { -- | User requesting the asset. Implicitly qualified with the source domain.
    GetAsset -> UserId
user :: UserId,
    -- | Asset key for the asset to download. Implicitly qualified with the
    -- target domain.
    GetAsset -> AssetKey
key :: AssetKey,
    -- | Optional asset token.
    GetAsset -> Maybe AssetToken
token :: Maybe AssetToken
  }
  deriving stock (GetAsset -> GetAsset -> Bool
(GetAsset -> GetAsset -> Bool)
-> (GetAsset -> GetAsset -> Bool) -> Eq GetAsset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetAsset -> GetAsset -> Bool
== :: GetAsset -> GetAsset -> Bool
$c/= :: GetAsset -> GetAsset -> Bool
/= :: GetAsset -> GetAsset -> Bool
Eq, Int -> GetAsset -> ShowS
[GetAsset] -> ShowS
GetAsset -> String
(Int -> GetAsset -> ShowS)
-> (GetAsset -> String) -> ([GetAsset] -> ShowS) -> Show GetAsset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetAsset -> ShowS
showsPrec :: Int -> GetAsset -> ShowS
$cshow :: GetAsset -> String
show :: GetAsset -> String
$cshowList :: [GetAsset] -> ShowS
showList :: [GetAsset] -> ShowS
Show, (forall x. GetAsset -> Rep GetAsset x)
-> (forall x. Rep GetAsset x -> GetAsset) -> Generic GetAsset
forall x. Rep GetAsset x -> GetAsset
forall x. GetAsset -> Rep GetAsset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetAsset -> Rep GetAsset x
from :: forall x. GetAsset -> Rep GetAsset x
$cto :: forall x. Rep GetAsset x -> GetAsset
to :: forall x. Rep GetAsset x -> GetAsset
Generic)
  deriving (Gen GetAsset
Gen GetAsset -> (GetAsset -> [GetAsset]) -> Arbitrary GetAsset
GetAsset -> [GetAsset]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen GetAsset
arbitrary :: Gen GetAsset
$cshrink :: GetAsset -> [GetAsset]
shrink :: GetAsset -> [GetAsset]
Arbitrary) via (GenericUniform GetAsset)
  deriving ([GetAsset] -> Value
[GetAsset] -> Encoding
GetAsset -> Value
GetAsset -> Encoding
(GetAsset -> Value)
-> (GetAsset -> Encoding)
-> ([GetAsset] -> Value)
-> ([GetAsset] -> Encoding)
-> ToJSON GetAsset
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: GetAsset -> Value
toJSON :: GetAsset -> Value
$ctoEncoding :: GetAsset -> Encoding
toEncoding :: GetAsset -> Encoding
$ctoJSONList :: [GetAsset] -> Value
toJSONList :: [GetAsset] -> Value
$ctoEncodingList :: [GetAsset] -> Encoding
toEncodingList :: [GetAsset] -> Encoding
ToJSON, Value -> Parser [GetAsset]
Value -> Parser GetAsset
(Value -> Parser GetAsset)
-> (Value -> Parser [GetAsset]) -> FromJSON GetAsset
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser GetAsset
parseJSON :: Value -> Parser GetAsset
$cparseJSONList :: Value -> Parser [GetAsset]
parseJSONList :: Value -> Parser [GetAsset]
FromJSON) via (CustomEncoded GetAsset)

instance ToSchema GetAsset

data GetAssetResponse = GetAssetResponse
  {GetAssetResponse -> Bool
available :: Bool}
  deriving stock (GetAssetResponse -> GetAssetResponse -> Bool
(GetAssetResponse -> GetAssetResponse -> Bool)
-> (GetAssetResponse -> GetAssetResponse -> Bool)
-> Eq GetAssetResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetAssetResponse -> GetAssetResponse -> Bool
== :: GetAssetResponse -> GetAssetResponse -> Bool
$c/= :: GetAssetResponse -> GetAssetResponse -> Bool
/= :: GetAssetResponse -> GetAssetResponse -> Bool
Eq, Int -> GetAssetResponse -> ShowS
[GetAssetResponse] -> ShowS
GetAssetResponse -> String
(Int -> GetAssetResponse -> ShowS)
-> (GetAssetResponse -> String)
-> ([GetAssetResponse] -> ShowS)
-> Show GetAssetResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetAssetResponse -> ShowS
showsPrec :: Int -> GetAssetResponse -> ShowS
$cshow :: GetAssetResponse -> String
show :: GetAssetResponse -> String
$cshowList :: [GetAssetResponse] -> ShowS
showList :: [GetAssetResponse] -> ShowS
Show, (forall x. GetAssetResponse -> Rep GetAssetResponse x)
-> (forall x. Rep GetAssetResponse x -> GetAssetResponse)
-> Generic GetAssetResponse
forall x. Rep GetAssetResponse x -> GetAssetResponse
forall x. GetAssetResponse -> Rep GetAssetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetAssetResponse -> Rep GetAssetResponse x
from :: forall x. GetAssetResponse -> Rep GetAssetResponse x
$cto :: forall x. Rep GetAssetResponse x -> GetAssetResponse
to :: forall x. Rep GetAssetResponse x -> GetAssetResponse
Generic)
  deriving (Gen GetAssetResponse
Gen GetAssetResponse
-> (GetAssetResponse -> [GetAssetResponse])
-> Arbitrary GetAssetResponse
GetAssetResponse -> [GetAssetResponse]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen GetAssetResponse
arbitrary :: Gen GetAssetResponse
$cshrink :: GetAssetResponse -> [GetAssetResponse]
shrink :: GetAssetResponse -> [GetAssetResponse]
Arbitrary) via (GenericUniform GetAssetResponse)
  deriving ([GetAssetResponse] -> Value
[GetAssetResponse] -> Encoding
GetAssetResponse -> Value
GetAssetResponse -> Encoding
(GetAssetResponse -> Value)
-> (GetAssetResponse -> Encoding)
-> ([GetAssetResponse] -> Value)
-> ([GetAssetResponse] -> Encoding)
-> ToJSON GetAssetResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: GetAssetResponse -> Value
toJSON :: GetAssetResponse -> Value
$ctoEncoding :: GetAssetResponse -> Encoding
toEncoding :: GetAssetResponse -> Encoding
$ctoJSONList :: [GetAssetResponse] -> Value
toJSONList :: [GetAssetResponse] -> Value
$ctoEncodingList :: [GetAssetResponse] -> Encoding
toEncodingList :: [GetAssetResponse] -> Encoding
ToJSON, Value -> Parser [GetAssetResponse]
Value -> Parser GetAssetResponse
(Value -> Parser GetAssetResponse)
-> (Value -> Parser [GetAssetResponse])
-> FromJSON GetAssetResponse
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser GetAssetResponse
parseJSON :: Value -> Parser GetAssetResponse
$cparseJSONList :: Value -> Parser [GetAssetResponse]
parseJSONList :: Value -> Parser [GetAssetResponse]
FromJSON) via (CustomEncoded GetAssetResponse)

instance ToSchema GetAssetResponse

type CargoholdApi =
  FedEndpoint "get-asset" GetAsset GetAssetResponse
    :<|> StreamingFedEndpoint "stream-asset" GetAsset AssetSource

swaggerDoc :: OpenApi
swaggerDoc :: OpenApi
swaggerDoc = Proxy
  (Named
     "get-asset"
     ("get-asset"
      :> (OriginDomainHeader
          :> (ReqBody '[JSON] GetAsset :> Post '[JSON] GetAssetResponse)))
   :<|> StreamingFedEndpoint "stream-asset" GetAsset AssetSource)
-> OpenApi
forall {k} (api :: k). HasOpenApi api => Proxy api -> OpenApi
toOpenApi (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @CargoholdApi)