Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
RecurlyClient.Common
Description
This module serves the purpose of defining common functionality which remains the same across all OpenAPI specifications.
Synopsis
- doCallWithConfiguration :: MonadHTTP m => Configuration -> Text -> Text -> [QueryParameter] -> m (Response ByteString)
- doCallWithConfigurationM :: MonadHTTP m => Text -> Text -> [QueryParameter] -> ClientT m (Response ByteString)
- doBodyCallWithConfiguration :: (MonadHTTP m, ToJSON body) => Configuration -> Text -> Text -> [QueryParameter] -> Maybe body -> RequestBodyEncoding -> m (Response ByteString)
- doBodyCallWithConfigurationM :: (MonadHTTP m, ToJSON body) => Text -> Text -> [QueryParameter] -> Maybe body -> RequestBodyEncoding -> ClientT m (Response ByteString)
- runWithConfiguration :: Configuration -> ClientT m a -> m a
- textToByte :: Text -> ByteString
- byteToText :: ByteString -> Text
- stringifyModel :: ToJSON a => a -> Text
- anonymousSecurityScheme :: SecurityScheme
- jsonObjectToList :: KeyMap v -> [(Text, v)]
- data Configuration = Configuration {}
- type SecurityScheme = Request -> Request
- class Monad m => MonadHTTP m where
- httpBS :: Request -> m (Response ByteString)
- newtype JsonByteString = JsonByteString ByteString
- newtype JsonDateTime = JsonDateTime ZonedTime
- data RequestBodyEncoding
- data QueryParameter = QueryParameter {}
- data Nullable a
- newtype ClientT m a = ClientT (ReaderT Configuration m a)
- type ClientM a = ClientT IO a
Documentation
doCallWithConfiguration Source #
Arguments
:: MonadHTTP m | |
=> Configuration | Configuration options like base URL and security scheme |
-> Text | HTTP method (GET, POST, etc.) |
-> Text | Path to append to the base URL (path parameters should already be replaced) |
-> [QueryParameter] | Query parameters |
-> m (Response ByteString) | The raw response from the server |
This is the main functionality of this module
It makes a concrete Call to a Server without a body
doCallWithConfigurationM :: MonadHTTP m => Text -> Text -> [QueryParameter] -> ClientT m (Response ByteString) Source #
Same as doCallWithConfiguration
but run in a ReaderT
environment which contains the configuration.
This is useful if multiple calls have to be executed with the same configuration.
doBodyCallWithConfiguration Source #
Arguments
:: (MonadHTTP m, ToJSON body) | |
=> Configuration | Configuration options like base URL and security scheme |
-> Text | HTTP method (GET, POST, etc.) |
-> Text | Path to append to the base URL (path parameters should already be replaced) |
-> [QueryParameter] | Query parameters |
-> Maybe body | Request body |
-> RequestBodyEncoding | JSON or form data deepobjects |
-> m (Response ByteString) | The raw response from the server |
This is the main functionality of this module
It makes a concrete Call to a Server with a body
doBodyCallWithConfigurationM :: (MonadHTTP m, ToJSON body) => Text -> Text -> [QueryParameter] -> Maybe body -> RequestBodyEncoding -> ClientT m (Response ByteString) Source #
Same as doBodyCallWithConfiguration
but run in a ReaderT
environment which contains the configuration.
This is useful if multiple calls have to be executed with the same configuration.
runWithConfiguration :: Configuration -> ClientT m a -> m a Source #
Run a ClientT
monad transformer in another monad with a specified configuration
textToByte :: Text -> ByteString Source #
Convert Text
a to ByteString
byteToText :: ByteString -> Text Source #
Convert a ByteString
to Text
stringifyModel :: ToJSON a => a -> Text Source #
This function makes the code generation for URL parameters easier as it allows to stringify a value
The Show
class is not sufficient as strings should not be stringified with quotes.
anonymousSecurityScheme :: SecurityScheme Source #
Anonymous security scheme which does not alter the request in any way
jsonObjectToList :: KeyMap v -> [(Text, v)] Source #
data Configuration Source #
An operation can and must be configured with data, which may be common for many operations.
This configuration consists of information about the server URL and the used security scheme.
In OpenAPI these information can be defined
- Root level
- Path level
- Operation level
To get started, the defaultConfiguration
can be used and changed accordingly.
Note that it is possible that bearerAuthenticationSecurityScheme
is not available because it is not a security scheme in the OpenAPI specification.
defaultConfiguration { configSecurityScheme = bearerAuthenticationSecurityScheme "token" }
Constructors
Configuration | |
Fields
|
Instances
Monad m => MonadReader Configuration (ClientT m) Source # | |
Defined in RecurlyClient.Common Methods ask :: ClientT m Configuration # local :: (Configuration -> Configuration) -> ClientT m a -> ClientT m a # reader :: (Configuration -> a) -> ClientT m a # |
type SecurityScheme = Request -> Request Source #
This type specifies a security scheme which can modify a request according to the scheme (e. g. add an Authorization header)
class Monad m => MonadHTTP m where Source #
Abstracts the usage of httpBS
away,
so that it can be used for testing
newtype JsonByteString Source #
Wraps a ByteString
to implement ToJSON
and FromJSON
Constructors
JsonByteString ByteString |
Instances
newtype JsonDateTime Source #
Constructors
JsonDateTime ZonedTime |
Instances
FromJSON JsonDateTime Source # | |
Defined in RecurlyClient.Common | |
ToJSON JsonDateTime Source # | |
Defined in RecurlyClient.Common Methods toJSON :: JsonDateTime -> Value # toEncoding :: JsonDateTime -> Encoding # toJSONList :: [JsonDateTime] -> Value # toEncodingList :: [JsonDateTime] -> Encoding # | |
Show JsonDateTime Source # | |
Defined in RecurlyClient.Common Methods showsPrec :: Int -> JsonDateTime -> ShowS # show :: JsonDateTime -> String # showList :: [JsonDateTime] -> ShowS # | |
Eq JsonDateTime Source # | |
Defined in RecurlyClient.Common | |
Ord JsonDateTime Source # | |
Defined in RecurlyClient.Common Methods compare :: JsonDateTime -> JsonDateTime -> Ordering # (<) :: JsonDateTime -> JsonDateTime -> Bool # (<=) :: JsonDateTime -> JsonDateTime -> Bool # (>) :: JsonDateTime -> JsonDateTime -> Bool # (>=) :: JsonDateTime -> JsonDateTime -> Bool # max :: JsonDateTime -> JsonDateTime -> JsonDateTime # min :: JsonDateTime -> JsonDateTime -> JsonDateTime # |
data RequestBodyEncoding Source #
Defines how a request body is encoded
Constructors
RequestBodyEncodingJSON | Encode the body as JSON |
RequestBodyEncodingFormData | Encode the body as form data |
data QueryParameter Source #
Defines a query parameter with the information necessary for serialization
Constructors
QueryParameter | |
Fields |
Instances
Show QueryParameter Source # | |
Defined in RecurlyClient.Common Methods showsPrec :: Int -> QueryParameter -> ShowS # show :: QueryParameter -> String # showList :: [QueryParameter] -> ShowS # | |
Eq QueryParameter Source # | |
Defined in RecurlyClient.Common Methods (==) :: QueryParameter -> QueryParameter -> Bool # (/=) :: QueryParameter -> QueryParameter -> Bool # |
The monad in which the operations can be run.
Contains the Configuration
to run the requests with.
Run it with runWithConfiguration
Constructors
ClientT (ReaderT Configuration m a) |
Instances
MonadTrans ClientT Source # | |
Defined in RecurlyClient.Common | |
Monad m => MonadReader Configuration (ClientT m) Source # | |
Defined in RecurlyClient.Common Methods ask :: ClientT m Configuration # local :: (Configuration -> Configuration) -> ClientT m a -> ClientT m a # reader :: (Configuration -> a) -> ClientT m a # | |
MonadIO m => MonadIO (ClientT m) Source # | |
Defined in RecurlyClient.Common | |
Applicative m => Applicative (ClientT m) Source # | |
Functor m => Functor (ClientT m) Source # | |
Monad m => Monad (ClientT m) Source # | |
MonadHTTP m => MonadHTTP (ClientT m) Source # | |
Defined in RecurlyClient.Common |