module Hercules.Formats.CachixCache where

import Data.Aeson
import Data.Foldable
import Data.Text (Text)
import Hercules.Formats.Common
  ( noVersion,
    withKind,
    withVersions,
  )
import Prelude

-- | Credentials and keys for a cache.
data CachixCache = CachixCache
  { CachixCache -> [Text]
signingKeys :: [Text],
    CachixCache -> Maybe Text
authToken :: Maybe Text,
    CachixCache -> [Text]
publicKeys :: [Text]
  }

instance ToJSON CachixCache where
  toJSON :: CachixCache -> Value
toJSON CachixCache
a =
    [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
      [Text
"kind" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Value
String Text
"CachixCache", Text
"signingKeys" Text -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CachixCache -> [Text]
signingKeys CachixCache
a]
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> (Text -> [Pair]) -> [Text] -> [Pair]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Pair -> [Pair]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"authToken" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=)) (Maybe Text -> [Text]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ CachixCache -> Maybe Text
authToken CachixCache
a)
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Text
"publicKeys" Text -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CachixCache -> [Text]
publicKeys CachixCache
a]

  toEncoding :: CachixCache -> Encoding
toEncoding CachixCache
a =
    Series -> Encoding
pairs
      ( Text
"kind"
          Text -> Value -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Value
String Text
"CachixCache"
          Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<> Text
"signingKeys"
          Text -> [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CachixCache -> [Text]
signingKeys CachixCache
a
          Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<> (Text -> Series) -> Maybe Text -> Series
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text
"authToken" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (CachixCache -> Maybe Text
authToken CachixCache
a)
          Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<> Text
"publicKeys"
          Text -> [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CachixCache -> [Text]
publicKeys CachixCache
a
      )

instance FromJSON CachixCache where
  parseJSON :: Value -> Parser CachixCache
parseJSON =
    Text
-> (Object -> Parser CachixCache) -> Value -> Parser CachixCache
forall a. Text -> (Object -> Parser a) -> Value -> Parser a
withKind Text
"CachixCache" ((Object -> Parser CachixCache) -> Value -> Parser CachixCache)
-> (Object -> Parser CachixCache) -> Value -> Parser CachixCache
forall a b. (a -> b) -> a -> b
$
      [VersionParser CachixCache] -> Object -> Parser CachixCache
forall a. [VersionParser a] -> Object -> Parser a
withVersions
        [ (Object -> Parser CachixCache) -> VersionParser CachixCache
forall a. (Object -> Parser a) -> VersionParser a
noVersion ((Object -> Parser CachixCache) -> VersionParser CachixCache)
-> (Object -> Parser CachixCache) -> VersionParser CachixCache
forall a b. (a -> b) -> a -> b
$ \Object
o ->
            [Text] -> Maybe Text -> [Text] -> CachixCache
CachixCache
              ([Text] -> Maybe Text -> [Text] -> CachixCache)
-> Parser [Text] -> Parser (Maybe Text -> [Text] -> CachixCache)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe [Text] -> [Text]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"signingKeys")
              Parser (Maybe Text -> [Text] -> CachixCache)
-> Parser (Maybe Text) -> Parser ([Text] -> CachixCache)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
              Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"authToken"
              Parser ([Text] -> CachixCache)
-> Parser [Text] -> Parser CachixCache
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
              Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"publicKeys"
        ]