linode-v4-0.1.0.2: Haskell wrapper for the Linode v4 API

Safe HaskellNone
LanguageHaskell2010

Network.Linode.Response

Documentation

data Distribution Source #

Instances

Eq Distribution Source # 
Show Distribution Source # 
Generic Distribution Source # 

Associated Types

type Rep Distribution :: * -> * #

ToJSON Distribution Source # 
FromJSON Distribution Source # 
type Rep Distribution Source # 

data Service Source #

Instances

Eq Service Source # 

Methods

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

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

Show Service Source # 
Generic Service Source # 

Associated Types

type Rep Service :: * -> * #

Methods

from :: Service -> Rep Service x #

to :: Rep Service x -> Service #

ToJSON Service Source # 
FromJSON Service Source # 
type Rep Service Source # 

data DNSZone Source #

Instances

Eq DNSZone Source # 

Methods

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

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

Show DNSZone Source # 
Generic DNSZone Source # 

Associated Types

type Rep DNSZone :: * -> * #

Methods

from :: DNSZone -> Rep DNSZone x #

to :: Rep DNSZone x -> DNSZone #

ToJSON DNSZone Source # 
FromJSON DNSZone Source # 
type Rep DNSZone Source # 
type Rep DNSZone = D1 (MetaData "DNSZone" "Network.Linode.Response" "linode-v4-0.1.0.2-2Zvkj6sPYLK3m0Ifb3IHRH" False) (C1 (MetaCons "DNSZone" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "dnszone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "soa_email") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) (S1 (MetaSel (Just Symbol "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "refresh_sec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "retry_sec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "expire_sec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "ttl_sec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "status") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) (S1 (MetaSel (Just Symbol "master_ips") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) ((:*:) (S1 (MetaSel (Just Symbol "axfr_ips") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) (S1 (MetaSel (Just Symbol "display_group") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

data Kernel Source #

Constructors

Kernel 

Fields

Instances

Eq Kernel Source # 

Methods

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

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

Show Kernel Source # 
Generic Kernel Source # 

Associated Types

type Rep Kernel :: * -> * #

Methods

from :: Kernel -> Rep Kernel x #

to :: Rep Kernel x -> Kernel #

ToJSON Kernel Source # 
FromJSON Kernel Source # 
type Rep Kernel Source # 

data LinodeAlerts Source #

data LinodeIPAddressesPublic Source #

Constructors

LinodeIPAddressesPublic 

Fields

data Linode Source #

Instances

Eq Linode Source # 

Methods

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

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

Show Linode Source # 
Generic Linode Source # 

Associated Types

type Rep Linode :: * -> * #

Methods

from :: Linode -> Rep Linode x #

to :: Rep Linode x -> Linode #

ToJSON Linode Source # 
FromJSON Linode Source # 
type Rep Linode Source # 
type Rep Linode = D1 (MetaData "Linode" "Network.Linode.Response" "linode-v4-0.1.0.2-2Zvkj6sPYLK3m0Ifb3IHRH" False) (C1 (MetaCons "Linode" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "alerts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LinodeAlerts)) (S1 (MetaSel (Just Symbol "backups") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LinodeBackups)))) ((:*:) (S1 (MetaSel (Just Symbol "created") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "datacenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Datacenter)) (S1 (MetaSel (Just Symbol "distribution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Distribution)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "group") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "ips") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LinodeIPAddresses)) (S1 (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "services") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Service])) (S1 (MetaSel (Just Symbol "state") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "total_transfer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "updated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

data Backup Source #

Instances

Eq Backup Source # 

Methods

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

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

Show Backup Source # 
Generic Backup Source # 

Associated Types

type Rep Backup :: * -> * #

Methods

from :: Backup -> Rep Backup x #

to :: Rep Backup x -> Backup #

ToJSON Backup Source # 
FromJSON Backup Source # 
type Rep Backup Source # 

data Disk Source #

Constructors

Disk 

data Disks Source #

Constructors

Disks 

Fields

Instances

Eq Disks Source # 

Methods

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

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

Show Disks Source # 

Methods

showsPrec :: Int -> Disks -> ShowS #

show :: Disks -> String #

showList :: [Disks] -> ShowS #

Generic Disks Source # 

Associated Types

type Rep Disks :: * -> * #

Methods

from :: Disks -> Rep Disks x #

to :: Rep Disks x -> Disks #

ToJSON Disks Source # 
FromJSON Disks Source # 
type Rep Disks Source # 

data ConfigDisks Source #

Constructors

ConfigDisks 

Instances

Eq ConfigDisks Source # 
Show ConfigDisks Source # 
Generic ConfigDisks Source # 

Associated Types

type Rep ConfigDisks :: * -> * #

ToJSON ConfigDisks Source # 
FromJSON ConfigDisks Source # 
type Rep ConfigDisks Source # 

data ConfigHelpers Source #

data Config Source #

Instances

Eq Config Source # 

Methods

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

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

Show Config Source # 
Generic Config Source # 

Associated Types

type Rep Config :: * -> * #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

ToJSON Config Source # 
FromJSON Config Source # 
type Rep Config Source # 
type Rep Config = D1 (MetaData "Config" "Network.Linode.Response" "linode-v4-0.1.0.2-2Zvkj6sPYLK3m0Ifb3IHRH" False) (C1 (MetaCons "Config" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "comments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "created") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "devtmpfs_automount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "disks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConfigDisks))) ((:*:) (S1 (MetaSel (Just Symbol "helpers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConfigHelpers)) (S1 (MetaSel (Just Symbol "kernel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kernel))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "ram_limit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "root_device") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "root_device_ro") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "run_level") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "updated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "virt_mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

data UDF Source #

Constructors

UDF 

Fields

Instances

Eq UDF Source # 

Methods

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

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

Show UDF Source # 

Methods

showsPrec :: Int -> UDF -> ShowS #

show :: UDF -> String #

showList :: [UDF] -> ShowS #

Generic UDF Source # 

Associated Types

type Rep UDF :: * -> * #

Methods

from :: UDF -> Rep UDF x #

to :: Rep UDF x -> UDF #

ToJSON UDF Source # 

Methods

toJSON :: UDF -> Value #

toEncoding :: UDF -> Encoding #

FromJSON UDF Source # 

Methods

parseJSON :: Value -> Parser UDF #

type Rep UDF Source # 

data StackScript Source #

Instances

Eq StackScript Source # 
Show StackScript Source # 
Generic StackScript Source # 

Associated Types

type Rep StackScript :: * -> * #

ToJSON StackScript Source # 
FromJSON StackScript Source # 
type Rep StackScript Source # 
type Rep StackScript = D1 (MetaData "StackScript" "Network.Linode.Response" "linode-v4-0.1.0.2-2Zvkj6sPYLK3m0Ifb3IHRH" False) (C1 (MetaCons "StackScript" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "customer_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "user_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "distributions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Distribution])) (S1 (MetaSel (Just Symbol "deployments_total") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "deployments_active") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "is_public") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "created") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "updated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "rev_note") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "script") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "user_defined_fields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [UDF])))))))