| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Cloudy.Scaleway
Documentation
data PlainTextNoUTF8 Source #
Instances
| Accept PlainTextNoUTF8 Source # | |
Defined in Cloudy.Scaleway Methods contentType :: Proxy PlainTextNoUTF8 -> MediaType # contentTypes :: Proxy PlainTextNoUTF8 -> NonEmpty MediaType # | |
| MimeRender PlainTextNoUTF8 UserData Source # | |
Defined in Cloudy.Scaleway Methods mimeRender :: Proxy PlainTextNoUTF8 -> UserData -> ByteString # | |
| MimeRender PlainTextNoUTF8 Text Source # | |
Defined in Cloudy.Scaleway Methods mimeRender :: Proxy PlainTextNoUTF8 -> Text -> ByteString # | |
| MimeUnrender PlainTextNoUTF8 UserData Source # | |
Defined in Cloudy.Scaleway Methods mimeUnrender :: Proxy PlainTextNoUTF8 -> ByteString -> Either String UserData # mimeUnrenderWithType :: Proxy PlainTextNoUTF8 -> MediaType -> ByteString -> Either String UserData # | |
| MimeUnrender PlainTextNoUTF8 Text Source # | |
Defined in Cloudy.Scaleway Methods mimeUnrender :: Proxy PlainTextNoUTF8 -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainTextNoUTF8 -> MediaType -> ByteString -> Either String Text # | |
Instances
| FromJSON PerPage Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON PerPage Source # | |
| Show PerPage Source # | |
| FromHttpApiData PerPage Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text PerPage # parseHeader :: ByteString -> Either Text PerPage # | |
| ToHttpApiData PerPage Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: PerPage -> Text # toEncodedUrlPiece :: PerPage -> Builder # toHeader :: PerPage -> ByteString # toQueryParam :: PerPage -> Text # toEncodedQueryParam :: PerPage -> Builder # | |
Instances
| FromJSON PageNum Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON PageNum Source # | |
| Show PageNum Source # | |
| FromHttpApiData PageNum Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text PageNum # parseHeader :: ByteString -> Either Text PageNum # | |
| ToHttpApiData PageNum Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: PageNum -> Text # toEncodedUrlPiece :: PageNum -> Builder # toHeader :: PageNum -> ByteString # toQueryParam :: PageNum -> Text # toEncodedQueryParam :: PageNum -> Builder # | |
type family Paged verb ct resp where ... Source #
Equations
| Paged verb ct resp = QueryParam "per_page" PerPage :> (QueryParam "page" PageNum :> verb ct (Headers '[Header "x-total-count" Int] resp)) |
Instances
| FromJSON Zone Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON Zone Source # | |
| Bounded Zone Source # | |
| Enum Zone Source # | |
| Show Zone Source # | |
| Eq Zone Source # | |
| ToHttpApiData Zone Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: Zone -> Text # toEncodedUrlPiece :: Zone -> Builder # toHeader :: Zone -> ByteString # toQueryParam :: Zone -> Text # toEncodedQueryParam :: Zone -> Builder # | |
allScalewayZones :: [Zone] Source #
zoneToText :: Zone -> Text Source #
Instances
| FromJSON ImageId Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON ImageId Source # | |
| Show ImageId Source # | |
| Eq ImageId Source # | |
| FromHttpApiData ImageId Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text ImageId # parseHeader :: ByteString -> Either Text ImageId # | |
| ToHttpApiData ImageId Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: ImageId -> Text # toEncodedUrlPiece :: ImageId -> Builder # toHeader :: ImageId -> ByteString # toQueryParam :: ImageId -> Text # toEncodedQueryParam :: ImageId -> Builder # | |
Instances
| FromJSON IpId Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON IpId Source # | |
| Show IpId Source # | |
| Eq IpId Source # | |
| FromHttpApiData IpId Source # | |
Defined in Cloudy.Scaleway | |
| ToHttpApiData IpId Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: IpId -> Text # toEncodedUrlPiece :: IpId -> Builder # toHeader :: IpId -> ByteString # toQueryParam :: IpId -> Text # toEncodedQueryParam :: IpId -> Builder # | |
newtype OrganizationId Source #
Constructors
| OrganizationId | |
Fields | |
Instances
Constructors
| ProjectId | |
Fields
| |
Instances
| FromJSON ProjectId Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON ProjectId Source # | |
| Show ProjectId Source # | |
| Eq ProjectId Source # | |
| FromHttpApiData ProjectId Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text ProjectId # parseHeader :: ByteString -> Either Text ProjectId # | |
| ToHttpApiData ProjectId Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: ProjectId -> Text # toEncodedUrlPiece :: ProjectId -> Builder # toHeader :: ProjectId -> ByteString # toQueryParam :: ProjectId -> Text # toEncodedQueryParam :: ProjectId -> Builder # | |
Constructors
| ServerId | |
Fields
| |
Instances
| FromJSON ServerId Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON ServerId Source # | |
| Show ServerId Source # | |
| Eq ServerId Source # | |
| FromHttpApiData ServerId Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text ServerId # parseHeader :: ByteString -> Either Text ServerId # | |
| ToHttpApiData ServerId Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: ServerId -> Text # toEncodedUrlPiece :: ServerId -> Builder # toHeader :: ServerId -> ByteString # toQueryParam :: ServerId -> Text # toEncodedQueryParam :: ServerId -> Builder # | |
Constructors
| VolumeId | |
Fields
| |
Instances
| FromJSON VolumeId Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON VolumeId Source # | |
| Show VolumeId Source # | |
| Eq VolumeId Source # | |
| FromHttpApiData VolumeId Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text VolumeId # parseHeader :: ByteString -> Either Text VolumeId # | |
| ToHttpApiData VolumeId Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: VolumeId -> Text # toEncodedUrlPiece :: VolumeId -> Builder # toHeader :: VolumeId -> ByteString # toQueryParam :: VolumeId -> Text # toEncodedQueryParam :: VolumeId -> Builder # | |
newtype UserDataKey Source #
Constructors
| UserDataKey | |
Fields | |
Instances
| FromJSON UserDataKey Source # | |
Defined in Cloudy.Scaleway | |
| ToJSON UserDataKey Source # | |
Defined in Cloudy.Scaleway Methods toJSON :: UserDataKey -> Value # toEncoding :: UserDataKey -> Encoding # toJSONList :: [UserDataKey] -> Value # toEncodingList :: [UserDataKey] -> Encoding # omitField :: UserDataKey -> Bool # | |
| Show UserDataKey Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> UserDataKey -> ShowS # show :: UserDataKey -> String # showList :: [UserDataKey] -> ShowS # | |
| Eq UserDataKey Source # | |
Defined in Cloudy.Scaleway | |
| FromHttpApiData UserDataKey Source # | |
Defined in Cloudy.Scaleway Methods parseUrlPiece :: Text -> Either Text UserDataKey # parseHeader :: ByteString -> Either Text UserDataKey # parseQueryParam :: Text -> Either Text UserDataKey # | |
| ToHttpApiData UserDataKey Source # | |
Defined in Cloudy.Scaleway Methods toUrlPiece :: UserDataKey -> Text # toEncodedUrlPiece :: UserDataKey -> Builder # toHeader :: UserDataKey -> ByteString # toQueryParam :: UserDataKey -> Text # | |
Constructors
| UserData | |
Fields
| |
Instances
| Show UserData Source # | |
| Eq UserData Source # | |
| MimeRender PlainTextNoUTF8 UserData Source # | |
Defined in Cloudy.Scaleway Methods mimeRender :: Proxy PlainTextNoUTF8 -> UserData -> ByteString # | |
| MimeUnrender PlainTextNoUTF8 UserData Source # | |
Defined in Cloudy.Scaleway Methods mimeUnrender :: Proxy PlainTextNoUTF8 -> ByteString -> Either String UserData # mimeUnrenderWithType :: Proxy PlainTextNoUTF8 -> MediaType -> ByteString -> Either String UserData # | |
data ServersReqVolume Source #
Constructors
| ServersReqVolume | |
Fields
| |
Instances
| ToJSON ServersReqVolume Source # | |
Defined in Cloudy.Scaleway Methods toJSON :: ServersReqVolume -> Value # toEncoding :: ServersReqVolume -> Encoding # toJSONList :: [ServersReqVolume] -> Value # toEncodingList :: [ServersReqVolume] -> Encoding # omitField :: ServersReqVolume -> Bool # | |
| Show ServersReqVolume Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ServersReqVolume -> ShowS # show :: ServersReqVolume -> String # showList :: [ServersReqVolume] -> ShowS # | |
data ServersRespVolume Source #
Constructors
| ServersRespVolume | |
Instances
| FromJSON ServersRespVolume Source # | |
Defined in Cloudy.Scaleway Methods parseJSON :: Value -> Parser ServersRespVolume # parseJSONList :: Value -> Parser [ServersRespVolume] # | |
| Show ServersRespVolume Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ServersRespVolume -> ShowS # show :: ServersRespVolume -> String # showList :: [ServersRespVolume] -> ShowS # | |
Constructors
| IpsResp | |
Fields
| |
data ServersReq Source #
Constructors
| ServersReq | |
Instances
| ToJSON ServersReq Source # | |
Defined in Cloudy.Scaleway Methods toJSON :: ServersReq -> Value # toEncoding :: ServersReq -> Encoding # toJSONList :: [ServersReq] -> Value # toEncodingList :: [ServersReq] -> Encoding # omitField :: ServersReq -> Bool # | |
| Show ServersReq Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ServersReq -> ShowS # show :: ServersReq -> String # showList :: [ServersReq] -> ShowS # | |
data ServersResp Source #
Constructors
| ServersResp | |
Instances
| FromJSON ServersResp Source # | |
Defined in Cloudy.Scaleway | |
| Show ServersResp Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ServersResp -> ShowS # show :: ServersResp -> String # showList :: [ServersResp] -> ShowS # | |
data ServersActionReq Source #
Constructors
| ServersActionReq | |
Instances
| ToJSON ServersActionReq Source # | |
Defined in Cloudy.Scaleway Methods toJSON :: ServersActionReq -> Value # toEncoding :: ServersActionReq -> Encoding # toJSONList :: [ServersActionReq] -> Value # toEncodingList :: [ServersActionReq] -> Encoding # omitField :: ServersActionReq -> Bool # | |
| Show ServersActionReq Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ServersActionReq -> ShowS # show :: ServersActionReq -> String # showList :: [ServersActionReq] -> ShowS # | |
data VolumesReq Source #
Constructors
| VolumesReq | |
Instances
| ToJSON VolumesReq Source # | |
Defined in Cloudy.Scaleway Methods toJSON :: VolumesReq -> Value # toEncoding :: VolumesReq -> Encoding # toJSONList :: [VolumesReq] -> Value # toEncodingList :: [VolumesReq] -> Encoding # omitField :: VolumesReq -> Bool # | |
| Show VolumesReq Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> VolumesReq -> ShowS # show :: VolumesReq -> String # showList :: [VolumesReq] -> ShowS # | |
data VolumeConstraint Source #
Constructors
| VolumeConstraint | |
Instances
| FromJSON VolumeConstraint Source # | |
Defined in Cloudy.Scaleway Methods parseJSON :: Value -> Parser VolumeConstraint # parseJSONList :: Value -> Parser [VolumeConstraint] # | |
| Show VolumeConstraint Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> VolumeConstraint -> ShowS # show :: VolumeConstraint -> String # showList :: [VolumeConstraint] -> ShowS # | |
newtype ProductServersResp Source #
Constructors
| ProductServersResp | |
Fields | |
Instances
| FromJSON ProductServersResp Source # | |
Defined in Cloudy.Scaleway Methods parseJSON :: Value -> Parser ProductServersResp # parseJSONList :: Value -> Parser [ProductServersResp] # | |
| Show ProductServersResp Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ProductServersResp -> ShowS # show :: ProductServersResp -> String # showList :: [ProductServersResp] -> ShowS # | |
data ProductServer Source #
Constructors
| ProductServer | |
Fields
| |
Instances
| FromJSON ProductServer Source # | |
Defined in Cloudy.Scaleway Methods parseJSON :: Value -> Parser ProductServer # parseJSONList :: Value -> Parser [ProductServer] # | |
| Show ProductServer Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ProductServer -> ShowS # show :: ProductServer -> String # showList :: [ProductServer] -> ShowS # | |
newtype ProductServersAvailabilityResp Source #
Constructors
| ProductServersAvailabilityResp | |
Fields | |
Instances
| FromJSON ProductServersAvailabilityResp Source # | |
Defined in Cloudy.Scaleway | |
| Show ProductServersAvailabilityResp Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ProductServersAvailabilityResp -> ShowS # show :: ProductServersAvailabilityResp -> String # showList :: [ProductServersAvailabilityResp] -> ShowS # | |
newtype ImagesResp Source #
Constructors
| ImagesResp | |
Fields
| |
Instances
| FromJSON ImagesResp Source # | |
Defined in Cloudy.Scaleway | |
| Show ImagesResp Source # | |
Defined in Cloudy.Scaleway Methods showsPrec :: Int -> ImagesResp -> ShowS # show :: ImagesResp -> String # showList :: [ImagesResp] -> ShowS # | |
Constructors
| Image | |
Fields
| |
type InstanceIpsPostApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("ips" :> (ReqBody '[JSON] IpsReq :> PostCreated '[JSON] IpsResp)))))) Source #
type InstanceIpsDeleteApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("ips" :> (Capture "ip_id" IpId :> DeleteNoContent)))))) Source #
type InstanceServersPostApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("servers" :> (ReqBody '[JSON] ServersReq :> PostCreated '[JSON] ServersResp)))))) Source #
type InstanceServersGetApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("servers" :> (Capture "server_id" ServerId :> Get '[JSON] ServersResp)))))) Source #
type InstanceServersActionPostApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("servers" :> (Capture "server_id" ServerId :> ("action" :> (ReqBody '[JSON] ServersActionReq :> PostAccepted '[JSON] TaskResp)))))))) Source #
type InstanceServersUserDataGetApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("servers" :> (Capture "server_id" ServerId :> ("user_data" :> (Capture "key" UserDataKey :> Get '[PlainTextNoUTF8] UserData)))))))) Source #
type InstanceServersUserDataPatchApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("servers" :> (Capture "server_id" ServerId :> ("user_data" :> (Capture "key" UserDataKey :> (ReqBody '[PlainTextNoUTF8] UserData :> PatchNoContent))))))))) Source #
type InstanceVolumesPatchApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("volumes" :> (Capture "volume_id" VolumeId :> (ReqBody '[JSON] VolumesReq :> Patch '[JSON] Value))))))) Source #
type InstanceProductsServersGetApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("products" :> ("servers" :> (QueryParam "per_page" PerPage :> Get '[JSON] ProductServersResp))))))) Source #
type InstanceProductsServersAvailabilityGetApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("products" :> ("servers" :> ("availability" :> (QueryParam "per_page" PerPage :> Get '[JSON] ProductServersAvailabilityResp)))))))) Source #
type InstanceImagesGetApi = AuthProtect "auth-token" :> ("instance" :> ("v1" :> ("zones" :> (Capture "zone" Zone :> ("images" :> (QueryParam "arch" Text :> Paged Get '[JSON] ImagesResp)))))) Source #
type ScalewayApi = InstanceIpsPostApi :<|> (InstanceIpsDeleteApi :<|> (InstanceServersPostApi :<|> (InstanceServersGetApi :<|> (InstanceServersActionPostApi :<|> (InstanceServersUserDataGetApi :<|> (InstanceServersUserDataPatchApi :<|> (InstanceVolumesPatchApi :<|> (InstanceProductsServersGetApi :<|> (InstanceProductsServersAvailabilityGetApi :<|> InstanceImagesGetApi))))))))) Source #
ipsPostApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> IpsReq -> ClientM IpsResp Source #
ipsDeleteApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> IpId -> ClientM NoContent Source #
serversPostApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> ServersReq -> ClientM ServersResp Source #
serversGetApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> ServerId -> ClientM ServersResp Source #
serversActionPostApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> ServerId -> ServersActionReq -> ClientM TaskResp Source #
serversUserDataGetApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> ServerId -> UserDataKey -> ClientM UserData Source #
serversUserDataPatchApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> ServerId -> UserDataKey -> UserData -> ClientM NoContent Source #
volumesPatchApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> VolumeId -> VolumesReq -> ClientM Value Source #
productsServersGetApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> Maybe PerPage -> ClientM ProductServersResp Source #
productsServersAvailabilityGetApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> Maybe PerPage -> ClientM ProductServersAvailabilityResp Source #
imagesGetApi :: AuthenticatedRequest (AuthProtect "auth-token") -> Zone -> Maybe Text -> Maybe PerPage -> Maybe PageNum -> ClientM (Headers '[Header "x-total-count" Int] ImagesResp) Source #