powerdns-0.4.1: PowerDNS API bindings for api/v1
Safe HaskellNone
LanguageHaskell2010

PowerDNS.Client

Description

All the endpoints provide only a very slim wrapper around the PowerDNS API preserving its idiosyncracies.

Synopsis

Authentication

applyXApiKey Source #

Arguments

:: Text

API key

-> ClientEnv 
-> ClientEnv 

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.

data Version Source #

Constructors

Version 

Instances

Instances details
Eq Version Source # 
Instance details

Defined in PowerDNS.API.Version

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Data Version Source # 
Instance details

Defined in PowerDNS.API.Version

Methods

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 #

Ord Version Source # 
Instance details

Defined in PowerDNS.API.Version

Show Version Source # 
Instance details

Defined in PowerDNS.API.Version

Generic Version Source # 
Instance details

Defined in PowerDNS.API.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

ToJSON Version Source # 
Instance details

Defined in PowerDNS.API.Version

FromJSON Version Source # 
Instance details

Defined in PowerDNS.API.Version

NFData Version Source # 
Instance details

Defined in PowerDNS.API.Version

Methods

rnf :: Version -> () #

type Rep Version Source # 
Instance details

Defined in PowerDNS.API.Version

type Rep Version = D1 ('MetaData "Version" "PowerDNS.API.Version" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" '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

listZones Source #

Arguments

:: 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

createZone Source #

Arguments

:: 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.

getZone Source #

Arguments

:: 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

deleteZone Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM NoContent 

Delete a given zone by id. See Zones API Documentation

updateRecords Source #

Arguments

:: 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.

updateZone Source #

Arguments

:: 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.

triggerAxfr Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM NoContent 

Trigger zone transfer on a slave. See Zones API Documentation

notifySlaves Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM NoContent 

Send DNS notify to slaves. See Zones API Documentation

getZoneAxfr Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM Text

Zone in AXFR format

Return zone in AXFR format. See Zones API Documentation

rectifyZone Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM Text 

Rectify the zone data. See Zones API Documentation

Data types

data Zone Source #

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

Instances

Instances details
Eq Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: Zone -> Zone -> Bool #

(/=) :: Zone -> Zone -> Bool #

Data Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Zone -> c Zone #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Zone #

toConstr :: Zone -> Constr #

dataTypeOf :: Zone -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Zone) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Zone) #

gmapT :: (forall b. Data b => b -> b) -> Zone -> Zone #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Zone -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Zone -> r #

gmapQ :: (forall d. Data d => d -> u) -> Zone -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Zone -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Zone -> m Zone #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Zone -> m Zone #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Zone -> m Zone #

Ord Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

compare :: Zone -> Zone -> Ordering #

(<) :: Zone -> Zone -> Bool #

(<=) :: Zone -> Zone -> Bool #

(>) :: Zone -> Zone -> Bool #

(>=) :: Zone -> Zone -> Bool #

max :: Zone -> Zone -> Zone #

min :: Zone -> Zone -> Zone #

Show Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

showsPrec :: Int -> Zone -> ShowS #

show :: Zone -> String #

showList :: [Zone] -> ShowS #

Generic Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep Zone :: Type -> Type #

Methods

from :: Zone -> Rep Zone x #

to :: Rep Zone x -> Zone #

ToJSON Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: Zone -> () #

Empty Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

empty :: Zone Source #

type Rep Zone Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep Zone = D1 ('MetaData "Zone" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "Zone" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "zone_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "zone_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CIText))) :*: (S1 ('MetaSel ('Just "zone_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "zone_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "zone_kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind))))) :*: ((S1 ('MetaSel ('Just "zone_rrsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [RRSet])) :*: (S1 ('MetaSel ('Just "zone_serial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Just "zone_notified_serial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)))) :*: (S1 ('MetaSel ('Just "zone_edited_serial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "zone_masters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "zone_dnssec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))) :*: (((S1 ('MetaSel ('Just "zone_nsec3param") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "zone_nsec3narrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "zone_presigned") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "zone_soa_edit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "zone_soa_edit_api") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: ((S1 ('MetaSel ('Just "zone_api_rectify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "zone_zone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "zone_account") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "zone_nameservers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "zone_master_tsig_key_ids") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "zone_slave_tsig_key_ids") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text]))))))))

data Kind Source #

Constructors

Native 
Master 
Slave 

Instances

Instances details
Eq Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: Kind -> Kind -> Bool #

(/=) :: Kind -> Kind -> Bool #

Data Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

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 #

toConstr :: Kind -> Constr #

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 #

Ord Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

compare :: Kind -> Kind -> Ordering #

(<) :: Kind -> Kind -> Bool #

(<=) :: Kind -> Kind -> Bool #

(>) :: Kind -> Kind -> Bool #

(>=) :: Kind -> Kind -> Bool #

max :: Kind -> Kind -> Kind #

min :: Kind -> Kind -> Kind #

Show Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

showsPrec :: Int -> Kind -> ShowS #

show :: Kind -> String #

showList :: [Kind] -> ShowS #

Generic Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep Kind :: Type -> Type #

Methods

from :: Kind -> Rep Kind x #

to :: Rep Kind x -> Kind #

ToJSON Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: Kind -> () #

type Rep Kind Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep Kind = D1 ('MetaData "Kind" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "Native" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Master" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Slave" 'PrefixI 'False) (U1 :: Type -> Type)))

data RRSets Source #

A list of RRSets

Constructors

RRSets 

Fields

Instances

Instances details
Eq RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: RRSets -> RRSets -> Bool #

(/=) :: RRSets -> RRSets -> Bool #

Data RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

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 #

Ord RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Show RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Generic RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep RRSets :: Type -> Type #

Methods

from :: RRSets -> Rep RRSets x #

to :: Rep RRSets x -> RRSets #

ToJSON RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: RRSets -> () #

type Rep RRSets Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep RRSets = D1 ('MetaData "RRSets" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "RRSets" 'PrefixI 'True) (S1 ('MetaSel ('Just "rrsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RRSet])))

data RRSet Source #

RRSet according to PowerDNS Documentation.

Note that Eq and Ord use limited case-sensitivity on rrset_name as per RFC4343

Instances

Instances details
Eq RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: RRSet -> RRSet -> Bool #

(/=) :: RRSet -> RRSet -> Bool #

Data RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

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 #

toConstr :: RRSet -> Constr #

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 #

Ord RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

compare :: RRSet -> RRSet -> Ordering #

(<) :: RRSet -> RRSet -> Bool #

(<=) :: RRSet -> RRSet -> Bool #

(>) :: RRSet -> RRSet -> Bool #

(>=) :: RRSet -> RRSet -> Bool #

max :: RRSet -> RRSet -> RRSet #

min :: RRSet -> RRSet -> RRSet #

Show RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

showsPrec :: Int -> RRSet -> ShowS #

show :: RRSet -> String #

showList :: [RRSet] -> ShowS #

Generic RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep RRSet :: Type -> Type #

Methods

from :: RRSet -> Rep RRSet x #

to :: Rep RRSet x -> RRSet #

ToJSON RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: RRSet -> () #

type Rep RRSet Source # 
Instance details

Defined in PowerDNS.API.Zones

data Record Source #

Record according to PowerDNS Documentation

Constructors

Record 

Instances

Instances details
Eq Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: Record -> Record -> Bool #

(/=) :: Record -> Record -> Bool #

Data Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

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 #

Ord Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Show Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Generic Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep Record :: Type -> Type #

Methods

from :: Record -> Rep Record x #

to :: Rep Record x -> Record #

ToJSON Record Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON Record Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData Record Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: Record -> () #

type Rep Record Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep Record = D1 ('MetaData "Record" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" '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)))

data Comment Source #

Comment according to PowerDNS Documentation

Instances

Instances details
Eq Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Data Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

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 #

Ord Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Show Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Generic Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep Comment :: Type -> Type #

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

ToJSON Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: Comment -> () #

Empty Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

empty :: Comment Source #

type Rep Comment Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep Comment = D1 ('MetaData "Comment" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" '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.

Constructors

Replace 
Delete 

Instances

Instances details
Eq ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Data ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeType -> c ChangeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeType #

toConstr :: ChangeType -> Constr #

dataTypeOf :: ChangeType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChangeType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeType) #

gmapT :: (forall b. Data b => b -> b) -> ChangeType -> ChangeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

Ord ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Show ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Generic ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep ChangeType :: Type -> Type #

ToJSON ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: ChangeType -> () #

type Rep ChangeType Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep ChangeType = D1 ('MetaData "ChangeType" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "Replace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Delete" 'PrefixI 'False) (U1 :: Type -> Type))

data RecordType Source #

Instances

Instances details
Eq RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Data RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordType -> c RecordType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecordType #

toConstr :: RecordType -> Constr #

dataTypeOf :: RecordType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecordType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecordType) #

gmapT :: (forall b. Data b => b -> b) -> RecordType -> RecordType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecordType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordType -> m RecordType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordType -> m RecordType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordType -> m RecordType #

Ord RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Show RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Generic RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep RecordType :: Type -> Type #

ToJSON RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

FromJSON RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

NFData RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

Methods

rnf :: RecordType -> () #

type Rep RecordType Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep RecordType = D1 ('MetaData "RecordType" "PowerDNS.API.Zones" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (((((C1 ('MetaCons "A" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AAAA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AFSDB" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ALIAS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "APL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CAA" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CERT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CDNSKEY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CNAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DNSKEY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DNAME" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HINFO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KEY" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LOC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NAPTR" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NSEC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NSEC3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NSEC3PARAM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OPENPGPKEY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PTR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RP" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "RRSIG" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SOA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SPF" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SSHFP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SRV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TKEY" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TSIG" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TLSA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMIMEA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TXT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "URI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A6" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DHCID" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DLV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EUI48" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "EUI64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IPSECKEY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KX" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MAILA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MAILB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MINFO" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RKEY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SIG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WKS" 'PrefixI 'False) (U1 :: Type -> Type)))))))

Cryptokeys

See documentation at PowerDNS Cryptokeys API

listCryptoKeys Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> ClientM [Cryptokey] 

List all crypto keys. See Cryptokeys API Documentation

createCryptokey Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> Cryptokey

Cryptokey to create

-> ClientM Cryptokey

Created cryptokey

Create a new crypto key. See Cryptokeys API Documentation

getCryptokey Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> Text

Cryptokey ID

-> ClientM Cryptokey 

Get existing crypto key. See Cryptokeys API Documentation

updateCryptokey Source #

Arguments

:: 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

deleteCryptokey Source #

Arguments

:: Text

Server name

-> Text

Zone ID

-> Text

Cryptokey ID

-> ClientM NoContent 

Delete existing crypto key. See Cryptokeys API Documentation

Data types

data Cryptokey Source #

Instances

Instances details
Eq Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Data Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cryptokey -> c Cryptokey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cryptokey #

toConstr :: Cryptokey -> Constr #

dataTypeOf :: Cryptokey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cryptokey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cryptokey) #

gmapT :: (forall b. Data b => b -> b) -> Cryptokey -> Cryptokey #

gmapQl :: (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 #

gmapQ :: (forall d. Data d => d -> u) -> Cryptokey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cryptokey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cryptokey -> m Cryptokey #

Ord Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Show Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Generic Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Associated Types

type Rep Cryptokey :: Type -> Type #

ToJSON Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

FromJSON Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

NFData Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Methods

rnf :: Cryptokey -> () #

Empty Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

type Rep Cryptokey Source # 
Instance details

Defined in PowerDNS.API.Cryptokeys

Servers

See documentation at PowerDNS Servers API

Also contains PowerDNS Search API and PowerDNS Cache API

getServer Source #

Arguments

:: Text

Server ID

-> ClientM Server 

Get existing server. See Servers API Documentation

search Source #

Arguments

:: 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

flushCache Source #

Arguments

:: Text

Server ID

-> Text

Domain

-> ClientM CacheFlushResult 

Flushes a domain from the cache. See Cache API Documentation

statistics Source #

Arguments

:: 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

data Server Source #

Instances

Instances details
Eq Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

(==) :: Server -> Server -> Bool #

(/=) :: Server -> Server -> Bool #

Data Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Server -> c Server #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Server #

toConstr :: Server -> Constr #

dataTypeOf :: Server -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Server) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server) #

gmapT :: (forall b. Data b => b -> b) -> Server -> Server #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r #

gmapQ :: (forall d. Data d => d -> u) -> Server -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Server -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Server -> m Server #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server #

Ord Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Show Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Generic Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Associated Types

type Rep Server :: Type -> Type #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

ToJSON Server Source # 
Instance details

Defined in PowerDNS.API.Servers

FromJSON Server Source # 
Instance details

Defined in PowerDNS.API.Servers

NFData Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

rnf :: Server -> () #

Empty Server Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

empty :: Server Source #

type Rep Server Source # 
Instance details

Defined in PowerDNS.API.Servers

type Rep Server = D1 ('MetaData "Server" "PowerDNS.API.Servers" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "Server" 'PrefixI 'True) ((S1 ('MetaSel ('Just "server_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "server_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "server_daemon_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "server_version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "server_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "server_config_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "server_zones_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))

data SearchResult Source #

Instances

Instances details
Eq SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Data SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SearchResult -> c SearchResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SearchResult #

toConstr :: SearchResult -> Constr #

dataTypeOf :: SearchResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SearchResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SearchResult) #

gmapT :: (forall b. Data b => b -> b) -> SearchResult -> SearchResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SearchResult -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SearchResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> SearchResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SearchResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SearchResult -> m SearchResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchResult -> m SearchResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchResult -> m SearchResult #

Ord SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Show SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Generic SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Associated Types

type Rep SearchResult :: Type -> Type #

ToJSON SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

FromJSON SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

NFData SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

rnf :: SearchResult -> () #

type Rep SearchResult Source # 
Instance details

Defined in PowerDNS.API.Servers

data ObjectType Source #

Constructors

TyAll 
TyZone 
TyRecord 
TyComment 

Instances

Instances details
Eq ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Data ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectType -> c ObjectType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectType #

toConstr :: ObjectType -> Constr #

dataTypeOf :: ObjectType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectType) #

gmapT :: (forall b. Data b => b -> b) -> ObjectType -> ObjectType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType #

Ord ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Show ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Generic ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Associated Types

type Rep ObjectType :: Type -> Type #

ToJSON ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

FromJSON ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

NFData ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

rnf :: ObjectType -> () #

ToHttpApiData ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

FromHttpApiData ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

type Rep ObjectType Source # 
Instance details

Defined in PowerDNS.API.Servers

type Rep ObjectType = D1 ('MetaData "ObjectType" "PowerDNS.API.Servers" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) ((C1 ('MetaCons "TyAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyZone" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TyRecord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyComment" 'PrefixI 'False) (U1 :: Type -> Type)))

data CacheFlushResult Source #

Constructors

CacheFlushResult 

Instances

Instances details
Eq CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Data CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CacheFlushResult -> c CacheFlushResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CacheFlushResult #

toConstr :: CacheFlushResult -> Constr #

dataTypeOf :: CacheFlushResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CacheFlushResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CacheFlushResult) #

gmapT :: (forall b. Data b => b -> b) -> CacheFlushResult -> CacheFlushResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CacheFlushResult -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CacheFlushResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> CacheFlushResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CacheFlushResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CacheFlushResult -> m CacheFlushResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CacheFlushResult -> m CacheFlushResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CacheFlushResult -> m CacheFlushResult #

Ord CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Show CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Generic CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Associated Types

type Rep CacheFlushResult :: Type -> Type #

ToJSON CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

FromJSON CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

NFData CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

Methods

rnf :: CacheFlushResult -> () #

type Rep CacheFlushResult Source # 
Instance details

Defined in PowerDNS.API.Servers

type Rep CacheFlushResult = D1 ('MetaData "CacheFlushResult" "PowerDNS.API.Servers" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) (C1 ('MetaCons "CacheFlushResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "cfr_count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "cfr_result") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Metadata

See documentation at PowerDNS Metadata API

listMetadata Source #

Arguments

:: Text

Server ID

-> Text

Zone ID

-> ClientM [Metadata] 

List metadata for existing zone. See Metadata API Documentation

createMetadata Source #

Arguments

:: Text

Server ID

-> Text

Zone ID

-> Metadata 
-> ClientM NoContent 

Create metadata for zone. See Metadata API Documentation

getMetadata Source #

Arguments

:: Text

Server ID

-> Text

Zone ID

-> Text

Kind

-> ClientM Metadata 

Get metadata for zone by kind. See Metadata API Documentation

updateMetadata Source #

Arguments

:: Text

Server ID

-> Text

Zone ID

-> Text

Kind

-> Metadata 
-> ClientM Metadata 

Update metadata for zone by kind. See Metadata API Documentation

deleteMetadata Source #

Arguments

:: Text

Server ID

-> Text

Zone ID

-> Text

Kind

-> ClientM NoContent 

Delete metadata for zone by kind. See Metadata API Documentation

Data types

data Metadata Source #

Constructors

Metadata 

Fields

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Data Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Methods

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 #

Ord Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Show Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Generic Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Associated Types

type Rep Metadata :: Type -> Type #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

ToJSON Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

FromJSON Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

NFData Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

Methods

rnf :: Metadata -> () #

type Rep Metadata Source # 
Instance details

Defined in PowerDNS.API.Metadata

type Rep Metadata = D1 ('MetaData "Metadata" "PowerDNS.API.Metadata" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" '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

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

Data types

data TSIGKey Source #

Constructors

TSIGKey 

Fields

Instances

Instances details
Eq TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Methods

(==) :: TSIGKey -> TSIGKey -> Bool #

(/=) :: TSIGKey -> TSIGKey -> Bool #

Data TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Methods

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 #

Ord TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Show TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Generic TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Associated Types

type Rep TSIGKey :: Type -> Type #

Methods

from :: TSIGKey -> Rep TSIGKey x #

to :: Rep TSIGKey x -> TSIGKey #

ToJSON TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

FromJSON TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

NFData TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Methods

rnf :: TSIGKey -> () #

type Rep TSIGKey Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

type Rep TSIGKey = D1 ('MetaData "TSIGKey" "PowerDNS.API.TSIGKeys" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" '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

Instances

Instances details
Eq TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Data TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TSIGAlgorithm -> c TSIGAlgorithm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TSIGAlgorithm #

toConstr :: TSIGAlgorithm -> Constr #

dataTypeOf :: TSIGAlgorithm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TSIGAlgorithm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TSIGAlgorithm) #

gmapT :: (forall b. Data b => b -> b) -> TSIGAlgorithm -> TSIGAlgorithm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TSIGAlgorithm -> r #

gmapQ :: (forall d. Data d => d -> u) -> TSIGAlgorithm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TSIGAlgorithm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TSIGAlgorithm -> m TSIGAlgorithm #

Ord TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Show TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Generic TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Associated Types

type Rep TSIGAlgorithm :: Type -> Type #

ToJSON TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

FromJSON TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

NFData TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

Methods

rnf :: TSIGAlgorithm -> () #

type Rep TSIGAlgorithm Source # 
Instance details

Defined in PowerDNS.API.TSIGKeys

type Rep TSIGAlgorithm = D1 ('MetaData "TSIGAlgorithm" "PowerDNS.API.TSIGKeys" "powerdns-0.4.1-7JamDv2LDIOEBr1WHWJeCq" 'False) ((C1 ('MetaCons "HMAC_MD5" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HMAC_SHA1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HMAC_SHA224" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HMAC_SHA256" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HMAC_SHA384" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HMAC_SHA512" 'PrefixI 'False) (U1 :: Type -> Type))))

Utilities

empty :: Empty a => a Source #

Produce an empty value