module Cachix.Types.BinaryCache where

import Cachix.Types.Permission (Permission)
import Data.Aeson (FromJSON, ToJSON)
import Data.Swagger (ToParamSchema (..), ToSchema)
import Protolude
import Servant.API

data BinaryCache = BinaryCache
  { BinaryCache -> Text
name :: Text,
    BinaryCache -> Text
uri :: Text,
    BinaryCache -> Bool
isPublic :: Bool,
    BinaryCache -> [Text]
publicSigningKeys :: [Text],
    BinaryCache -> Text
githubUsername :: Text,
    BinaryCache -> Permission
permission :: Permission,
    BinaryCache -> CompressionMethod
preferredCompressionMethod :: CompressionMethod
  }
  deriving (Int -> BinaryCache -> ShowS
[BinaryCache] -> ShowS
BinaryCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinaryCache] -> ShowS
$cshowList :: [BinaryCache] -> ShowS
show :: BinaryCache -> String
$cshow :: BinaryCache -> String
showsPrec :: Int -> BinaryCache -> ShowS
$cshowsPrec :: Int -> BinaryCache -> ShowS
Show, forall x. Rep BinaryCache x -> BinaryCache
forall x. BinaryCache -> Rep BinaryCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BinaryCache x -> BinaryCache
$cfrom :: forall x. BinaryCache -> Rep BinaryCache x
Generic, Value -> Parser [BinaryCache]
Value -> Parser BinaryCache
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BinaryCache]
$cparseJSONList :: Value -> Parser [BinaryCache]
parseJSON :: Value -> Parser BinaryCache
$cparseJSON :: Value -> Parser BinaryCache
FromJSON, [BinaryCache] -> Encoding
[BinaryCache] -> Value
BinaryCache -> Encoding
BinaryCache -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BinaryCache] -> Encoding
$ctoEncodingList :: [BinaryCache] -> Encoding
toJSONList :: [BinaryCache] -> Value
$ctoJSONList :: [BinaryCache] -> Value
toEncoding :: BinaryCache -> Encoding
$ctoEncoding :: BinaryCache -> Encoding
toJSON :: BinaryCache -> Value
$ctoJSON :: BinaryCache -> Value
ToJSON, Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
ToSchema, BinaryCache -> ()
forall a. (a -> ()) -> NFData a
rnf :: BinaryCache -> ()
$crnf :: BinaryCache -> ()
NFData)

data CompressionMethod = XZ | ZSTD
  deriving (Int -> CompressionMethod -> ShowS
[CompressionMethod] -> ShowS
CompressionMethod -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompressionMethod] -> ShowS
$cshowList :: [CompressionMethod] -> ShowS
show :: CompressionMethod -> String
$cshow :: CompressionMethod -> String
showsPrec :: Int -> CompressionMethod -> ShowS
$cshowsPrec :: Int -> CompressionMethod -> ShowS
Show, ReadPrec [CompressionMethod]
ReadPrec CompressionMethod
Int -> ReadS CompressionMethod
ReadS [CompressionMethod]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompressionMethod]
$creadListPrec :: ReadPrec [CompressionMethod]
readPrec :: ReadPrec CompressionMethod
$creadPrec :: ReadPrec CompressionMethod
readList :: ReadS [CompressionMethod]
$creadList :: ReadS [CompressionMethod]
readsPrec :: Int -> ReadS CompressionMethod
$creadsPrec :: Int -> ReadS CompressionMethod
Read, forall x. Rep CompressionMethod x -> CompressionMethod
forall x. CompressionMethod -> Rep CompressionMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompressionMethod x -> CompressionMethod
$cfrom :: forall x. CompressionMethod -> Rep CompressionMethod x
Generic, Value -> Parser [CompressionMethod]
Value -> Parser CompressionMethod
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CompressionMethod]
$cparseJSONList :: Value -> Parser [CompressionMethod]
parseJSON :: Value -> Parser CompressionMethod
$cparseJSON :: Value -> Parser CompressionMethod
FromJSON, [CompressionMethod] -> Encoding
[CompressionMethod] -> Value
CompressionMethod -> Encoding
CompressionMethod -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CompressionMethod] -> Encoding
$ctoEncodingList :: [CompressionMethod] -> Encoding
toJSONList :: [CompressionMethod] -> Value
$ctoJSONList :: [CompressionMethod] -> Value
toEncoding :: CompressionMethod -> Encoding
$ctoEncoding :: CompressionMethod -> Encoding
toJSON :: CompressionMethod -> Value
$ctoJSON :: CompressionMethod -> Value
ToJSON, Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
ToSchema, CompressionMethod -> ()
forall a. (a -> ()) -> NFData a
rnf :: CompressionMethod -> ()
$crnf :: CompressionMethod -> ()
NFData)

instance FromHttpApiData CompressionMethod where
  parseUrlPiece :: Text -> Either Text CompressionMethod
parseUrlPiece Text
"xz" = forall a b. b -> Either a b
Right CompressionMethod
XZ
  parseUrlPiece Text
"zst" = forall a b. b -> Either a b
Right CompressionMethod
ZSTD
  parseUrlPiece Text
compressionMethod = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text
"Wrong compression method: " forall a. Semigroup a => a -> a -> a
<> Text
compressionMethod

instance ToHttpApiData CompressionMethod where
  toUrlPiece :: CompressionMethod -> Text
toUrlPiece CompressionMethod
XZ = Text
"xz"
  toUrlPiece CompressionMethod
ZSTD = Text
"zst"

instance ToParamSchema CompressionMethod where
  toParamSchema :: forall (t :: SwaggerKind (*)).
Proxy CompressionMethod -> ParamSchema t
toParamSchema Proxy CompressionMethod
_ = forall a (t :: SwaggerKind (*)).
ToParamSchema a =>
Proxy a -> ParamSchema t
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy Text)