{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#if MIN_VERSION_base(4,9,0)
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
#endif
module Servant.Reflex
( client
, clientWithOpts
, clientWithOptsAndResultHandler
, clientWithRoute
, clientWithRouteAndResultHandler
, BuildHeaderKeysTo(..)
, toHeaders
, HasClient
, Client
, module Servant.Common.Req
, module Servant.Common.BaseUrl
) where
import Control.Applicative
import Data.Monoid ((<>))
import qualified Data.Set as Set
import qualified Data.Text.Encoding as E
import Data.CaseInsensitive (mk)
import Data.Functor.Identity
import Data.Proxy (Proxy (..))
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Exts (Constraint)
import GHC.TypeLits (KnownSymbol, symbolVal)
import Servant.API ((:<|>)(..),(:>), BasicAuth,
BasicAuthData, BuildHeadersTo(..),
Capture, contentType, Header,
Headers(..), HttpVersion, IsSecure,
MimeRender(..), MimeUnrender,
NoContent, QueryFlag, QueryParam,
QueryParams, Raw, ReflectMethod(..),
RemoteHost, ReqBody,
ToHttpApiData(..), Vault, Verb)
import qualified Servant.Auth as Auth
import Reflex.Dom.Core (Dynamic, Event, Reflex,
XhrRequest(..),
XhrResponseHeaders(..),
XhrResponse(..), attachPromptlyDynWith, constDyn, ffor, fmapMaybe,
leftmost, performRequestsAsync,
)
import Servant.Common.BaseUrl (BaseUrl(..), Scheme(..), baseUrlWidget,
showBaseUrl,
SupportsServantReflex)
import Servant.Common.Req (ClientOptions(..),
defaultClientOptions,
Req, ReqResult(..), QParam(..),
QueryPart(..), addHeader, authData,
defReq, evalResponse, prependToPathParts,
performRequestsCT,
performRequestsNoBody,
performSomeRequestsAsync,
qParamToQueryPart, reqBody,
reqSuccess, reqFailure,
reqMethod, respHeaders,
response,
reqTag,
qParams, withCredentials)
client
:: (HasClient t m layout tag)
=> Proxy layout
-> Proxy m
-> Proxy tag
-> Dynamic t BaseUrl
-> Client t m layout tag
client p q t baseurl = clientWithRoute p q t defReq baseurl defaultClientOptions
clientWithOpts
:: (HasClient t m layout tag)
=> Proxy layout
-> Proxy m
-> Proxy tag
-> Dynamic t BaseUrl
-> ClientOptions
-> Client t m layout tag
clientWithOpts p q t baseurl = clientWithRoute p q t defReq baseurl
clientWithOptsAndResultHandler
:: (HasClient t m layout tag)
=> Proxy layout
-> Proxy m
-> Proxy tag
-> Dynamic t BaseUrl
-> ClientOptions
-> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a)))
-> Client t m layout tag
clientWithOptsAndResultHandler p q t = clientWithRouteAndResultHandler p q t defReq
class Monad m => HasClient t m layout (tag :: *) where
type Client t m layout tag :: *
clientWithRoute
:: Proxy layout
-> Proxy m
-> Proxy tag
-> Req t
-> Dynamic t BaseUrl
-> ClientOptions
-> Client t m layout tag
clientWithRoute l m t r b o = clientWithRouteAndResultHandler l m t r b o return
clientWithRouteAndResultHandler
:: Proxy layout
-> Proxy m
-> Proxy tag
-> Req t
-> Dynamic t BaseUrl
-> ClientOptions
-> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a)))
-> Client t m layout tag
instance (HasClient t m a tag, HasClient t m b tag) => HasClient t m (a :<|> b) tag where
type Client t m (a :<|> b) tag = Client t m a tag :<|> Client t m b tag
clientWithRouteAndResultHandler Proxy q pTag req baseurl opts wrap =
clientWithRouteAndResultHandler (Proxy :: Proxy a) q pTag req baseurl opts wrap :<|>
clientWithRouteAndResultHandler (Proxy :: Proxy b) q pTag req baseurl opts wrap
instance (SupportsServantReflex t m, ToHttpApiData a, HasClient t m sublayout tag)
=> HasClient t m (Capture capture a :> sublayout) tag where
type Client t m (Capture capture a :> sublayout) tag =
Dynamic t (Either Text a) -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap val =
clientWithRouteAndResultHandler
(Proxy :: Proxy sublayout) q t (prependToPathParts p req) baseurl opts wrap
where p = (fmap . fmap) (toUrlPiece) val
instance {-# OVERLAPPABLE #-}
(MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts), SupportsServantReflex t m
) => HasClient t m (Verb method status cts' a) tag where
type Client t m (Verb method status cts' a) tag =
Event t tag -> m (Event t (ReqResult tag a))
clientWithRouteAndResultHandler Proxy _ _ req baseurl opts wrap trigs =
wrap =<< fmap runIdentity <$> performRequestsCT (Proxy :: Proxy ct) method (constDyn $ Identity $ req') baseurl opts trigs
where method = E.decodeUtf8 $ reflectMethod (Proxy :: Proxy method)
req' = req { reqMethod = method }
instance {-# OVERLAPPING #-}
(ReflectMethod method, SupportsServantReflex t m) =>
HasClient t m (Verb method status cts NoContent) tag where
type Client t m (Verb method status cts NoContent) tag =
Event t tag -> m (Event t (ReqResult tag NoContent))
clientWithRouteAndResultHandler Proxy _ _ req baseurl opts wrap trigs =
wrap =<< fmap runIdentity <$> performRequestsNoBody method (constDyn $ Identity req) baseurl opts trigs
where method = E.decodeUtf8 $ reflectMethod (Proxy :: Proxy method)
toHeaders :: BuildHeadersTo ls => ReqResult tag a -> ReqResult tag (Headers ls a)
toHeaders r =
let toBS = E.encodeUtf8
hdrs = maybe []
(\xhr -> fmap (\(h,v) -> (mk (toBS h), toBS v))
(Map.toList $ _xhrResponse_headers xhr))
(response r)
in ffor r $ \a -> Headers {getResponse = a ,getHeadersHList = buildHeadersTo hdrs}
class BuildHeaderKeysTo hs where
buildHeaderKeysTo :: Proxy hs -> [T.Text]
instance {-# OVERLAPPABLE #-} BuildHeaderKeysTo '[]
where buildHeaderKeysTo _ = []
instance {-# OVERLAPPABLE #-} (BuildHeaderKeysTo xs, KnownSymbol h)
=> BuildHeaderKeysTo ((Header h v) ': xs) where
buildHeaderKeysTo _ = T.pack (symbolVal (Proxy :: Proxy h)) : buildHeaderKeysTo (Proxy :: Proxy xs)
instance {-# OVERLAPPABLE #-}
( MimeUnrender ct a, BuildHeadersTo ls, BuildHeaderKeysTo ls,
ReflectMethod method, cts' ~ (ct ': cts),
SupportsServantReflex t m
) => HasClient t m (Verb method status cts' (Headers ls a)) tag where
type Client t m (Verb method status cts' (Headers ls a)) tag =
Event t tag -> m (Event t (ReqResult tag (Headers ls a)))
clientWithRouteAndResultHandler Proxy _ _ req baseurl opts wrap trigs = do
let method = E.decodeUtf8 $ reflectMethod (Proxy :: Proxy method)
resp <- fmap runIdentity <$> performRequestsCT (Proxy :: Proxy ct) method (constDyn $ Identity req') baseurl opts trigs
wrap $ toHeaders <$> resp
where req' = req { respHeaders =
OnlyHeaders (Set.fromList (buildHeaderKeysTo (Proxy :: Proxy ls)))
}
instance {-# OVERLAPPABLE #-}
( BuildHeadersTo ls, BuildHeaderKeysTo ls, ReflectMethod method,
SupportsServantReflex t m
) => HasClient t m (Verb method status cts (Headers ls NoContent)) tag where
type Client t m (Verb method status cts (Headers ls NoContent)) tag
= Event t tag -> m (Event t (ReqResult tag (Headers ls NoContent)))
clientWithRouteAndResultHandler Proxy _ _ req baseurl opts wrap trigs = do
let method = E.decodeUtf8 $ reflectMethod (Proxy :: Proxy method)
resp <- fmap runIdentity <$> performRequestsNoBody method (constDyn $ Identity req') baseurl opts trigs
wrap $ toHeaders <$> resp
where req' = req {respHeaders =
OnlyHeaders (Set.fromList (buildHeaderKeysTo (Proxy :: Proxy ls)))
}
instance (KnownSymbol sym, ToHttpApiData a,
HasClient t m sublayout tag, SupportsServantReflex t m)
=> HasClient t m (Header sym a :> sublayout) tag where
type Client t m (Header sym a :> sublayout) tag =
Dynamic t (Either Text a) -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap eVal =
clientWithRouteAndResultHandler
(Proxy :: Proxy sublayout) q t
(Servant.Common.Req.addHeader hname eVal req)
baseurl opts wrap
where hname = T.pack $ symbolVal (Proxy :: Proxy sym)
instance HasClient t m sublayout tag
=> HasClient t m (HttpVersion :> sublayout) tag where
type Client t m (HttpVersion :> sublayout) tag =
Client t m sublayout tag
clientWithRouteAndResultHandler Proxy =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout)
instance (KnownSymbol sym, ToHttpApiData a, HasClient t m sublayout tag, Reflex t)
=> HasClient t m (QueryParam sym a :> sublayout) tag where
type Client t m (QueryParam sym a :> sublayout) tag =
Dynamic t (QParam a) -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap mparam =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout) q t
(req {qParams = paramPair : qParams req}) baseurl opts wrap
where pname = symbolVal (Proxy :: Proxy sym)
p prm = QueryPartParam $ fmap qParamToQueryPart prm
paramPair = (T.pack pname, p mparam)
instance (KnownSymbol sym, ToHttpApiData a, HasClient t m sublayout tag, Reflex t)
=> HasClient t m (QueryParams sym a :> sublayout) tag where
type Client t m (QueryParams sym a :> sublayout) tag =
Dynamic t [a] -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap paramlist =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout) q t req' baseurl opts wrap
where req' = req { qParams = (T.pack pname, params') : qParams req }
pname = symbolVal (Proxy :: Proxy sym)
params' = QueryPartParams $ (fmap . fmap) toQueryParam
paramlist
instance (KnownSymbol sym, HasClient t m sublayout tag, Reflex t)
=> HasClient t m (QueryFlag sym :> sublayout) tag where
type Client t m (QueryFlag sym :> sublayout) tag =
Dynamic t Bool -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap flag =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout) q t req' baseurl opts wrap
where req' = req { qParams = thisPair : qParams req }
thisPair = (T.pack pName, QueryPartFlag flag) :: (Text, QueryPart t)
pName = symbolVal (Proxy :: Proxy sym)
instance SupportsServantReflex t m => HasClient t m Raw tag where
type Client t m Raw tag = Dynamic t (Either Text (XhrRequest ()))
-> Event t tag
-> m (Event t (ReqResult tag ()))
clientWithRouteAndResultHandler _ _ _ _ baseurl _ wrap xhrs triggers = do
let xhrs' = liftA2 (\x path -> case x of
Left e -> Left e
Right jx -> Right $ jx { _xhrRequest_url = path <> _xhrRequest_url jx }
) xhrs (showBaseUrl <$> baseurl)
xhrs'' = attachPromptlyDynWith (flip (,)) xhrs' triggers :: Event t (tag, Either Text (XhrRequest ()))
badReq = fmapMaybe (\(t,x) -> either (Just . (t,)) (const Nothing) x) xhrs'' :: Event t (tag, Text)
okReq = fmapMaybe (\(t,x) -> either (const Nothing) (Just . (t,)) x) xhrs'' :: Event t (tag, XhrRequest ())
resps <- performRequestsAsync okReq
wrap $ leftmost [ uncurry RequestFailure <$> badReq
, evalResponse (const $ Right ()) <$> resps
]
instance (MimeRender ct a, HasClient t m sublayout tag, Reflex t)
=> HasClient t m (ReqBody (ct ': cts) a :> sublayout) tag where
type Client t m (ReqBody (ct ': cts) a :> sublayout) tag =
Dynamic t (Either Text a) -> Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap body =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout) q t req' baseurl opts wrap
where req' = req { reqBody = bodyBytesCT }
ctProxy = Proxy :: Proxy ct
ctString = T.pack $ show $ contentType ctProxy
bodyBytesCT = Just $ (fmap . fmap)
(\b -> (mimeRender ctProxy b, ctString))
body
instance (KnownSymbol path, HasClient t m sublayout tag, Reflex t) => HasClient t m (path :> sublayout) tag where
type Client t m (path :> sublayout) tag = Client t m sublayout tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap =
clientWithRouteAndResultHandler (Proxy :: Proxy sublayout) q t
(prependToPathParts (pure (Right $ T.pack p)) req) baseurl opts wrap
where p = symbolVal (Proxy :: Proxy path)
instance HasClient t m api tag => HasClient t m (Vault :> api) tag where
type Client t m (Vault :> api) tag = Client t m api tag
clientWithRouteAndResultHandler Proxy =
clientWithRouteAndResultHandler (Proxy :: Proxy api)
instance HasClient t m api tag => HasClient t m (RemoteHost :> api) tag where
type Client t m (RemoteHost :> api) tag = Client t m api tag
clientWithRouteAndResultHandler Proxy =
clientWithRouteAndResultHandler (Proxy :: Proxy api)
instance HasClient t m api tag => HasClient t m (IsSecure :> api) tag where
type Client t m (IsSecure :> api) tag = Client t m api tag
clientWithRouteAndResultHandler Proxy =
clientWithRouteAndResultHandler (Proxy :: Proxy api)
instance (HasClient t m api tag, Reflex t)
=> HasClient t m (BasicAuth realm usr :> api) tag where
type Client t m (BasicAuth realm usr :> api) tag = Dynamic t (Maybe BasicAuthData)
-> Client t m api tag
clientWithRouteAndResultHandler Proxy q t req baseurl opts wrap authdata =
clientWithRouteAndResultHandler (Proxy :: Proxy api) q t req' baseurl opts wrap
where
req' = req { authData = Just authdata }
instance (HasCookieAuth auths, HasClient t m api tag) => HasClient t m (Auth.Auth auths a :> api) tag where
type Client t m (Auth.Auth auths a :> api) tag = Client t m api tag
clientWithRouteAndResultHandler Proxy = clientWithRouteAndResultHandler (Proxy :: Proxy api)
type family HasCookieAuth xs :: Constraint where
HasCookieAuth (Auth.Cookie ': xs) = ()
HasCookieAuth (x ': xs) = HasCookieAuth xs
HasCookieAuth '[] = CookieAuthNotEnabled
class CookieAuthNotEnabled