Skip to content

Commit fe20b5a

Browse files
authored
Merge pull request #920 from phadej/free-client
Add Servant.Client.Free
2 parents 6d1ae0d + 454f533 commit fe20b5a

File tree

6 files changed

+37
-4
lines changed

6 files changed

+37
-4
lines changed

servant-client-core/servant-client-core.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,10 +31,12 @@ source-repository head
3131
library
3232
exposed-modules:
3333
Servant.Client.Core
34+
Servant.Client.Free
3435
Servant.Client.Core.Reexport
3536
Servant.Client.Core.Internal.Auth
3637
Servant.Client.Core.Internal.BaseUrl
3738
Servant.Client.Core.Internal.BasicAuth
39+
Servant.Client.Core.Internal.ClientF
3840
Servant.Client.Core.Internal.Generic
3941
Servant.Client.Core.Internal.HasClient
4042
Servant.Client.Core.Internal.Request
@@ -65,6 +67,7 @@ library
6567
base-compat >= 0.9.3 && < 0.10
6668
, base64-bytestring >= 1.0.0.1 && < 1.1
6769
, exceptions >= 0.8.3 && < 0.9
70+
, free >= 5.0.1 && < 5.1
6871
, generics-sop >= 0.3.1.0 && < 0.4
6972
, http-api-data >= 0.3.7.1 && < 0.4
7073
, http-media >= 0.7.1.1 && < 0.8
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
{-# LANGUAGE DeriveFunctor #-}
2+
module Servant.Client.Core.Internal.ClientF where
3+
4+
import Servant.Client.Core.Internal.Request
5+
6+
data ClientF a
7+
= RunRequest Request (Response -> a)
8+
| StreamingRequest Request (StreamingResponse -> a)
9+
| Throw ServantError
10+
deriving (Functor)

servant-client-core/src/Servant/Client/Core/Internal/RunClient.hs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Prelude ()
1010
import Prelude.Compat
1111

1212
import Control.Monad (unless)
13+
import Control.Monad.Free (Free (..), liftF)
1314
import Data.Foldable (toList)
1415
import Data.Proxy (Proxy)
1516
import qualified Data.Text as T
@@ -18,16 +19,17 @@ import Network.HTTP.Media (MediaType, matches,
1819
import Servant.API (MimeUnrender,
1920
contentTypes,
2021
mimeUnrender)
22+
2123
import Servant.Client.Core.Internal.Request (Request, Response, GenResponse (..),
2224
StreamingResponse (..),
2325
ServantError (..))
26+
import Servant.Client.Core.Internal.ClientF
2427

25-
class (Monad m) => RunClient m where
28+
class Monad m => RunClient m where
2629
-- | How to make a request.
2730
runRequest :: Request -> m Response
2831
streamingRequest :: Request -> m StreamingResponse
2932
throwServantError :: ServantError -> m a
30-
catchServantError :: m a -> (ServantError -> m a) -> m a
3133

3234
checkContentTypeHeader :: RunClient m => Response -> m MediaType
3335
checkContentTypeHeader response =
@@ -48,3 +50,8 @@ decodedAs response contentType = do
4850
Right val -> return val
4951
where
5052
accept = toList $ contentTypes contentType
53+
54+
instance ClientF ~ f => RunClient (Free f) where
55+
runRequest req = liftF (RunRequest req id)
56+
streamingRequest req = liftF (StreamingRequest req id)
57+
throwServantError = liftF . Throw
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
{-# LANGUAGE ScopedTypeVariables, FlexibleContexts, GADTs #-}
2+
module Servant.Client.Free (
3+
client,
4+
ClientF (..),
5+
module Servant.Client.Core.Reexport,
6+
) where
7+
8+
import Data.Proxy (Proxy (..))
9+
import Control.Monad.Free
10+
import Servant.Client.Core
11+
import Servant.Client.Core.Reexport
12+
import Servant.Client.Core.Internal.ClientF
13+
14+
client :: HasClient (Free ClientF) api => Proxy api -> Client (Free ClientF) api
15+
client api = api `clientIn` (Proxy :: Proxy (Free ClientF))

servant-client-ghcjs/src/Servant/Client/Internal/XhrClient.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,6 @@ instance Alt ClientM where
7878
instance RunClient ClientM where
7979
runRequest = performRequest
8080
throwServantError = throwError
81-
catchServantError = catchError
8281

8382
instance ClientLike (ClientM a) (ClientM a) where
8483
mkClient = id

servant-client/src/Servant/Client/Internal/HttpClient.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,6 @@ instance RunClient ClientM where
9696
runRequest = performRequest
9797
streamingRequest = performStreamingRequest
9898
throwServantError = throwError
99-
catchServantError = catchError
10099

101100
instance ClientLike (ClientM a) (ClientM a) where
102101
mkClient = id

0 commit comments

Comments
 (0)