renamed Union -> Alternative
This commit is contained in:
parent
8539fa10fa
commit
08e2a6a895
5 changed files with 10 additions and 10 deletions
|
@ -28,7 +28,7 @@ library
|
|||
Servant.API.QQ
|
||||
Servant.API.Raw
|
||||
Servant.API.Sub
|
||||
Servant.API.Union
|
||||
Servant.API.Alternative
|
||||
Servant.Utils.Text
|
||||
build-depends:
|
||||
base >=4.7 && <5
|
||||
|
|
|
@ -4,7 +4,7 @@ module Servant.API (
|
|||
-- | Type-level combinator for expressing subrouting: @':>'@
|
||||
module Servant.API.Sub,
|
||||
-- | Type-level combinator for alternative endpoints: @':<|>'@
|
||||
module Servant.API.Union,
|
||||
module Servant.API.Alternative,
|
||||
|
||||
-- * Accessing information from the request
|
||||
-- | Capturing parts of the url path as parsed values: @'Capture'@
|
||||
|
@ -38,4 +38,4 @@ import Servant.API.QueryParam
|
|||
import Servant.API.QQ (sitemap)
|
||||
import Servant.API.ReqBody
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Union
|
||||
import Servant.API.Alternative
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
module Servant.API.Union where
|
||||
module Servant.API.Alternative where
|
||||
|
||||
import Data.Proxy
|
||||
import Servant.Client
|
|
@ -21,7 +21,7 @@ import Servant.API.Delete
|
|||
import Servant.API.QueryParam
|
||||
import Servant.API.ReqBody
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Union
|
||||
import Servant.API.Alternative
|
||||
|
||||
class ExpSYM repr' repr | repr -> repr', repr' -> repr where
|
||||
lit :: String -> repr' -> repr
|
||||
|
|
|
@ -27,7 +27,7 @@ import Servant.API.Post
|
|||
import Servant.API.QueryParam
|
||||
import Servant.API.Raw
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Union
|
||||
import Servant.API.Alternative
|
||||
import Servant.Server
|
||||
|
||||
|
||||
|
@ -184,20 +184,20 @@ rawSpec = do
|
|||
simpleBody response `shouldBe` cs (show ["bar" :: String])
|
||||
|
||||
|
||||
type UnionApi =
|
||||
type AlternativeApi =
|
||||
"foo" :> Get Person
|
||||
:<|> "bar" :> Get Animal
|
||||
unionApi :: Proxy UnionApi
|
||||
unionApi :: Proxy AlternativeApi
|
||||
unionApi = Proxy
|
||||
|
||||
unionServer :: Server UnionApi
|
||||
unionServer :: Server AlternativeApi
|
||||
unionServer =
|
||||
return alice
|
||||
:<|> return jerry
|
||||
|
||||
unionSpec :: Spec
|
||||
unionSpec = do
|
||||
describe "Servant.API.Union" $ do
|
||||
describe "Servant.API.Alternative" $ do
|
||||
with (return $ serve unionApi unionServer) $ do
|
||||
it "unions endpoints" $ do
|
||||
response <- get "/foo"
|
||||
|
|
Loading…
Reference in a new issue