{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}
module PowerDNS.API.Cryptokeys
(
CryptokeysAPI(..)
, Cryptokey(..)
)
where
import Data.Data (Data)
import Control.DeepSeq (NFData)
import Data.Aeson.TH (defaultOptions,
fieldLabelModifier,
deriveJSON)
import qualified Data.Text as T
import Servant.API
import Servant.API.Generic
import PowerDNS.Internal.Utils (Empty(..), strip)
data CryptokeysAPI f = CryptokeysAPI
{ forall f.
CryptokeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("zones"
:> (Capture "zone_id" Text
:> ("cryptokeys" :> Get '[JSON] [Cryptokey])))))
apiListCryptokeys :: f :- "servers" :> Capture "server_id" T.Text :> "zones" :> Capture "zone_id" T.Text :> "cryptokeys"
:> Get '[JSON] [Cryptokey]
, forall f.
CryptokeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("zones"
:> (Capture "zone_id" Text
:> ("cryptokeys"
:> (ReqBody '[JSON] Cryptokey
:> PostCreated '[JSON] Cryptokey))))))
apiCreateCryptokey :: f :- "servers" :> Capture "server_id" T.Text :> "zones" :> Capture "zone_id" T.Text :> "cryptokeys"
:> ReqBody '[JSON] Cryptokey
:> PostCreated '[JSON] Cryptokey
, forall f.
CryptokeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("zones"
:> (Capture "zone_id" Text
:> ("cryptokeys"
:> (Capture "cryptokey_id" Text :> Get '[JSON] Cryptokey))))))
apiGetCryptokey :: f :- "servers" :> Capture "server_id" T.Text :> "zones" :> Capture "zone_id" T.Text :> "cryptokeys" :> Capture "cryptokey_id" T.Text
:> Get '[JSON] Cryptokey
, forall f.
CryptokeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("zones"
:> (Capture "zone_id" Text
:> ("cryptokeys"
:> (Capture "cryptokey_id" Text
:> (ReqBody '[JSON] Cryptokey :> PutNoContent)))))))
apiUpdateCryptokey :: f :- "servers" :> Capture "server_id" T.Text :> "zones" :> Capture "zone_id" T.Text :> "cryptokeys" :> Capture "cryptokey_id" T.Text
:> ReqBody '[JSON] Cryptokey
:> PutNoContent
, forall f.
CryptokeysAPI f
-> f
:- ("servers"
:> (Capture "server_id" Text
:> ("zones"
:> (Capture "zone_id" Text
:> ("cryptokeys"
:> (Capture "cryptokey_id" Text :> DeleteNoContent))))))
apiDeleteCryptokey :: f :- "servers" :> Capture "server_id" T.Text :> "zones" :> Capture "zone_id" T.Text :> "cryptokeys" :> Capture "cryptokey_id" T.Text
:> DeleteNoContent
} deriving (forall x. CryptokeysAPI f -> Rep (CryptokeysAPI f) x)
-> (forall x. Rep (CryptokeysAPI f) x -> CryptokeysAPI f)
-> Generic (CryptokeysAPI f)
forall x. Rep (CryptokeysAPI f) x -> CryptokeysAPI f
forall x. CryptokeysAPI f -> Rep (CryptokeysAPI f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall f x. Rep (CryptokeysAPI f) x -> CryptokeysAPI f
forall f x. CryptokeysAPI f -> Rep (CryptokeysAPI f) x
$cfrom :: forall f x. CryptokeysAPI f -> Rep (CryptokeysAPI f) x
from :: forall x. CryptokeysAPI f -> Rep (CryptokeysAPI f) x
$cto :: forall f x. Rep (CryptokeysAPI f) x -> CryptokeysAPI f
to :: forall x. Rep (CryptokeysAPI f) x -> CryptokeysAPI f
Generic
data Cryptokey = Cryptokey
{ Cryptokey -> Maybe Text
ck_type :: Maybe T.Text
, Cryptokey -> Maybe Integer
ck_id :: Maybe Integer
, Cryptokey -> Maybe Text
ck_keytype :: Maybe T.Text
, Cryptokey -> Maybe Bool
ck_active :: Maybe Bool
, Cryptokey -> Maybe Bool
ck_published :: Maybe Bool
, Cryptokey -> Maybe Text
ck_dnskey :: Maybe T.Text
, Cryptokey -> Maybe [Text]
ck_ds :: Maybe [T.Text]
, Cryptokey -> Maybe Text
ck_privatekey :: Maybe T.Text
, Cryptokey -> Maybe Text
ck_algorithm :: Maybe T.Text
, Cryptokey -> Maybe Integer
ck_bits :: Maybe Integer
} deriving (Cryptokey -> Cryptokey -> Bool
(Cryptokey -> Cryptokey -> Bool)
-> (Cryptokey -> Cryptokey -> Bool) -> Eq Cryptokey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cryptokey -> Cryptokey -> Bool
== :: Cryptokey -> Cryptokey -> Bool
$c/= :: Cryptokey -> Cryptokey -> Bool
/= :: Cryptokey -> Cryptokey -> Bool
Eq, Eq Cryptokey
Eq Cryptokey
-> (Cryptokey -> Cryptokey -> Ordering)
-> (Cryptokey -> Cryptokey -> Bool)
-> (Cryptokey -> Cryptokey -> Bool)
-> (Cryptokey -> Cryptokey -> Bool)
-> (Cryptokey -> Cryptokey -> Bool)
-> (Cryptokey -> Cryptokey -> Cryptokey)
-> (Cryptokey -> Cryptokey -> Cryptokey)
-> Ord Cryptokey
Cryptokey -> Cryptokey -> Bool
Cryptokey -> Cryptokey -> Ordering
Cryptokey -> Cryptokey -> Cryptokey
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
$ccompare :: Cryptokey -> Cryptokey -> Ordering
compare :: Cryptokey -> Cryptokey -> Ordering
$c< :: Cryptokey -> Cryptokey -> Bool
< :: Cryptokey -> Cryptokey -> Bool
$c<= :: Cryptokey -> Cryptokey -> Bool
<= :: Cryptokey -> Cryptokey -> Bool
$c> :: Cryptokey -> Cryptokey -> Bool
> :: Cryptokey -> Cryptokey -> Bool
$c>= :: Cryptokey -> Cryptokey -> Bool
>= :: Cryptokey -> Cryptokey -> Bool
$cmax :: Cryptokey -> Cryptokey -> Cryptokey
max :: Cryptokey -> Cryptokey -> Cryptokey
$cmin :: Cryptokey -> Cryptokey -> Cryptokey
min :: Cryptokey -> Cryptokey -> Cryptokey
Ord, Int -> Cryptokey -> ShowS
[Cryptokey] -> ShowS
Cryptokey -> String
(Int -> Cryptokey -> ShowS)
-> (Cryptokey -> String)
-> ([Cryptokey] -> ShowS)
-> Show Cryptokey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cryptokey -> ShowS
showsPrec :: Int -> Cryptokey -> ShowS
$cshow :: Cryptokey -> String
show :: Cryptokey -> String
$cshowList :: [Cryptokey] -> ShowS
showList :: [Cryptokey] -> ShowS
Show, (forall x. Cryptokey -> Rep Cryptokey x)
-> (forall x. Rep Cryptokey x -> Cryptokey) -> Generic Cryptokey
forall x. Rep Cryptokey x -> Cryptokey
forall x. Cryptokey -> Rep Cryptokey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cryptokey -> Rep Cryptokey x
from :: forall x. Cryptokey -> Rep Cryptokey x
$cto :: forall x. Rep Cryptokey x -> Cryptokey
to :: forall x. Rep Cryptokey x -> Cryptokey
Generic, Cryptokey -> ()
(Cryptokey -> ()) -> NFData Cryptokey
forall a. (a -> ()) -> NFData a
$crnf :: Cryptokey -> ()
rnf :: Cryptokey -> ()
NFData, Typeable Cryptokey
Typeable Cryptokey
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cryptokey -> c Cryptokey)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cryptokey)
-> (Cryptokey -> Constr)
-> (Cryptokey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cryptokey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cryptokey))
-> ((forall b. Data b => b -> b) -> Cryptokey -> Cryptokey)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r)
-> (forall u. (forall d. Data d => d -> u) -> Cryptokey -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Cryptokey -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey)
-> Data Cryptokey
Cryptokey -> Constr
Cryptokey -> DataType
(forall b. Data b => b -> b) -> Cryptokey -> Cryptokey
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) -> Cryptokey -> u
forall u. (forall d. Data d => d -> u) -> Cryptokey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cryptokey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cryptokey -> c Cryptokey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cryptokey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cryptokey)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cryptokey -> c Cryptokey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cryptokey -> c Cryptokey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cryptokey
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cryptokey
$ctoConstr :: Cryptokey -> Constr
toConstr :: Cryptokey -> Constr
$cdataTypeOf :: Cryptokey -> DataType
dataTypeOf :: Cryptokey -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cryptokey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cryptokey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cryptokey)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cryptokey)
$cgmapT :: (forall b. Data b => b -> b) -> Cryptokey -> Cryptokey
gmapT :: (forall b. Data b => b -> b) -> Cryptokey -> Cryptokey
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Cryptokey -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cryptokey -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Cryptokey -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cryptokey -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cryptokey -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey
Data, Cryptokey
Cryptokey -> Empty Cryptokey
forall a. a -> Empty a
$cempty :: Cryptokey
empty :: Cryptokey
Empty)
$(deriveJSON defaultOptions { fieldLabelModifier = strip "ck_"} ''Cryptokey)