Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
All the endpoints provide only a very slim wrapper around the PowerDNS API preserving its idiosyncracies.
Synopsis
- applyXApiKey :: Text -> ClientEnv -> ClientEnv
- listVersions :: ClientM [Version]
- data Version = Version {}
- listZones :: Text -> Maybe Text -> Maybe Bool -> ClientM [Zone]
- createZone :: Text -> Maybe Bool -> Zone -> ClientM Zone
- getZone :: Text -> Text -> Maybe Bool -> ClientM Zone
- deleteZone :: Text -> Text -> ClientM NoContent
- updateRecords :: Text -> Text -> RRSets -> ClientM NoContent
- updateZone :: Text -> Text -> Zone -> ClientM NoContent
- triggerAxfr :: Text -> Text -> ClientM Result
- notifySlaves :: Text -> Text -> ClientM Result
- getZoneAxfr :: Text -> Text -> ClientM Result
- rectifyZone :: Text -> Text -> ClientM Result
- data Zone = Zone {
- zone_id :: Maybe Text
- zone_name :: Maybe CIText
- zone_type :: Maybe Text
- zone_url :: Maybe Text
- zone_kind :: Maybe Kind
- zone_rrsets :: Maybe [RRSet]
- zone_serial :: Maybe Integer
- zone_notified_serial :: Maybe Integer
- zone_edited_serial :: Maybe Integer
- zone_masters :: Maybe [Text]
- zone_dnssec :: Maybe Bool
- zone_nsec3param :: Maybe Text
- zone_nsec3narrow :: Maybe Bool
- zone_presigned :: Maybe Bool
- zone_soa_edit :: Maybe Text
- zone_soa_edit_api :: Maybe Text
- zone_api_rectify :: Maybe Bool
- zone_zone :: Maybe Text
- zone_account :: Maybe Text
- zone_nameservers :: Maybe [Text]
- zone_master_tsig_key_ids :: Maybe [Text]
- zone_slave_tsig_key_ids :: Maybe [Text]
- data Kind
- data RRSets = RRSets {}
- data RRSet = RRSet {}
- data Record = Record {}
- data Comment = Comment {}
- data ChangeType
- data RecordType
- = A
- | AAAA
- | AFSDB
- | ALIAS
- | APL
- | CAA
- | CERT
- | CDNSKEY
- | CDS
- | CNAME
- | DNSKEY
- | DNAME
- | DS
- | HINFO
- | KEY
- | LOC
- | MX
- | NAPTR
- | NS
- | NSEC
- | NSEC3
- | NSEC3PARAM
- | OPENPGPKEY
- | PTR
- | RP
- | RRSIG
- | SOA
- | SPF
- | SSHFP
- | SRV
- | TKEY
- | TSIG
- | TLSA
- | SMIMEA
- | TXT
- | URI
- | A6
- | DHCID
- | DLV
- | EUI48
- | EUI64
- | IPSECKEY
- | KX
- | MAILA
- | MAILB
- | MINFO
- | MR
- | RKEY
- | SIG
- | WKS
- newtype Result = Result Text
- listCryptoKeys :: Text -> Text -> ClientM [Cryptokey]
- createCryptokey :: Text -> Text -> Cryptokey -> ClientM Cryptokey
- getCryptokey :: Text -> Text -> Text -> ClientM Cryptokey
- updateCryptokey :: Text -> Text -> Text -> Cryptokey -> ClientM NoContent
- deleteCryptokey :: Text -> Text -> Text -> ClientM NoContent
- data Cryptokey
- listServers :: ClientM [Server]
- getServer :: Text -> ClientM Server
- search :: Text -> Text -> Integer -> Maybe ObjectType -> ClientM [SearchResult]
- flushCache :: Text -> Text -> ClientM CacheFlushResult
- statistics :: Text -> Maybe Text -> Maybe Bool -> ClientM [AnyStatisticItem]
- data Server = Server {}
- data SearchResult = SearchResult {
- sr_content :: Text
- sr_disabled :: Bool
- sr_name :: Text
- sr_object_type :: ObjectType
- sr_zone_id :: Text
- sr_zone :: Text
- sr_type :: Text
- sr_ttl :: Integer
- data ObjectType
- data CacheFlushResult = CacheFlushResult {
- cfr_count :: Integer
- cfr_result :: Text
- listMetadata :: Text -> Text -> ClientM [Metadata]
- createMetadata :: Text -> Text -> Metadata -> ClientM NoContent
- getMetadata :: Text -> Text -> Text -> ClientM Metadata
- updateMetadata :: Text -> Text -> Text -> Metadata -> ClientM Metadata
- deleteMetadata :: Text -> Text -> Text -> ClientM NoContent
- data Metadata = Metadata {
- md_kind :: Text
- md_metadata :: [Text]
- listTSIGKeys :: Text -> ClientM [TSIGKey]
- createTSIGKey :: Text -> TSIGKey -> ClientM TSIGKey
- getTSIGKey :: Text -> Text -> ClientM TSIGKey
- updateTSIGKey :: Text -> Text -> TSIGKey -> ClientM TSIGKey
- deleteTSIGKey :: Text -> Text -> ClientM NoContent
- data TSIGKey = TSIGKey {}
- data TSIGAlgorithm
- empty :: Empty a => a
Authentication
Causes all requests with this ClientEnv
to be sent with the specified key embedded in a X-API-Key header.
Version
listVersions :: ClientM [Version] Source #
List the API versions and urls from the server. This is an undocumented endpoint.
Version | |
|
Instances
FromJSON Version Source # | |
Defined in PowerDNS.API.Version | |
ToJSON Version Source # | |
Data Version Source # | |
Defined in PowerDNS.API.Version gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Generic Version Source # | |
Read Version Source # | |
Show Version Source # | |
NFData Version Source # | |
Defined in PowerDNS.API.Version | |
Eq Version Source # | |
Ord Version Source # | |
type Rep Version Source # | |
Defined in PowerDNS.API.Version type Rep Version = D1 ('MetaData "Version" "PowerDNS.API.Version" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "version_version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "version_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Zones
See documentation at PowerDNS Zones API
Because the required fields of a Zone
differs between various requests and responses, every field
is wrapped with Maybe. It is the users responsibility to check with the PowerDNS API to know when a
field must be specified. For convenience empty
can be used to generate a value of Zone
with all
fields set to Nothing
.
let zone = empty { zone_name = Just "some.domain." , zone_kind = Just Native , zone_type = Just "zone" } in createZone "localhost" -- Server ID Nothing -- Show RRsets in response zone -- The zone we are creating
:: Text | Server name |
-> Maybe Text | Limit to zone |
-> Maybe Bool | Whether or not to include dnssec and edited_serial fields |
-> ClientM [Zone] |
List all zones for the server. See Zones API Documentation
:: Text | Server name |
-> Maybe Bool | Whether or not to include RRsets in the response |
-> Zone | The zone to create |
-> ClientM Zone |
Create a new zone. See Zones API Documentation
empty
with record update syntax is useful avoid having to specify Nothing
for unwanted fields.
:: Text | Server name |
-> Text | Zone ID |
-> Maybe Bool | Wheher or not to include RRsets in the response |
-> ClientM Zone |
Get details for zone. See Zones API Documentation
Delete a given zone by id. See Zones API Documentation
:: Text | Server name |
-> Text | Zone ID |
-> RRSets | The RRsets to create, update or delete. |
-> ClientM NoContent |
Update records of a zone. See Zones API Documentation
Caution: If rrset_records or rrset_comments is set to Just []
on a Delete
changetype,
this will delete all existing records or comments respectively for the domain.
:: Text | Server name |
-> Text | Zone ID |
-> Zone | Patch record. Fields with Just are changed, Nothing are ignored |
-> ClientM NoContent |
Modify zone. See Zones API Documentation
empty
with record update syntax is useful avoid having to specify Nothing
for unwanted fields.
Trigger zone transfer on a slave. See Zones API Documentation
Send DNS notify to slaves. See Zones API Documentation
Return zone in AXFR format. See Zones API Documentation
Rectify the zone data. See Zones API Documentation
Data types
Zone according to PowerDNS Documentation. All fields are optional because the PowerDNS API differs on which fields are required depending on the endpoint.
Note that Eq
and Ord
use limited case-sensitivity on zone_name
and equivalently contained rrset names
as per RFC4343
Zone | |
|
Instances
Instances
FromJSON Kind Source # | |
Defined in PowerDNS.API.Zones | |
ToJSON Kind Source # | |
Data Kind Source # | |
Defined in PowerDNS.API.Zones gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Kind -> c Kind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Kind # dataTypeOf :: Kind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Kind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Kind) # gmapT :: (forall b. Data b => b -> b) -> Kind -> Kind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Kind -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Kind -> r # gmapQ :: (forall d. Data d => d -> u) -> Kind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Kind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Kind -> m Kind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Kind -> m Kind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Kind -> m Kind # | |
Generic Kind Source # | |
Read Kind Source # | |
Show Kind Source # | |
NFData Kind Source # | |
Defined in PowerDNS.API.Zones | |
Eq Kind Source # | |
Ord Kind Source # | |
type Rep Kind Source # | |
Defined in PowerDNS.API.Zones |
A list of RRSets
Instances
FromJSON RRSets Source # | |
Defined in PowerDNS.API.Zones | |
ToJSON RRSets Source # | |
Data RRSets Source # | |
Defined in PowerDNS.API.Zones gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RRSets -> c RRSets # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RRSets # toConstr :: RRSets -> Constr # dataTypeOf :: RRSets -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RRSets) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RRSets) # gmapT :: (forall b. Data b => b -> b) -> RRSets -> RRSets # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RRSets -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RRSets -> r # gmapQ :: (forall d. Data d => d -> u) -> RRSets -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RRSets -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RRSets -> m RRSets # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RRSets -> m RRSets # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RRSets -> m RRSets # | |
Generic RRSets Source # | |
Read RRSets Source # | |
Show RRSets Source # | |
NFData RRSets Source # | |
Defined in PowerDNS.API.Zones | |
Eq RRSets Source # | |
Ord RRSets Source # | |
type Rep RRSets Source # | |
Defined in PowerDNS.API.Zones |
RRSet according to PowerDNS Documentation.
Note that Eq
and Ord
use limited case-sensitivity on rrset_name
as per RFC4343
RRSet | |
|
Instances
FromJSON RRSet Source # | |
Defined in PowerDNS.API.Zones | |
ToJSON RRSet Source # | |
Data RRSet Source # | |
Defined in PowerDNS.API.Zones gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RRSet -> c RRSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RRSet # dataTypeOf :: RRSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RRSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RRSet) # gmapT :: (forall b. Data b => b -> b) -> RRSet -> RRSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RRSet -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RRSet -> r # gmapQ :: (forall d. Data d => d -> u) -> RRSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RRSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RRSet -> m RRSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RRSet -> m RRSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RRSet -> m RRSet # | |
Generic RRSet Source # | |
Read RRSet Source # | |
Show RRSet Source # | |
NFData RRSet Source # | |
Defined in PowerDNS.API.Zones | |
Eq RRSet Source # | |
Ord RRSet Source # | |
type Rep RRSet Source # | |
Defined in PowerDNS.API.Zones type Rep RRSet = D1 ('MetaData "RRSet" "PowerDNS.API.Zones" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "RRSet" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rrset_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CIText) :*: (S1 ('MetaSel ('Just "rrset_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RecordType) :*: S1 ('MetaSel ('Just "rrset_ttl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word32)))) :*: (S1 ('MetaSel ('Just "rrset_changetype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChangeType)) :*: (S1 ('MetaSel ('Just "rrset_records") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Record])) :*: S1 ('MetaSel ('Just "rrset_comments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Comment])))))) |
Record according to PowerDNS Documentation
Instances
FromJSON Record Source # | |
Defined in PowerDNS.API.Zones | |
ToJSON Record Source # | |
Data Record Source # | |
Defined in PowerDNS.API.Zones gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Record -> c Record # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Record # toConstr :: Record -> Constr # dataTypeOf :: Record -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Record) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Record) # gmapT :: (forall b. Data b => b -> b) -> Record -> Record # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Record -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Record -> r # gmapQ :: (forall d. Data d => d -> u) -> Record -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Record -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Record -> m Record # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Record -> m Record # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Record -> m Record # | |
Generic Record Source # | |
Read Record Source # | |
Show Record Source # | |
NFData Record Source # | |
Defined in PowerDNS.API.Zones | |
Eq Record Source # | |
Ord Record Source # | |
type Rep Record Source # | |
Defined in PowerDNS.API.Zones type Rep Record = D1 ('MetaData "Record" "PowerDNS.API.Zones" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "Record" 'PrefixI 'True) (S1 ('MetaSel ('Just "record_content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "record_disabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
Comment according to PowerDNS Documentation
Instances
FromJSON Comment Source # | |
Defined in PowerDNS.API.Zones | |
ToJSON Comment Source # | |
Data Comment Source # | |
Defined in PowerDNS.API.Zones gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comment -> c Comment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comment # toConstr :: Comment -> Constr # dataTypeOf :: Comment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment) # gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # | |
Generic Comment Source # | |
Read Comment Source # | |
Show Comment Source # | |
NFData Comment Source # | |
Defined in PowerDNS.API.Zones | |
Eq Comment Source # | |
Ord Comment Source # | |
Empty Comment Source # | |
Defined in PowerDNS.API.Zones | |
type Rep Comment Source # | |
Defined in PowerDNS.API.Zones type Rep Comment = D1 ('MetaData "Comment" "PowerDNS.API.Zones" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "Comment" 'PrefixI 'True) (S1 ('MetaSel ('Just "comment_content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "comment_account") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "comment_modified_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))))) |
data ChangeType Source #
Whether or not an RRSet
replace or delete an existing entry.
If the ChangeType
is left at Nothing
it will create a new domain entry.
Instances
data RecordType Source #
Instances
A simple newtype wrapper, because the original PowerDNS API encodes some textual result types more equal than others.
Cryptokeys
See documentation at PowerDNS Cryptokeys API
List all crypto keys. See Cryptokeys API Documentation
:: Text | Server name |
-> Text | Zone ID |
-> Cryptokey | Cryptokey to create |
-> ClientM Cryptokey | Created cryptokey |
Create a new crypto key. See Cryptokeys API Documentation
Get existing crypto key. See Cryptokeys API Documentation
:: Text | Server name |
-> Text | Zone ID |
-> Text | Cryptokey ID |
-> Cryptokey | Patch record. Fields with Just are changed, Nothing are ignored |
-> ClientM NoContent |
Update existing crypto key. See Cryptokeys API Documentation
Delete existing crypto key. See Cryptokeys API Documentation
Data types
Instances
Servers
See documentation at PowerDNS Servers API
Also contains PowerDNS Search API and PowerDNS Cache API
listServers :: ClientM [Server] Source #
List available servers. See Servers API Documentation
Get existing server. See Servers API Documentation
:: Text | Server ID |
-> Text | String to search for |
-> Integer | Maximum number of results |
-> Maybe ObjectType | Limit results to specified object type, if any. |
-> ClientM [SearchResult] |
Searches in various object types for an arbitrary string. See Search API Documentation
:: Text | Server ID |
-> Text | Domain |
-> ClientM CacheFlushResult |
Flushes a domain from the cache. See Cache API Documentation
:: Text | Server ID |
-> Maybe Text | Only return statistic items with this name. |
-> Maybe Bool | Whether or not to return ring items. |
-> ClientM [AnyStatisticItem] |
Get server wide statistics. See Cache API Documentation
Data types
Server | |
|
Instances
data SearchResult Source #
SearchResult | |
|
Instances
data ObjectType Source #
Instances
data CacheFlushResult Source #
Instances
Metadata
See documentation at PowerDNS Metadata API
List metadata for existing zone. See Metadata API Documentation
Create metadata for zone. See Metadata API Documentation
Get metadata for zone by kind. See Metadata API Documentation
Update metadata for zone by kind. See Metadata API Documentation
Delete metadata for zone by kind. See Metadata API Documentation
Data types
Metadata | |
|
Instances
FromJSON Metadata Source # | |
Defined in PowerDNS.API.Metadata | |
ToJSON Metadata Source # | |
Data Metadata Source # | |
Defined in PowerDNS.API.Metadata gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Metadata -> c Metadata # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Metadata # toConstr :: Metadata -> Constr # dataTypeOf :: Metadata -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Metadata) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metadata) # gmapT :: (forall b. Data b => b -> b) -> Metadata -> Metadata # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Metadata -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Metadata -> r # gmapQ :: (forall d. Data d => d -> u) -> Metadata -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Metadata -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Metadata -> m Metadata # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Metadata -> m Metadata # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Metadata -> m Metadata # | |
Generic Metadata Source # | |
Read Metadata Source # | |
Show Metadata Source # | |
NFData Metadata Source # | |
Defined in PowerDNS.API.Metadata | |
Eq Metadata Source # | |
Ord Metadata Source # | |
Defined in PowerDNS.API.Metadata | |
type Rep Metadata Source # | |
Defined in PowerDNS.API.Metadata type Rep Metadata = D1 ('MetaData "Metadata" "PowerDNS.API.Metadata" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "Metadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "md_kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "md_metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) |
TSIGKeys
See documentation at PowerDNS TSIGKeys API as well as related TSIG documentation
listTSIGKeys :: Text -> ClientM [TSIGKey] Source #
List all TSIG keys. See TSIGKeys API Documentation
createTSIGKey :: Text -> TSIGKey -> ClientM TSIGKey Source #
Create a new TSIG key. If the key is left empty, the server will generate one. See TSIGKeys API Documentation
getTSIGKey :: Text -> Text -> ClientM TSIGKey Source #
Get TSIG key by its id. See TSIGKeys API Documentation
updateTSIGKey :: Text -> Text -> TSIGKey -> ClientM TSIGKey Source #
Update existig TSIG key. See TSIGKeys API Documentation
deleteTSIGKey :: Text -> Text -> ClientM NoContent Source #
Delete existing TSIG key. See TSIGKeys API Documentation
Data types
TSIGKey | |
|
Instances
FromJSON TSIGKey Source # | |
Defined in PowerDNS.API.TSIGKeys | |
ToJSON TSIGKey Source # | |
Data TSIGKey Source # | |
Defined in PowerDNS.API.TSIGKeys gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TSIGKey -> c TSIGKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TSIGKey # toConstr :: TSIGKey -> Constr # dataTypeOf :: TSIGKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TSIGKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TSIGKey) # gmapT :: (forall b. Data b => b -> b) -> TSIGKey -> TSIGKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TSIGKey -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TSIGKey -> r # gmapQ :: (forall d. Data d => d -> u) -> TSIGKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TSIGKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TSIGKey -> m TSIGKey # | |
Generic TSIGKey Source # | |
Read TSIGKey Source # | |
Show TSIGKey Source # | |
NFData TSIGKey Source # | |
Defined in PowerDNS.API.TSIGKeys | |
Eq TSIGKey Source # | |
Ord TSIGKey Source # | |
type Rep TSIGKey Source # | |
Defined in PowerDNS.API.TSIGKeys type Rep TSIGKey = D1 ('MetaData "TSIGKey" "PowerDNS.API.TSIGKeys" "powerdns-0.4.4-4F1xBB6Mfb27BKd2dcmgst" 'False) (C1 ('MetaCons "TSIGKey" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tsk_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tsk_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tsk_algorithm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TSIGAlgorithm)) :*: S1 ('MetaSel ('Just "tsk_key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString))))) |
data TSIGAlgorithm Source #
Supported algorithms according to PowerDNS TSIG Documentation