react-flux-servant-0.1.1: Allow react-flux stores to send requests to a servant server

Safe HaskellNone
LanguageHaskell2010

React.Flux.Addons.Servant

Description

Make calls to an API defined using Servant.API from your React.Flux stores. You must call initAjax from your main function for this to work. For now, this module only works with JSON.

The general pattern I currently use is to create a store action to trigger the request and another store action to process the response. Only the store action to trigger the request is exported. This does lead to a bit of tedious boilerplate since you need actions for each request, so I am still searching for a better API that perhaps takes advantage of the servant API type-level computation to reduce the boilerplate. For now, until I figure out a better way, this direct approach does work. If you have any ideas for a good API, please open an issue on bitbucket (even if you don't have full code)!

As an example, say that the API consists of two methods:

type GetUser = "user" :> Capture "user_id" UserId :> Get '[JSON] User
type SetUser = "user" :> Capture "user_id" UserId :> ReqBody '[JSON] User :> Post '[JSON] ()
type MyAPI = GetUser :<|> SetUser

I would create a store as follows:

data RequestStatus = NoPendingRequest | PendingRequest | PreviousRequestHadError String

data UserStore = UserStore
  { users :: Map.HashMap UserId User
  , reqStatus :: RequestStatus
  }

data UserStoreAction = RequestUser UserId
                     | RequestUserResponse UserId (Either (Int,String) User)
                     | UpdateUser UserId User
                     | UpdateUserResponse UserId (Either (Int, String) ())
  deriving (Show, Generic, NFData)

cfg :: ApiRequestConfig MyAPI
cfg = ApiRequestConfig "https://www.example.com" NoTimeout

instance StoreData UserStore where
  type StoreAction UserStore = UserStoreAction

  transform (RequestUser uid) us = do
    request cfg (Proxy :: Proxy GetUser) uid $
      \r -> return [SomeStoreAction userStore $ RequestUserResponse uid r]
    return $ us {reqStatus = PendingRequest}

  transform (RequestUserResponse _ (Left (_errCode, err))) us =
    return $ us {reqStatus = PreviousRequestHadError err}

  transform (RequestUserResponse uid (Right u)) us =
    return $ us { reqStatus = NoPendingRequest
                , users = Map.insert uid u (users us)
                }

  transform (UpdateUser uid u) us = do
    request cfg (Proxy :: Proxy SetUser) uid u $
      \r -> return [SomeStoreAction userStore $ UpdateUserResponse uid r]
    return $ us { reqStatus = PendingRequest
                , users = Map.insert uid u (users us)
                }

  transform (UpdateUserResponse uid (Left (_errCode, err))) us =
    return $ us { reqStatus = PreviousRequestHadError err
                , users = Map.delete uid (users us)
                }

  transform (UpdateUserResponse _ (Right ())) us =
    return $ us { reqStatus = NoPendingRequest}

userStore :: ReactStore UserStore
userStore = mkStore $ UserStore Map.empty NoPendingRequest

Synopsis

Documentation

type HandleResponse a = Either (Int, String) a -> IO [SomeStoreAction] Source #

When a response from the server arrives, it is either an error or a valid response. An error is turned into a Left value consisting of the HTTP response code and the response body. If a 200 HTTP response is received, it is parsed to a value according to the servant API definition and passed as a Right value. You must then turn the response into a store action. I suggest that you just pass the value along directly to a store action without any computation; the computation can happen inside the store.

data RequestTimeout :: * #

An optional timeout to use for XMLHttpRequest.timeout. When a request times out, a status code of 504 is set in respStatus and the response handler executes.

data ApiRequestConfig api Source #

Settings for requests built using this module.

Constructors

ApiRequestConfig 

Fields

  • urlPrefix :: JSString

    A prefix for all requests; it should include the domain and any prefix path that is required. To this prefix a forward slash is appended and then the path built using the Servant API definition.

  • timeout :: RequestTimeout

    The timeout to use for requests. If a timeout occurs, a Left value with code 504 is passed to HandleResponse.

request :: (IsElem endpoint api, HasAjaxRequest endpoint) => ApiRequestConfig api -> Proxy endpoint -> MkRequest endpoint Source #

Make a request to a servant endpoint. You must call initAjax from your main function for this to work.

request takes the ApiRequestConfig, a proxy for the endpoint, parameters for the request (request body, query params, path captures, etc.), and value of type HandleResponse. The result of request is then a value of type IO (). In order to type-check that the proper values for the request body, path captures, etc. are passed, the MkRequest associated type is used. MkRequest expands to a function with one argument for each path piece and an argument for the HandleResponse. For example,

type GetUser = "user" :> Capture "user_id" UserId :> Get '[JSON] User
type SetUser = "user" :> Capture "user_id" UserId :> ReqBody '[JSON] User :> Post '[JSON] ()
type MyAPI = GetUser :<|> SetUser

Then

MkRequest GetUser ~ UserId -> HandleResponse User -> IO ()
MkRequest SetUser ~ UserId -> User -> HandleResponse () -> IO ()

so that

request cfg (Proxy :: Proxy GetUser) :: UserId -> HandleResponse User -> IO ()
request cfg (Proxy :: Proxy SetUser) :: UserId -> User -> HandleResponse () -> IO ()

class HasAjaxRequest endpoint where Source #

A class very similar to Servant.Utils.Links. You shouldn't need to use this class directly: instead use request. Having said that, the MkRequest type defined in this typeclass is important as it determines what values you must pass to request to obtain a proper request.

Minimal complete definition

toRequest

Associated Types

type MkRequest endpoint Source #

Methods

toRequest :: Proxy endpoint -> Request -> MkRequest endpoint Source #

Instances

(KnownSymbol sym, ToHttpApiData a, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k * (QueryParam * sym a) sub) Source # 

Associated Types

type MkRequest ((:>) k * (QueryParam * sym a) sub) (endpoint :: (:>) k * (QueryParam * sym a) sub) :: * Source #

Methods

toRequest :: Proxy ((k :> *) (QueryParam * sym a) sub) endpoint -> Request -> MkRequest ((k :> *) (QueryParam * sym a) sub) endpoint Source #

(KnownSymbol sym, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k * (QueryFlag sym) sub) Source # 

Associated Types

type MkRequest ((:>) k * (QueryFlag sym) sub) (endpoint :: (:>) k * (QueryFlag sym) sub) :: * Source #

Methods

toRequest :: Proxy ((k :> *) (QueryFlag sym) sub) endpoint -> Request -> MkRequest ((k :> *) (QueryFlag sym) sub) endpoint Source #

(KnownSymbol sym, ToHttpApiData a, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k * (Header sym a) sub) Source # 

Associated Types

type MkRequest ((:>) k * (Header sym a) sub) (endpoint :: (:>) k * (Header sym a) sub) :: * Source #

Methods

toRequest :: Proxy ((k :> *) (Header sym a) sub) endpoint -> Request -> MkRequest ((k :> *) (Header sym a) sub) endpoint Source #

(ToHttpApiData v, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k * (Capture * sym v) sub) Source # 

Associated Types

type MkRequest ((:>) k * (Capture * sym v) sub) (endpoint :: (:>) k * (Capture * sym v) sub) :: * Source #

Methods

toRequest :: Proxy ((k :> *) (Capture * sym v) sub) endpoint -> Request -> MkRequest ((k :> *) (Capture * sym v) sub) endpoint Source #

(KnownSymbol sym, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k Symbol sym sub) Source # 

Associated Types

type MkRequest ((:>) k Symbol sym sub) (endpoint :: (:>) k Symbol sym sub) :: * Source #

Methods

toRequest :: Proxy ((k :> Symbol) sym sub) endpoint -> Request -> MkRequest ((k :> Symbol) sym sub) endpoint Source #

(ToJSON a, HasAjaxRequest k sub) => HasAjaxRequest * ((:>) k * (ReqBody * ((:) * JSON ([] *)) a) sub) Source # 

Associated Types

type MkRequest ((:>) k * (ReqBody * ((:) * JSON ([] *)) a) sub) (endpoint :: (:>) k * (ReqBody * ((:) * JSON ([] *)) a) sub) :: * Source #

Methods

toRequest :: Proxy ((k :> *) (ReqBody * ((* ': JSON) [*]) a) sub) endpoint -> Request -> MkRequest ((k :> *) (ReqBody * ((* ': JSON) [*]) a) sub) endpoint Source #

(ReflectMethod k1 m, FromJSON a) => HasAjaxRequest * (Verb * k1 m s ((:) * JSON ([] *)) a) Source # 

Associated Types

type MkRequest (Verb * k1 m s ((:) * JSON ([] *)) a) (endpoint :: Verb * k1 m s ((:) * JSON ([] *)) a) :: * Source #

Methods

toRequest :: Proxy (Verb * k1 m s ((* ': JSON) [*]) a) endpoint -> Request -> MkRequest (Verb * k1 m s ((* ': JSON) [*]) a) endpoint Source #