swagger-petstore-0.0.1.4: Auto-generated swagger-petstore API Client

Safe HaskellNone
LanguageHaskell2010

SwaggerPetstore.Core

Contents

Description

 

Synopsis

SwaggerPetstoreConfig

data SwaggerPetstoreConfig Source #

Constructors

SwaggerPetstoreConfig 

Fields

newConfig :: IO SwaggerPetstoreConfig Source #

constructs a default SwaggerPetstoreConfig

configHost:

http://petstore.swagger.io:80/v2

configUserAgent:

"swagger-haskell-http-client/1.0.0"

addAuthMethod :: AuthMethod auth => SwaggerPetstoreConfig -> auth -> SwaggerPetstoreConfig Source #

updates config use AuthMethod on matching requests

withStdoutLogging :: SwaggerPetstoreConfig -> IO SwaggerPetstoreConfig Source #

updates the config to use stdout logging

withStderrLogging :: SwaggerPetstoreConfig -> IO SwaggerPetstoreConfig Source #

updates the config to use stderr logging

withNoLogging :: SwaggerPetstoreConfig -> SwaggerPetstoreConfig Source #

updates the config to disable logging

SwaggerPetstoreRequest

data SwaggerPetstoreRequest req contentType res Source #

Represents a request. The "req" type variable is the request type. The "res" type variable is the response type.

Constructors

SwaggerPetstoreRequest 

Fields

Instances

Show (SwaggerPetstoreRequest req contentType res) Source # 

Methods

showsPrec :: Int -> SwaggerPetstoreRequest req contentType res -> ShowS #

show :: SwaggerPetstoreRequest req contentType res -> String #

showList :: [SwaggerPetstoreRequest req contentType res] -> ShowS #

HasBodyParam

class HasBodyParam req param where Source #

Designates the body parameter of a request

Methods

setBodyParam :: forall contentType res. (Consumes req contentType, MimeRender contentType param) => SwaggerPetstoreRequest req contentType res -> param -> SwaggerPetstoreRequest req contentType res Source #

Instances

HasBodyParam UpdateUser User Source #

Body Param "body" - Updated user object

Methods

setBodyParam :: (Consumes UpdateUser contentType, MimeRender contentType User) => SwaggerPetstoreRequest UpdateUser contentType res -> User -> SwaggerPetstoreRequest UpdateUser contentType res Source #

HasBodyParam CreateUsersWithListInput Body Source #

Body Param "body" - List of user object

HasBodyParam CreateUsersWithArrayInput Body Source #

Body Param "body" - List of user object

HasBodyParam CreateUser User Source #

Body Param "body" - Created user object

Methods

setBodyParam :: (Consumes CreateUser contentType, MimeRender contentType User) => SwaggerPetstoreRequest CreateUser contentType res -> User -> SwaggerPetstoreRequest CreateUser contentType res Source #

HasBodyParam PlaceOrder Order Source #

Body Param "body" - order placed for purchasing the pet

Methods

setBodyParam :: (Consumes PlaceOrder contentType, MimeRender contentType Order) => SwaggerPetstoreRequest PlaceOrder contentType res -> Order -> SwaggerPetstoreRequest PlaceOrder contentType res Source #

HasBodyParam UpdatePet Pet Source #

Body Param "body" - Pet object that needs to be added to the store

Methods

setBodyParam :: (Consumes UpdatePet contentType, MimeRender contentType Pet) => SwaggerPetstoreRequest UpdatePet contentType res -> Pet -> SwaggerPetstoreRequest UpdatePet contentType res Source #

HasBodyParam AddPet Pet Source #

Body Param "body" - Pet object that needs to be added to the store

Methods

setBodyParam :: (Consumes AddPet contentType, MimeRender contentType Pet) => SwaggerPetstoreRequest AddPet contentType res -> Pet -> SwaggerPetstoreRequest AddPet contentType res Source #

HasBodyParam TestClassname Client Source #

Body Param "body" - client model

Methods

setBodyParam :: (Consumes TestClassname contentType, MimeRender contentType Client) => SwaggerPetstoreRequest TestClassname contentType res -> Client -> SwaggerPetstoreRequest TestClassname contentType res Source #

HasBodyParam TestClientModel Client Source #

Body Param "body" - client model

HasBodyParam FakeOuterStringSerialize OuterString Source #

Body Param "body" - Input string as post body

HasBodyParam FakeOuterNumberSerialize OuterNumber Source #

Body Param "body" - Input number as post body

HasBodyParam FakeOuterCompositeSerialize OuterComposite Source #

Body Param "body" - Input composite as post body

HasBodyParam FakeOuterBooleanSerialize OuterBoolean Source #

Body Param "body" - Input boolean as post body

HasBodyParam TestSpecialTags Client Source #

Body Param "body" - client model

HasOptionalParam

class HasOptionalParam req param where Source #

Designates the optional parameters of a request

Minimal complete definition

applyOptionalParam | (-&-)

Methods

applyOptionalParam :: SwaggerPetstoreRequest req contentType res -> param -> SwaggerPetstoreRequest req contentType res Source #

Apply an optional parameter to a request

(-&-) :: SwaggerPetstoreRequest req contentType res -> param -> SwaggerPetstoreRequest req contentType res infixl 2 Source #

infix operator / alias for addOptionalParam

Instances

HasOptionalParam UploadFile File Source #

Optional Param "file" - file to upload

HasOptionalParam UploadFile AdditionalMetadata Source #

Optional Param "additionalMetadata" - Additional data to pass to server

HasOptionalParam UpdatePetWithForm StatusText Source #

Optional Param "status" - Updated status of the pet

HasOptionalParam UpdatePetWithForm Name2 Source #

Optional Param "name" - Updated name of the pet

HasOptionalParam DeletePet ApiKey Source # 
HasOptionalParam TestEnumParameters EnumQueryStringArray Source #

Optional Param "enum_query_string_array" - Query parameter enum test (string array)

HasOptionalParam TestEnumParameters EnumQueryString Source #

Optional Param "enum_query_string" - Query parameter enum test (string)

HasOptionalParam TestEnumParameters EnumQueryInteger Source #

Optional Param "enum_query_integer" - Query parameter enum test (double)

HasOptionalParam TestEnumParameters EnumQueryDouble Source #

Optional Param "enum_query_double" - Query parameter enum test (double)

HasOptionalParam TestEnumParameters EnumHeaderStringArray Source #

Optional Param "enum_header_string_array" - Header parameter enum test (string array)

HasOptionalParam TestEnumParameters EnumHeaderString Source #

Optional Param "enum_header_string" - Header parameter enum test (string)

HasOptionalParam TestEnumParameters EnumFormStringArray Source #

Optional Param "enum_form_string_array" - Form parameter enum test (string array)

HasOptionalParam TestEnumParameters EnumFormString Source #

Optional Param "enum_form_string" - Form parameter enum test (string)

HasOptionalParam TestEndpointParameters Password Source #

Optional Param "password" - None

HasOptionalParam TestEndpointParameters ParamString Source #

Optional Param "string" - None

HasOptionalParam TestEndpointParameters ParamInteger Source #

Optional Param "integer" - None

HasOptionalParam TestEndpointParameters ParamFloat Source #

Optional Param "float" - None

HasOptionalParam TestEndpointParameters ParamDateTime Source #

Optional Param "dateTime" - None

HasOptionalParam TestEndpointParameters ParamDate Source #

Optional Param "date" - None

HasOptionalParam TestEndpointParameters ParamBinary Source #

Optional Param "binary" - None

HasOptionalParam TestEndpointParameters Int64 Source #

Optional Param "int64" - None

HasOptionalParam TestEndpointParameters Int32 Source #

Optional Param "int32" - None

HasOptionalParam TestEndpointParameters Callback Source #

Optional Param "callback" - None

data Params Source #

Request Params

Instances

SwaggerPetstoreRequest Utils

_mkRequest Source #

Arguments

:: Method

Method

-> [ByteString]

Endpoint

-> SwaggerPetstoreRequest req contentType res

req: Request Type, res: Response Type

setHeader :: SwaggerPetstoreRequest req contentType res -> [Header] -> SwaggerPetstoreRequest req contentType res Source #

removeHeader :: SwaggerPetstoreRequest req contentType res -> [HeaderName] -> SwaggerPetstoreRequest req contentType res Source #

_setContentTypeHeader :: forall req contentType res. MimeType contentType => SwaggerPetstoreRequest req contentType res -> SwaggerPetstoreRequest req contentType res Source #

_setAcceptHeader :: forall req contentType res accept. MimeType accept => SwaggerPetstoreRequest req contentType res -> accept -> SwaggerPetstoreRequest req contentType res Source #

setQuery :: SwaggerPetstoreRequest req contentType res -> [QueryItem] -> SwaggerPetstoreRequest req contentType res Source #

addForm :: SwaggerPetstoreRequest req contentType res -> Form -> SwaggerPetstoreRequest req contentType res Source #

_addMultiFormPart :: SwaggerPetstoreRequest req contentType res -> Part -> SwaggerPetstoreRequest req contentType res Source #

_setBodyBS :: SwaggerPetstoreRequest req contentType res -> ByteString -> SwaggerPetstoreRequest req contentType res Source #

_setBodyLBS :: SwaggerPetstoreRequest req contentType res -> ByteString -> SwaggerPetstoreRequest req contentType res Source #

_hasAuthType :: AuthMethod authMethod => SwaggerPetstoreRequest req contentType res -> Proxy authMethod -> SwaggerPetstoreRequest req contentType res Source #

Params Utils

Swagger CollectionFormat Utils

data CollectionFormat Source #

Determines the format of the array if type array is used.

Constructors

CommaSeparated

CSV format for multiple parameters.

SpaceSeparated

Also called SSV

TabSeparated

Also called TSV

PipeSeparated

`value1|value2|value2`

MultiParamArray

Using multiple GET parameters, e.g. `foo=bar&foo=baz`. This is valid only for parameters in "query" (Query) or "formData" (Form)

_toColl :: Traversable f => CollectionFormat -> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)] Source #

_toCollA :: (Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t ByteString)]) -> f (t [a]) -> [(b, t ByteString)] Source #

_toCollA' :: (Monoid c, Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t c)]) -> (Char -> c) -> f (t [a]) -> [(b, t c)] Source #

AuthMethods

data AnyAuthMethod Source #

An existential wrapper for any AuthMethod

Constructors

AuthMethod a => AnyAuthMethod a 

_applyAuthMethods :: SwaggerPetstoreRequest req contentType res -> SwaggerPetstoreConfig -> IO (SwaggerPetstoreRequest req contentType res) Source #

apply all matching AuthMethods in config to request

Utils

_omitNulls :: [(Text, Value)] -> Value Source #

Removes Null fields. (OpenAPI-Specification 2.0 does not allow Null in JSON)

_toFormItem :: (ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text]) Source #

Encodes fields using WH.toQueryParam

_emptyToNothing :: Maybe String -> Maybe String Source #

Collapse (Just "") to Nothing

_memptyToNothing :: (Monoid a, Eq a) => Maybe a -> Maybe a Source #

Collapse (Just mempty) to Nothing

DateTime Formatting

newtype DateTime Source #

Constructors

DateTime 

Fields

Instances

Eq DateTime Source # 
Data DateTime Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateTime -> c DateTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateTime #

toConstr :: DateTime -> Constr #

dataTypeOf :: DateTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DateTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime) #

gmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> DateTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DateTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime #

Ord DateTime Source # 
Show DateTime Source # 
ToJSON DateTime Source # 
FromJSON DateTime Source # 
NFData DateTime Source # 

Methods

rnf :: DateTime -> () #

ToHttpApiData DateTime Source # 
FromHttpApiData DateTime Source # 
FormatTime DateTime Source # 
ParseTime DateTime Source # 
MimeRender MimeMultipartFormData DateTime Source # 

_readDateTime :: (ParseTime t, Monad m, Alternative m) => String -> m t Source #

_parseISO8601

_showDateTime :: (t ~ UTCTime, FormatTime t) => t -> String Source #

TI.formatISO8601Millis

_parseISO8601 :: (ParseTime t, Monad m, Alternative m) => String -> m t Source #

parse an ISO8601 date-time string

Date Formatting

newtype Date Source #

Constructors

Date 

Fields

Instances

Enum Date Source # 

Methods

succ :: Date -> Date #

pred :: Date -> Date #

toEnum :: Int -> Date #

fromEnum :: Date -> Int #

enumFrom :: Date -> [Date] #

enumFromThen :: Date -> Date -> [Date] #

enumFromTo :: Date -> Date -> [Date] #

enumFromThenTo :: Date -> Date -> Date -> [Date] #

Eq Date Source # 

Methods

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

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

Data Date Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Date -> c Date #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Date #

toConstr :: Date -> Constr #

dataTypeOf :: Date -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Date) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date) #

gmapT :: (forall b. Data b => b -> b) -> Date -> Date #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r #

gmapQ :: (forall d. Data d => d -> u) -> Date -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Date -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Date -> m Date #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date #

Ord Date Source # 

Methods

compare :: Date -> Date -> Ordering #

(<) :: Date -> Date -> Bool #

(<=) :: Date -> Date -> Bool #

(>) :: Date -> Date -> Bool #

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Show Date Source # 

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Ix Date Source # 

Methods

range :: (Date, Date) -> [Date] #

index :: (Date, Date) -> Date -> Int #

unsafeIndex :: (Date, Date) -> Date -> Int

inRange :: (Date, Date) -> Date -> Bool #

rangeSize :: (Date, Date) -> Int #

unsafeRangeSize :: (Date, Date) -> Int

ToJSON Date Source # 
FromJSON Date Source # 
NFData Date Source # 

Methods

rnf :: Date -> () #

ToHttpApiData Date Source # 
FromHttpApiData Date Source # 
FormatTime Date Source # 
ParseTime Date Source # 

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Date #

MimeRender MimeMultipartFormData Date Source # 

_readDate :: (ParseTime t, Monad m) => String -> m t Source #

TI.parseTimeM True TI.defaultTimeLocale "%Y-%m-%d"

_showDate :: FormatTime t => t -> String Source #

TI.formatTime TI.defaultTimeLocale "%Y-%m-%d"

Byte/Binary Formatting

newtype ByteArray Source #

base64 encoded characters

Constructors

ByteArray 

Instances

Eq ByteArray Source # 
Data ByteArray Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteArray -> c ByteArray #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteArray #

toConstr :: ByteArray -> Constr #

dataTypeOf :: ByteArray -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteArray) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray) #

gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteArray -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteArray -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

Ord ByteArray Source # 
Show ByteArray Source # 
ToJSON ByteArray Source # 
FromJSON ByteArray Source # 
NFData ByteArray Source # 

Methods

rnf :: ByteArray -> () #

ToHttpApiData ByteArray Source # 
FromHttpApiData ByteArray Source # 
MimeRender MimeMultipartFormData ByteArray Source # 

_readByteArray :: Monad m => Text -> m ByteArray Source #

read base64 encoded characters

_showByteArray :: ByteArray -> Text Source #

show base64 encoded characters

newtype Binary Source #

any sequence of octets

Constructors

Binary 

Fields

Instances

Eq Binary Source # 

Methods

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

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

Data Binary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binary -> c Binary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binary #

toConstr :: Binary -> Constr #

dataTypeOf :: Binary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Binary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary) #

gmapT :: (forall b. Data b => b -> b) -> Binary -> Binary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

Ord Binary Source # 
Show Binary Source # 
ToJSON Binary Source # 
FromJSON Binary Source # 
NFData Binary Source # 

Methods

rnf :: Binary -> () #

ToHttpApiData Binary Source # 
FromHttpApiData Binary Source # 
MimeRender MimeMultipartFormData Binary Source # 

Lens Type Aliases

type Lens_' s a = Lens_ s s a a Source #

type Lens_ s t a b = forall f. Functor f => (a -> f b) -> s -> f t Source #