6
6
{-# LANGUAGE MultiParamTypeClasses #-}
7
7
{-# LANGUAGE OverloadedStrings #-}
8
8
{-# LANGUAGE PolyKinds #-}
9
+ {-# LANGUAGE RankNTypes #-}
9
10
{-# LANGUAGE ScopedTypeVariables #-}
10
11
{-# LANGUAGE TypeFamilies #-}
11
12
{-# LANGUAGE TypeOperators #-}
@@ -97,6 +98,12 @@ clientIn p pm = clientWithRoute pm p defaultRequest
97
98
class RunClient m => HasClient m api where
98
99
type Client (m :: * -> * ) (api :: * ) :: *
99
100
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
101
+ hoistClientMonad
102
+ :: Proxy m
103
+ -> Proxy api
104
+ -> (forall x . mon x -> mon' x )
105
+ -> Client mon api
106
+ -> Client mon' api
100
107
101
108
102
109
-- | A client querying function for @a ':<|>' b@ will actually hand you
@@ -118,6 +125,10 @@ instance (HasClient m a, HasClient m b) => HasClient m (a :<|> b) where
118
125
clientWithRoute pm (Proxy :: Proxy a ) req :<|>
119
126
clientWithRoute pm (Proxy :: Proxy b ) req
120
127
128
+ hoistClientMonad pm _ f (ca :<|> cb) =
129
+ hoistClientMonad pm (Proxy :: Proxy a ) f ca :<|>
130
+ hoistClientMonad pm (Proxy :: Proxy b ) f cb
131
+
121
132
-- | Singleton type representing a client for an empty API.
122
133
data EmptyClient = EmptyClient deriving (Eq , Show , Bounded , Enum )
123
134
@@ -134,6 +145,7 @@ data EmptyClient = EmptyClient deriving (Eq, Show, Bounded, Enum)
134
145
instance RunClient m => HasClient m EmptyAPI where
135
146
type Client m EmptyAPI = EmptyClient
136
147
clientWithRoute _pm Proxy _ = EmptyClient
148
+ hoistClientMonad _ _ _ EmptyClient = EmptyClient
137
149
138
150
-- | If you use a 'Capture' in one of your endpoints in your API,
139
151
-- the corresponding querying function will automatically take
@@ -166,6 +178,9 @@ instance (KnownSymbol capture, ToHttpApiData a, HasClient m api)
166
178
167
179
where p = (toUrlPiece val)
168
180
181
+ hoistClientMonad pm _ f cl = \ a ->
182
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl a)
183
+
169
184
-- | If you use a 'CaptureAll' in one of your endpoints in your API,
170
185
-- the corresponding querying function will automatically take an
171
186
-- additional argument of a list of the type specified by your
@@ -198,6 +213,9 @@ instance (KnownSymbol capture, ToHttpApiData a, HasClient m sublayout)
198
213
199
214
where ps = map (toUrlPiece) vals
200
215
216
+ hoistClientMonad pm _ f cl = \ as ->
217
+ hoistClientMonad pm (Proxy :: Proxy sublayout ) f (cl as)
218
+
201
219
instance OVERLAPPABLE_
202
220
-- Note [Non-Empty Content Types]
203
221
( RunClient m , MimeUnrender ct a , ReflectMethod method , cts' ~ (ct ': cts )
@@ -213,6 +231,8 @@ instance OVERLAPPABLE_
213
231
accept = contentTypes (Proxy :: Proxy ct )
214
232
method = reflectMethod (Proxy :: Proxy method )
215
233
234
+ hoistClientMonad _ _ f ma = f ma
235
+
216
236
instance OVERLAPPING_
217
237
( RunClient m , ReflectMethod method
218
238
) => HasClient m (Verb method status cts NoContent ) where
@@ -223,6 +243,8 @@ instance OVERLAPPING_
223
243
return NoContent
224
244
where method = reflectMethod (Proxy :: Proxy method )
225
245
246
+ hoistClientMonad _ _ f ma = f ma
247
+
226
248
instance OVERLAPPING_
227
249
-- Note [Non-Empty Content Types]
228
250
( RunClient m , MimeUnrender ct a , BuildHeadersTo ls
@@ -244,6 +266,8 @@ instance OVERLAPPING_
244
266
where method = reflectMethod (Proxy :: Proxy method )
245
267
accept = contentTypes (Proxy :: Proxy ct )
246
268
269
+ hoistClientMonad _ _ f ma = f ma
270
+
247
271
instance OVERLAPPING_
248
272
( RunClient m , BuildHeadersTo ls , ReflectMethod method
249
273
) => HasClient m (Verb method status cts (Headers ls NoContent )) where
@@ -256,6 +280,8 @@ instance OVERLAPPING_
256
280
, getHeadersHList = buildHeadersTo . toList $ responseHeaders response
257
281
}
258
282
283
+ hoistClientMonad _ _ f ma = f ma
284
+
259
285
instance OVERLAPPABLE_
260
286
( RunClient m , MimeUnrender ct a , ReflectMethod method ,
261
287
FramingUnrender framing a , BuildFromStream a (f a )
@@ -304,6 +330,7 @@ instance OVERLAPPABLE_
304
330
processResult (Left err, _) = Just (Left err)
305
331
k go
306
332
333
+ hoistClientMonad _ _ f ma = f ma
307
334
308
335
-- | If you use a 'Header' in one of your endpoints in your API,
309
336
-- the corresponding querying function will automatically take
@@ -345,6 +372,9 @@ instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequire
345
372
add :: a -> Request
346
373
add value = addHeader hname value req
347
374
375
+ hoistClientMonad pm _ f cl = \ arg ->
376
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl arg)
377
+
348
378
-- | Using a 'HttpVersion' combinator in your API doesn't affect the client
349
379
-- functions.
350
380
instance HasClient m api
@@ -356,18 +386,24 @@ instance HasClient m api
356
386
clientWithRoute pm Proxy =
357
387
clientWithRoute pm (Proxy :: Proxy api )
358
388
389
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
390
+
359
391
-- | Ignore @'Summary'@ in client functions.
360
392
instance HasClient m api => HasClient m (Summary desc :> api ) where
361
393
type Client m (Summary desc :> api ) = Client m api
362
394
363
395
clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api )
364
396
397
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
398
+
365
399
-- | Ignore @'Description'@ in client functions.
366
400
instance HasClient m api => HasClient m (Description desc :> api ) where
367
401
type Client m (Description desc :> api ) = Client m api
368
402
369
403
clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api )
370
404
405
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
406
+
371
407
-- | If you use a 'QueryParam' in one of your endpoints in your API,
372
408
-- the corresponding querying function will automatically take
373
409
-- an additional argument of the type specified by your 'QueryParam',
@@ -410,6 +446,9 @@ instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequire
410
446
pname :: Text
411
447
pname = pack $ symbolVal (Proxy :: Proxy sym )
412
448
449
+ hoistClientMonad pm _ f cl = \ arg ->
450
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl arg)
451
+
413
452
-- | If you use a 'QueryParams' in one of your endpoints in your API,
414
453
-- the corresponding querying function will automatically take
415
454
-- an additional argument, a list of values of the type specified
@@ -453,6 +492,9 @@ instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
453
492
where pname = pack $ symbolVal (Proxy :: Proxy sym )
454
493
paramlist' = map (Just . toQueryParam) paramlist
455
494
495
+ hoistClientMonad pm _ f cl = \ as ->
496
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl as)
497
+
456
498
-- | If you use a 'QueryFlag' in one of your endpoints in your API,
457
499
-- the corresponding querying function will automatically take
458
500
-- an additional 'Bool' argument.
@@ -489,6 +531,8 @@ instance (KnownSymbol sym, HasClient m api)
489
531
490
532
where paramname = pack $ symbolVal (Proxy :: Proxy sym )
491
533
534
+ hoistClientMonad pm _ f cl = \ b ->
535
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl b)
492
536
493
537
-- | Pick a 'Method' and specify where the server you want to query is. You get
494
538
-- back the full `Response`.
@@ -500,6 +544,8 @@ instance RunClient m => HasClient m Raw where
500
544
clientWithRoute _pm Proxy req httpMethod = do
501
545
runRequest req { requestMethod = httpMethod }
502
546
547
+ hoistClientMonad _ _ f cl = \ meth -> f (cl meth)
548
+
503
549
-- | If you use a 'ReqBody' in one of your endpoints in your API,
504
550
-- the corresponding querying function will automatically take
505
551
-- an additional argument of the type specified by your 'ReqBody'.
@@ -533,6 +579,9 @@ instance (MimeRender ct a, HasClient m api)
533
579
req
534
580
)
535
581
582
+ hoistClientMonad pm _ f cl = \ a ->
583
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl a)
584
+
536
585
-- | Make the querying function append @path@ to the request path.
537
586
instance (KnownSymbol path , HasClient m api ) => HasClient m (path :> api ) where
538
587
type Client m (path :> api ) = Client m api
@@ -543,30 +592,40 @@ instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where
543
592
544
593
where p = pack $ symbolVal (Proxy :: Proxy path )
545
594
595
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
596
+
546
597
instance HasClient m api => HasClient m (Vault :> api ) where
547
598
type Client m (Vault :> api ) = Client m api
548
599
549
600
clientWithRoute pm Proxy req =
550
601
clientWithRoute pm (Proxy :: Proxy api ) req
551
602
603
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
604
+
552
605
instance HasClient m api => HasClient m (RemoteHost :> api ) where
553
606
type Client m (RemoteHost :> api ) = Client m api
554
607
555
608
clientWithRoute pm Proxy req =
556
609
clientWithRoute pm (Proxy :: Proxy api ) req
557
610
611
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
612
+
558
613
instance HasClient m api => HasClient m (IsSecure :> api ) where
559
614
type Client m (IsSecure :> api ) = Client m api
560
615
561
616
clientWithRoute pm Proxy req =
562
617
clientWithRoute pm (Proxy :: Proxy api ) req
563
618
619
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api ) f cl
620
+
564
621
instance HasClient m subapi =>
565
622
HasClient m (WithNamedContext name context subapi ) where
566
623
567
624
type Client m (WithNamedContext name context subapi ) = Client m subapi
568
625
clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy subapi )
569
626
627
+ hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy subapi ) f cl
628
+
570
629
instance ( HasClient m api
571
630
) => HasClient m (AuthProtect tag :> api ) where
572
631
type Client m (AuthProtect tag :> api )
@@ -575,6 +634,9 @@ instance ( HasClient m api
575
634
clientWithRoute pm Proxy req (AuthenticatedRequest (val,func)) =
576
635
clientWithRoute pm (Proxy :: Proxy api ) (func val req)
577
636
637
+ hoistClientMonad pm _ f cl = \ authreq ->
638
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl authreq)
639
+
578
640
-- * Basic Authentication
579
641
580
642
instance HasClient m api => HasClient m (BasicAuth realm usr :> api ) where
@@ -583,6 +645,9 @@ instance HasClient m api => HasClient m (BasicAuth realm usr :> api) where
583
645
clientWithRoute pm Proxy req val =
584
646
clientWithRoute pm (Proxy :: Proxy api ) (basicAuthReq val req)
585
647
648
+ hoistClientMonad pm _ f cl = \ bauth ->
649
+ hoistClientMonad pm (Proxy :: Proxy api ) f (cl bauth)
650
+
586
651
587
652
{- Note [Non-Empty Content Types]
588
653
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
0 commit comments