Copyright | (c) Yiğit Özkavcı 2017 |
---|---|
License | MIT |
Maintainer | yigitozkavci8@gmail.com |
Stability | beta |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Every computation within this module should be assessed via DO
monad.
An example usage:
{-# LANGUAGE OverloadedStrings #-} module Main where import Network.DigitalOcean import Control.Monad.Except import Control.Monad.Reader client ::Client
client =Client
"my api key" main :: IO () main = do result <- runExceptT $ (runReaderT $ "runDO" doActions) client case result of Left err -> print err Right _ -> return () createViaSshKeys ::DO
() createViaSshKeys = do -- Read a public key from a key pair and create ssh keys on DigitalOcean with it pubKey <- liftIO $ readFile "/Users/yigitozkavci/.ssh/do_api_rsa.pub" sshKey <-createSSHKey
(SSHKeyPayload
"my ssh key" pubKey) -- Create 2 droplets with our newly uploaded ssh keys let dropletPayload =IDropletPayload
"nyc3" "512mb"Ubuntu1404x64
(Just [sshkeyFingerprint sshKey]) Nothing Nothing Nothing Nothing Nothing Nothing Nothing droplets <- map dropletId <$>createDroplets
["droplet-1", "droplet-2"] dropletPayload -- Take snapshot of our newly created droplets forM_ droplets $ dropletId ->performDropletAction
dropletId (TakeSnapshot
(Just "bulk snapshot"))
- getAccounts :: DO Account
- getActions :: Maybe PaginationConfig -> DO [Action]
- getAction :: ActionId -> DO Action
- getRegions :: DO [Region]
- getVolumes :: DO [Volume]
- getVolume :: VolumeId -> DO Volume
- createVolume :: VolumePayload -> DO Volume
- getVolumesByName :: String -> String -> DO [Volume]
- deleteVolume :: VolumeId -> DO ()
- deleteVolumeByName :: String -> String -> DO ()
- performSingleVolumeAction :: VolumeId -> VolumeAction -> DO Action
- performListVolumeAction :: VolumeAction -> DO Action
- performVolumeAction :: VolumeAction -> DO Action
- getVolumeActions :: VolumeId -> DO [Action]
- getVolumeAction :: VolumeId -> ActionId -> DO Action
- data ResourceType
- getSnapshots :: Maybe ResourceType -> DO [Snapshot]
- getSnapshot :: SnapshotId -> DO Snapshot
- deleteSnapshot :: SnapshotId -> DO ()
- getSnapshotsOfVolume :: VolumeId -> DO [Snapshot]
- createSnapshotOfVolume :: VolumeId -> SnapshotPayload -> DO Snapshot
- createCertificate :: Certificatepayload -> DO Certificate
- getCertificate :: CertificateId -> DO Certificate
- getCertificates :: Maybe PaginationConfig -> DO [Certificate]
- deleteCertificate :: CertificateId -> DO ()
- getDomains :: DO [Domain]
- getDomain :: DomainName -> DO Domain
- createDomain :: DomainPayload -> DO Domain
- deleteDomain :: DomainName -> DO ()
- getDomainRecords :: DomainName -> DO [DomainRecord]
- createDomainRecord :: DomainName -> DomainRecordPayload -> DO DomainRecord
- getDomainRecord :: DomainName -> DomainRecordId -> DO DomainRecord
- updateDomainRecord :: DomainName -> DomainRecordId -> DomainRecordPayload -> DO DomainRecord
- deleteDomainRecord :: DomainName -> DomainRecordId -> DO ()
- getImages :: Maybe PaginationConfig -> ImageOptions -> DO [Image]
- getImageActions :: ImageId -> DO [Action]
- getImageAction :: ImageId -> ActionId -> DO Action
- getImage :: ImageId -> DO [Image]
- getImageBySlug :: String -> DO [Image]
- updateImage :: ImageId -> ImagePayload -> DO Image
- deleteImage :: ImageId -> DO ()
- performImageAction :: ImageId -> ImageAction -> DO Action
- getSizes :: DO [Size]
- getDroplets :: Maybe PaginationConfig -> DO [Droplet]
- createDroplet :: DropletName -> IDropletPayload -> DO Droplet
- createDroplets :: [DropletName] -> IDropletPayload -> DO [Droplet]
- getDroplet :: DropletId -> DO Droplet
- getDropletsByTag :: String -> DO [Droplet]
- getDropletKernels :: DropletId -> DO [Kernel]
- getDropletSnapshots :: DropletId -> DO [Snapshot]
- getDropletBackups :: DropletId -> DO [Backup]
- getDropletActions :: DropletId -> DO [Action]
- deleteDroplet :: DropletId -> DO ()
- deleteDropletByTag :: String -> DO ()
- getDropletNeighbors :: DropletId -> DO [Droplet]
- getNeighbors :: DO Neighbors
- performDropletAction :: DropletId -> DropletAction -> DO Action
- performDropletActionOnTag :: String -> DropletAction -> DO [Action]
- getDropletAction :: DropletId -> ActionId -> DO Action
- getFloatingIps :: DO [FloatingIp]
- createFloatingIp :: FloatingIpPayload -> DO FloatingIp
- getFloatingIp :: IpAddress -> DO FloatingIp
- deleteFloatingIp :: IpAddress -> DO ()
- performFloatingIpAction :: IpAddress -> FloatingIpAction -> DO Action
- getFloatingIpActions :: IpAddress -> DO [Action]
- getFloatingIpAction :: IpAddress -> ActionId -> DO Action
- createFirewall :: FirewallPayload -> DO Firewall
- getFirewall :: FirewallId -> DO Firewall
- getFirewalls :: DO [Firewall]
- updateFirewall :: FirewallId -> FirewallPayload -> DO Firewall
- deleteFirewall :: FirewallId -> DO ()
- addDropletsToFirewall :: FirewallId -> DropletsPayload -> DO ()
- removeDropletsFromFirewall :: FirewallId -> DropletsPayload -> DO ()
- addTagsToFirewall :: FirewallId -> TagsPayload -> DO ()
- removeTagsFromFirewall :: FirewallId -> TagsPayload -> DO ()
- addRulesToFirewall :: FirewallId -> FirewallRulesPayload -> DO ()
- removeRulesFromFirewall :: FirewallId -> FirewallRulesPayload -> DO ()
- createLoadBalancer :: LoadBalancerPayload -> DO LoadBalancer
- getLoadBalancer :: LoadBalancerId -> DO LoadBalancer
- getLoadBalancers :: DO [LoadBalancer]
- updateLoadBalancer :: LoadBalancerPayload -> DO LoadBalancer
- deleteLoadBalancer :: LoadBalancerId -> DO ()
- addDropletsToLoadBalancer :: LoadBalancerId -> DropletsPayload -> DO ()
- removeDropletsFromLoadBalancer :: LoadBalancerId -> DropletsPayload -> DO ()
- addForwardingRulesToLoadBalancer :: LoadBalancerId -> [ForwardingRule] -> DO ()
- removeForwardingRulesFromLoadBalancer :: LoadBalancerId -> [ForwardingRule] -> DO ()
- getSSHKeys :: DO [SSHKey]
- createSSHKey :: SSHKeyPayload -> DO SSHKey
- getSSHKey :: Either SSHKeyId String -> DO SSHKey
- updateSSHKey :: Either SSHKeyId String -> String -> DO SSHKey
- destroySSHKey :: Either SSHKeyId String -> DO ()
Account
getAccounts :: DO Account Source #
Actions
getActions :: Maybe PaginationConfig -> DO [Action] Source #
Regions
getRegions :: DO [Region] Source #
Volumes
getVolumes :: DO [Volume] Source #
createVolume :: VolumePayload -> DO Volume Source #
deleteVolume :: VolumeId -> DO () Source #
performSingleVolumeAction :: VolumeId -> VolumeAction -> DO Action Source #
Snapshots
getSnapshots :: Maybe ResourceType -> DO [Snapshot] Source #
getSnapshot :: SnapshotId -> DO Snapshot Source #
deleteSnapshot :: SnapshotId -> DO () Source #
Certificates
getCertificates :: Maybe PaginationConfig -> DO [Certificate] Source #
deleteCertificate :: CertificateId -> DO () Source #
Domains
getDomains :: DO [Domain] Source #
createDomain :: DomainPayload -> DO Domain Source #
deleteDomain :: DomainName -> DO () Source #
Domain Records
getDomainRecords :: DomainName -> DO [DomainRecord] Source #
getDomainRecord :: DomainName -> DomainRecordId -> DO DomainRecord Source #
updateDomainRecord :: DomainName -> DomainRecordId -> DomainRecordPayload -> DO DomainRecord Source #
deleteDomainRecord :: DomainName -> DomainRecordId -> DO () Source #
Images
getImages :: Maybe PaginationConfig -> ImageOptions -> DO [Image] Source #
updateImage :: ImageId -> ImagePayload -> DO Image Source #
deleteImage :: ImageId -> DO () Source #
performImageAction :: ImageId -> ImageAction -> DO Action Source #
Sizes
Droplets
getDroplets :: Maybe PaginationConfig -> DO [Droplet] Source #
createDroplet :: DropletName -> IDropletPayload -> DO Droplet Source #
createDroplets :: [DropletName] -> IDropletPayload -> DO [Droplet] Source #
deleteDroplet :: DropletId -> DO () Source #
deleteDropletByTag :: String -> DO () Source #
performDropletAction :: DropletId -> DropletAction -> DO Action Source #
performDropletActionOnTag :: String -> DropletAction -> DO [Action] Source #
Floating IPs
getFloatingIps :: DO [FloatingIp] Source #
getFloatingIp :: IpAddress -> DO FloatingIp Source #
deleteFloatingIp :: IpAddress -> DO () Source #
Firewalls
getFirewall :: FirewallId -> DO Firewall Source #
getFirewalls :: DO [Firewall] Source #
updateFirewall :: FirewallId -> FirewallPayload -> DO Firewall Source #
deleteFirewall :: FirewallId -> DO () Source #
addDropletsToFirewall :: FirewallId -> DropletsPayload -> DO () Source #
removeDropletsFromFirewall :: FirewallId -> DropletsPayload -> DO () Source #
addTagsToFirewall :: FirewallId -> TagsPayload -> DO () Source #
removeTagsFromFirewall :: FirewallId -> TagsPayload -> DO () Source #
addRulesToFirewall :: FirewallId -> FirewallRulesPayload -> DO () Source #
removeRulesFromFirewall :: FirewallId -> FirewallRulesPayload -> DO () Source #
Load Balancers
deleteLoadBalancer :: LoadBalancerId -> DO () Source #
addDropletsToLoadBalancer :: LoadBalancerId -> DropletsPayload -> DO () Source #
removeDropletsFromLoadBalancer :: LoadBalancerId -> DropletsPayload -> DO () Source #
addForwardingRulesToLoadBalancer :: LoadBalancerId -> [ForwardingRule] -> DO () Source #
removeForwardingRulesFromLoadBalancer :: LoadBalancerId -> [ForwardingRule] -> DO () Source #
SSH Keys
getSSHKeys :: DO [SSHKey] Source #
createSSHKey :: SSHKeyPayload -> DO SSHKey Source #