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

PowerDNS.API.Zones

Description

Implementation of the API endpoints described at PowerDNS Zones API

Synopsis

API

data ZonesAPI f Source #

Constructors

ZonesAPI 

Fields

Instances

Instances details
Generic (ZonesAPI f) Source # 
Instance details

Defined in PowerDNS.API.Zones

Associated Types

type Rep (ZonesAPI f) :: Type -> Type #

Methods

from :: ZonesAPI f -> Rep (ZonesAPI f) x #

to :: Rep (ZonesAPI f) x -> ZonesAPI f #

type Rep (ZonesAPI f) Source # 
Instance details

Defined in PowerDNS.API.Zones

type Rep (ZonesAPI f) = D1 ('MetaData "ZonesAPI" "PowerDNS.API.Zones" "powerdns-0.2.0-KVEAOheVEexEs5OVtLI9gW" 'False) (C1 ('MetaCons "ZonesAPI" 'PrefixI 'True) (((S1 ('MetaSel ('Just "apiListZones") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (QueryParam "zone" Text :> (QueryParam "dnssec" Bool :> Get '[JSON] [Zone]))))))) :*: S1 ('MetaSel ('Just "apiCreateZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (QueryParam "rrset" Bool :> (ReqBody '[JSON] Zone :> PostCreated '[JSON] Zone)))))))) :*: (S1 ('MetaSel ('Just "apiGetZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> (QueryParam "rrsets" Bool :> Get '[JSON] Zone))))))) :*: (S1 ('MetaSel ('Just "apiDeleteZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> DeleteNoContent)))))) :*: S1 ('MetaSel ('Just "apiUpdateRecords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> (ReqBody '[JSON] RRSets :> PatchNoContent)))))))))) :*: ((S1 ('MetaSel ('Just "apiUpdateZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> (ReqBody '[JSON] Zone :> PutNoContent))))))) :*: S1 ('MetaSel ('Just "apiTriggerAxfr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> ("axfr-retrieve" :> Put '[JSON] NoContent)))))))) :*: (S1 ('MetaSel ('Just "apiNotifySlaves") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> ("notify" :> Put '[JSON] NoContent))))))) :*: (S1 ('MetaSel ('Just "apiGetZoneAxfr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> ("export" :> Get '[JSON] Text))))))) :*: S1 ('MetaSel ('Just "apiRectifyZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("servers" :> (Capture "server_id" Text :> ("zones" :> (Capture "zone_id" Text :> ("rectify" :> Put '[JSON] Text))))))))))))

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.

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.2.0-KVEAOheVEexEs5OVtLI9gW" '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 Text))) :*: (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.2.0-KVEAOheVEexEs5OVtLI9gW" '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.2.0-KVEAOheVEexEs5OVtLI9gW" 'False) (C1 ('MetaCons "RRSets" 'PrefixI 'True) (S1 ('MetaSel ('Just "rrsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RRSet])))

data RRSet Source #

RRSet according to PowerDNS Documentation.

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.2.0-KVEAOheVEexEs5OVtLI9gW" '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.2.0-KVEAOheVEexEs5OVtLI9gW" '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 "commant_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.2.0-KVEAOheVEexEs5OVtLI9gW" '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.2.0-KVEAOheVEexEs5OVtLI9gW" '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)))))))