httpstan-0.2.0.0: Auto-generated httpstan API Client
Safe HaskellSafe-Inferred
LanguageHaskell2010

Httpstan.Core

Description

 
Synopsis

HttpstanConfig

data HttpstanConfig Source #

 

Constructors

HttpstanConfig 

Fields

Instances

Instances details
Show HttpstanConfig Source #

display the config

Instance details

Defined in Httpstan.Core

newConfig :: IO HttpstanConfig Source #

constructs a default HttpstanConfig

configHost:

http://localhost

configUserAgent:

"httpstan/0.1.0.0"

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

updates config use AuthMethod on matching requests

withStdoutLogging :: HttpstanConfig -> IO HttpstanConfig Source #

updates the config to use stdout logging

withStderrLogging :: HttpstanConfig -> IO HttpstanConfig Source #

updates the config to use stderr logging

withNoLogging :: HttpstanConfig -> HttpstanConfig Source #

updates the config to disable logging

HttpstanRequest

data HttpstanRequest req contentType res accept Source #

Represents a request.

Type Variables:

  • req - request operation
  • contentType - MimeType associated with request body
  • res - response model
  • accept - MimeType associated with response body

Constructors

HttpstanRequest 

Fields

Instances

Instances details
Show (HttpstanRequest req contentType res accept) Source # 
Instance details

Defined in Httpstan.Core

Methods

showsPrec :: Int -> HttpstanRequest req contentType res accept -> ShowS #

show :: HttpstanRequest req contentType res accept -> String #

showList :: [HttpstanRequest req contentType res accept] -> ShowS #

rMethodL :: Lens_' (HttpstanRequest req contentType res accept) Method Source #

rMethod Lens

rUrlPathL :: Lens_' (HttpstanRequest req contentType res accept) [ByteString] Source #

rParamsL :: Lens_' (HttpstanRequest req contentType res accept) Params Source #

rParams Lens

rAuthTypesL :: Lens_' (HttpstanRequest req contentType res accept) [TypeRep] Source #

rParams Lens

HasBodyParam

class HasBodyParam req param where Source #

Designates the body parameter of a request

Minimal complete definition

Nothing

Methods

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

Instances

Instances details
HasBodyParam V1ModelsModelIdFitsPost CreateFitRequest Source #

Body Param "body" - Full stan::services function name and associated arguments to call with Stan model.

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsModelIdLogProbGradPost AdjustTransform Source #

Body Param "adjust_transform" - Boolean to control whether we apply a Jacobian adjust transform.

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsModelIdLogProbPost AdjustTransform Source #

Body Param "adjust_transform" - Boolean to control whether we apply a Jacobian adjust transform.

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsModelIdParamsPost ParamData Source #

Body Param "data" - Data for Stan Model. Needed to calculate param names and dimensions.

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsModelIdTransformInitsPost ConstrainedParameters Source #

Body Param "constrained_parameters" - Constrained parameter values and their specified context

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsModelIdWriteArrayPost IncludeGqs Source #

Body Param "include_gqs" - Boolean to control whether we include generated quantities.

Instance details

Defined in Httpstan.API.ApiDefault

HasBodyParam V1ModelsPost CreateModelRequest Source #

Body Param "body" - Stan program code to compile

Instance details

Defined in Httpstan.API.ApiDefault

Methods

setBodyParam :: (Consumes V1ModelsPost contentType, MimeRender contentType CreateModelRequest) => HttpstanRequest V1ModelsPost contentType res accept -> CreateModelRequest -> HttpstanRequest V1ModelsPost contentType res accept Source #

HasOptionalParam

class HasOptionalParam req param where Source #

Designates the optional parameters of a request

Minimal complete definition

applyOptionalParam | (-&-)

Methods

applyOptionalParam :: HttpstanRequest req contentType res accept -> param -> HttpstanRequest req contentType res accept Source #

Apply an optional parameter to a request

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

infix operator / alias for addOptionalParam

data Params Source #

Request Params

Instances

Instances details
Show Params Source # 
Instance details

Defined in Httpstan.Core

HttpstanRequest Utils

_mkRequest Source #

Arguments

:: Method

Method

-> [ByteString]

Endpoint

-> HttpstanRequest req contentType res accept

req: Request Type, res: Response Type

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

addHeader :: HttpstanRequest req contentType res accept -> [Header] -> HttpstanRequest req contentType res accept Source #

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

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

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

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

addQuery :: HttpstanRequest req contentType res accept -> [QueryItem] -> HttpstanRequest req contentType res accept Source #

addForm :: HttpstanRequest req contentType res accept -> Form -> HttpstanRequest req contentType res accept Source #

_addMultiFormPart :: HttpstanRequest req contentType res accept -> Part -> HttpstanRequest req contentType res accept Source #

_setBodyBS :: HttpstanRequest req contentType res accept -> ByteString -> HttpstanRequest req contentType res accept Source #

_setBodyLBS :: HttpstanRequest req contentType res accept -> ByteString -> HttpstanRequest req contentType res accept Source #

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

Params Utils

OpenAPI 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

class Typeable a => AuthMethod a where Source #

Provides a method to apply auth methods to requests

Methods

applyAuthMethod :: HttpstanConfig -> a -> HttpstanRequest req contentType res accept -> IO (HttpstanRequest req contentType res accept) Source #

Instances

Instances details
AuthMethod AnyAuthMethod Source # 
Instance details

Defined in Httpstan.Core

Methods

applyAuthMethod :: HttpstanConfig -> AnyAuthMethod -> HttpstanRequest req contentType res accept -> IO (HttpstanRequest req contentType res accept) Source #

data AnyAuthMethod Source #

An existential wrapper for any AuthMethod

Constructors

forall a.AuthMethod a => AnyAuthMethod a 

Instances

Instances details
AuthMethod AnyAuthMethod Source # 
Instance details

Defined in Httpstan.Core

Methods

applyAuthMethod :: HttpstanConfig -> AnyAuthMethod -> HttpstanRequest req contentType res accept -> IO (HttpstanRequest req contentType res accept) Source #

_applyAuthMethods :: HttpstanRequest req contentType res accept -> HttpstanConfig -> IO (HttpstanRequest req contentType res accept) Source #

apply all matching AuthMethods in config to request

Utils

_omitNulls :: [(Key, 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

Instances details
Data DateTime Source # 
Instance details

Defined in Httpstan.Core

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 :: forall r r'. (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 #

Show DateTime Source # 
Instance details

Defined in Httpstan.Core

NFData DateTime Source # 
Instance details

Defined in Httpstan.Core

Methods

rnf :: DateTime -> () #

Eq DateTime Source # 
Instance details

Defined in Httpstan.Core

Ord DateTime Source # 
Instance details

Defined in Httpstan.Core

FromHttpApiData DateTime Source # 
Instance details

Defined in Httpstan.Core

ToHttpApiData DateTime Source # 
Instance details

Defined in Httpstan.Core

FromJSON DateTime Source # 
Instance details

Defined in Httpstan.Core

ToJSON DateTime Source # 
Instance details

Defined in Httpstan.Core

MimeRender MimeMultipartFormData DateTime Source # 
Instance details

Defined in Httpstan.Core

_readDateTime :: (MonadFail m, Alternative m) => String -> m DateTime Source #

_parseISO8601

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

TI.formatISO8601Millis

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

parse an ISO8601 date-time string

Date Formatting

newtype Date Source #

Constructors

Date 

Fields

Instances

Instances details
Data Date Source # 
Instance details

Defined in Httpstan.Core

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 :: forall r r'. (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 #

Enum Date Source # 
Instance details

Defined in Httpstan.Core

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] #

Ix Date Source # 
Instance details

Defined in Httpstan.Core

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 #

Show Date Source # 
Instance details

Defined in Httpstan.Core

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

NFData Date Source # 
Instance details

Defined in Httpstan.Core

Methods

rnf :: Date -> () #

Eq Date Source # 
Instance details

Defined in Httpstan.Core

Methods

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

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

Ord Date Source # 
Instance details

Defined in Httpstan.Core

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 #

FromHttpApiData Date Source # 
Instance details

Defined in Httpstan.Core

ToHttpApiData Date Source # 
Instance details

Defined in Httpstan.Core

FromJSON Date Source # 
Instance details

Defined in Httpstan.Core

ToJSON Date Source # 
Instance details

Defined in Httpstan.Core

MimeRender MimeMultipartFormData Date Source # 
Instance details

Defined in Httpstan.Core

_readDate :: MonadFail m => String -> m Date 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

Instances details
Data ByteArray Source # 
Instance details

Defined in Httpstan.Core

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 :: forall r r'. (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 #

Show ByteArray Source # 
Instance details

Defined in Httpstan.Core

NFData ByteArray Source # 
Instance details

Defined in Httpstan.Core

Methods

rnf :: ByteArray -> () #

Eq ByteArray Source # 
Instance details

Defined in Httpstan.Core

Ord ByteArray Source # 
Instance details

Defined in Httpstan.Core

FromHttpApiData ByteArray Source # 
Instance details

Defined in Httpstan.Core

ToHttpApiData ByteArray Source # 
Instance details

Defined in Httpstan.Core

FromJSON ByteArray Source # 
Instance details

Defined in Httpstan.Core

ToJSON ByteArray Source # 
Instance details

Defined in Httpstan.Core

MimeRender MimeMultipartFormData ByteArray Source # 
Instance details

Defined in Httpstan.Core

_readByteArray :: MonadFail 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

Instances details
Data Binary Source # 
Instance details

Defined in Httpstan.Core

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 :: forall r r'. (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 #

Show Binary Source # 
Instance details

Defined in Httpstan.Core

NFData Binary Source # 
Instance details

Defined in Httpstan.Core

Methods

rnf :: Binary -> () #

Eq Binary Source # 
Instance details

Defined in Httpstan.Core

Methods

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

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

Ord Binary Source # 
Instance details

Defined in Httpstan.Core

FromHttpApiData Binary Source # 
Instance details

Defined in Httpstan.Core

ToHttpApiData Binary Source # 
Instance details

Defined in Httpstan.Core

FromJSON Binary Source # 
Instance details

Defined in Httpstan.Core

ToJSON Binary Source # 
Instance details

Defined in Httpstan.Core

MimeRender MimeMultipartFormData Binary Source # 
Instance details

Defined in Httpstan.Core

Lens Type Aliases

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

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