Skip to content

Commit 002fa21

Browse files
author
Gaël Deest
authored
Merge pull request #1531 from gdeest/servant-auth-named-routes
servant-auth-server: Support NamedRoutes
2 parents cdd7c34 + bd9151b commit 002fa21

File tree

3 files changed

+29
-1
lines changed

3 files changed

+29
-1
lines changed

servant-auth/servant-auth-server/src/Servant/Auth/Server/Internal/AddSetCookie.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,8 @@ import Data.Tagged (Tagged (..))
1111
import qualified Network.HTTP.Types as HTTP
1212
import Network.Wai (mapResponseHeaders)
1313
import Servant
14+
import Servant.API.Generic
15+
import Servant.Server.Generic
1416
import Web.Cookie
1517

1618
-- What are we doing here? Well, the idea is to add headers to the response,
@@ -34,6 +36,7 @@ type family AddSetCookieApiVerb a where
3436
type family AddSetCookieApi a :: *
3537
type instance AddSetCookieApi (a :> b) = a :> AddSetCookieApi b
3638
type instance AddSetCookieApi (a :<|> b) = AddSetCookieApi a :<|> AddSetCookieApi b
39+
type instance AddSetCookieApi (NamedRoutes api) = AddSetCookieApi (ToServantApi api)
3740
type instance AddSetCookieApi (Verb method stat ctyps a)
3841
= Verb method stat ctyps (AddSetCookieApiVerb a)
3942
type instance AddSetCookieApi Raw = Raw
@@ -72,6 +75,15 @@ instance {-# OVERLAPS #-}
7275
=> AddSetCookies ('S n) (a :<|> b) (a' :<|> b') where
7376
addSetCookies cookies (a :<|> b) = addSetCookies cookies a :<|> addSetCookies cookies b
7477

78+
instance {-# OVERLAPS #-}
79+
( AddSetCookies ('S n) (ServerT (ToServantApi api) m) cookiedApi
80+
, Generic (api (AsServerT m))
81+
, GServantProduct (Rep (api (AsServerT m)))
82+
, ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m
83+
)
84+
=> AddSetCookies ('S n) (api (AsServerT m)) cookiedApi where
85+
addSetCookies cookies = addSetCookies cookies . toServant
86+
7587
-- | for @servant <0.11@
7688
instance
7789
AddSetCookies ('S n) Application Application where

servant-auth/servant-auth-server/src/Servant/Auth/Server/Internal/ThrowAll.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,10 @@ module Servant.Auth.Server.Internal.ThrowAll where
88

99
import Control.Monad.Error.Class
1010
import Data.Tagged (Tagged (..))
11-
import Servant ((:<|>) (..), ServerError(..))
11+
import Servant ((:<|>) (..), ServerError(..), NamedRoutes(..))
12+
import Servant.API.Generic
13+
import Servant.Server.Generic
14+
import Servant.Server
1215
import Network.HTTP.Types
1316
import Network.Wai
1417

@@ -26,6 +29,12 @@ class ThrowAll a where
2629
instance (ThrowAll a, ThrowAll b) => ThrowAll (a :<|> b) where
2730
throwAll e = throwAll e :<|> throwAll e
2831

32+
instance
33+
( ThrowAll (ToServant api (AsServerT m)) , GenericServant api (AsServerT m)) =>
34+
ThrowAll (api (AsServerT m)) where
35+
36+
throwAll = fromServant . throwAll
37+
2938
-- Really this shouldn't be necessary - ((->) a) should be an instance of
3039
-- MonadError, no?
3140
instance {-# OVERLAPPING #-} ThrowAll b => ThrowAll (a -> b) where

servant-auth/servant-auth-server/test/Servant/Auth/ServerSpec.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ import Network.Wreq (Options, auth, basicAuth,
5050
import Network.Wreq.Types (Postable(..))
5151
import Servant hiding (BasicAuth,
5252
IsSecure (..), header)
53+
import Servant.API.Generic ((:-))
5354
import Servant.Auth.Server
5455
import Servant.Auth.Server.Internal.Cookie (expireTime)
5556
import Servant.Auth.Server.SetCookieOrphan ()
@@ -405,6 +406,7 @@ type API auths
405406
= Auth auths User :>
406407
( Get '[JSON] Int
407408
:<|> ReqBody '[JSON] Int :> Post '[JSON] Int
409+
:<|> NamedRoutes DummyRoutes
408410
:<|> "header" :> Get '[JSON] (Headers '[Header "Blah" Int] Int)
409411
#if MIN_VERSION_servant_server(0,15,0)
410412
:<|> "stream" :> StreamGet NoFraming OctetStream (SourceIO BS.ByteString)
@@ -416,6 +418,10 @@ type API auths
416418
:<|> "logout" :> Get '[JSON] (Headers '[ Header "Set-Cookie" SetCookie
417419
, Header "Set-Cookie" SetCookie ] NoContent)
418420

421+
data DummyRoutes mode = DummyRoutes
422+
{ dummyInt :: mode :- "dummy" :> Get '[JSON] Int
423+
} deriving Generic
424+
419425
jwtOnlyApi :: Proxy (API '[Servant.Auth.Server.JWT])
420426
jwtOnlyApi = Proxy
421427

@@ -476,6 +482,7 @@ server ccfg =
476482
(\authResult -> case authResult of
477483
Authenticated usr -> getInt usr
478484
:<|> postInt usr
485+
:<|> DummyRoutes { dummyInt = getInt usr }
479486
:<|> getHeaderInt
480487
#if MIN_VERSION_servant_server(0,15,0)
481488
:<|> return (S.source ["bytestring"])

0 commit comments

Comments
 (0)