hetzner-0.1.0.0: Hetzner Cloud client library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hetzner.Cloud

Description

Hetzner Cloud API client.

More information can be found on the official documentation.

Although not necessary, this module was designed with qualified imports in mind. For example:

import qualified Hetzner.Cloud as Hetzner

Pagination

Some requests use pagination. These take a page argument of type Maybe Int. You can use streamPages to get all pages through a conduit-based stream. For example, to get all servers as a stream:

streamPages $ getServers token :: ConduitT i Server m ()

Or to get all actions as a stream:

streamPages $ getActions token :: ConduitT i Action m ()

If you are not interested in the streaming functionality, you can simply use streamToList to turn the stream into a list:

streamToList $ streamPages $ getServers token :: m [Server]

Exceptions

This library makes extensive use of exceptions. Exceptions from this module have type CloudException. All functions that perform requests to Hetzner Cloud can throw this type of exception.

Synopsis

Tokens

newtype Token Source #

A token used to authenticate requests. All requests made with a token will have as scope the project where the token was made.

You can obtain one through the Hetzner Cloud Console.

Constructors

Token ByteString 

Server metadata

data Metadata Source #

Metadata that any server in the Hetzner cloud can discover about itself.

Constructors

Metadata 

Fields

Instances

Instances details
FromJSON Metadata Source # 
Instance details

Defined in Hetzner.Cloud

Show Metadata Source # 
Instance details

Defined in Hetzner.Cloud

getMetadata :: IO Metadata Source #

Obtain metadata from running server.

Hetzner Cloud API

Sections are in the same order as in the official documentation.

Actions

data ActionStatus Source #

Status of an action.

Constructors

ActionRunning Int

Action is still running. The Int argument is the progress percentage.

ActionSuccess ZonedTime

Action finished successfully. The finishing time is provided.

ActionError ZonedTime Error

Action finished with an error. The finishing time is provided, together with the error message.

Instances

Instances details
Show ActionStatus Source # 
Instance details

Defined in Hetzner.Cloud

newtype ActionID Source #

Action identifier.

Constructors

ActionID Int 

Instances

Instances details
FromJSON ActionID Source # 
Instance details

Defined in Hetzner.Cloud

Show ActionID Source # 
Instance details

Defined in Hetzner.Cloud

Eq ActionID Source # 
Instance details

Defined in Hetzner.Cloud

Ord ActionID Source # 
Instance details

Defined in Hetzner.Cloud

data Action Source #

Action.

Constructors

Action 

Instances

Instances details
FromJSON Action Source # 
Instance details

Defined in Hetzner.Cloud

Show Action Source # 
Instance details

Defined in Hetzner.Cloud

getActions Source #

Arguments

:: Token 
-> Maybe Int

Page.

-> IO (WithMeta "actions" [Action]) 

Get actions.

getAction :: Token -> ActionID -> IO Action Source #

Get a single action.

waitForAction :: Token -> ActionID -> IO ZonedTime Source #

Wait until an action is complete and returns the finishing time. It throws a CloudException if the action fails.

Datacenters

data Datacenter Source #

A datacenter within a location.

Instances

Instances details
FromJSON Datacenter Source # 
Instance details

Defined in Hetzner.Cloud

Show Datacenter Source # 
Instance details

Defined in Hetzner.Cloud

data DatacentersWithRecommendation Source #

Datacenter list with a datacenter recommendation for new servers.

Constructors

DatacentersWithRecommendation 

Fields

getDatacenter :: Token -> DatacenterID -> IO Datacenter Source #

Get a single datacenter.

Firewalls

newtype FirewallID Source #

Firewall identifier.

Constructors

FirewallID Int 

Floating IPs

Images

data OSFlavor Source #

Flavor of operative system.

Instances

Instances details
FromJSON OSFlavor Source # 
Instance details

Defined in Hetzner.Cloud

Show OSFlavor Source # 
Instance details

Defined in Hetzner.Cloud

data ImageType Source #

Image type.

Constructors

SystemImage Text

System image with name.

AppImage 
Snapshot Double

Snapshot with size in GB.

Backup ServerID 
Temporary 

Instances

Instances details
Show ImageType Source # 
Instance details

Defined in Hetzner.Cloud

newtype ImageID Source #

Image identifier.

Constructors

ImageID Int 

Instances

Instances details
FromJSON ImageID Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON ImageID Source # 
Instance details

Defined in Hetzner.Cloud

Show ImageID Source # 
Instance details

Defined in Hetzner.Cloud

Eq ImageID Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

Ord ImageID Source # 
Instance details

Defined in Hetzner.Cloud

data Image Source #

An image that can be mounted to a server.

Instances

Instances details
FromJSON Image Source # 
Instance details

Defined in Hetzner.Cloud

Show Image Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

getImages Source #

Arguments

:: Token 
-> Maybe Int

Page.

-> IO (WithMeta "images" [Image]) 

Get images.

getImage :: Token -> ImageID -> IO Image Source #

Get a single image.

Locations

data City Source #

Cities where Hetzner hosts their servers.

Instances

Instances details
FromJSON City Source # 
Instance details

Defined in Hetzner.Cloud

Show City Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> City -> ShowS #

show :: City -> String #

showList :: [City] -> ShowS #

Eq City Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

newtype LocationID Source #

Location identifier.

Constructors

LocationID Int 

getLocations :: Token -> IO [Location] Source #

Get all locations.

getLocation :: Token -> LocationID -> IO Location Source #

Get a single location.

Pricing

data Price Source #

A resource's price.

Constructors

Price 

Instances

Instances details
FromJSON Price Source # 
Instance details

Defined in Hetzner.Cloud

Show Price Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> Price -> ShowS #

show :: Price -> String #

showList :: [Price] -> ShowS #

Eq Price Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

Ord Price Source #

The Ord instance can be used to compare prices. Only the gross price is used for comparisons.

Instance details

Defined in Hetzner.Cloud

Methods

compare :: Price -> Price -> Ordering #

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

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

(>) :: Price -> Price -> Bool #

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

max :: Price -> Price -> Price #

min :: Price -> Price -> Price #

data PriceInLocation Source #

The price of a resource in a location. Hourly pricing is unavailable for some resources.

Constructors

PriceInLocation 

Fields

Servers

data ServerStatus Source #

A server status.

Instances

Instances details
FromJSON ServerStatus Source # 
Instance details

Defined in Hetzner.Cloud

Show ServerStatus Source # 
Instance details

Defined in Hetzner.Cloud

Eq ServerStatus Source # 
Instance details

Defined in Hetzner.Cloud

newtype ServerID Source #

Server identifier.

Constructors

ServerID Int 

Instances

Instances details
FromJSON ServerID Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON ServerID Source # 
Instance details

Defined in Hetzner.Cloud

Show ServerID Source # 
Instance details

Defined in Hetzner.Cloud

data NewServer Source #

Server creation configuration to be used with createServer.

Constructors

NewServer 

Fields

Instances

Instances details
ToJSON NewServer Source # 
Instance details

Defined in Hetzner.Cloud

Show NewServer Source # 
Instance details

Defined in Hetzner.Cloud

defaultNewServer Source #

Arguments

:: Text

Server name.

-> NewServer 

Default server configuration that can be used as a starting point for a custom server configuration.

Note that by default no SSH key is installed, which means you'll need the password in the response in order to access the server (you will also receive an e-mail with the password).

data CreatedServer Source #

A server that was just created with createServer.

Constructors

CreatedServer 

Fields

Instances

Instances details
FromJSON CreatedServer Source # 
Instance details

Defined in Hetzner.Cloud

Show CreatedServer Source # 
Instance details

Defined in Hetzner.Cloud

getServers Source #

Arguments

:: Token 
-> Maybe Int

Page.

-> IO (WithMeta "servers" [Server]) 

Get servers.

getServer :: Token -> ServerID -> IO Server Source #

Get a single server.

createServer :: Token -> NewServer -> IO CreatedServer Source #

Create a new server.

deleteServer :: Token -> ServerID -> IO Action Source #

Delete a server.

Server types

data Architecture Source #

Computer architecture.

Constructors

X86 
Arm 

Instances

Instances details
FromJSON Architecture Source # 
Instance details

Defined in Hetzner.Cloud

Show Architecture Source # 
Instance details

Defined in Hetzner.Cloud

Eq Architecture Source # 
Instance details

Defined in Hetzner.Cloud

data StorageType Source #

Type of server boot drive.

Instances

Instances details
FromJSON StorageType Source # 
Instance details

Defined in Hetzner.Cloud

Show StorageType Source # 
Instance details

Defined in Hetzner.Cloud

Eq StorageType Source # 
Instance details

Defined in Hetzner.Cloud

data CPUType Source #

CPU types available.

Constructors

SharedCPU 
DedicatedCPU 

Instances

Instances details
FromJSON CPUType Source # 
Instance details

Defined in Hetzner.Cloud

Show CPUType Source # 
Instance details

Defined in Hetzner.Cloud

Eq CPUType Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

data ServerType Source #

Server characteristics.

Constructors

ServerType 

Instances

Instances details
FromJSON ServerType Source # 
Instance details

Defined in Hetzner.Cloud

Show ServerType Source # 
Instance details

Defined in Hetzner.Cloud

getServerTypes :: Token -> IO [ServerType] Source #

Get all server types.

SSH Keys

newtype SSHKeyID Source #

SSH key identifier.

Constructors

SSHKeyID Int 

Instances

Instances details
FromJSON SSHKeyID Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON SSHKeyID Source # 
Instance details

Defined in Hetzner.Cloud

Show SSHKeyID Source # 
Instance details

Defined in Hetzner.Cloud

Eq SSHKeyID Source # 
Instance details

Defined in Hetzner.Cloud

Ord SSHKeyID Source # 
Instance details

Defined in Hetzner.Cloud

data SSHKey Source #

SSH key information.

Instances

Instances details
FromJSON SSHKey Source # 
Instance details

Defined in Hetzner.Cloud

Show SSHKey Source # 
Instance details

Defined in Hetzner.Cloud

getSSHKeys :: Token -> IO [SSHKey] Source #

Get all uploaded SSH keys.

getSSHKey :: Token -> SSHKeyID -> IO SSHKey Source #

Get a single SSH key.

createSSHKey Source #

Arguments

:: Token 
-> Text

Name for the SSH key.

-> Text

Public key.

-> [Label]

List of labels to attach to the key.

-> IO SSHKey 

Upload an SSH key.

deleteSSHKey :: Token -> SSHKeyID -> IO () Source #

Delete an SSH key.

updateSSHKey Source #

Arguments

:: Token 
-> SSHKeyID 
-> Text

New name for the key.

-> [Label]

New labels for the key.

-> IO () 

Update name and labels of an SSH key.

Volumes

newtype VolumeID Source #

Volume identifier.

Constructors

VolumeID Int 

Instances

Instances details
FromJSON VolumeID Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON VolumeID Source # 
Instance details

Defined in Hetzner.Cloud

Show VolumeID Source # 
Instance details

Defined in Hetzner.Cloud

Eq VolumeID Source # 
Instance details

Defined in Hetzner.Cloud

Ord VolumeID Source # 
Instance details

Defined in Hetzner.Cloud

Exceptions

data Error Source #

An error returned by Hetzner.

Constructors

Error 

Fields

Instances

Instances details
FromJSON Error Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON Error Source # 
Instance details

Defined in Hetzner.Cloud

Show Error Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

data CloudException Source #

Exception produced while performing a request to Hetzner Cloud.

Labels

data LabelKey Source #

Label key.

Constructors

LabelKey 

Fields

data Label Source #

Labels are key-value pairs that can be attached to all resources.

Constructors

Label 

Instances

Instances details
Show Label Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Eq Label Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

type LabelMap = Map LabelKey Text Source #

A label map maps label keys to values.

toLabelMap :: [Label] -> LabelMap Source #

Build a label map from a list of labels.

fromLabelMap :: LabelMap -> [Label] Source #

Get a list of labels from a label map.

data LabelSelector Source #

Label selectors can be used to filter results.

Constructors

LabelEqual Label

Select when label is equal.

LabelNotEqual Label

Select when label is not equal.

KeyPresent LabelKey

Select when key is present.

KeyNotPresent LabelKey

Select when key is not present.

KeyValueIn LabelKey [Text]

Select when label has one of the values.

KeyValueNotIn LabelKey [Text]

Select when label has none of the values.

LabelAll [LabelSelector]

Select only when all selectors succeed.

Instances

Instances details
Monoid LabelSelector Source #

Neutral element is a selector that always succeeds.

Instance details

Defined in Hetzner.Cloud

Semigroup LabelSelector Source #

Semigroup under "and" operation.

Instance details

Defined in Hetzner.Cloud

Other types

Regions

data Region Source #

Network zones.

Constructors

EUCentral

Nuremberg, Falkenstein, Helsinki.

USWest

Hillsboro (OR).

USEast

Ashburn (VA).

Instances

Instances details
FromJSON Region Source # 
Instance details

Defined in Hetzner.Cloud

ToJSON Region Source # 
Instance details

Defined in Hetzner.Cloud

Show Region Source # 
Instance details

Defined in Hetzner.Cloud

Eq Region Source # 
Instance details

Defined in Hetzner.Cloud

Methods

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

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

Resources

data ResourceID Source #

A resource ID is an ID from one of the available resources.

Constructors

ResourceServerID ServerID

Server ID.

Instances

Instances details
FromJSON ResourceID Source # 
Instance details

Defined in Hetzner.Cloud

Show ResourceID Source # 
Instance details

Defined in Hetzner.Cloud

Public networks

data FirewallStatus Source #

A firewall ID and whether the firewall is applied or not.

Instances

Instances details
FromJSON FirewallStatus Source # 
Instance details

Defined in Hetzner.Cloud

Show FirewallStatus Source # 
Instance details

Defined in Hetzner.Cloud

data PublicIPInfo dnsptr ip Source #

Public IP information.

Constructors

PublicIPInfo 

Fields

Instances

Instances details
(FromJSON dnsptr, FromJSON ip) => FromJSON (PublicIPInfo dnsptr ip) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

parseJSON :: Value -> Parser (PublicIPInfo dnsptr ip) #

parseJSONList :: Value -> Parser [PublicIPInfo dnsptr ip] #

(Show dnsptr, Show ip) => Show (PublicIPInfo dnsptr ip) Source # 
Instance details

Defined in Hetzner.Cloud

Methods

showsPrec :: Int -> PublicIPInfo dnsptr ip -> ShowS #

show :: PublicIPInfo dnsptr ip -> String #

showList :: [PublicIPInfo dnsptr ip] -> ShowS #

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

cloudQuery Source #

Arguments

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

Method

-> ByteString

Path

-> Maybe body

Request body. You may use noBody to skip.

-> Token

Authorization token

-> Maybe Int

Page

-> IO a 

Generic Hetzner Cloud query.

This function is used to implement Hetzner Cloud queries.

If there is any issue while performing the request, a CloudException will be thrown.

The page argument determines which page will be requested. If not provided, it will request the first page. If a page is requested outside the valid range, an empty list will be returned, not a failure.

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