22{-# LANGUAGE DeriveGeneric #-}
33{-# LANGUAGE FlexibleContexts #-}
44{-# LANGUAGE FlexibleInstances #-}
5+ {-# LANGUAGE LambdaCase #-}
56{-# LANGUAGE OverloadedStrings #-}
67{-# LANGUAGE PolyKinds #-}
78{-# LANGUAGE ScopedTypeVariables #-}
@@ -25,6 +26,8 @@ import qualified Data.ByteString as BS
2526import qualified Data.ByteString.Base64 as Base64
2627import Data.Char
2728 (toUpper )
29+ import Data.Map
30+ (fromList , notMember )
2831import Data.Maybe
2932 (fromMaybe )
3033import Data.Proxy
@@ -49,20 +52,21 @@ import Network.Wai.Test
4952import Servant.API
5053 ((:<|>) (.. ), (:>) , AuthProtect , BasicAuth ,
5154 BasicAuthData (BasicAuthData ), Capture , Capture' , CaptureAll ,
52- Delete , EmptyAPI , Fragment , Get , HasStatus (StatusOf ), Header ,
53- Headers , HttpVersion , IsSecure (.. ), JSON , Lenient ,
54- NoContent (.. ), NoContentVerb , NoFraming , OctetStream , Patch ,
55- PlainText , Post , Put , QueryFlag , QueryParam , QueryParams , Raw ,
56- RemoteHost , ReqBody , SourceIO , StdMethod (.. ), Stream , Strict ,
57- UVerb , Union , Verb , WithStatus (.. ), addHeader )
55+ Delete , EmptyAPI , Fragment , Get , GetNoContent ,
56+ HasStatus (StatusOf ), Header , Headers , HttpVersion ,
57+ IsSecure (.. ), JSON , Lenient , NoContent (.. ), NoContentVerb ,
58+ NoFraming , OctetStream , Patch , PlainText , Post , Put ,
59+ QueryFlag , QueryParam , QueryParams , Raw , RemoteHost , ReqBody ,
60+ SourceIO , StdMethod (.. ), Stream , StreamGet , Strict , UVerb ,
61+ Union , Verb , WithRoutingHeader , WithStatus (.. ), addHeader )
5862import Servant.Server
5963 (Context ((:.) , EmptyContext ), Handler , Server , Tagged (.. ),
60- emptyServer , err401 , err403 , err404 , respond , serve ,
64+ emptyServer , err401 , err403 , err404 , err500 , respond , serve ,
6165 serveWithContext )
6266import Servant.Test.ComprehensiveAPI
6367import qualified Servant.Types.SourceT as S
6468import Test.Hspec
65- (Spec , context , describe , it , shouldBe , shouldContain )
69+ (Spec , context , describe , it , shouldBe , shouldContain , shouldSatisfy )
6670import Test.Hspec.Wai
6771 (get , liftIO , matchHeaders , matchStatus , shouldRespondWith ,
6872 with , (<:>) )
@@ -103,6 +107,7 @@ spec = do
103107 miscCombinatorSpec
104108 basicAuthSpec
105109 genAuthSpec
110+ routedPathHeadersSpec
106111
107112------------------------------------------------------------------------------
108113-- * verbSpec {{{
@@ -842,6 +847,102 @@ genAuthSpec = do
842847 it " plays nice with subsequent Raw endpoints" $ do
843848 get " /foo" `shouldRespondWith` 418
844849
850+ -- }}}
851+ ------------------------------------------------------------------------------
852+ -- * Routed path response headers {{{
853+ ------------------------------------------------------------------------------
854+
855+ type RoutedPathApi = WithRoutingHeader :>
856+ ( " content" :> Get '[JSON ] Person
857+ :<|> " noContent" :> GetNoContent
858+ :<|> " header" :> Get '[JSON ] (Headers '[Header " H" Int ] Person )
859+ :<|> " stream" :> StreamGet NoFraming OctetStream (SourceIO BS. ByteString )
860+ :<|> " animal" :> ( Capture " legs" Integer :> Get '[JSON ] Animal
861+ :<|> CaptureAll " legs" Integer :> Get '[JSON ] Animal
862+ :<|> Capture " name" String :> Get '[JSON ] Animal
863+ )
864+ ) :<|> " withoutHeader" :> Get '[JSON ] Person
865+
866+ routedPathApi :: Proxy RoutedPathApi
867+ routedPathApi = Proxy
868+
869+ routedPathServer :: Server RoutedPathApi
870+ routedPathServer =
871+ ( return alice
872+ :<|> return NoContent
873+ :<|> return (addHeader 5 alice)
874+ :<|> return (S. source [" bytestring" ])
875+ :<|> (( \ case
876+ 2 -> return tweety
877+ 4 -> return jerry
878+ _ -> throwError err500
879+ ):<|> ( \ legs -> case sum legs of
880+ 2 -> return tweety
881+ 4 -> return jerry
882+ _ -> throwError err500
883+ ):<|> ( \ case
884+ " tweety" -> return tweety
885+ " jerry" -> return jerry
886+ " bob" -> return beholder
887+ _ -> throwError err404
888+ ))
889+ ) :<|> return alice
890+
891+ routedPathHeadersSpec :: Spec
892+ routedPathHeadersSpec = do
893+ describe " Server routing header" $ do
894+ with (return $ serve routedPathApi routedPathServer) $ do
895+ it " returns the routed path on verbs" $ do
896+ response <- THW. request methodGet " /content" [] " "
897+ liftIO $ simpleHeaders response `shouldContain`
898+ [(" Servant-Routed-Path" , " /content" )]
899+
900+ it " returns the routed path on noContent verbs" $ do
901+ response <- THW. request methodGet " /noContent" [] " "
902+ liftIO $ simpleHeaders response `shouldContain`
903+ [(" Servant-Routed-Path" , " /noContent" )]
904+
905+ it " returns the routed path on streams" $ do
906+ response <- THW. request methodGet " /stream" [] " "
907+ liftIO $ simpleHeaders response `shouldContain`
908+ [(" Servant-Routed-Path" , " /stream" )]
909+
910+ it " plays nice with manually added headers" $ do
911+ response <- THW. request methodGet " /header" [] " "
912+ liftIO $ do
913+ simpleHeaders response `shouldContain` [(" Servant-Routed-Path" , " /header" )]
914+ simpleHeaders response `shouldContain` [(" H" , " 5" )]
915+
916+ it " abstracts captured values" $ do
917+ response <- THW. request methodGet " /animal/4" [] " "
918+ liftIO $ simpleHeaders response `shouldContain`
919+ [(" Servant-Routed-Path" , " /animal/<legs::CaptureSingle>" )]
920+
921+ it " abstracts captured lists" $ do
922+ response <- THW. request methodGet " /animal/1/1/0" [] " "
923+ liftIO $ simpleHeaders response `shouldContain`
924+ [(" Servant-Routed-Path" , " /animal/<legs::CaptureList>" )]
925+
926+ it " supports backtracking on routing errors" $ do
927+ response <- THW. request methodGet " /animal/jerry" [] " "
928+ liftIO $ simpleHeaders response `shouldContain`
929+ [(" Servant-Routed-Path" , " /animal/<name::CaptureSingle>" )]
930+
931+ it " returns the routed path on a failing route" $ do
932+ response <- THW. request methodGet " /animal/0" [] " "
933+ liftIO $ simpleHeaders response `shouldContain`
934+ [(" Servant-Routed-Path" , " /animal/<legs::CaptureSingle>" )]
935+
936+ it " is missing when no route matches" $ do
937+ response <- THW. request methodGet " /wrongPath" [] " "
938+ liftIO $ simpleHeaders response `shouldSatisfy`
939+ (notMember " Servant-Routed-Path" ) . fromList
940+
941+ it " is missing when WithRoutingHeader is missing" $ do
942+ response <- THW. request methodGet " /withoutHeader" [] " "
943+ liftIO $ simpleHeaders response `shouldSatisfy`
944+ (notMember " Servant-Routed-Path" ) . fromList
945+
845946-- }}}
846947------------------------------------------------------------------------------
847948-- * UVerb {{{
0 commit comments