@@ -9,7 +9,7 @@ import Control.Monad
99import Data.Proxy
1010 (Proxy (.. ))
1111import Data.Text
12- (unpack )
12+ (Text , unpack )
1313import Data.Typeable
1414 (typeRep )
1515import Network.HTTP.Types
@@ -29,6 +29,7 @@ spec :: Spec
2929spec = describe " Servant.Server.Internal.Router" $ do
3030 routerSpec
3131 distributivitySpec
32+ serverLayoutSpec
3233
3334routerSpec :: Spec
3435routerSpec = do
@@ -103,12 +104,28 @@ distributivitySpec =
103104 it " properly handles mixing static paths at different levels" $ do
104105 level `shouldHaveSameStructureAs` levelRef
105106
107+ serverLayoutSpec :: Spec
108+ serverLayoutSpec =
109+ describe " serverLayout" $ do
110+ it " correctly represents the example API" $ do
111+ exampleLayout `shouldHaveLayout` expectedExampleLayout
112+ it " aggregates capture hints when different" $ do
113+ dynamic `shouldHaveLayout` expectedDynamicLayout
114+ it " nubs capture hints when equal" $ do
115+ dynamicSameType `shouldHaveLayout` expectedDynamicSameTypeLayout
116+
106117shouldHaveSameStructureAs ::
107118 (HasServer api1 '[] , HasServer api2 '[] ) => Proxy api1 -> Proxy api2 -> Expectation
108119shouldHaveSameStructureAs p1 p2 =
109120 unless (sameStructure (makeTrivialRouter p1) (makeTrivialRouter p2)) $
110121 expectationFailure (" expected:\n " ++ unpack (layout p2) ++ " \n but got:\n " ++ unpack (layout p1))
111122
123+ shouldHaveLayout ::
124+ (HasServer api '[] ) => Proxy api -> Text -> Expectation
125+ shouldHaveLayout p l =
126+ unless (routerLayout (makeTrivialRouter p) == l) $
127+ expectationFailure (" expected:\n " ++ unpack l ++ " \n but got:\n " ++ unpack (layout p))
128+
112129makeTrivialRouter :: (HasServer layout '[] ) => Proxy layout -> Router ()
113130makeTrivialRouter p =
114131 route p EmptyContext (emptyDelayed (FailFatal err501))
@@ -344,3 +361,74 @@ level = Proxy
344361
345362levelRef :: Proxy LevelRef
346363levelRef = Proxy
364+
365+ -- The example API for the 'layout' function.
366+ -- Should get factorized by the 'choice' smart constructor.
367+ type ExampleLayout =
368+ " a" :> " d" :> Get '[JSON ] NoContent
369+ :<|> " b" :> Capture " x" Int :> Get '[JSON ] Bool
370+ :<|> " c" :> Put '[JSON ] Bool
371+ :<|> " a" :> " e" :> Get '[JSON ] Int
372+ :<|> " b" :> Capture " x" Int :> Put '[JSON ] Bool
373+ :<|> Raw
374+
375+ exampleLayout :: Proxy ExampleLayout
376+ exampleLayout = Proxy
377+
378+ -- The expected representation of the example API layout
379+ --
380+ expectedExampleLayout :: Text
381+ expectedExampleLayout =
382+ " /\n \
383+ \├─ a/\n \
384+ \│ ├─ d/\n \
385+ \│ │ └─•\n \
386+ \│ └─ e/\n \
387+ \│ └─•\n \
388+ \├─ b/\n \
389+ \│ └─ <capture x::Int>/\n \
390+ \│ ├─•\n \
391+ \│ ┆\n \
392+ \│ └─•\n \
393+ \├─ c/\n \
394+ \│ └─•\n \
395+ \┆\n \
396+ \└─ <raw>\n "
397+
398+ -- The expected representation of the Dynamic API layout.
399+ --
400+ expectedDynamicLayout :: Text
401+ expectedDynamicLayout =
402+ " /\n \
403+ \└─ a/\n \
404+ \ └─ <capture foo::Int|bar::Bool|baz::Char>/\n \
405+ \ ├─ b/\n \
406+ \ │ └─•\n \
407+ \ ├─ c/\n \
408+ \ │ └─•\n \
409+ \ └─ d/\n \
410+ \ └─•\n "
411+
412+ -- The same Dynamic API as above, except that the captured
413+ -- values have the same hints
414+ type DynamicSameType =
415+ " a" :> Capture " foo" Int :> " b" :> End
416+ :<|> " a" :> Capture " foo" Int :> " c" :> End
417+ :<|> " a" :> Capture " foo" Int :> " d" :> End
418+
419+ dynamicSameType :: Proxy DynamicSameType
420+ dynamicSameType = Proxy
421+
422+ -- The expected representation of the DynamicSameType API layout.
423+ --
424+ expectedDynamicSameTypeLayout :: Text
425+ expectedDynamicSameTypeLayout =
426+ " /\n \
427+ \└─ a/\n \
428+ \ └─ <capture foo::Int>/\n \
429+ \ ├─ b/\n \
430+ \ │ └─•\n \
431+ \ ├─ c/\n \
432+ \ │ └─•\n \
433+ \ └─ d/\n \
434+ \ └─•\n "
0 commit comments