{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}
module PowerDNS.API.TSIGKeys
(
TSIGKeysAPI(..)
, TSIGKey(..)
, TSIGAlgorithm(..)
)
where
import qualified Control.Monad.Fail as Fail
import Data.Char (toLower)
import Data.Data (Data)
import Data.Functor ((<&>))
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON(..), ToJSON(..), Value(String),
object, withObject, (.:), (.:?), (.=))
import Data.Aeson.TH (allNullaryToStringTag, constructorTagModifier,
defaultOptions, deriveJSON)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as BS64
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Servant.API
import Servant.API.Generic
data TSIGKeysAPI f = TSIGKeysAPI
{ forall f.
TSIGKeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("tsigkeys" :> Get '[JSON] [TSIGKey])))
apiListTSIGKeys :: f :- "servers" :> Capture "server_id" T.Text :> "tsigkeys"
:> Get '[JSON] [TSIGKey]
, forall f.
TSIGKeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("tsigkeys"
:> (ReqBody '[JSON] TSIGKey :> PostCreated '[JSON] TSIGKey))))
apiCreateTSIGKey :: f :- "servers" :> Capture "server_id" T.Text :> "tsigkeys"
:> ReqBody '[JSON] TSIGKey
:> PostCreated '[JSON] TSIGKey
, forall f.
TSIGKeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("tsigkeys"
:> (Capture "tsigkey_id" Text :> Get '[JSON] TSIGKey))))
apiGetTSIGKey :: f :- "servers" :> Capture "server_id" T.Text :> "tsigkeys" :> Capture "tsigkey_id" T.Text
:> Get '[JSON] TSIGKey
, forall f.
TSIGKeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("tsigkeys"
:> (Capture "tsigkey_id" Text
:> (ReqBody '[JSON] TSIGKey :> Put '[JSON] TSIGKey)))))
apiUpdateTSIGKey :: f :- "servers" :> Capture "server_id" T.Text :> "tsigkeys" :> Capture "tsigkey_id" T.Text
:> ReqBody '[JSON] TSIGKey
:> Put '[JSON] TSIGKey
, forall f.
TSIGKeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("tsigkeys" :> (Capture "tsigkey_id" Text :> DeleteNoContent))))
apiDeleteTSIGKey :: f :- "servers" :> Capture "server_id" T.Text :> "tsigkeys" :> Capture "tsigkey_id" T.Text
:> DeleteNoContent
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall f x. Rep (TSIGKeysAPI f) x -> TSIGKeysAPI f
forall f x. TSIGKeysAPI f -> Rep (TSIGKeysAPI f) x
$cto :: forall f x. Rep (TSIGKeysAPI f) x -> TSIGKeysAPI f
$cfrom :: forall f x. TSIGKeysAPI f -> Rep (TSIGKeysAPI f) x
Generic
data TSIGKey = TSIGKey
{ TSIGKey -> Text
tsk_name :: T.Text
, TSIGKey -> Text
tsk_id :: T.Text
, TSIGKey -> Maybe TSIGAlgorithm
tsk_algorithm :: Maybe TSIGAlgorithm
, TSIGKey -> Maybe ByteString
tsk_key :: Maybe BS.ByteString
} deriving (TSIGKey -> TSIGKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TSIGKey -> TSIGKey -> Bool
$c/= :: TSIGKey -> TSIGKey -> Bool
== :: TSIGKey -> TSIGKey -> Bool
$c== :: TSIGKey -> TSIGKey -> Bool
Eq, Eq TSIGKey
TSIGKey -> TSIGKey -> Bool
TSIGKey -> TSIGKey -> Ordering
TSIGKey -> TSIGKey -> TSIGKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TSIGKey -> TSIGKey -> TSIGKey
$cmin :: TSIGKey -> TSIGKey -> TSIGKey
max :: TSIGKey -> TSIGKey -> TSIGKey
$cmax :: TSIGKey -> TSIGKey -> TSIGKey
>= :: TSIGKey -> TSIGKey -> Bool
$c>= :: TSIGKey -> TSIGKey -> Bool
> :: TSIGKey -> TSIGKey -> Bool
$c> :: TSIGKey -> TSIGKey -> Bool
<= :: TSIGKey -> TSIGKey -> Bool
$c<= :: TSIGKey -> TSIGKey -> Bool
< :: TSIGKey -> TSIGKey -> Bool
$c< :: TSIGKey -> TSIGKey -> Bool
compare :: TSIGKey -> TSIGKey -> Ordering
$ccompare :: TSIGKey -> TSIGKey -> Ordering
Ord, Int -> TSIGKey -> ShowS
[TSIGKey] -> ShowS
TSIGKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TSIGKey] -> ShowS
$cshowList :: [TSIGKey] -> ShowS
show :: TSIGKey -> String
$cshow :: TSIGKey -> String
showsPrec :: Int -> TSIGKey -> ShowS
$cshowsPrec :: Int -> TSIGKey -> ShowS
Show, forall x. Rep TSIGKey x -> TSIGKey
forall x. TSIGKey -> Rep TSIGKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TSIGKey x -> TSIGKey
$cfrom :: forall x. TSIGKey -> Rep TSIGKey x
Generic, TSIGKey -> ()
forall a. (a -> ()) -> NFData a
rnf :: TSIGKey -> ()
$crnf :: TSIGKey -> ()
NFData, Typeable TSIGKey
TSIGKey -> DataType
TSIGKey -> Constr
(forall b. Data b => b -> b) -> TSIGKey -> TSIGKey
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TSIGKey -> u
forall u. (forall d. Data d => d -> u) -> TSIGKey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGKey -> c TSIGKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TSIGKey)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TSIGKey -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TSIGKey -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TSIGKey -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TSIGKey -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGKey -> r
gmapT :: (forall b. Data b => b -> b) -> TSIGKey -> TSIGKey
$cgmapT :: (forall b. Data b => b -> b) -> TSIGKey -> TSIGKey
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TSIGKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TSIGKey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGKey)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGKey)
dataTypeOf :: TSIGKey -> DataType
$cdataTypeOf :: TSIGKey -> DataType
toConstr :: TSIGKey -> Constr
$ctoConstr :: TSIGKey -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGKey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGKey -> c TSIGKey
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGKey -> c TSIGKey
Data)
data TSIGAlgorithm = HMAC_MD5
| HMAC_SHA1
| HMAC_SHA224
| HMAC_SHA256
| HMAC_SHA384
| HMAC_SHA512
deriving (TSIGAlgorithm -> TSIGAlgorithm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c/= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
== :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c== :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
Eq, Eq TSIGAlgorithm
TSIGAlgorithm -> TSIGAlgorithm -> Bool
TSIGAlgorithm -> TSIGAlgorithm -> Ordering
TSIGAlgorithm -> TSIGAlgorithm -> TSIGAlgorithm
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TSIGAlgorithm -> TSIGAlgorithm -> TSIGAlgorithm
$cmin :: TSIGAlgorithm -> TSIGAlgorithm -> TSIGAlgorithm
max :: TSIGAlgorithm -> TSIGAlgorithm -> TSIGAlgorithm
$cmax :: TSIGAlgorithm -> TSIGAlgorithm -> TSIGAlgorithm
>= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c>= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
> :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c> :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
<= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c<= :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
< :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
$c< :: TSIGAlgorithm -> TSIGAlgorithm -> Bool
compare :: TSIGAlgorithm -> TSIGAlgorithm -> Ordering
$ccompare :: TSIGAlgorithm -> TSIGAlgorithm -> Ordering
Ord, Int -> TSIGAlgorithm -> ShowS
[TSIGAlgorithm] -> ShowS
TSIGAlgorithm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TSIGAlgorithm] -> ShowS
$cshowList :: [TSIGAlgorithm] -> ShowS
show :: TSIGAlgorithm -> String
$cshow :: TSIGAlgorithm -> String
showsPrec :: Int -> TSIGAlgorithm -> ShowS
$cshowsPrec :: Int -> TSIGAlgorithm -> ShowS
Show, forall x. Rep TSIGAlgorithm x -> TSIGAlgorithm
forall x. TSIGAlgorithm -> Rep TSIGAlgorithm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TSIGAlgorithm x -> TSIGAlgorithm
$cfrom :: forall x. TSIGAlgorithm -> Rep TSIGAlgorithm x
Generic, TSIGAlgorithm -> ()
forall a. (a -> ()) -> NFData a
rnf :: TSIGAlgorithm -> ()
$crnf :: TSIGAlgorithm -> ()
NFData, Typeable TSIGAlgorithm
TSIGAlgorithm -> DataType
TSIGAlgorithm -> Constr
(forall b. Data b => b -> b) -> TSIGAlgorithm -> TSIGAlgorithm
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TSIGAlgorithm -> u
forall u. (forall d. Data d => d -> u) -> TSIGAlgorithm -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGAlgorithm
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGAlgorithm -> c TSIGAlgorithm
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGAlgorithm)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TSIGAlgorithm)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TSIGAlgorithm -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TSIGAlgorithm -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TSIGAlgorithm -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TSIGAlgorithm -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r
gmapT :: (forall b. Data b => b -> b) -> TSIGAlgorithm -> TSIGAlgorithm
$cgmapT :: (forall b. Data b => b -> b) -> TSIGAlgorithm -> TSIGAlgorithm
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TSIGAlgorithm)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TSIGAlgorithm)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGAlgorithm)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TSIGAlgorithm)
dataTypeOf :: TSIGAlgorithm -> DataType
$cdataTypeOf :: TSIGAlgorithm -> DataType
toConstr :: TSIGAlgorithm -> Constr
$ctoConstr :: TSIGAlgorithm -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGAlgorithm
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TSIGAlgorithm
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGAlgorithm -> c TSIGAlgorithm
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TSIGAlgorithm -> c TSIGAlgorithm
Data)
$(deriveJSON defaultOptions { allNullaryToStringTag = True
, constructorTagModifier = fmap $ \c ->
if c == '_' then '-' else toLower c
} ''TSIGAlgorithm)
instance ToJSON TSIGKey where
toJSON :: TSIGKey -> Value
toJSON TSIGKey
key = [Pair] -> Value
object [ Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TSIGKey -> Text
tsk_name TSIGKey
key
, Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TSIGKey -> Text
tsk_id TSIGKey
key
, Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"TSIGKey"
, Key
"algorithm" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TSIGKey -> Maybe TSIGAlgorithm
tsk_algorithm TSIGKey
key
, Key
"key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TSIGKey -> Maybe ByteString
tsk_key TSIGKey
key forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> ByteString -> Text
encode64)
]
instance FromJSON TSIGKey where
parseJSON :: Value -> Parser TSIGKey
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TSIGKey" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
tsk_name <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Text
tsk_id <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Maybe TSIGAlgorithm
tsk_algorithm <- Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"algorithm"
Maybe ByteString
tsk_key <- Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"key" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall (m :: * -> *). MonadFail m => Text -> m ByteString
decode64
forall (f :: * -> *) a. Applicative f => a -> f a
pure TSIGKey{Maybe ByteString
Maybe TSIGAlgorithm
Text
tsk_key :: Maybe ByteString
tsk_algorithm :: Maybe TSIGAlgorithm
tsk_id :: Text
tsk_name :: Text
tsk_key :: Maybe ByteString
tsk_algorithm :: Maybe TSIGAlgorithm
tsk_id :: Text
tsk_name :: Text
..}
encode64 :: BS.ByteString -> T.Text
encode64 :: ByteString -> Text
encode64 = ByteString -> Text
T.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BS64.encode
decode64 :: Fail.MonadFail m => T.Text -> m BS.ByteString
decode64 :: forall (m :: * -> *). MonadFail m => Text -> m ByteString
decode64 Text
i = case ByteString -> Either String ByteString
BS64.decode (Text -> ByteString
T.encodeUtf8 Text
i) of
Left String
err -> forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
err
Right ByteString
k -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
k