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
import Text.Read

type BinaryCacheName = Text

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
(Int -> BinaryCache -> ShowS)
-> (BinaryCache -> String)
-> ([BinaryCache] -> ShowS)
-> Show BinaryCache
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryCache -> ShowS
showsPrec :: Int -> BinaryCache -> ShowS
$cshow :: BinaryCache -> String
show :: BinaryCache -> String
$cshowList :: [BinaryCache] -> ShowS
showList :: [BinaryCache] -> ShowS
Show, (forall x. BinaryCache -> Rep BinaryCache x)
-> (forall x. Rep BinaryCache x -> BinaryCache)
-> Generic BinaryCache
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
$cfrom :: forall x. BinaryCache -> Rep BinaryCache x
from :: forall x. BinaryCache -> Rep BinaryCache x
$cto :: forall x. Rep BinaryCache x -> BinaryCache
to :: forall x. Rep BinaryCache x -> BinaryCache
Generic, Maybe BinaryCache
Value -> Parser [BinaryCache]
Value -> Parser BinaryCache
(Value -> Parser BinaryCache)
-> (Value -> Parser [BinaryCache])
-> Maybe BinaryCache
-> FromJSON BinaryCache
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BinaryCache
parseJSON :: Value -> Parser BinaryCache
$cparseJSONList :: Value -> Parser [BinaryCache]
parseJSONList :: Value -> Parser [BinaryCache]
$comittedField :: Maybe BinaryCache
omittedField :: Maybe BinaryCache
FromJSON, [BinaryCache] -> Value
[BinaryCache] -> Encoding
BinaryCache -> Bool
BinaryCache -> Value
BinaryCache -> Encoding
(BinaryCache -> Value)
-> (BinaryCache -> Encoding)
-> ([BinaryCache] -> Value)
-> ([BinaryCache] -> Encoding)
-> (BinaryCache -> Bool)
-> ToJSON BinaryCache
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BinaryCache -> Value
toJSON :: BinaryCache -> Value
$ctoEncoding :: BinaryCache -> Encoding
toEncoding :: BinaryCache -> Encoding
$ctoJSONList :: [BinaryCache] -> Value
toJSONList :: [BinaryCache] -> Value
$ctoEncodingList :: [BinaryCache] -> Encoding
toEncodingList :: [BinaryCache] -> Encoding
$comitField :: BinaryCache -> Bool
omitField :: BinaryCache -> Bool
ToJSON, Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
(Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema)
-> ToSchema BinaryCache
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy BinaryCache -> Declare (Definitions Schema) NamedSchema
ToSchema, BinaryCache -> ()
(BinaryCache -> ()) -> NFData BinaryCache
forall a. (a -> ()) -> NFData a
$crnf :: BinaryCache -> ()
rnf :: BinaryCache -> ()
NFData)

data CompressionMethod = XZ | ZSTD
  deriving (Int -> CompressionMethod -> ShowS
[CompressionMethod] -> ShowS
CompressionMethod -> String
(Int -> CompressionMethod -> ShowS)
-> (CompressionMethod -> String)
-> ([CompressionMethod] -> ShowS)
-> Show CompressionMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompressionMethod -> ShowS
showsPrec :: Int -> CompressionMethod -> ShowS
$cshow :: CompressionMethod -> String
show :: CompressionMethod -> String
$cshowList :: [CompressionMethod] -> ShowS
showList :: [CompressionMethod] -> ShowS
Show, CompressionMethod -> CompressionMethod -> Bool
(CompressionMethod -> CompressionMethod -> Bool)
-> (CompressionMethod -> CompressionMethod -> Bool)
-> Eq CompressionMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompressionMethod -> CompressionMethod -> Bool
== :: CompressionMethod -> CompressionMethod -> Bool
$c/= :: CompressionMethod -> CompressionMethod -> Bool
/= :: CompressionMethod -> CompressionMethod -> Bool
Eq, (forall x. CompressionMethod -> Rep CompressionMethod x)
-> (forall x. Rep CompressionMethod x -> CompressionMethod)
-> Generic CompressionMethod
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
$cfrom :: forall x. CompressionMethod -> Rep CompressionMethod x
from :: forall x. CompressionMethod -> Rep CompressionMethod x
$cto :: forall x. Rep CompressionMethod x -> CompressionMethod
to :: forall x. Rep CompressionMethod x -> CompressionMethod
Generic, Maybe CompressionMethod
Value -> Parser [CompressionMethod]
Value -> Parser CompressionMethod
(Value -> Parser CompressionMethod)
-> (Value -> Parser [CompressionMethod])
-> Maybe CompressionMethod
-> FromJSON CompressionMethod
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CompressionMethod
parseJSON :: Value -> Parser CompressionMethod
$cparseJSONList :: Value -> Parser [CompressionMethod]
parseJSONList :: Value -> Parser [CompressionMethod]
$comittedField :: Maybe CompressionMethod
omittedField :: Maybe CompressionMethod
FromJSON, [CompressionMethod] -> Value
[CompressionMethod] -> Encoding
CompressionMethod -> Bool
CompressionMethod -> Value
CompressionMethod -> Encoding
(CompressionMethod -> Value)
-> (CompressionMethod -> Encoding)
-> ([CompressionMethod] -> Value)
-> ([CompressionMethod] -> Encoding)
-> (CompressionMethod -> Bool)
-> ToJSON CompressionMethod
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CompressionMethod -> Value
toJSON :: CompressionMethod -> Value
$ctoEncoding :: CompressionMethod -> Encoding
toEncoding :: CompressionMethod -> Encoding
$ctoJSONList :: [CompressionMethod] -> Value
toJSONList :: [CompressionMethod] -> Value
$ctoEncodingList :: [CompressionMethod] -> Encoding
toEncodingList :: [CompressionMethod] -> Encoding
$comitField :: CompressionMethod -> Bool
omitField :: CompressionMethod -> Bool
ToJSON, Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
(Proxy CompressionMethod
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema CompressionMethod
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy CompressionMethod -> Declare (Definitions Schema) NamedSchema
ToSchema, CompressionMethod -> ()
(CompressionMethod -> ()) -> NFData CompressionMethod
forall a. (a -> ()) -> NFData a
$crnf :: CompressionMethod -> ()
rnf :: CompressionMethod -> ()
NFData)

instance Read CompressionMethod where
  readsPrec :: Int -> ReadS CompressionMethod
readsPrec Int
_ String
value =
    case (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map Char -> Char
toUpper String
value of
      String
"XZ" -> [(CompressionMethod
XZ, String
"")]
      String
"ZST" -> [(CompressionMethod
ZSTD, String
"")]
      String
"ZSTD" -> [(CompressionMethod
ZSTD, String
"")]
      String
_ -> []

instance FromHttpApiData CompressionMethod where
  parseUrlPiece :: Text -> Either Text CompressionMethod
parseUrlPiece Text
"xz" = CompressionMethod -> Either Text CompressionMethod
forall a b. b -> Either a b
Right CompressionMethod
XZ
  parseUrlPiece Text
"zst" = CompressionMethod -> Either Text CompressionMethod
forall a b. b -> Either a b
Right CompressionMethod
ZSTD
  parseUrlPiece Text
compressionMethod = Text -> Either Text CompressionMethod
forall a b. a -> Either a b
Left (Text -> Either Text CompressionMethod)
-> Text -> Either Text CompressionMethod
forall a b. (a -> b) -> a -> b
$ Text
"Wrong compression method: " Text -> Text -> Text
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
_ = Proxy Text -> ParamSchema t
forall a (t :: SwaggerKind (*)).
ToParamSchema a =>
Proxy a -> ParamSchema t
forall (t :: SwaggerKind (*)). Proxy Text -> ParamSchema t
toParamSchema (Proxy Text
forall {k} (t :: k). Proxy t
Proxy :: Proxy Text)