hetzner-0.6.0.0: Hetzner Cloud and DNS library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hetzner.DNS

Description

Client for the Hetzner DNS API.

Synopsis

Tokens

newtype Token Source #

A token used to authenticate requests.

You can create one in the Hetzner DNS Console.

Constructors

Token ByteString 

Instances

Instances details
IsString Token Source # 
Instance details

Defined in Hetzner.DNS

Methods

fromString :: String -> Token #

Show Token Source # 
Instance details

Defined in Hetzner.DNS

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Hetzner.DNS

Methods

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

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

Ord Token Source # 
Instance details

Defined in Hetzner.DNS

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

getTokenFromEnv :: IO (Maybe Token) Source #

Lookup Token from the environment variable HETZNER_DNS_TOKEN.

Hetzner DNS

Zones

newtype ZoneID Source #

Zone identifier.

Constructors

ZoneID Text 

Instances

Instances details
FromJSON ZoneID Source # 
Instance details

Defined in Hetzner.DNS

ToJSON ZoneID Source # 
Instance details

Defined in Hetzner.DNS

Show ZoneID Source # 
Instance details

Defined in Hetzner.DNS

Eq ZoneID Source # 
Instance details

Defined in Hetzner.DNS

Methods

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

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

Ord ZoneID Source # 
Instance details

Defined in Hetzner.DNS

data ZoneStatus Source #

Status of a Zone.

Constructors

Verified 
Failed 
Pending 

Instances

Instances details
FromJSON ZoneStatus Source # 
Instance details

Defined in Hetzner.DNS

Show ZoneStatus Source # 
Instance details

Defined in Hetzner.DNS

data Zone Source #

DNS zone.

Instances

Instances details
FromJSON Zone Source # 
Instance details

Defined in Hetzner.DNS

Show Zone Source # 
Instance details

Defined in Hetzner.DNS

Methods

showsPrec :: Int -> Zone -> ShowS #

show :: Zone -> String #

showList :: [Zone] -> ShowS #

getZones :: Token -> Maybe Int -> IO (WithMeta "zones" [Zone]) Source #

Get zones.

getZone :: Token -> ZoneID -> IO Zone Source #

Get a single zone.

updateZone Source #

Arguments

:: Token 
-> ZoneID

ID of zone to update.

-> Text

New zone name.

-> Maybe Int

New TTL. If not provided, it won't change.

-> IO Zone 

Update a zone's name and TTL.

deleteZone :: Token -> ZoneID -> IO () Source #

Delete a zone.

Records

newtype RecordID Source #

A record identifier.

Constructors

RecordID Text 

Instances

Instances details
FromJSON RecordID Source # 
Instance details

Defined in Hetzner.DNS

ToJSON RecordID Source # 
Instance details

Defined in Hetzner.DNS

Show RecordID Source # 
Instance details

Defined in Hetzner.DNS

Eq RecordID Source # 
Instance details

Defined in Hetzner.DNS

Ord RecordID Source # 
Instance details

Defined in Hetzner.DNS

allRecordTypes :: [RecordType] Source #

List with all supported record types.

data Record Source #

A DNS record.

Constructors

Record 

Fields

Instances

Instances details
FromJSON Record Source # 
Instance details

Defined in Hetzner.DNS

Show Record Source # 
Instance details

Defined in Hetzner.DNS

getRecords Source #

Arguments

:: Token 
-> Maybe ZoneID

Optionally filter by zone.

-> IO [Record] 

Get DNS records.

getRecord :: Token -> RecordID -> IO Record Source #

Get a single DNS record.

createRecord Source #

Arguments

:: Token 
-> ZoneID

Zone to add the record to.

-> Text

Record name.

-> RecordType

Record type.

-> Text

Record value.

-> Maybe Int

Optional TTL.

-> IO Record 

Create a DNS record.

updateRecord Source #

Arguments

:: Token 
-> RecordID

Record to update.

-> ZoneID

Zone for the record.

-> Text

New record name.

-> RecordType

New recored type.

-> Text

New record value.

-> Maybe Int

Optinally, a new TTL.

-> IO Record 

Update a DNS record.

deleteRecord :: Token -> RecordID -> IO () Source #

Delete a DNS record.

Exceptions

data DNSException Source #

Exception produced while performing a request to Hetzner DNS.

Streaming

streamPages Source #

Arguments

:: forall key f a i m. (Foldable f, MonadIO m) 
=> (Maybe Int -> IO (WithMeta key (f a)))

Function that takes page number and returns result.

-> ConduitT i a m ()

Conduit-based stream that yields results downstream.

Stream results using a function that takes a page number, going through all the pages.

streamToList :: Monad m => ConduitT () a m () -> m [a] Source #

Convenient function to turn streams into lists.

Generic interface

Generic queries

dnsQuery Source #

Arguments

:: (ToJSON body, FromJSON a) 
=> ByteString

Method.

-> ByteString

Path.

-> Maybe body

Request body. You may use noBody to skip.

-> Query

Additional query options.

-> Token

Authorization token.

-> Maybe Int

Page.

-> IO a 

Generic Hetzner DNS query.

noBody :: Maybe Void Source #

Used to send requests without a body.

JSON Wrappers

data WithKey (key :: Symbol) a Source #

Wrap a value with the key of the value within a JSON object.

Constructors

WithKey 

Fields

Instances

Instances details
Foldable (WithKey key) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

fold :: Monoid m => WithKey key m -> m #

foldMap :: Monoid m => (a -> m) -> WithKey key a -> m #

foldMap' :: Monoid m => (a -> m) -> WithKey key a -> m #

foldr :: (a -> b -> b) -> b -> WithKey key a -> b #

foldr' :: (a -> b -> b) -> b -> WithKey key a -> b #

foldl :: (b -> a -> b) -> b -> WithKey key a -> b #

foldl' :: (b -> a -> b) -> b -> WithKey key a -> b #

foldr1 :: (a -> a -> a) -> WithKey key a -> a #

foldl1 :: (a -> a -> a) -> WithKey key a -> a #

toList :: WithKey key a -> [a] #

null :: WithKey key a -> Bool #

length :: WithKey key a -> Int #

elem :: Eq a => a -> WithKey key a -> Bool #

maximum :: Ord a => WithKey key a -> a #

minimum :: Ord a => WithKey key a -> a #

sum :: Num a => WithKey key a -> a #

product :: Num a => WithKey key a -> a #

Functor (WithKey key) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

fmap :: (a -> b) -> WithKey key a -> WithKey key b #

(<$) :: a -> WithKey key b -> WithKey key a #

(KnownSymbol key, FromJSON a) => FromJSON (WithKey key a) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

parseJSON :: Value -> Parser (WithKey key a) #

parseJSONList :: Value -> Parser [WithKey key a] #

Show a => Show (WithKey key a) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> WithKey key a -> ShowS #

show :: WithKey key a -> String #

showList :: [WithKey key a] -> ShowS #

data WithMeta (key :: Symbol) a Source #

A value together with response metadata. The type is annotated with the JSON key of the value.

Constructors

WithMeta 

Fields

Instances

Instances details
Foldable (WithMeta key) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

fold :: Monoid m => WithMeta key m -> m #

foldMap :: Monoid m => (a -> m) -> WithMeta key a -> m #

foldMap' :: Monoid m => (a -> m) -> WithMeta key a -> m #

foldr :: (a -> b -> b) -> b -> WithMeta key a -> b #

foldr' :: (a -> b -> b) -> b -> WithMeta key a -> b #

foldl :: (b -> a -> b) -> b -> WithMeta key a -> b #

foldl' :: (b -> a -> b) -> b -> WithMeta key a -> b #

foldr1 :: (a -> a -> a) -> WithMeta key a -> a #

foldl1 :: (a -> a -> a) -> WithMeta key a -> a #

toList :: WithMeta key a -> [a] #

null :: WithMeta key a -> Bool #

length :: WithMeta key a -> Int #

elem :: Eq a => a -> WithMeta key a -> Bool #

maximum :: Ord a => WithMeta key a -> a #

minimum :: Ord a => WithMeta key a -> a #

sum :: Num a => WithMeta key a -> a #

product :: Num a => WithMeta key a -> a #

Functor (WithMeta key) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

fmap :: (a -> b) -> WithMeta key a -> WithMeta key b #

(<$) :: a -> WithMeta key b -> WithMeta key a #

(KnownSymbol key, FromJSON a) => FromJSON (WithMeta key a) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

parseJSON :: Value -> Parser (WithMeta key a) #

parseJSONList :: Value -> Parser [WithMeta key a] #

Show a => Show (WithMeta key a) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> WithMeta key a -> ShowS #

show :: WithMeta key a -> String #

showList :: [WithMeta key a] -> ShowS #

Response metadata

data ResponseMeta Source #

Metadata attached to a response.

Constructors

ResponseMeta 

Instances

Instances details
FromJSON ResponseMeta Source # 
Instance details

Defined in Hetzner.Cloud

Show ResponseMeta Source # 
Instance details

Defined in Hetzner.Cloud

data Pagination Source #

Pagination information.

Instances

Instances details
FromJSON Pagination Source # 
Instance details

Defined in Hetzner.Cloud

Show Pagination Source # 
Instance details

Defined in Hetzner.Cloud