linode-0.3.0.0: Bindings to the Linode API

LicenseBSD3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.Linode

Contents

Description

This package contains some helpers to create and configure Linode instances. They all require an API key, which can be created on the Linode website.

Usage example. We want to create one Linode instance in Atlanta with 1GB of RAM:

import Network.Linode
import Data.List (find)
import qualified System.Process as P
import Data.Foldable (traverse_)
import Data.Monoid ((<>))

main :: IO()
main = do
  apiKey <- fmap (head . words) (readFile "apiKey")
  sshPublicKey <- readFile "id_rsa.pub"
  let options = defaultLinodeCreationOptions {
    datacenterChoice = "atlanta",
    planChoice = "Linode 1024",
    sshKey = Just sshPublicKey
  }
  c <- createLinode apiKey True options
  case c of
    Left err -> print err
    Right linode -> do
      traverse_ (\a -> waitForSSH a >> setup a) (publicAddress linode)
      print linode

setup address = P.callCommand $ "scp yourfile root@" <> ip address <> ":/root"

You should see something like this:

Creating empty linode (Linode 1024 at atlanta)
Creating disk (24448 MB)
..............
Creating swap (128 MB)
........
Creating config
Booting
......................................
Booted linode 1481198

And get something like that:

Linode {
  linodeId = LinodeId {unLinodeId = 1481198},
  linodeConfigId = ConfigId {unConfigId = 2251152},
  linodeDatacenterName = "atlanta",
  linodePassword = "We4kP4ssw0rd",
  linodeAddresses = [Address {ip = "45.79.194.121", rdnsName = "li1293-121.members.linode.com"}]}

Synopsis

Most common operations

createLinode :: ApiKey -> Bool -> LinodeCreationOptions -> IO (Either LinodeError Linode) Source #

Create a Linode instance and boot it.

createCluster :: ApiKey -> LinodeCreationOptions -> Int -> Bool -> IO (Either [LinodeError] [Linode]) Source #

Create a Linode cluster.

defaultLinodeCreationOptions :: LinodeCreationOptions Source #

Default options to create an instance. Please customize the security options.

waitForSSH :: Address -> IO () Source #

Wait until an ssh connexion is possible, then add the Linode's ip in known_hosts.

A newly created Linode is unreachable during a few seconds.

deleteCluster :: ApiKey -> [LinodeId] -> IO ([LinodeError], [DeletedLinode]) Source #

Delete a list of Linode instances.

Lower level API calls

getAccountInfo :: ApiKey -> ExceptT LinodeError IO AccountInfo Source #

Read your global account information: network usage, billing state and billing method.

getDatacenters :: ApiKey -> ExceptT LinodeError IO [Datacenter] Source #

Read all Linode datacenters: dallas, fremont, atlanta, newark, london, tokyo, singapore, frankfurt

getDistributions :: ApiKey -> ExceptT LinodeError IO [Distribution] Source #

Read all available Linux distributions. For example, Debian 8.1 has id 140.

getInstances :: ApiKey -> ExceptT LinodeError IO [Instance] Source #

Read detailed information about all your instances.

getKernels :: ApiKey -> ExceptT LinodeError IO [Kernel] Source #

Read all available Linux kernels.

getPlans :: ApiKey -> ExceptT LinodeError IO [Plan] Source #

Read all plans offered by Linode. A plan specifies the available CPU, RAM, network usage and pricing of an instance. The smallest plan is Linode 1024.

getIpList :: ApiKey -> LinodeId -> ExceptT LinodeError IO [Address] Source #

Read all IP addresses of an instance.

createConfig :: ApiKey -> LinodeId -> KernelId -> String -> [DiskId] -> ExceptT LinodeError IO CreatedConfig Source #

Create a Linode Config (a bag of instance options).

createDiskFromDistribution :: ApiKey -> LinodeId -> DistributionId -> String -> Int -> String -> Maybe String -> ExceptT LinodeError IO CreatedDisk Source #

Create a disk from a supported Linux distribution. Size in MB.

createDisklessLinode :: ApiKey -> DatacenterId -> PlanId -> PaymentTerm -> ExceptT LinodeError IO CreatedLinode Source #

Create a Linode instance with no disk and no configuration. You probably want createLinode instead.

jobList :: ApiKey -> LinodeId -> ExceptT LinodeError IO [WaitingJob] Source #

List of pending jobs for this Linode instance.

Helpers

waitUntilCompletion :: ApiKey -> LinodeId -> Bool -> IO () Source #

Wait until all operations on one instance are done.

select :: ApiKey -> LinodeCreationOptions -> ExceptT LinodeError IO (Datacenter, Distribution, Plan, Kernel) Source #

Select a Datacenter, a Plan, a Linux distribution and kernel from all Linode offering.

publicAddress :: Linode -> Maybe Address Source #

Pick one public address of the Linode Instance

Examples

exampleCreateOneLinode :: IO (Maybe Linode) Source #

Example of Linode creation. It expects the apiKey and id_rsa.pub files in the current directory.

exampleCreateTwoLinodes :: IO (Maybe [Linode]) Source #

Example of Linodes creation. It expects the apiKey and id_rsa.pub files in the current directory.