From d02c7668ee5f1a043b9a846d74133c708b806c93 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 08:18:16 +0000 Subject: [PATCH 01/28] Add EmptyAPI type --- servant/servant.cabal | 1 + servant/src/Servant/API/Empty.hs | 10 ++++++++++ 2 files changed, 11 insertions(+) create mode 100644 servant/src/Servant/API/Empty.hs diff --git a/servant/servant.cabal b/servant/servant.cabal index 14229d16..3e126d66 100644 --- a/servant/servant.cabal +++ b/servant/servant.cabal @@ -36,6 +36,7 @@ library Servant.API.BasicAuth Servant.API.Capture Servant.API.ContentTypes + Servant.API.Empty Servant.API.Experimental.Auth Servant.API.Header Servant.API.HttpVersion diff --git a/servant/src/Servant/API/Empty.hs b/servant/src/Servant/API/Empty.hs new file mode 100644 index 00000000..5aa5c0ab --- /dev/null +++ b/servant/src/Servant/API/Empty.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# OPTIONS_HADDOCK not-home #-} +module Servant.API.Empty(EmptyAPI(..)) where + +import Data.Typeable (Typeable) +import Prelude () +import Prelude.Compat + +-- | An empty API: one which serves nothing. +data EmptyAPI = EmptyAPI deriving (Typeable, Eq, Show, Bounded) From 5a65563d9a3898ebce8aaedcb5076d0568161451 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 08:19:37 +0000 Subject: [PATCH 02/28] Re-export EmptyAPI(..) from Servant.API --- servant/src/Servant/API.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/servant/src/Servant/API.hs b/servant/src/Servant/API.hs index 08594137..f1a0e64b 100644 --- a/servant/src/Servant/API.hs +++ b/servant/src/Servant/API.hs @@ -5,6 +5,8 @@ module Servant.API ( -- | Type-level combinator for expressing subrouting: @':>'@ module Servant.API.Alternative, -- | Type-level combinator for alternative endpoints: @':<|>'@ + module Servant.API.Empty, + -- | Type-level combinator for an empty API: @'EmptyAPI'@ -- * Accessing information from the request module Servant.API.Capture, @@ -66,6 +68,7 @@ import Servant.API.ContentTypes (Accept (..), FormUrlEncoded, MimeRender (..), NoContent (NoContent), MimeUnrender (..), OctetStream, PlainText) +import Servant.API.Empty (EmptyAPI (..)) import Servant.API.Experimental.Auth (AuthProtect) import Servant.API.Header (Header (..)) import Servant.API.HttpVersion (HttpVersion (..)) From e8c71586002bee75c63f116754920f75878ef957 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:18:01 +0000 Subject: [PATCH 03/28] Renumber APIs in the tutorial to be in order --- doc/tutorial/ApiType.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/tutorial/ApiType.lhs b/doc/tutorial/ApiType.lhs index d43b141d..7de0bc96 100644 --- a/doc/tutorial/ApiType.lhs +++ b/doc/tutorial/ApiType.lhs @@ -321,7 +321,7 @@ data BasicAuth (realm :: Symbol) (userData :: *) Which is used like so: ``` haskell -type ProtectedAPI12 +type ProtectedAPI11 = UserAPI -- this is public :<|> BasicAuth "my-realm" User :> UserAPI2 -- this is protected by auth ``` @@ -334,7 +334,7 @@ you want to plug a [wai `Application`](http://hackage.haskell.org/package/wai) into your webservice: ``` haskell -type UserAPI11 = "users" :> Get '[JSON] [User] +type UserAPI12 = "users" :> Get '[JSON] [User] -- a /users endpoint :<|> Raw From b81fbe445d7c248620244951777733921ee1415e Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:21:42 +0000 Subject: [PATCH 04/28] Renumber again to make room for the EmptyAPI example --- doc/tutorial/ApiType.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/tutorial/ApiType.lhs b/doc/tutorial/ApiType.lhs index 7de0bc96..2cdc8b65 100644 --- a/doc/tutorial/ApiType.lhs +++ b/doc/tutorial/ApiType.lhs @@ -334,7 +334,7 @@ you want to plug a [wai `Application`](http://hackage.haskell.org/package/wai) into your webservice: ``` haskell -type UserAPI12 = "users" :> Get '[JSON] [User] +type UserAPI13 = "users" :> Get '[JSON] [User] -- a /users endpoint :<|> Raw From 8a16f47fbab6e2f7778422c926dc769394d27208 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:21:58 +0000 Subject: [PATCH 05/28] Add EmptyAPI example (no prose yet) --- doc/tutorial/ApiType.lhs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/doc/tutorial/ApiType.lhs b/doc/tutorial/ApiType.lhs index 2cdc8b65..546e62ef 100644 --- a/doc/tutorial/ApiType.lhs +++ b/doc/tutorial/ApiType.lhs @@ -326,6 +326,16 @@ type ProtectedAPI11 :<|> BasicAuth "my-realm" User :> UserAPI2 -- this is protected by auth ``` +### Empty APIs + +TODO motivation... + +``` haskell ignore +type UserAPI12 + = UserAPI + :<|> EmptyAPI -- this adds nothing to the API +``` + ### Interoperability with `wai`: `Raw` Finally, we also include a combinator named `Raw` that provides an escape hatch From 94483d586cf946f5b6b28e834f4ea14a94e0ec7f Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:34:07 +0000 Subject: [PATCH 06/28] Add `instance HasServer EmptyAPI` --- doc/tutorial/Server.lhs | 9 +++++++++ servant-server/src/Servant/Server.hs | 2 ++ servant-server/src/Servant/Server/Internal.hs | 14 ++++++++++++-- 3 files changed, 23 insertions(+), 2 deletions(-) diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index 0de0907b..9b81d30e 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -1020,6 +1020,15 @@ serverFor = error "..." -- or the mailing list if you get stuck! ``` +TODO prose + +``` haskell +type CombinedAPI2 = CombinedAPI :<|> EmptyAPI + +server11 :: Server CombinedAPI2 +server11 = server10 :<|> emptyAPIServer +``` + ## Using another monad for your handlers Remember how `Server` turns combinators for HTTP methods into `Handler`? Well, actually, there's more to that. `Server` is actually a diff --git a/servant-server/src/Servant/Server.hs b/servant-server/src/Servant/Server.hs index 47fdf0cf..212277e2 100644 --- a/servant-server/src/Servant/Server.hs +++ b/servant-server/src/Servant/Server.hs @@ -17,6 +17,8 @@ module Servant.Server , -- * Handlers for all standard combinators HasServer(..) , Server + , EmptyAPIServer + , emptyAPIServer , Handler (..) , runHandler diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index 31d7b751..fc2c80c0 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -32,7 +32,7 @@ import Data.Maybe (fromMaybe, mapMaybe) import Data.Either (partitionEithers) import Data.String (fromString) import Data.String.Conversions (cs, (<>)) -import Data.Tagged (Tagged, untag) +import Data.Tagged (Tagged(..), untag) import qualified Data.Text as T import Data.Typeable import GHC.TypeLits (KnownNat, KnownSymbol, natVal, @@ -52,7 +52,7 @@ import Web.HttpApiData (FromHttpApiData, parseHeader, parseUrlPieceMaybe, parseUrlPieces) import Servant.API ((:<|>) (..), (:>), BasicAuth, Capture, - CaptureAll, Verb, + CaptureAll, Verb, EmptyAPI, ReflectMethod(reflectMethod), IsSecure(..), Header, QueryFlag, QueryParam, QueryParams, Raw, @@ -532,6 +532,16 @@ instance HasServer api context => HasServer (HttpVersion :> api) context where route Proxy context subserver = route (Proxy :: Proxy api) context (passToServer subserver httpVersion) +data EmptyAPIServer = EmptyAPIServer + +emptyAPIServer :: Server EmptyAPI +emptyAPIServer = Tagged EmptyAPIServer + +instance HasServer EmptyAPI context where + type ServerT EmptyAPI m = Tagged m EmptyAPIServer + + route Proxy _ _ = StaticRouter mempty mempty + -- | Basic Authentication instance ( KnownSymbol realm , HasServer api context From 4c64c13af0a2300d721a8e4e55d9652fc4d97e11 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:42:06 +0000 Subject: [PATCH 07/28] Add EmptyAPIClient and `instance HasClient EmptyAPI` --- doc/tutorial/Client.lhs | 5 ++++- servant-client/src/Servant/Client.hs | 8 ++++++++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/doc/tutorial/Client.lhs b/doc/tutorial/Client.lhs index 284d6e83..d409a437 100644 --- a/doc/tutorial/Client.lhs +++ b/doc/tutorial/Client.lhs @@ -62,6 +62,7 @@ Enough chitchat, let's see an example. Consider the following API type from the type API = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position :<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email + :<|> EmptyAPI ``` What we are going to get with **servant-client** here is three functions, one to query each endpoint: @@ -76,6 +77,8 @@ hello :: Maybe String -- ^ an optional value for "name" marketing :: ClientInfo -- ^ value for the request body -> ClientM Email + +emptyClient :: EmptyAPIClient ``` Each function makes available as an argument any value that the response may @@ -88,7 +91,7 @@ the function `client`. It takes one argument: api :: Proxy API api = Proxy -position :<|> hello :<|> marketing = client api +position :<|> hello :<|> marketing :<|> emptyClient = client api ``` `client api` returns client functions for our _entire_ API, combined with `:<|>`, which we can pattern match on as above. You could say `client` "calculates" the correct type and number of client functions for the API type it is given (via a `Proxy`), as well as their implementations. diff --git a/servant-client/src/Servant/Client.hs b/servant-client/src/Servant/Client.hs index d6084edf..cd68adc9 100644 --- a/servant-client/src/Servant/Client.hs +++ b/servant-client/src/Servant/Client.hs @@ -24,6 +24,7 @@ module Servant.Client , ClientEnv (ClientEnv) , mkAuthenticateReq , ServantError(..) + , EmptyAPIClient(..) , module Servant.Common.BaseUrl ) where @@ -88,6 +89,13 @@ instance (HasClient a, HasClient b) => HasClient (a :<|> b) where clientWithRoute (Proxy :: Proxy a) req :<|> clientWithRoute (Proxy :: Proxy b) req +-- | TODO docs +data EmptyAPIClient = EmptyAPIClient + +instance HasClient EmptyAPI where + type Client EmptyAPI = EmptyAPIClient + clientWithRoute Proxy _ = EmptyAPIClient + -- | If you use a 'Capture' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument of the type specified by your 'Capture'. From a87067a6c1cf03fada25bb5ab8f095c479ea5d40 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:51:50 +0000 Subject: [PATCH 08/28] Actually, serve this one so it's useful in the Docs tutorial --- doc/tutorial/Server.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index 9b81d30e..75119cf6 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -1023,10 +1023,10 @@ serverFor = error "..." TODO prose ``` haskell -type CombinedAPI2 = CombinedAPI :<|> EmptyAPI +type CombinedAPI2 = API :<|> EmptyAPI server11 :: Server CombinedAPI2 -server11 = server10 :<|> emptyAPIServer +server11 = server3 :<|> emptyAPIServer ``` ## Using another monad for your handlers From 2cfa71891ba52db6d7c6d567e24132dc5443f23e Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 09:52:55 +0000 Subject: [PATCH 09/28] Add `instance HasDocs EmptyAPI` --- doc/tutorial/Docs.lhs | 7 ++++--- servant-docs/src/Servant/Docs/Internal.hs | 4 ++++ 2 files changed, 8 insertions(+), 3 deletions(-) diff --git a/doc/tutorial/Docs.lhs b/doc/tutorial/Docs.lhs index 67f6f60c..9dae710c 100644 --- a/doc/tutorial/Docs.lhs +++ b/doc/tutorial/Docs.lhs @@ -38,9 +38,10 @@ Like client function generation, documentation generation amounts to inspecting This time however, we have to assist **servant**. While it is able to deduce a lot of things about our API, it can't magically come up with descriptions of the various pieces of our APIs that are human-friendly and explain what's going on "at the business-logic level". A good example to study for documentation generation is our webservice with the `/position`, `/hello` and `/marketing` endpoints from earlier: ``` haskell -type ExampleAPI = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position +type ExampleAPI = ("position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position :<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage - :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email + :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email) + :<|> EmptyAPI exampleAPI :: Proxy ExampleAPI exampleAPI = Proxy @@ -220,7 +221,7 @@ api :: Proxy DocsAPI api = Proxy server :: Server DocsAPI -server = Server.server3 :<|> Tagged serveDocs where +server = (Server.server3 :<|> emptyAPIServer) :<|> Tagged serveDocs where serveDocs _ respond = respond $ responseLBS ok200 [plain] docsBS plain = ("Content-Type", "text/plain") diff --git a/servant-docs/src/Servant/Docs/Internal.hs b/servant-docs/src/Servant/Docs/Internal.hs index 2884473c..b5088f7a 100644 --- a/servant-docs/src/Servant/Docs/Internal.hs +++ b/servant-docs/src/Servant/Docs/Internal.hs @@ -683,6 +683,10 @@ instance OVERLAPPABLE_ p2 :: Proxy b p2 = Proxy +-- | The generated docs for @'EmptyAPI'@ are empty. +instance HasDocs EmptyAPI where + docsFor Proxy _ _ = emptyAPI + -- | @"books" :> 'Capture' "isbn" Text@ will appear as -- @/books/:isbn@ in the docs. instance (KnownSymbol sym, ToCapture (Capture sym a), HasDocs api) From fa3f1869f2e92ffe0145ef877e9cc17e7b4a184d Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:01:33 +0000 Subject: [PATCH 10/28] Add EmptyForeignAPI and `instance HasForeign ... EmptyAPI` --- doc/tutorial/Javascript.lhs | 2 ++ servant-foreign/src/Servant/Foreign/Internal.hs | 10 ++++++++++ 2 files changed, 12 insertions(+) diff --git a/doc/tutorial/Javascript.lhs b/doc/tutorial/Javascript.lhs index 6a7aa6bb..8187d2c2 100644 --- a/doc/tutorial/Javascript.lhs +++ b/doc/tutorial/Javascript.lhs @@ -45,6 +45,7 @@ Now let's have the API type(s) and the accompanying datatypes. ``` haskell type API = "point" :> Get '[JSON] Point :<|> "books" :> QueryParam "q" Text :> Get '[JSON] (Search Book) + :<|> EmptyAPI type API' = API :<|> Raw @@ -133,6 +134,7 @@ api' = Proxy server :: Server API server = randomPoint :<|> searchBook + :<|> emptyAPIServer server' :: Server API' server' = server diff --git a/servant-foreign/src/Servant/Foreign/Internal.hs b/servant-foreign/src/Servant/Foreign/Internal.hs index ac68631c..fd12befd 100644 --- a/servant-foreign/src/Servant/Foreign/Internal.hs +++ b/servant-foreign/src/Servant/Foreign/Internal.hs @@ -187,6 +187,13 @@ instance (HasForeign lang ftype a, HasForeign lang ftype b) foreignFor lang ftype (Proxy :: Proxy a) req :<|> foreignFor lang ftype (Proxy :: Proxy b) req +data EmptyForeignAPI = EmptyForeignAPI + +instance HasForeign lang ftype EmptyAPI where + type Foreign ftype EmptyAPI = EmptyForeignAPI + + foreignFor Proxy Proxy Proxy _ = EmptyForeignAPI + instance (KnownSymbol sym, HasForeignType lang ftype t, HasForeign lang ftype api) => HasForeign lang ftype (Capture sym t :> api) where type Foreign ftype (Capture sym t :> api) = Foreign ftype api @@ -349,6 +356,9 @@ instance HasForeign lang ftype api class GenerateList ftype reqs where generateList :: reqs -> [Req ftype] +instance GenerateList ftype EmptyForeignAPI where + generateList _ = [] + instance GenerateList ftype (Req ftype) where generateList r = [r] From 937a5c98fd5a999760684791e761c15149e2ed7a Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:18:57 +0000 Subject: [PATCH 11/28] Add test for emptyAPIServer --- servant-server/test/Servant/ServerSpec.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/servant-server/test/Servant/ServerSpec.hs b/servant-server/test/Servant/ServerSpec.hs index 3db3e27c..fbcd1929 100644 --- a/servant-server/test/Servant/ServerSpec.hs +++ b/servant-server/test/Servant/ServerSpec.hs @@ -42,14 +42,14 @@ import Servant.API ((:<|>) (..), (:>), AuthProtect, Headers, HttpVersion, IsSecure (..), JSON, NoContent (..), Patch, PlainText, - Post, Put, + Post, Put, EmptyAPI, QueryFlag, QueryParam, QueryParams, Raw, RemoteHost, ReqBody, StdMethod (..), Verb, addHeader) import Servant.API.Internal.Test.ComprehensiveAPI import Servant.Server (Server, Handler, Tagged (..), err401, err403, err404, serve, serveWithContext, - Context((:.), EmptyContext)) + Context((:.), EmptyContext), emptyAPIServer) import Test.Hspec (Spec, context, describe, it, shouldBe, shouldContain) import qualified Test.Hspec.Wai as THW @@ -609,6 +609,7 @@ type MiscCombinatorsAPI = "version" :> HttpVersion :> Get '[JSON] String :<|> "secure" :> IsSecure :> Get '[JSON] String :<|> "host" :> RemoteHost :> Get '[JSON] String + :<|> "empty" :> EmptyAPI miscApi :: Proxy MiscCombinatorsAPI miscApi = Proxy @@ -617,6 +618,7 @@ miscServ :: Server MiscCombinatorsAPI miscServ = versionHandler :<|> secureHandler :<|> hostHandler + :<|> emptyAPIServer where versionHandler = return . show secureHandler Secure = return "secure" @@ -635,6 +637,9 @@ miscCombinatorSpec = with (return $ serve miscApi miscServ) $ it "Checks that hspec-wai issues request from 0.0.0.0" $ go "/host" "\"0.0.0.0:0\"" + it "Doesn't serve anything from the empty API" $ + Test.Hspec.Wai.get "empty" `shouldRespondWith` 404 + where go path res = Test.Hspec.Wai.get path `shouldRespondWith` res -- }}} From e60bdadead842506b8188cac72126173dcb5cdde Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:21:37 +0000 Subject: [PATCH 12/28] Demonstrate that a client for EmptyAPI pattern-matches EmptyAPIClient --- servant-client/test/Servant/ClientSpec.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/servant-client/test/Servant/ClientSpec.hs b/servant-client/test/Servant/ClientSpec.hs index 219a178c..882c2a74 100644 --- a/servant-client/test/Servant/ClientSpec.hs +++ b/servant-client/test/Servant/ClientSpec.hs @@ -111,6 +111,8 @@ type Api = Get '[JSON] (String, Maybe Int, Bool, [(String, [Rational])]) :<|> "headers" :> Get '[JSON] (Headers TestHeaders Bool) :<|> "deleteContentType" :> DeleteNoContent '[JSON] NoContent + :<|> "empty" :> EmptyAPI + api :: Proxy Api api = Proxy @@ -130,6 +132,7 @@ getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])] -> SCR.ClientM (String, Maybe Int, Bool, [(String, [Rational])]) getRespHeaders :: SCR.ClientM (Headers TestHeaders Bool) getDeleteContentType :: SCR.ClientM NoContent + getGet :<|> getDeleteEmpty :<|> getCapture @@ -142,7 +145,8 @@ getGet :<|> getRawFailure :<|> getMultiple :<|> getRespHeaders - :<|> getDeleteContentType = client api + :<|> getDeleteContentType + :<|> EmptyAPIClient = client api server :: Application server = serve api ( @@ -162,6 +166,7 @@ server = serve api ( :<|> (\ a b c d -> return (a, b, c, d)) :<|> (return $ addHeader 1729 $ addHeader "eg2" True) :<|> return NoContent + :<|> emptyAPIServer ) From 2c6aca0fc6d05b4539ceed5bcdbe10f0a3b0eaf8 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:26:06 +0000 Subject: [PATCH 13/28] Add to ComprehensiveAPI --- servant/src/Servant/API/Internal/Test/ComprehensiveAPI.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/servant/src/Servant/API/Internal/Test/ComprehensiveAPI.hs b/servant/src/Servant/API/Internal/Test/ComprehensiveAPI.hs index e7c15633..0f39a910 100644 --- a/servant/src/Servant/API/Internal/Test/ComprehensiveAPI.hs +++ b/servant/src/Servant/API/Internal/Test/ComprehensiveAPI.hs @@ -37,7 +37,8 @@ type ComprehensiveAPIWithoutRaw = Verb 'POST 204 '[JSON] NoContent :<|> Verb 'POST 204 '[JSON] Int :<|> WithNamedContext "foo" '[] GET :<|> - CaptureAll "foo" Int :> GET + CaptureAll "foo" Int :> GET :<|> + EmptyAPI comprehensiveAPIWithoutRaw :: Proxy ComprehensiveAPIWithoutRaw comprehensiveAPIWithoutRaw = Proxy From 4b7ffc94618aeac47b5469f9d8bab0495179b8c7 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:29:27 +0000 Subject: [PATCH 14/28] Add test that EmptyAPI does not generate any docs --- servant-docs/test/Servant/DocsSpec.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/servant-docs/test/Servant/DocsSpec.hs b/servant-docs/test/Servant/DocsSpec.hs index 054ea00a..3daffbcf 100644 --- a/servant-docs/test/Servant/DocsSpec.hs +++ b/servant-docs/test/Servant/DocsSpec.hs @@ -104,6 +104,9 @@ spec = describe "Servant.Docs" $ do it "contains request body samples" $ md `shouldContain` "17" + it "does not generate any docs mentioning the 'empty-api' path" $ + md `shouldNotContain` "empty-api" + -- * APIs @@ -128,6 +131,7 @@ instance MimeRender PlainText Int where type TestApi1 = Get '[JSON, PlainText] (Headers '[Header "Location" String] Int) :<|> ReqBody '[JSON] String :> Post '[JSON] Datatype1 :<|> Header "X-Test" Int :> Put '[JSON] Int + :<|> "empty-api" :> EmptyAPI data TT = TT1 | TT2 deriving (Show, Eq) data UT = UT1 | UT2 deriving (Show, Eq) From 113561639a2303229d325808354c5765b8de4280 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:31:02 +0000 Subject: [PATCH 15/28] Fix name of test --- servant-foreign/test/Servant/ForeignSpec.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/servant-foreign/test/Servant/ForeignSpec.hs b/servant-foreign/test/Servant/ForeignSpec.hs index d88c1abb..f7c910ab 100644 --- a/servant-foreign/test/Servant/ForeignSpec.hs +++ b/servant-foreign/test/Servant/ForeignSpec.hs @@ -63,7 +63,7 @@ testApi = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy String) (Proxy :: P listFromAPISpec :: Spec listFromAPISpec = describe "listFromAPI" $ do - it "generates 4 endpoints for TestApi" $ do + it "generates 5 endpoints for TestApi" $ do length testApi `shouldBe` 5 let [getReq, postReq, putReq, deleteReq, captureAllReq] = testApi From e73f00b333fbf7791fc38d20521deaff67b38a28 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 10:31:33 +0000 Subject: [PATCH 16/28] Test that no foreign functions are generated for an EmptyAPI --- servant-foreign/test/Servant/ForeignSpec.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/servant-foreign/test/Servant/ForeignSpec.hs b/servant-foreign/test/Servant/ForeignSpec.hs index f7c910ab..3bc572a5 100644 --- a/servant-foreign/test/Servant/ForeignSpec.hs +++ b/servant-foreign/test/Servant/ForeignSpec.hs @@ -57,6 +57,7 @@ type TestApi :<|> "test" :> QueryParams "params" Int :> ReqBody '[JSON] String :> Put '[JSON] NoContent :<|> "test" :> Capture "id" Int :> Delete '[JSON] NoContent :<|> "test" :> CaptureAll "ids" Int :> Get '[JSON] [Int] + :<|> "test" :> EmptyAPI testApi :: [Req String] testApi = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy String) (Proxy :: Proxy TestApi) From 178f05595a180dd418f9ea66b1472ec61a571121 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 11:06:37 +0000 Subject: [PATCH 17/28] Better docs for EmptyAPIClient --- servant-client/src/Servant/Client.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/servant-client/src/Servant/Client.hs b/servant-client/src/Servant/Client.hs index cd68adc9..cf1ce9e7 100644 --- a/servant-client/src/Servant/Client.hs +++ b/servant-client/src/Servant/Client.hs @@ -89,9 +89,19 @@ instance (HasClient a, HasClient b) => HasClient (a :<|> b) where clientWithRoute (Proxy :: Proxy a) req :<|> clientWithRoute (Proxy :: Proxy b) req --- | TODO docs +-- | Singleton type representing a client for an empty API. data EmptyAPIClient = EmptyAPIClient +-- | The client for 'EmptyAPI' is simply 'EmptyAPIClient'. +-- +-- > type MyAPI = "books" :> Get '[JSON] [Book] -- GET /books +-- > :<|> "nothing" :> EmptyAPI +-- > +-- > myApi :: Proxy MyApi +-- > myApi = Proxy +-- > +-- > getAllBooks :: ClientM [Book] +-- > (getAllBooks :<|> EmptyAPIClient) = client myApi instance HasClient EmptyAPI where type Client EmptyAPI = EmptyAPIClient clientWithRoute Proxy _ = EmptyAPIClient From 62560079b1bd275c53c3b1a79c433da9b4c8c33d Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 11:09:54 +0000 Subject: [PATCH 18/28] Add docs for serving an EmptyAPI --- servant-server/src/Servant/Server/Internal.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index fc2c80c0..057e3f19 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -532,11 +532,19 @@ instance HasServer api context => HasServer (HttpVersion :> api) context where route Proxy context subserver = route (Proxy :: Proxy api) context (passToServer subserver httpVersion) +-- | Singleton type representing a server that serves an empty API data EmptyAPIServer = EmptyAPIServer +-- | Server for `EmptyAPI` emptyAPIServer :: Server EmptyAPI emptyAPIServer = Tagged EmptyAPIServer +-- | The server for an `EmptyAPI` is `emptyAPIServer`. +-- +-- > type MyApi = "nothing" :> EmptyApi +-- > +-- > server :: Server MyApi +-- > server = emptyAPIServer instance HasServer EmptyAPI context where type ServerT EmptyAPI m = Tagged m EmptyAPIServer From 6feb27e7b25f43ee71e47af5c047bf2dd2f312c1 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 15:53:19 +0000 Subject: [PATCH 19/28] Rename EmptyAPIServer to EmptyServer and add deriving clause --- servant-server/src/Servant/Server.hs | 2 +- servant-server/src/Servant/Server/Internal.hs | 8 ++++---- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/servant-server/src/Servant/Server.hs b/servant-server/src/Servant/Server.hs index 212277e2..c3e1c90a 100644 --- a/servant-server/src/Servant/Server.hs +++ b/servant-server/src/Servant/Server.hs @@ -17,7 +17,7 @@ module Servant.Server , -- * Handlers for all standard combinators HasServer(..) , Server - , EmptyAPIServer + , EmptyServer , emptyAPIServer , Handler (..) , runHandler diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index 057e3f19..f343f038 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -532,12 +532,12 @@ instance HasServer api context => HasServer (HttpVersion :> api) context where route Proxy context subserver = route (Proxy :: Proxy api) context (passToServer subserver httpVersion) --- | Singleton type representing a server that serves an empty API -data EmptyAPIServer = EmptyAPIServer +-- | Singleton type representing a server that serves an empty API. +data EmptyServer = EmptyServer deriving (Typeable, Eq, Show, Bounded, Enum) -- | Server for `EmptyAPI` emptyAPIServer :: Server EmptyAPI -emptyAPIServer = Tagged EmptyAPIServer +emptyAPIServer = Tagged EmptyServer -- | The server for an `EmptyAPI` is `emptyAPIServer`. -- @@ -546,7 +546,7 @@ emptyAPIServer = Tagged EmptyAPIServer -- > server :: Server MyApi -- > server = emptyAPIServer instance HasServer EmptyAPI context where - type ServerT EmptyAPI m = Tagged m EmptyAPIServer + type ServerT EmptyAPI m = Tagged m EmptyServer route Proxy _ _ = StaticRouter mempty mempty From f5d9983381b96ee1ce03e97e3e1d4982e1c92972 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 15:59:41 +0000 Subject: [PATCH 20/28] Rename emptyAPIServer to emptyServer --- doc/tutorial/Docs.lhs | 2 +- doc/tutorial/Javascript.lhs | 2 +- doc/tutorial/Server.lhs | 2 +- servant-client/test/Servant/ClientSpec.hs | 3 +-- servant-server/src/Servant/Server.hs | 2 +- servant-server/src/Servant/Server/Internal.hs | 4 ++-- servant-server/test/Servant/ServerSpec.hs | 4 ++-- 7 files changed, 9 insertions(+), 10 deletions(-) diff --git a/doc/tutorial/Docs.lhs b/doc/tutorial/Docs.lhs index 9dae710c..9903ec98 100644 --- a/doc/tutorial/Docs.lhs +++ b/doc/tutorial/Docs.lhs @@ -221,7 +221,7 @@ api :: Proxy DocsAPI api = Proxy server :: Server DocsAPI -server = (Server.server3 :<|> emptyAPIServer) :<|> Tagged serveDocs where +server = (Server.server3 :<|> emptyServer) :<|> Tagged serveDocs where serveDocs _ respond = respond $ responseLBS ok200 [plain] docsBS plain = ("Content-Type", "text/plain") diff --git a/doc/tutorial/Javascript.lhs b/doc/tutorial/Javascript.lhs index 8187d2c2..f0158d1f 100644 --- a/doc/tutorial/Javascript.lhs +++ b/doc/tutorial/Javascript.lhs @@ -134,7 +134,7 @@ api' = Proxy server :: Server API server = randomPoint :<|> searchBook - :<|> emptyAPIServer + :<|> emptyServer server' :: Server API' server' = server diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index 75119cf6..a364224c 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -1026,7 +1026,7 @@ TODO prose type CombinedAPI2 = API :<|> EmptyAPI server11 :: Server CombinedAPI2 -server11 = server3 :<|> emptyAPIServer +server11 = server3 :<|> emptyServer ``` ## Using another monad for your handlers diff --git a/servant-client/test/Servant/ClientSpec.hs b/servant-client/test/Servant/ClientSpec.hs index 882c2a74..3a4a2481 100644 --- a/servant-client/test/Servant/ClientSpec.hs +++ b/servant-client/test/Servant/ClientSpec.hs @@ -166,8 +166,7 @@ server = serve api ( :<|> (\ a b c d -> return (a, b, c, d)) :<|> (return $ addHeader 1729 $ addHeader "eg2" True) :<|> return NoContent - :<|> emptyAPIServer - ) + :<|> emptyServer) type FailApi = diff --git a/servant-server/src/Servant/Server.hs b/servant-server/src/Servant/Server.hs index c3e1c90a..9a117821 100644 --- a/servant-server/src/Servant/Server.hs +++ b/servant-server/src/Servant/Server.hs @@ -18,7 +18,7 @@ module Servant.Server HasServer(..) , Server , EmptyServer - , emptyAPIServer + , emptyServer , Handler (..) , runHandler diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index f343f038..8880d35c 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -536,8 +536,8 @@ instance HasServer api context => HasServer (HttpVersion :> api) context where data EmptyServer = EmptyServer deriving (Typeable, Eq, Show, Bounded, Enum) -- | Server for `EmptyAPI` -emptyAPIServer :: Server EmptyAPI -emptyAPIServer = Tagged EmptyServer +emptyServer :: Server EmptyAPI +emptyServer = Tagged EmptyServer -- | The server for an `EmptyAPI` is `emptyAPIServer`. -- diff --git a/servant-server/test/Servant/ServerSpec.hs b/servant-server/test/Servant/ServerSpec.hs index fbcd1929..0a641559 100644 --- a/servant-server/test/Servant/ServerSpec.hs +++ b/servant-server/test/Servant/ServerSpec.hs @@ -49,7 +49,7 @@ import Servant.API ((:<|>) (..), (:>), AuthProtect, import Servant.API.Internal.Test.ComprehensiveAPI import Servant.Server (Server, Handler, Tagged (..), err401, err403, err404, serve, serveWithContext, - Context((:.), EmptyContext), emptyAPIServer) + Context((:.), EmptyContext), emptyServer) import Test.Hspec (Spec, context, describe, it, shouldBe, shouldContain) import qualified Test.Hspec.Wai as THW @@ -618,7 +618,7 @@ miscServ :: Server MiscCombinatorsAPI miscServ = versionHandler :<|> secureHandler :<|> hostHandler - :<|> emptyAPIServer + :<|> emptyServer where versionHandler = return . show secureHandler Secure = return "secure" From 0bbc4f98a4f05f94309d4b7daddb38e735e2dac6 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 16:00:15 +0000 Subject: [PATCH 21/28] Rename EmptyAPIClient to EmptyClient --- doc/tutorial/Client.lhs | 4 +--- servant-client/src/Servant/Client.hs | 12 ++++++------ servant-client/test/Servant/ClientSpec.hs | 2 +- 3 files changed, 8 insertions(+), 10 deletions(-) diff --git a/doc/tutorial/Client.lhs b/doc/tutorial/Client.lhs index d409a437..cb8a24b7 100644 --- a/doc/tutorial/Client.lhs +++ b/doc/tutorial/Client.lhs @@ -77,8 +77,6 @@ hello :: Maybe String -- ^ an optional value for "name" marketing :: ClientInfo -- ^ value for the request body -> ClientM Email - -emptyClient :: EmptyAPIClient ``` Each function makes available as an argument any value that the response may @@ -91,7 +89,7 @@ the function `client`. It takes one argument: api :: Proxy API api = Proxy -position :<|> hello :<|> marketing :<|> emptyClient = client api +position :<|> hello :<|> marketing :<|> EmptyClient = client api ``` `client api` returns client functions for our _entire_ API, combined with `:<|>`, which we can pattern match on as above. You could say `client` "calculates" the correct type and number of client functions for the API type it is given (via a `Proxy`), as well as their implementations. diff --git a/servant-client/src/Servant/Client.hs b/servant-client/src/Servant/Client.hs index cf1ce9e7..dfe2721c 100644 --- a/servant-client/src/Servant/Client.hs +++ b/servant-client/src/Servant/Client.hs @@ -24,7 +24,7 @@ module Servant.Client , ClientEnv (ClientEnv) , mkAuthenticateReq , ServantError(..) - , EmptyAPIClient(..) + , EmptyClient(..) , module Servant.Common.BaseUrl ) where @@ -90,9 +90,9 @@ instance (HasClient a, HasClient b) => HasClient (a :<|> b) where clientWithRoute (Proxy :: Proxy b) req -- | Singleton type representing a client for an empty API. -data EmptyAPIClient = EmptyAPIClient +data EmptyClient = EmptyClient deriving (Eq, Show, Bounded, Enum) --- | The client for 'EmptyAPI' is simply 'EmptyAPIClient'. +-- | The client for 'EmptyAPI' is simply 'EmptyClient'. -- -- > type MyAPI = "books" :> Get '[JSON] [Book] -- GET /books -- > :<|> "nothing" :> EmptyAPI @@ -101,10 +101,10 @@ data EmptyAPIClient = EmptyAPIClient -- > myApi = Proxy -- > -- > getAllBooks :: ClientM [Book] --- > (getAllBooks :<|> EmptyAPIClient) = client myApi +-- > (getAllBooks :<|> EmptyClient) = client myApi instance HasClient EmptyAPI where - type Client EmptyAPI = EmptyAPIClient - clientWithRoute Proxy _ = EmptyAPIClient + type Client EmptyAPI = EmptyClient + clientWithRoute Proxy _ = EmptyClient -- | If you use a 'Capture' in one of your endpoints in your API, -- the corresponding querying function will automatically take diff --git a/servant-client/test/Servant/ClientSpec.hs b/servant-client/test/Servant/ClientSpec.hs index 3a4a2481..14e9f917 100644 --- a/servant-client/test/Servant/ClientSpec.hs +++ b/servant-client/test/Servant/ClientSpec.hs @@ -146,7 +146,7 @@ getGet :<|> getMultiple :<|> getRespHeaders :<|> getDeleteContentType - :<|> EmptyAPIClient = client api + :<|> EmptyClient = client api server :: Application server = serve api ( From 021bcd9e237d5a489bb953ea9724414f6c65a200 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 16:03:25 +0000 Subject: [PATCH 22/28] Document that EmptyAPI is, morally speaking, the unit of :<|> --- servant/src/Servant/API/Empty.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/servant/src/Servant/API/Empty.hs b/servant/src/Servant/API/Empty.hs index 5aa5c0ab..d9b80787 100644 --- a/servant/src/Servant/API/Empty.hs +++ b/servant/src/Servant/API/Empty.hs @@ -6,5 +6,7 @@ import Data.Typeable (Typeable) import Prelude () import Prelude.Compat --- | An empty API: one which serves nothing. +-- | An empty API: one which serves nothing. Morally speaking, this should be +-- the unit of ':<|>'. Implementors of interpretations of API types should +-- treat 'EmptyAPI' as close to the unit as possible. data EmptyAPI = EmptyAPI deriving (Typeable, Eq, Show, Bounded) From 249a8386a5d60974cca941a69b7b81b6f30f7d24 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 16:04:25 +0000 Subject: [PATCH 23/28] Derive Enum on EmptyAPI --- servant/src/Servant/API/Empty.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/servant/src/Servant/API/Empty.hs b/servant/src/Servant/API/Empty.hs index d9b80787..efc79356 100644 --- a/servant/src/Servant/API/Empty.hs +++ b/servant/src/Servant/API/Empty.hs @@ -9,4 +9,4 @@ import Prelude.Compat -- | An empty API: one which serves nothing. Morally speaking, this should be -- the unit of ':<|>'. Implementors of interpretations of API types should -- treat 'EmptyAPI' as close to the unit as possible. -data EmptyAPI = EmptyAPI deriving (Typeable, Eq, Show, Bounded) +data EmptyAPI = EmptyAPI deriving (Typeable, Eq, Show, Bounded, Enum) From 7d07db7ed30df90bc9c4de4e332e80204345fee3 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 16:25:01 +0000 Subject: [PATCH 24/28] Add test for safeLink applied to an EmptyAPI type --- servant/test/Servant/Utils/LinksSpec.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/servant/test/Servant/Utils/LinksSpec.hs b/servant/test/Servant/Utils/LinksSpec.hs index 05abd67a..b8dbcee7 100644 --- a/servant/test/Servant/Utils/LinksSpec.hs +++ b/servant/test/Servant/Utils/LinksSpec.hs @@ -25,6 +25,7 @@ type TestApi = :<|> "post" :> ReqBody '[JSON] 'True :> Post '[JSON] NoContent :<|> "delete" :> Header "ponies" String :> Delete '[JSON] NoContent :<|> "raw" :> Raw + :<|> NoEndpoint apiLink :: (IsElem endpoint TestApi, HasLink endpoint) @@ -98,6 +99,11 @@ spec = describe "Servant.Utils.Links" $ do -- ...Could not deduce... -- ... -- +-- >>> apiLink (Proxy :: Proxy NoEndpoint) +-- ... +-- ...No instance for... +-- ... +-- -- sanity check -- >>> toUrlPiece $ apiLink (Proxy :: Proxy AllGood) -- "get" @@ -107,3 +113,4 @@ type WrongContentType = "get" :> Get '[OctetStream] NoContent type WrongMethod = "get" :> Post '[JSON] NoContent type NotALink = "hello" :> ReqBody '[JSON] 'True :> Get '[JSON] Bool type AllGood = "get" :> Get '[JSON] NoContent +type NoEndpoint = "empty" :> EmptyAPI From f3ac10a1c4e23703a9f72bd231b472a68e6e5135 Mon Sep 17 00:00:00 2001 From: David Turner Date: Tue, 16 May 2017 16:26:47 +0000 Subject: [PATCH 25/28] Add missing DeriveDataTypeable --- servant-server/src/Servant/Server/Internal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index 8880d35c..65db4a83 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -1,6 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} From a3c5f17749398403eb3e1266361a082fb17452a6 Mon Sep 17 00:00:00 2001 From: David Turner Date: Wed, 17 May 2017 05:12:23 +0000 Subject: [PATCH 26/28] Generalise type of `emptyServer` so it can be `Enter`ed --- servant-server/src/Servant/Server.hs | 4 ++-- servant-server/src/Servant/Server/Internal.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/servant-server/src/Servant/Server.hs b/servant-server/src/Servant/Server.hs index 9a117821..66e0ef9b 100644 --- a/servant-server/src/Servant/Server.hs +++ b/servant-server/src/Servant/Server.hs @@ -221,8 +221,8 @@ layoutWithContext p context = -- -- >>> import Control.Monad.Reader -- >>> import qualified Control.Category as C --- >>> type ReaderAPI = "ep1" :> Get '[JSON] Int :<|> "ep2" :> Get '[JSON] String :<|> Raw --- >>> let readerServer = return 1797 :<|> ask :<|> Tagged (error "raw server") :: ServerT ReaderAPI (Reader String) +-- >>> type ReaderAPI = "ep1" :> Get '[JSON] Int :<|> "ep2" :> Get '[JSON] String :<|> Raw :<|> EmptyAPI +-- >>> let readerServer = return 1797 :<|> ask :<|> Tagged (error "raw server") :<|> emptyServer :: ServerT ReaderAPI (Reader String) -- >>> let nt = generalizeNat C.. (runReaderTNat "hi") :: Reader String :~> Handler -- >>> let mainServer = enter nt readerServer :: Server ReaderAPI -- diff --git a/servant-server/src/Servant/Server/Internal.hs b/servant-server/src/Servant/Server/Internal.hs index 65db4a83..d336fb0f 100644 --- a/servant-server/src/Servant/Server/Internal.hs +++ b/servant-server/src/Servant/Server/Internal.hs @@ -537,7 +537,7 @@ instance HasServer api context => HasServer (HttpVersion :> api) context where data EmptyServer = EmptyServer deriving (Typeable, Eq, Show, Bounded, Enum) -- | Server for `EmptyAPI` -emptyServer :: Server EmptyAPI +emptyServer :: ServerT EmptyAPI m emptyServer = Tagged EmptyServer -- | The server for an `EmptyAPI` is `emptyAPIServer`. From aa3716b6aac80e132af9fca3c6529ce2305b3835 Mon Sep 17 00:00:00 2001 From: David Turner Date: Wed, 17 May 2017 05:50:38 +0000 Subject: [PATCH 27/28] Tidy up tutorial --- doc/tutorial/ApiType.lhs | 21 ++++++++++++++++----- doc/tutorial/Client.lhs | 15 +++++++++++++-- doc/tutorial/Docs.lhs | 7 +++---- doc/tutorial/Javascript.lhs | 2 -- doc/tutorial/Server.lhs | 5 +++-- 5 files changed, 35 insertions(+), 15 deletions(-) diff --git a/doc/tutorial/ApiType.lhs b/doc/tutorial/ApiType.lhs index 546e62ef..b770dcde 100644 --- a/doc/tutorial/ApiType.lhs +++ b/doc/tutorial/ApiType.lhs @@ -328,14 +328,25 @@ type ProtectedAPI11 ### Empty APIs -TODO motivation... +Sometimes it is useful to be able to generalise an API over the type of some +part of it: -``` haskell ignore -type UserAPI12 - = UserAPI - :<|> EmptyAPI -- this adds nothing to the API +``` haskell +type UserAPI12 innerAPI + = UserAPI -- this is the fixed bit of the API + :<|> "inner" :> innerAPI -- this lets us put various other APIs under /inner ``` +If there is a case where you do not have anything extra to serve, you can use +the `EmptyAPI` combinator to indicate this: + +``` haskell +type UserAPI12Alone = UserAPI12 EmptyAPI +``` + +This also works well as a placeholder for unfinished parts of an API while it +is under development. + ### Interoperability with `wai`: `Raw` Finally, we also include a combinator named `Raw` that provides an escape hatch diff --git a/doc/tutorial/Client.lhs b/doc/tutorial/Client.lhs index cb8a24b7..93ba56f3 100644 --- a/doc/tutorial/Client.lhs +++ b/doc/tutorial/Client.lhs @@ -62,7 +62,6 @@ Enough chitchat, let's see an example. Consider the following API type from the type API = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position :<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email - :<|> EmptyAPI ``` What we are going to get with **servant-client** here is three functions, one to query each endpoint: @@ -89,11 +88,23 @@ the function `client`. It takes one argument: api :: Proxy API api = Proxy -position :<|> hello :<|> marketing :<|> EmptyClient = client api +position :<|> hello :<|> marketing = client api ``` `client api` returns client functions for our _entire_ API, combined with `:<|>`, which we can pattern match on as above. You could say `client` "calculates" the correct type and number of client functions for the API type it is given (via a `Proxy`), as well as their implementations. +If there is an `EmptyAPI` within your API, this matches the `EmptyClient` +constructor: + +``` haskell ignore +type API' = API :<|> EmptyAPI + +api' :: Proxy API' +api' = Proxy + +(position' :<|> hello' :<|> marketing') :<|> EmptyClient = client api' +``` + ``` haskell ignore -- | URI scheme to use data Scheme = diff --git a/doc/tutorial/Docs.lhs b/doc/tutorial/Docs.lhs index 9903ec98..67f6f60c 100644 --- a/doc/tutorial/Docs.lhs +++ b/doc/tutorial/Docs.lhs @@ -38,10 +38,9 @@ Like client function generation, documentation generation amounts to inspecting This time however, we have to assist **servant**. While it is able to deduce a lot of things about our API, it can't magically come up with descriptions of the various pieces of our APIs that are human-friendly and explain what's going on "at the business-logic level". A good example to study for documentation generation is our webservice with the `/position`, `/hello` and `/marketing` endpoints from earlier: ``` haskell -type ExampleAPI = ("position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position +type ExampleAPI = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position :<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage - :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email) - :<|> EmptyAPI + :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email exampleAPI :: Proxy ExampleAPI exampleAPI = Proxy @@ -221,7 +220,7 @@ api :: Proxy DocsAPI api = Proxy server :: Server DocsAPI -server = (Server.server3 :<|> emptyServer) :<|> Tagged serveDocs where +server = Server.server3 :<|> Tagged serveDocs where serveDocs _ respond = respond $ responseLBS ok200 [plain] docsBS plain = ("Content-Type", "text/plain") diff --git a/doc/tutorial/Javascript.lhs b/doc/tutorial/Javascript.lhs index f0158d1f..6a7aa6bb 100644 --- a/doc/tutorial/Javascript.lhs +++ b/doc/tutorial/Javascript.lhs @@ -45,7 +45,6 @@ Now let's have the API type(s) and the accompanying datatypes. ``` haskell type API = "point" :> Get '[JSON] Point :<|> "books" :> QueryParam "q" Text :> Get '[JSON] (Search Book) - :<|> EmptyAPI type API' = API :<|> Raw @@ -134,7 +133,6 @@ api' = Proxy server :: Server API server = randomPoint :<|> searchBook - :<|> emptyServer server' :: Server API' server' = server diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index a364224c..831eed1f 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -1020,10 +1020,11 @@ serverFor = error "..." -- or the mailing list if you get stuck! ``` -TODO prose +If the API contains the `EmptyAPI` combinator, the corresponding server is +called `emptyServer`: ``` haskell -type CombinedAPI2 = API :<|> EmptyAPI +type CombinedAPI2 = API :<|> "empty" :> EmptyAPI server11 :: Server CombinedAPI2 server11 = server3 :<|> emptyServer From 8b993b9d114c376cfcf1762997107335d32f8d36 Mon Sep 17 00:00:00 2001 From: David Turner Date: Wed, 17 May 2017 08:24:04 +0000 Subject: [PATCH 28/28] Changes to docs as suggested --- doc/tutorial/ApiType.lhs | 3 ++- doc/tutorial/Client.lhs | 5 +++-- doc/tutorial/Docs.lhs | 2 ++ doc/tutorial/Javascript.lhs | 3 +++ doc/tutorial/Server.lhs | 5 +++-- 5 files changed, 13 insertions(+), 5 deletions(-) diff --git a/doc/tutorial/ApiType.lhs b/doc/tutorial/ApiType.lhs index b770dcde..cc2d3717 100644 --- a/doc/tutorial/ApiType.lhs +++ b/doc/tutorial/ApiType.lhs @@ -345,7 +345,8 @@ type UserAPI12Alone = UserAPI12 EmptyAPI ``` This also works well as a placeholder for unfinished parts of an API while it -is under development. +is under development, for when you know that there should be _something_ there +but you don't yet know what. Think of it as similar to the unit type `()`. ### Interoperability with `wai`: `Raw` diff --git a/doc/tutorial/Client.lhs b/doc/tutorial/Client.lhs index 93ba56f3..94aee690 100644 --- a/doc/tutorial/Client.lhs +++ b/doc/tutorial/Client.lhs @@ -93,8 +93,9 @@ position :<|> hello :<|> marketing = client api `client api` returns client functions for our _entire_ API, combined with `:<|>`, which we can pattern match on as above. You could say `client` "calculates" the correct type and number of client functions for the API type it is given (via a `Proxy`), as well as their implementations. -If there is an `EmptyAPI` within your API, this matches the `EmptyClient` -constructor: +If you have an `EmptyAPI` in your API, servant-client will hand you a value of +type `EmptyClient` in the corresponding slot, where `data EmptyClient = +EmptyClient`, as a way to indicate that you can't do anything useful with it. ``` haskell ignore type API' = API :<|> EmptyAPI diff --git a/doc/tutorial/Docs.lhs b/doc/tutorial/Docs.lhs index 67f6f60c..1d428698 100644 --- a/doc/tutorial/Docs.lhs +++ b/doc/tutorial/Docs.lhs @@ -89,6 +89,8 @@ instance ToSample Email where ``` Types that are used as request or response bodies have to instantiate the `ToSample` typeclass which lets you specify one or more examples of values. `Capture`s and `QueryParam`s have to instantiate their respective `ToCapture` and `ToParam` classes and provide a name and some information about the concrete meaning of that argument, as illustrated in the code above. +The `EmptyAPI` combinator needs no special treatment as it generates no +documentation: an empty API has no endpoints to document. With all of this, we can derive docs for our API. diff --git a/doc/tutorial/Javascript.lhs b/doc/tutorial/Javascript.lhs index 6a7aa6bb..033735ed 100644 --- a/doc/tutorial/Javascript.lhs +++ b/doc/tutorial/Javascript.lhs @@ -149,6 +149,9 @@ Why two different API types, proxies and servers though? Simply because we don't want to generate javascript functions for the `Raw` part of our API type, so we need a `Proxy` for our API type `API'` without its `Raw` endpoint. +The `EmptyAPI` combinator needs no special treatment as it generates no +Javascript functions: an empty API has no endpoints to access. + Very similarly to how one can derive haskell functions, we can derive the javascript with just a simple function call to `jsForAPI` from `Servant.JS`. diff --git a/doc/tutorial/Server.lhs b/doc/tutorial/Server.lhs index 831eed1f..e287a26b 100644 --- a/doc/tutorial/Server.lhs +++ b/doc/tutorial/Server.lhs @@ -1020,8 +1020,9 @@ serverFor = error "..." -- or the mailing list if you get stuck! ``` -If the API contains the `EmptyAPI` combinator, the corresponding server is -called `emptyServer`: +When your API contains the `EmptyAPI` combinator, you'll want to use +`emptyServer` in the corresponding slot for your server, which will simply fail +with 404 whenever a request reaches it: ``` haskell type CombinedAPI2 = API :<|> "empty" :> EmptyAPI