Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- dispatchLbs :: (Produces req accept, MimeType contentType) => Manager -> KubernetesClientConfig -> KubernetesRequest req contentType res accept -> IO (Response ByteString)
- data MimeResult res = MimeResult {}
- data MimeError = MimeError {}
- dispatchMime :: forall req contentType res accept. (Produces req accept, MimeUnrender accept res, MimeType contentType) => Manager -> KubernetesClientConfig -> KubernetesRequest req contentType res accept -> IO (MimeResult res)
- dispatchMime' :: (Produces req accept, MimeUnrender accept res, MimeType contentType) => Manager -> KubernetesClientConfig -> KubernetesRequest req contentType res accept -> IO (Either MimeError res)
- dispatchLbsUnsafe :: (MimeType accept, MimeType contentType) => Manager -> KubernetesClientConfig -> KubernetesRequest req contentType res accept -> IO (Response ByteString)
- dispatchInitUnsafe :: Manager -> KubernetesClientConfig -> InitRequest req contentType res accept -> IO (Response ByteString)
- newtype InitRequest req contentType res accept = InitRequest {}
- _toInitRequest :: (MimeType accept, MimeType contentType) => KubernetesClientConfig -> KubernetesRequest req contentType res accept -> IO (InitRequest req contentType res accept)
- modifyInitRequest :: InitRequest req contentType res accept -> (Request -> Request) -> InitRequest req contentType res accept
- modifyInitRequestM :: Monad m => InitRequest req contentType res accept -> (Request -> m Request) -> m (InitRequest req contentType res accept)
- runConfigLog :: MonadIO m => KubernetesClientConfig -> LogExec m
- runConfigLogWithExceptions :: (MonadCatch m, MonadIO m) => Text -> KubernetesClientConfig -> LogExec m
Dispatch
Lbs
:: (Produces req accept, MimeType contentType) | |
=> Manager | http-client Connection manager |
-> KubernetesClientConfig | config |
-> KubernetesRequest req contentType res accept | request |
-> IO (Response ByteString) | response |
send a request returning the raw http response
Mime
data MimeResult res Source #
pair of decoded http body and http response
MimeResult | |
|
Instances
pair of unrender/parser error and http response
MimeError | |
|
:: forall req contentType res accept. (Produces req accept, MimeUnrender accept res, MimeType contentType) | |
=> Manager | http-client Connection manager |
-> KubernetesClientConfig | config |
-> KubernetesRequest req contentType res accept | request |
-> IO (MimeResult res) | response |
send a request returning the MimeResult
:: (Produces req accept, MimeUnrender accept res, MimeType contentType) | |
=> Manager | http-client Connection manager |
-> KubernetesClientConfig | config |
-> KubernetesRequest req contentType res accept | request |
-> IO (Either MimeError res) | response |
like dispatchMime
, but only returns the decoded http body
Unsafe
:: (MimeType accept, MimeType contentType) | |
=> Manager | http-client Connection manager |
-> KubernetesClientConfig | config |
-> KubernetesRequest req contentType res accept | request |
-> IO (Response ByteString) | response |
like dispatchReqLbs
, but does not validate the operation is a Producer
of the "accept" MimeType
. (Useful if the server's response is undocumented)
:: Manager | http-client Connection manager |
-> KubernetesClientConfig | config |
-> InitRequest req contentType res accept | init request |
-> IO (Response ByteString) | response |
dispatch an InitRequest
InitRequest
newtype InitRequest req contentType res accept Source #
wraps an http-client Request
with request/response type parameters
Instances
Show (InitRequest req contentType res accept) Source # | |
Defined in Kubernetes.OpenAPI.Client showsPrec :: Int -> InitRequest req contentType res accept -> ShowS # show :: InitRequest req contentType res accept -> String # showList :: [InitRequest req contentType res accept] -> ShowS # |
:: (MimeType accept, MimeType contentType) | |
=> KubernetesClientConfig | config |
-> KubernetesRequest req contentType res accept | request |
-> IO (InitRequest req contentType res accept) | initialized request |
Build an http-client Request
record from the supplied config and request
modifyInitRequest :: InitRequest req contentType res accept -> (Request -> Request) -> InitRequest req contentType res accept Source #
modify the underlying Request
modifyInitRequestM :: Monad m => InitRequest req contentType res accept -> (Request -> m Request) -> m (InitRequest req contentType res accept) Source #
modify the underlying Request (monadic)
Logging
runConfigLog :: MonadIO m => KubernetesClientConfig -> LogExec m Source #
Run a block using the configured logger instance
runConfigLogWithExceptions :: (MonadCatch m, MonadIO m) => Text -> KubernetesClientConfig -> LogExec m Source #
Run a block using the configured logger instance (logs exceptions)