Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.DO
Contents
- type Command w a = FreeT (DO :+: (DropletCommands :+: (IPCommands :+: (DomainCommands :+: TagsCommands)))) (RESTT w) a
- type AuthToken = String
- type Slug = String
- type URI = String
- newtype Error = Error {}
- type Result a = Either Error a
- error :: String -> Result a
- data ToolConfiguration = Tool {}
- data Region
- = Region {
- regionName :: String
- regionSlug :: Slug
- regionSizes :: [SizeSlug]
- regionAvailable :: Bool
- | RegionSlug Slug
- | NoRegion
- = Region {
- sizeSlugs :: [String]
- data SizeSlug
- type ImageSlug = String
- type KeyId = Int
- defaultImage :: ImageSlug
- data BoxConfiguration = BoxConfiguration {
- configName :: String
- boxRegion :: Region
- size :: SizeSlug
- configImageSlug :: ImageSlug
- keys :: [KeyId]
- backgroundCreate :: Bool
- type Id = Integer
- data Mega
- data Giga
- newtype Bytes a = Bytes {}
- jsonBytes :: Int -> Parser (Bytes a)
- newtype Date = Date {}
- data Status
- data NetType
- data Network a
- data V4
- data V6
- jsonNetwork :: (FromJSON a3, FromJSON a2, FromJSON a1, FromJSON a) => (a3 -> a2 -> a1 -> a -> b) -> Object -> Parser b
- toJsonNetwork :: ToJSON netmask => IP -> netmask -> IP -> NetType -> Value
- data Networks
- data Droplet = Droplet {}
- data ImageType
- data Image = Image {
- imageId :: Id
- imageName :: String
- distribution :: String
- imageSlug :: Maybe Slug
- publicImage :: Bool
- imageRegions :: [Region]
- min_disk_size :: Bytes Giga
- image_created_at :: Date
- imageType :: ImageType
- data Key = Key {}
- type TransferRate = Double
- type Price = Double
- data Size = Size {
- szSlug :: SizeSlug
- szMemory :: Bytes Mega
- szVcpus :: Int
- szDisk :: Bytes Giga
- szTransfer :: TransferRate
- szPrice_Monthly :: Price
- szPrice_Hourly :: Price
- szRegions :: [Region]
- szAvailable :: Bool
- data ActionResult result = ActionResult {
- actionId :: Id
- actionStatus :: ActionStatus
- actionType :: result
- actionStartedAt :: Maybe Date
- actionCompletedAt :: Maybe Date
- actionResourceId :: Id
- actionResourceType :: String
- actionRegionSlug :: Region
- data ActionStatus
- data DropletActionType
- data Action
- newtype DomainName = DomainName {}
- data Domain = Domain {}
- data DomainConfig = DomainConfig DomainName IP
- data DNSType
- data DomainRecord = DomainRecord {
- recordId :: Id
- recordType :: DNSType
- recordName :: String
- recordData :: String
- recordPriority :: Maybe Int
- recordPort :: Maybe Int
- recordWeight :: Maybe Int
- parseRecord :: String -> Result DomainRecord
- data FloatingIP = FloatingIP {}
- data FloatingIPTarget
- data IPAction
- = AssignIP Id
- | UnassignIP
- data IPActionType
- data ResourceType
- resourceTypes :: [String]
- data Volume = Volume {}
- type TagName = String
- data Tag = Tag {}
- data TagResources = TagResources {}
- data TagDroplets = TagDroplets {}
- data TagVolumes = TagVolumes {}
- data TagPairs = TagPairs {
- tagPairsResources :: [TagPair]
- data TagPair = TagPair {}
- failParse :: (Show a1, Monad m) => a1 -> m a
- listKeys :: Monad w => Command w (Result [Key])
- listSizes :: Monad w => Command w (Result [Size])
- listRegions :: Monad w => Command w (Result [Region])
- listImages :: Monad w => Command w (Result [Image])
- listDroplets :: Monad w => Command w (Result [Droplet])
- createDroplet :: Monad w => BoxConfiguration -> Command w (Result Droplet)
- showDroplet :: Monad w => Integer -> Command w (Result Droplet)
- destroyDroplet :: Monad w => Integer -> Command w (Result ())
- dropletAction :: Monad w => Id -> Action -> Command w (Result (ActionResult DropletActionType))
- dropletConsole :: Monad w => Droplet -> Command w (Result ())
- getAction :: Monad w => Id -> Id -> Command w (Result (ActionResult DropletActionType))
- listDropletSnapshots :: Monad w => Id -> Command w (Result [Image])
- listFloatingIPs :: Monad w => Command w (Result [FloatingIP])
- createFloatingIP :: Monad w => FloatingIPTarget -> Command w (Result FloatingIP)
- deleteFloatingIP :: Monad w => IP -> Command w (Result ())
- assignFloatingIP :: Monad w => IP -> Id -> Command w (Result (ActionResult IPActionType))
- unassignFloatingIP :: Monad w => IP -> Command w (Result (ActionResult IPActionType))
- listDomains :: Monad w => Command w (Result [Domain])
- createDomain :: Monad w => DomainName -> IP -> Command w (Result Domain)
- deleteDomain :: Monad w => DomainName -> Command w (Result ())
- listRecords :: Monad w => DomainName -> Command w (Result [DomainRecord])
- createRecord :: Monad w => DomainName -> DomainRecord -> Command w (Result DomainRecord)
- deleteRecord :: Monad w => DomainName -> Id -> Command w (Result ())
- listTags :: Monad w => Command w (Result [Tag])
- createTag :: Monad w => TagName -> Command w (Result Tag)
- retrieveTag :: Monad w => TagName -> Command w (Result Tag)
- deleteTag :: Monad w => TagName -> Command w (Result ())
- tagResources :: Monad w => TagName -> TagPairs -> Command w (Result ())
- untagResources :: Monad w => TagName -> TagPairs -> Command w (Result ())
- runDOEnv :: Command IO a -> IO a
- runDO :: Command IO a -> Maybe AuthToken -> IO a
- runDODebug :: Command IO a -> Maybe AuthToken -> IO a
- getAuthFromEnv :: IO (Maybe AuthToken)
- outputResult :: (Pretty a, MonadIO m) => a -> m ()
- generateName :: IO String
- publicIP :: Droplet -> Maybe IP
- findByIdOrName :: String -> [Droplet] -> [Droplet]
Types
type Command w a = FreeT (DO :+: (DropletCommands :+: (IPCommands :+: (DomainCommands :+: TagsCommands)))) (RESTT w) a Source #
data ToolConfiguration Source #
A type for describing Region
A region can be assigned an empty object when it is undefined, or be referenced simply
by its slug
https://developers.digitalocean.com/documentation/v2/#regions
Constructors
Region | |
Fields
| |
RegionSlug Slug | |
NoRegion |
sizeSlugs :: [String] Source #
String representation of size slugs This maps to corresponding expected JSON string value.
Enumeration of all possible size slugs
data BoxConfiguration Source #
Constructors
BoxConfiguration | |
Fields
|
Instances
A type for various sizes Type parameter is used to define number's magnitude
Type of a single Network definition
This type is parameterized with a phantom type which lifts the network address type at the type level (could use DataKinds extension...). This allows distinguishing types of of networks while using same parsing.
Constructors
NetworkV4 | |
NetworkV6 | |
Fields
|
jsonNetwork :: (FromJSON a3, FromJSON a2, FromJSON a1, FromJSON a) => (a3 -> a2 -> a1 -> a -> b) -> Object -> Parser b Source #
Type of Networks configured for a Droplet
A network is either a list of IPv4 and IPv6 NICs definitions, or no network. We need this
because a droplet can contain an 'empty'
networks
JSON Object entry, instead of null
.
(Partial) Type of Droplets
https://developers.digitalocean.com/documentation/v2/#droplets
Constructors
Droplet | |
Type of droplet images
https://developers.digitalocean.com/documentation/v2/#images
Constructors
Image | |
Fields
|
Type of SSH Key
s
https://developers.digitalocean.com/documentation/v2/#ssh-keys
type TransferRate = Double Source #
Type of Size objects
Constructors
Size | |
Fields
|
Droplets Actions
data ActionResult result Source #
Type of action status This is returned when action is initiated or when status of some action is requested
Constructors
ActionResult | |
Fields
|
Instances
Show result => Show (ActionResult result) Source # | |
FromJSON r => FromJSON (ActionResult r) Source # | |
data DropletActionType Source #
Constructors
PowerOff | |
PowerOn | |
MakeSnapshot |
Constructors
DoPowerOff | |
DoPowerOn | |
CreateSnapshot String |
newtype DomainName Source #
Type of Domain zones
https://developers.digitalocean.com/documentation/v2/#domains
Constructors
DomainName | |
Instances
Constructors
Domain | |
Fields
|
Enumeration of possible DNS records types
data DomainRecord Source #
Type of Domain zone file entries
https://developers.digitalocean.com/documentation/v2/#domain-records
Constructors
DomainRecord | |
Fields
|
Instances
parseRecord :: String -> Result DomainRecord Source #
data FloatingIP Source #
Constructors
FloatingIP | |
Fields
|
Instances
Constructors
AssignIP Id | |
UnassignIP |
data IPActionType Source #
Instances
data ResourceType Source #
Type of Resources
Constructors
ResourceDroplet | |
ResourceVolume | |
ResourceBackend |
resourceTypes :: [String] Source #
Type of Block Storage (Volume)
https://developers.digitalocean.com/documentation/v2/#block-storage
Constructors
Volume | |
Fields
|
Constructors
Tag | |
Fields
|
data TagResources Source #
Constructors
TagResources | |
Fields
|
Instances
data TagDroplets Source #
Constructors
TagDroplets | |
Fields
|
Instances
data TagVolumes Source #
Constructors
TagVolumes | |
Fields
|
Instances
Constructors
TagPairs | |
Fields
|
Constructors
TagPair | |
Fields
|
Generic Commands
Droplets Commands
createDroplet :: Monad w => BoxConfiguration -> Command w (Result Droplet) Source #
dropletAction :: Monad w => Id -> Action -> Command w (Result (ActionResult DropletActionType)) Source #
getAction :: Monad w => Id -> Id -> Command w (Result (ActionResult DropletActionType)) Source #
Floating IPs Commands
listFloatingIPs :: Monad w => Command w (Result [FloatingIP]) Source #
createFloatingIP :: Monad w => FloatingIPTarget -> Command w (Result FloatingIP) Source #
assignFloatingIP :: Monad w => IP -> Id -> Command w (Result (ActionResult IPActionType)) Source #
unassignFloatingIP :: Monad w => IP -> Command w (Result (ActionResult IPActionType)) Source #
Domains Commands
createDomain :: Monad w => DomainName -> IP -> Command w (Result Domain) Source #
deleteDomain :: Monad w => DomainName -> Command w (Result ()) Source #
listRecords :: Monad w => DomainName -> Command w (Result [DomainRecord]) Source #
createRecord :: Monad w => DomainName -> DomainRecord -> Command w (Result DomainRecord) Source #
deleteRecord :: Monad w => DomainName -> Id -> Command w (Result ()) Source #
Tags Commands
Utilities
runDOEnv :: Command IO a -> IO a Source #
Run DO actions, extracting authentication token from environment variable AUTH_TOKEN
.
runDO :: Command IO a -> Maybe AuthToken -> IO a Source #
Run DO actions, passing a built authentication token.
runDODebug :: Command IO a -> Maybe AuthToken -> IO a Source #
Run DO actions, debugging requests, passing a built authentication token.
outputResult :: (Pretty a, MonadIO m) => a -> m () Source #
generateName :: IO String Source #