| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Linode.Types
- type ApiKey = String
 - data LinodeCreationOptions = LinodeCreationOptions {
- datacenterSelect :: [Datacenter] -> Maybe Datacenter
 - planSelect :: [Plan] -> Maybe Plan
 - kernelSelect :: [Kernel] -> Maybe Kernel
 - distributionSelect :: [Distribution] -> Maybe Distribution
 - paymentChoice :: PaymentTerm
 - swapAmount :: Int
 - password :: String
 - sshKey :: Maybe String
 - diskLabel :: String
 - config :: Maybe ConfigId
 
 - newtype ConfigId = ConfigId {
- unConfigId :: Int
 
 - newtype DatacenterId = DatacenterId Int
 - newtype DistributionId = DistributionId Int
 - newtype DiskId = DiskId {}
 - newtype LinodeId = LinodeId {
- unLinodeId :: Int
 
 - newtype JobId = JobId Int
 - newtype KernelId = KernelId Int
 - newtype PlanId = PlanId Int
 - data DiskType
 - data InstanceStatus
 - data PaymentTerm
 - data AccountInfo = AccountInfo {}
 - data Address = Address {}
 - data Datacenter = Datacenter {
- datacenterId :: DatacenterId
 - datacenterLocation :: Text
 - datacenterName :: Text
 
 - data Distribution = Distribution {
- distributionId :: DistributionId
 - distributionName :: Text
 - is64Bit :: Bool
 - minImageSize :: Int
 - requiresPvopsKernel :: Bool
 
 - data Instance = Instance {}
 - data Kernel = Kernel {}
 - data Plan = Plan {}
 - data BootedInstance = BootedInstance {}
 - data CreatedConfig = CreatedConfig {}
 - data CreatedLinode = CreatedLinode {}
 - data CreatedDisk = CreatedDisk {}
 - type DeletedLinode = CreatedLinode
 - data WaitingJob = WaitingJob {
- waitingJobId :: JobId
 - waitingJobLinodeId :: LinodeId
 - waitingJobSuccess :: Bool
 - waitingJobLabel :: Text
 
 - data Linode = Linode {
- linodeId :: LinodeId
 - linodeConfigId :: ConfigId
 - linodeDatacenterName :: Text
 - linodePassword :: String
 - linodeAddresses :: [Address]
 
 - type Cluster = [Linode]
 - data Response a = Response {
- responseErrors :: [LinodeError]
 - responseContent :: Maybe a
 
 - data LinodeError
- = BadRequest
 - | NoActionWasRequested
 - | TheRequestedClassDoesNotExist
 - | AuthenticationFailed
 - | ObjectNotFound
 - | ARequiredPropertyIsMissingForThisAction
 - | PropertyIsInvalid
 - | ADataValidationErrorHasOccurred
 - | MethodNotImplemented
 - | TooManyBatchedRequests
 - | RequestArrayIsntValidJSONOrWDDX
 - | BatchApproachingTimeout
 - | PermissionDenied
 - | APIRateLimitExceeded
 - | ChargingTheCreditCardFailed
 - | CreditCardIsExpired
 - | LimitOfLinodesAddedPerHourReached
 - | LinodeMustHaveNoDisksBeforeDelete
 - | DeserializationError Text
 - | NetworkError IOException
 - | UnknownError Int
 - | SelectionError String
 
 - linodeErrorFromCode :: Int -> LinodeError
 - instanceStatusFromInt :: Int -> Maybe InstanceStatus
 
Documentation
data LinodeCreationOptions Source
Constructors
| LinodeCreationOptions | |
Fields 
  | |
Constructors
| ConfigId | |
Fields 
  | |
newtype DistributionId Source
Constructors
| DistributionId Int | 
Constructors
| LinodeId | |
Fields 
  | |
data PaymentTerm Source
Instances
data AccountInfo Source
Constructors
| AccountInfo | |
Fields 
  | |
Instances
| Eq AccountInfo Source | |
| Show AccountInfo Source | |
| FromJSON AccountInfo Source | 
data Datacenter Source
Constructors
| Datacenter | |
Fields 
  | |
Instances
| Eq Datacenter Source | |
| Show Datacenter Source | |
| FromJSON Datacenter Source | 
data Distribution Source
Constructors
| Distribution | |
Fields 
  | |
Instances
| Eq Distribution Source | |
| Show Distribution Source | |
| FromJSON Distribution Source | 
Detailed info about a Linode instance. Memory and transfer are given in MB.
Constructors
| Instance | |
Fields 
  | |
Constructors
| Kernel | |
Constructors
| Plan | |
data CreatedConfig Source
Constructors
| CreatedConfig | |
Fields  | |
Instances
| Eq CreatedConfig Source | |
| Show CreatedConfig Source | |
| FromJSON CreatedConfig Source | 
data CreatedLinode Source
Constructors
| CreatedLinode | |
Fields  | |
Instances
| Eq CreatedLinode Source | |
| Show CreatedLinode Source | |
| FromJSON CreatedLinode Source | 
data CreatedDisk Source
Constructors
| CreatedDisk | |
Fields  | |
Instances
| Eq CreatedDisk Source | |
| Show CreatedDisk Source | |
| FromJSON CreatedDisk Source | 
type DeletedLinode = CreatedLinode Source
data WaitingJob Source
Constructors
| WaitingJob | |
Fields 
  | |
Instances
| Eq WaitingJob Source | |
| Show WaitingJob Source | |
| FromJSON WaitingJob Source | 
Basic info about a linode instance.
Constructors
| Linode | |
Fields 
  | |
Constructors
| Response | |
Fields 
  | |
data LinodeError Source
Constructors
Instances
| Eq LinodeError Source | |
| Show LinodeError Source | |
| FromJSON LinodeError Source |